summaryrefslogtreecommitdiff
path: root/accounts/gkleen@sif/taffybar/src/taffybar.hs
blob: 67ee942d058cceb7af939744d85f3a669f9e5c00 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
{-# LANGUAGE OverloadedStrings #-}

module Main where

import System.Taffybar (startTaffybar)
import System.Taffybar.Context (TaffybarConfig(..))
import System.Taffybar.Hooks
import System.Taffybar.SimpleConfig hiding (SimpleTaffyConfig(cssPaths))
import System.Taffybar.Widget
import qualified System.Taffybar.Widget.Clock as MyClock
import System.Taffybar.Widget.TooltipBattery

import Data.Time.Format
import Data.Time.LocalTime
import Data.Time.Calendar.WeekDate

import qualified Data.Text as T

import Control.Exception (SomeException, try)
import Control.Monad.Trans.Reader (mapReaderT)

import Paths_gkleen_sif_taffybar

import System.Log.Logger


main :: IO ()
main = do
  logger <- getLogger "System.Taffybar"
  saveGlobalLogger $ setLevel INFO logger

  myCssPath <- getDataFileName "taffybar.css"
  startTaffybar taffybarConfig{ cssPaths = pure myCssPath }


taffybarConfig :: TaffybarConfig
taffybarConfig =
  let myWorkspacesConfig =
        defaultWorkspacesConfig
        { maxIcons = Just 0
        , widgetGap = 7
        , showWorkspaceFn = \case
            -- Workspace{ workspaceState = Empty } -> False
            Workspace{ workspaceName } | workspaceName == "NSP" -> False
            _other -> True
        , getWindowIconPixbuf = \i d -> either (\(_ :: SomeException) -> Nothing) id <$> mapReaderT try (defaultGetWindowIconPixbuf i d)
        , urgentWorkspaceState = True
        }
      workspaces = workspacesNew myWorkspacesConfig
      clock = MyClock.textClockNewWith MyClock.defaultClockConfig
        { MyClock.clockUpdateStrategy = MyClock.RoundedTargetInterval 1 0.0
        , MyClock.clockFormat = \tl zt@ZonedTime{ zonedTimeToLocalTime = LocalTime{ localDay } }
                                -> let date = formatTime tl "%Y-%m-%d" localDay
                                       weekdate = "W" <> show2 woy <> "-" <> show dow
                                         where (_, woy, dow) = toWeekDate localDay
                                               show2 :: Int -> String
                                               show2 x = replicate (2 - length s) '0' ++ s
                                                 where s = show x
                                       time = formatTime tl "%H:%M:%S%Ez" zt
                                    in T.intercalate " " $ map T.pack [weekdate, date, time]
        }
      layout = layoutNew defaultLayoutConfig
      windowsW = windowsNew defaultWindowsConfig
        { getMenuLabel = truncatedGetMenuLabel 80
        , getActiveLabel = truncatedGetActiveLabel 80
        }
      worktime = commandRunnerNew 60 "worktime" [] "worktime"
      worktimeToday = commandRunnerNew 60 "worktime" ["today"] "worktime today"
      -- See https://github.com/taffybar/gtk-sni-tray#statusnotifierwatcher
      -- for a better way to set up the sni tray
      -- tray = sniTrayThatStartsWatcherEvenThoughThisIsABadWayToDoIt
      tray = sniTrayNew
      myConfig = defaultSimpleTaffyConfig
        { startWidgets =
            workspaces : map (>>= buildContentsBox) [ layout, windowsW ]
        , endWidgets = map (>>= buildContentsBox) $ reverse
          -- , mpris2New
          [ worktime, worktimeToday
          , clock
          , tray
          , batteryIconTooltipNew "$status$ $percentage$%$if(time)$$if(rate)$ ($rate$W $time$)$else$ ($time$)$endif$$elseif(rate)$ ($rate$W)$endif$"
          ]
        , barPosition = Top
        , barPadding = 2
        , barHeight = ExactSize 28
        , widgetSpacing = 10
        }
  in withBatteryRefresh $ withLogServer $
     withToggleServer $ toTaffyConfig myConfig