diff options
Diffstat (limited to 'accounts/gkleen@sif/taffybar/src/taffybar.hs')
-rw-r--r-- | accounts/gkleen@sif/taffybar/src/taffybar.hs | 83 |
1 files changed, 83 insertions, 0 deletions
diff --git a/accounts/gkleen@sif/taffybar/src/taffybar.hs b/accounts/gkleen@sif/taffybar/src/taffybar.hs new file mode 100644 index 00000000..dd713ea7 --- /dev/null +++ b/accounts/gkleen@sif/taffybar/src/taffybar.hs | |||
@@ -0,0 +1,83 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | ||
2 | |||
3 | module Main where | ||
4 | |||
5 | import System.Taffybar (startTaffybar) | ||
6 | import System.Taffybar.Context (TaffybarConfig(..)) | ||
7 | import System.Taffybar.Hooks | ||
8 | import System.Taffybar.SimpleConfig hiding (SimpleTaffyConfig(cssPath)) | ||
9 | import System.Taffybar.Widget | ||
10 | import qualified System.Taffybar.Widget.Clock as MyClock | ||
11 | import System.Taffybar.Widget.TooltipBattery | ||
12 | |||
13 | import Data.Time.Format | ||
14 | import Data.Time.LocalTime | ||
15 | import Data.Time.Calendar.WeekDate | ||
16 | |||
17 | import qualified Data.Text as T | ||
18 | |||
19 | import Control.Exception (SomeException, try) | ||
20 | import Control.Monad.Trans.Reader (mapReaderT) | ||
21 | |||
22 | import Paths_gkleen_sif_taffybar | ||
23 | |||
24 | |||
25 | main :: IO () | ||
26 | main = do | ||
27 | myCssPath <- getDataFileName "taffybar.css" | ||
28 | startTaffybar exampleTaffybarConfig{ cssPath = Just myCssPath } | ||
29 | |||
30 | |||
31 | exampleTaffybarConfig :: TaffybarConfig | ||
32 | exampleTaffybarConfig = | ||
33 | let myWorkspacesConfig = | ||
34 | defaultWorkspacesConfig | ||
35 | { maxIcons = Just 0 | ||
36 | , widgetGap = 7 | ||
37 | , showWorkspaceFn = \case | ||
38 | -- Workspace{ workspaceState = Empty } -> False | ||
39 | Workspace{ workspaceName } | workspaceName == "NSP" -> False | ||
40 | _other -> True | ||
41 | , getWindowIconPixbuf = \i d -> either (\(_ :: SomeException) -> Nothing) id <$> mapReaderT try (defaultGetWindowIconPixbuf i d) | ||
42 | } | ||
43 | workspaces = workspacesNew myWorkspacesConfig | ||
44 | clock = MyClock.textClockNewWith MyClock.defaultClockConfig | ||
45 | { MyClock.clockUpdateStrategy = MyClock.RoundedTargetInterval 1 0.0 | ||
46 | , MyClock.clockFormat = \tl zt@ZonedTime{ zonedTimeToLocalTime = LocalTime{ localDay } } | ||
47 | -> let date = formatTime tl "%Y-%m-%d" localDay | ||
48 | weekdate = "W" <> show2 woy <> "-" <> show dow | ||
49 | where (_, woy, dow) = toWeekDate localDay | ||
50 | show2 :: Int -> String | ||
51 | show2 x = replicate (2 - length s) '0' ++ s | ||
52 | where s = show x | ||
53 | time = formatTime tl "%H:%M:%S%Ez" zt | ||
54 | in T.intercalate " " $ map T.pack [date, weekdate, time] | ||
55 | } | ||
56 | layout = layoutNew defaultLayoutConfig | ||
57 | windowsW = windowsNew defaultWindowsConfig | ||
58 | { getMenuLabel = truncatedGetMenuLabel 80 | ||
59 | , getActiveLabel = truncatedGetActiveLabel 80 | ||
60 | } | ||
61 | worktime = commandRunnerNew 150 "worktime" [] "worktime" | ||
62 | worktimeToday = commandRunnerNew 150 "worktime" ["today"] "worktime today" | ||
63 | -- See https://github.com/taffybar/gtk-sni-tray#statusnotifierwatcher | ||
64 | -- for a better way to set up the sni tray | ||
65 | -- tray = sniTrayThatStartsWatcherEvenThoughThisIsABadWayToDoIt | ||
66 | tray = sniTrayNew | ||
67 | myConfig = defaultSimpleTaffyConfig | ||
68 | { startWidgets = | ||
69 | workspaces : map (>>= buildContentsBox) [ layout, windowsW ] | ||
70 | , endWidgets = map (>>= buildContentsBox) $ reverse | ||
71 | -- , mpris2New | ||
72 | [ worktime, worktimeToday | ||
73 | , clock | ||
74 | , tray | ||
75 | , batteryIconTooltipNew "$status$ $percentage$%$if(time)$$if(rate)$ ($rate$W $time$)$else$ ($time$)$endif$$elseif(rate)$ ($rate$W)$endif$" | ||
76 | ] | ||
77 | , barPosition = Top | ||
78 | , barPadding = 2 | ||
79 | , barHeight = 28 | ||
80 | , widgetSpacing = 10 | ||
81 | } | ||
82 | in withBatteryRefresh $ withLogServer $ | ||
83 | withToggleServer $ toTaffyConfig myConfig | ||