xmonad-config/lib/Xmobar/Plugins/Screensaver.hs

33 lines
984 B
Haskell
Raw Normal View History

{-# LANGUAGE LambdaCase #-}
2020-04-01 22:06:00 -04:00
--------------------------------------------------------------------------------
-- | Screensaver plugin
--
-- Use the custom DBus interface exported by the XMonad process so I can react
-- to signals spawned by commands
2020-04-01 20:17:47 -04:00
module Xmobar.Plugins.Screensaver (Screensaver(..)) where
2020-03-15 15:10:25 -04:00
2020-03-25 18:55:52 -04:00
import Control.Concurrent
import Control.Monad
2020-03-25 18:55:52 -04:00
import Xmobar
2020-04-01 20:17:47 -04:00
import XMonad.Hooks.DynamicLog (xmobarColor)
import XMonad.Internal.DBus.Screensaver
2020-03-15 15:10:25 -04:00
2020-03-25 18:55:52 -04:00
newtype Screensaver = Screensaver (String, String, String)
deriving (Read, Show)
2020-03-15 15:10:25 -04:00
instance Exec Screensaver where
alias (Screensaver _) = "screensaver"
start (Screensaver (text, colorOn, colorOff)) cb = do
_ <- matchSignal $ cb . fmtState
cb . fmtState =<< callQuery
forever (threadDelay 5000000)
where
fmtState = \case
2020-04-01 20:17:47 -04:00
Just s -> xmobarColor (if s then colorOn else colorOff) "" text
Nothing -> "N/A"