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

30 lines
902 B
Haskell
Raw Normal View History

{-# LANGUAGE LambdaCase #-}
2020-04-01 22:06:00 -04:00
--------------------------------------------------------------------------------
-- | Intel backlight 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.IntelBacklight (IntelBacklight(..)) where
2020-04-01 20:17:47 -04:00
import Control.Concurrent
import Control.Monad
2020-04-01 20:17:47 -04:00
import Xmobar
2020-04-01 20:17:47 -04:00
import XMonad.Internal.DBus.IntelBacklight
newtype IntelBacklight = IntelBacklight String deriving (Read, Show)
instance Exec IntelBacklight where
alias (IntelBacklight _) = "intelbacklight"
start (IntelBacklight icon) cb = do
_ <- matchSignal $ cb . formatBrightness
cb . formatBrightness =<< callGetBrightness
forever (threadDelay 5000000)
where
formatBrightness = \case
Just b -> icon ++ show (b `div` 100) ++ "%"
Nothing -> "N/A"