36 lines
979 B
Haskell
36 lines
979 B
Haskell
{-# LANGUAGE LambdaCase #-}
|
|
|
|
--------------------------------------------------------------------------------
|
|
-- | Intel backlight plugin
|
|
--
|
|
-- Use the custom DBus interface exported by the XMonad process so I can react
|
|
-- to signals spawned by commands
|
|
|
|
module Xmobar.Plugins.IntelBacklight
|
|
( IntelBacklight(..)
|
|
, blAlias
|
|
) where
|
|
|
|
import Control.Concurrent
|
|
import Control.Monad
|
|
|
|
import Xmobar
|
|
|
|
import XMonad.Internal.DBus.Brightness.IntelBacklight
|
|
|
|
newtype IntelBacklight = IntelBacklight String deriving (Read, Show)
|
|
|
|
blAlias :: String
|
|
blAlias = "intelbacklight"
|
|
|
|
instance Exec IntelBacklight where
|
|
alias (IntelBacklight _) = blAlias
|
|
start (IntelBacklight icon) cb = do
|
|
_ <- matchSignalIB $ cb . formatBrightness
|
|
cb . formatBrightness =<< callGetBrightnessIB
|
|
forever (threadDelay 5000000)
|
|
where
|
|
formatBrightness = \case
|
|
Just b -> icon ++ show (round b :: Integer) ++ "%"
|
|
Nothing -> "N/A"
|