xmonad-config/lib/XMonad/Internal/DBus/Brightness/Common.hs

215 lines
5.8 KiB
Haskell
Raw Normal View History

{-# LANGUAGE OverloadedStrings #-}
--------------------------------------------------------------------------------
2022-12-30 14:58:23 -05:00
-- DBus module for DBus brightness controls
module XMonad.Internal.DBus.Brightness.Common
2022-12-30 14:58:23 -05:00
( BrightnessConfig (..)
, BrightnessControls (..)
, brightnessControls
, brightnessExporter
, callGetBrightness
, matchSignal
, signalDep
2022-12-30 14:58:23 -05:00
)
where
import DBus
import DBus.Client
import qualified DBus.Introspection as I
import Data.Internal.DBus
2023-01-01 18:33:02 -05:00
import Data.Internal.XIO
2022-12-30 17:11:15 -05:00
import RIO
2022-12-30 14:58:23 -05:00
import qualified RIO.Text as T
import XMonad.Core (io)
import XMonad.Internal.DBus.Common
--------------------------------------------------------------------------------
2022-12-30 14:58:23 -05:00
-- External API
--
-- Define four methods to increase, decrease, maximize, or minimize the
-- brightness. These methods will all return the current brightness as a 32-bit
-- integer and emit a signal with the same brightness value. Additionally, there
-- is one method to get the current brightness.
data BrightnessConfig a b = BrightnessConfig
2022-12-30 14:58:23 -05:00
{ bcMin :: (a, a) -> IO b
, bcMax :: (a, a) -> IO b
, bcDec :: (a, a) -> IO b
, bcInc :: (a, a) -> IO b
, bcGet :: (a, a) -> IO b
, bcMinRaw :: a
, bcGetMax :: IO a
, bcPath :: ObjectPath
, bcInterface :: InterfaceName
2022-12-30 14:58:23 -05:00
, bcName :: T.Text
}
data BrightnessControls = BrightnessControls
{ bctlMax :: SometimesX
, bctlMin :: SometimesX
, bctlInc :: SometimesX
, bctlDec :: SometimesX
}
2022-12-30 14:58:23 -05:00
brightnessControls
:: XPQuery
-> BrightnessConfig a b
-> Maybe SesClient
-> BrightnessControls
2022-07-09 17:08:10 -04:00
brightnessControls q bc cl =
BrightnessControls
2022-12-30 14:58:23 -05:00
{ bctlMax = cb "max brightness" memMax
, bctlMin = cb "min brightness" memMin
, bctlInc = cb "increase brightness" memInc
, bctlDec = cb "decrease brightness" memDec
}
2021-11-11 00:11:15 -05:00
where
2022-07-09 17:08:10 -04:00
cb = callBacklight q cl bc
2022-12-30 14:58:23 -05:00
callGetBrightness
2022-12-30 17:11:15 -05:00
:: (MonadUnliftIO m, SafeClient c, Num n)
2022-12-30 14:58:23 -05:00
=> BrightnessConfig a b
-> c
2022-12-30 17:11:15 -05:00
-> m (Maybe n)
2022-12-30 14:58:23 -05:00
callGetBrightness BrightnessConfig {bcPath = p, bcInterface = i} client =
2021-11-27 13:24:13 -05:00
either (const Nothing) bodyGetBrightness
2022-12-30 14:58:23 -05:00
<$> callMethod client xmonadBusName p i memGet
2022-07-09 17:08:10 -04:00
signalDep :: BrightnessConfig a b -> DBusDependency_ SesClient
2022-12-30 14:58:23 -05:00
signalDep BrightnessConfig {bcPath = p, bcInterface = i} =
Endpoint [] xmonadBusName p i $ Signal_ memCur
2022-12-30 14:58:23 -05:00
matchSignal
2022-12-30 17:11:15 -05:00
:: (MonadUnliftIO m, SafeClient c, Num n)
2022-12-30 14:58:23 -05:00
=> BrightnessConfig a b
2022-12-30 17:11:15 -05:00
-> (Maybe n -> m ())
2022-12-30 14:58:23 -05:00
-> c
2022-12-30 17:11:15 -05:00
-> m ()
2022-12-30 14:58:23 -05:00
matchSignal BrightnessConfig {bcPath = p, bcInterface = i} cb =
void . addMatchCallback brMatcher (cb . bodyGetBrightness)
where
2021-11-27 13:24:13 -05:00
-- TODO add busname to this
2022-12-30 14:58:23 -05:00
brMatcher =
matchAny
{ matchPath = Just p
, matchInterface = Just i
, matchMember = Just memCur
}
--------------------------------------------------------------------------------
2022-12-30 14:58:23 -05:00
-- Internal DBus Crap
brightnessExporter
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m, RealFrac b)
2022-12-30 14:58:23 -05:00
=> XPQuery
-> [Fulfillment]
-> [IODependency_]
-> BrightnessConfig a b
-> Maybe SesClient
2023-01-01 12:43:54 -05:00
-> Sometimes (m (), m ())
2022-12-30 14:58:23 -05:00
brightnessExporter q ful deps bc@BrightnessConfig {bcName = n} cl =
Sometimes (T.append n " DBus Interface") q [Subfeature root "exporter"]
where
2023-01-01 12:43:54 -05:00
root = DBusRoot_ (exportBrightnessControlsInner bc) tree cl
tree = listToAnds (Bus ful xmonadBusName) $ fmap DBusIO deps
2021-11-11 00:11:15 -05:00
2023-01-01 12:43:54 -05:00
exportBrightnessControlsInner
:: (MonadReader env m, HasLogFunc env, MonadUnliftIO m, RealFrac b)
2022-12-30 17:15:50 -05:00
=> BrightnessConfig a b
-> SesClient
2023-01-01 12:43:54 -05:00
-> (m (), m ())
exportBrightnessControlsInner bc = cmd
2022-12-30 14:58:23 -05:00
where
cmd = exportPair (bcPath bc) $ \cl_ -> do
-- up = liftIO $ do
-- let ses = toClient cl
maxval <- liftIO $ bcGetMax bc -- assume the max value will never change
2023-01-01 12:43:54 -05:00
let bounds = (bcMinRaw bc, maxval)
let autoMethod' m f = autoMethod m $ emitBrightness bc cl_ =<< f bc bounds
2023-01-01 12:43:54 -05:00
let funget = bcGet bc
-- export
-- ses
-- (bcPath bc)
return $
2023-01-01 12:43:54 -05:00
defaultInterface
{ interfaceName = bcInterface bc
, interfaceMethods =
[ autoMethod' memMax bcMax
, autoMethod' memMin bcMin
, autoMethod' memInc bcInc
, autoMethod' memDec bcDec
, autoMethod memGet (round <$> funget bounds :: IO Int32)
]
, interfaceSignals = [sig]
}
-- down = liftIO $ unexport (toClient cl) (bcPath bc)
2022-12-30 14:58:23 -05:00
sig =
I.Signal
{ I.signalName = memCur
, I.signalArgs =
[ I.SignalArg
{ I.signalArgName = "brightness"
, I.signalArgType = TypeInt32
}
]
}
2022-12-30 17:11:15 -05:00
emitBrightness
:: (MonadUnliftIO m, RealFrac b)
=> BrightnessConfig a b
-> Client
-> b
-> m ()
2022-12-30 14:58:23 -05:00
emitBrightness BrightnessConfig {bcPath = p, bcInterface = i} client cur =
2022-12-30 17:11:15 -05:00
liftIO $ emit client $ sig {signalBody = [toVariant (round cur :: Int32)]}
where
sig = signal p i memCur
2022-12-30 14:58:23 -05:00
callBacklight
:: XPQuery
-> Maybe SesClient
-> BrightnessConfig a b
-> T.Text
-> MemberName
-> SometimesX
callBacklight
q
cl
BrightnessConfig
{ bcPath = p
, bcInterface = i
, bcName = n
}
controlName
m =
Sometimes (T.unwords [n, controlName]) q [Subfeature root "method call"]
where
root = DBusRoot_ cmd (Only_ $ Endpoint [] xmonadBusName p i $ Method_ m) cl
cmd c = io $ void $ callMethod c xmonadBusName p i m
bodyGetBrightness :: Num a => [Variant] -> Maybe a
bodyGetBrightness [b] = fromIntegral <$> (fromVariant b :: Maybe Int32)
2022-12-30 14:58:23 -05:00
bodyGetBrightness _ = Nothing
--------------------------------------------------------------------------------
2022-12-30 14:58:23 -05:00
-- DBus Members
memCur :: MemberName
memCur = memberName_ "CurrentBrightness"
memGet :: MemberName
memGet = memberName_ "GetBrightness"
memMax :: MemberName
memMax = memberName_ "MaxBrightness"
memMin :: MemberName
memMin = memberName_ "MinBrightness"
memInc :: MemberName
memInc = memberName_ "IncBrightness"
memDec :: MemberName
memDec = memberName_ "DecBrightness"