{-# LANGUAGE OverloadedStrings #-}
module System.Taffybar.Example where
import Data.Default (def)
import System.Taffybar.Context (TaffybarConfig(..))
import System.Taffybar.Hooks
import System.Taffybar.Information.CPU
import System.Taffybar.Information.Memory
import System.Taffybar.SimpleConfig
import System.Taffybar.Widget
import System.Taffybar.Widget.Generic.PollingGraph
transparent, yellow1, yellow2, green1, green2, taffyBlue
:: (Double, Double, Double, Double)
transparent :: (Double, Double, Double, Double)
transparent = (Double
0.0, Double
0.0, Double
0.0, Double
0.0)
yellow1 :: (Double, Double, Double, Double)
yellow1 = (Double
0.9453125, Double
0.63671875, Double
0.2109375, Double
1.0)
yellow2 :: (Double, Double, Double, Double)
yellow2 = (Double
0.9921875, Double
0.796875, Double
0.32421875, Double
1.0)
green1 :: (Double, Double, Double, Double)
green1 = (Double
0, Double
1, Double
0, Double
1)
green2 :: (Double, Double, Double, Double)
green2 = (Double
1, Double
0, Double
1, Double
0.5)
taffyBlue :: (Double, Double, Double, Double)
taffyBlue = (Double
0.129, Double
0.588, Double
0.953, Double
1)
myGraphConfig, netCfg, memCfg, cpuCfg :: GraphConfig
myGraphConfig :: GraphConfig
myGraphConfig =
GraphConfig
forall a. Default a => a
def
{ graphPadding = 0
, graphBorderWidth = 0
, graphWidth = 75
, graphBackgroundColor = transparent
}
netCfg :: GraphConfig
netCfg = GraphConfig
myGraphConfig
{ graphDataColors = [yellow1, yellow2]
, graphLabel = Just "net"
}
memCfg :: GraphConfig
memCfg = GraphConfig
myGraphConfig
{ graphDataColors = [taffyBlue]
, graphLabel = Just "mem"
}
cpuCfg :: GraphConfig
cpuCfg = GraphConfig
myGraphConfig
{ graphDataColors = [green1, green2]
, graphLabel = Just "cpu"
}
memCallback :: IO [Double]
memCallback :: IO [Double]
memCallback = do
MemoryInfo
mi <- IO MemoryInfo
parseMeminfo
[Double] -> IO [Double]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [MemoryInfo -> Double
memoryUsedRatio MemoryInfo
mi]
cpuCallback :: IO [Double]
cpuCallback :: IO [Double]
cpuCallback = do
(Double
_, Double
systemLoad, Double
totalLoad) <- IO (Double, Double, Double)
cpuLoad
[Double] -> IO [Double]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Double
totalLoad, Double
systemLoad]
exampleTaffybarConfig :: TaffybarConfig
exampleTaffybarConfig :: TaffybarConfig
exampleTaffybarConfig =
let myWorkspacesConfig :: WorkspacesConfig
myWorkspacesConfig =
WorkspacesConfig
forall a. Default a => a
def
{ minIcons = 1
, widgetGap = 0
, showWorkspaceFn = hideEmpty
}
workspaces :: TaffyIO Widget
workspaces = WorkspacesConfig -> TaffyIO Widget
workspacesNew WorkspacesConfig
myWorkspacesConfig
cpu :: TaffyIO Widget
cpu = GraphConfig -> Double -> IO [Double] -> TaffyIO Widget
forall (m :: * -> *).
MonadIO m =>
GraphConfig -> Double -> IO [Double] -> m Widget
pollingGraphNew GraphConfig
cpuCfg Double
0.5 IO [Double]
cpuCallback
mem :: TaffyIO Widget
mem = GraphConfig -> Double -> IO [Double] -> TaffyIO Widget
forall (m :: * -> *).
MonadIO m =>
GraphConfig -> Double -> IO [Double] -> m Widget
pollingGraphNew GraphConfig
memCfg Double
1 IO [Double]
memCallback
net :: TaffyIO Widget
net = GraphConfig -> Maybe [String] -> TaffyIO Widget
networkGraphNew GraphConfig
netCfg Maybe [String]
forall a. Maybe a
Nothing
clock :: TaffyIO Widget
clock = ClockConfig -> TaffyIO Widget
forall (m :: * -> *). MonadIO m => ClockConfig -> m Widget
textClockNewWith ClockConfig
forall a. Default a => a
def
layout :: TaffyIO Widget
layout = LayoutConfig -> TaffyIO Widget
layoutNew LayoutConfig
forall a. Default a => a
def
windowsW :: TaffyIO Widget
windowsW = WindowsConfig -> TaffyIO Widget
windowsNew WindowsConfig
forall a. Default a => a
def
tray :: TaffyIO Widget
tray = TaffyIO Widget
sniTrayThatStartsWatcherEvenThoughThisIsABadWayToDoIt
myConfig :: SimpleTaffyConfig
myConfig = SimpleTaffyConfig
forall a. Default a => a
def
{ startWidgets =
workspaces : map (>>= buildContentsBox) [ layout, windowsW ]
, endWidgets = map (>>= buildContentsBox)
[ batteryIconNew
, clock
, tray
, cpu
, mem
, net
, mpris2New
]
, barPosition = Top
, barPadding = 10
, barHeight = ExactSize 50
, widgetSpacing = 0
}
in TaffybarConfig -> TaffybarConfig
withLogServer (TaffybarConfig -> TaffybarConfig)
-> TaffybarConfig -> TaffybarConfig
forall a b. (a -> b) -> a -> b
$ TaffybarConfig -> TaffybarConfig
withToggleServer (TaffybarConfig -> TaffybarConfig)
-> TaffybarConfig -> TaffybarConfig
forall a b. (a -> b) -> a -> b
$ SimpleTaffyConfig -> TaffybarConfig
toTaffybarConfig SimpleTaffyConfig
myConfig