2022-12-26 14:45:49 -05:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
2021-11-07 13:35:08 -05:00
|
|
|
--------------------------------------------------------------------------------
|
2022-12-30 14:58:23 -05:00
|
|
|
-- DBus module for DBus brightness controls
|
2021-11-07 13:35:08 -05:00
|
|
|
|
|
|
|
module XMonad.Internal.DBus.Brightness.Common
|
2022-12-30 14:58:23 -05:00
|
|
|
( BrightnessConfig (..)
|
|
|
|
, BrightnessControls (..)
|
2021-11-20 12:40:53 -05:00
|
|
|
, brightnessControls
|
|
|
|
, brightnessExporter
|
2021-11-07 13:35:08 -05:00
|
|
|
, callGetBrightness
|
|
|
|
, matchSignal
|
2021-11-20 19:35:24 -05:00
|
|
|
, 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
|
|
|
|
import Data.Internal.Dependency
|
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
|
2021-11-07 13:35:08 -05:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
2022-12-30 14:58:23 -05:00
|
|
|
-- External API
|
2021-11-07 13:35:08 -05:00
|
|
|
--
|
|
|
|
-- 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
|
2021-11-07 13:35:08 -05:00
|
|
|
, bcInterface :: InterfaceName
|
2022-12-30 14:58:23 -05:00
|
|
|
, bcName :: T.Text
|
2021-11-07 13:35:08 -05:00
|
|
|
}
|
|
|
|
|
|
|
|
data BrightnessControls = BrightnessControls
|
2022-12-28 12:19:44 -05:00
|
|
|
{ bctlMax :: SometimesX
|
|
|
|
, bctlMin :: SometimesX
|
|
|
|
, bctlInc :: SometimesX
|
|
|
|
, bctlDec :: SometimesX
|
2021-11-07 13:35:08 -05:00
|
|
|
}
|
|
|
|
|
2022-12-30 14:58:23 -05:00
|
|
|
brightnessControls
|
|
|
|
:: XPQuery
|
|
|
|
-> BrightnessConfig a b
|
|
|
|
-> Maybe SesClient
|
2022-07-08 20:01:35 -04:00
|
|
|
-> BrightnessControls
|
2022-07-09 17:08:10 -04:00
|
|
|
brightnessControls q bc cl =
|
2021-11-20 12:40:53 -05:00
|
|
|
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
|
2021-11-07 13:35:08 -05:00
|
|
|
|
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
|
2021-11-07 13:35:08 -05:00
|
|
|
|
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} =
|
2022-07-09 01:02:37 -04:00
|
|
|
Endpoint [] xmonadBusName p i $ Signal_ memCur
|
2021-11-20 19:35:24 -05:00
|
|
|
|
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 =
|
2021-11-26 23:35:03 -05:00
|
|
|
void . addMatchCallback brMatcher (cb . bodyGetBrightness)
|
2021-11-07 13:35:08 -05:00
|
|
|
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
|
|
|
|
}
|
2021-11-07 13:35:08 -05:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
2022-12-30 14:58:23 -05:00
|
|
|
-- Internal DBus Crap
|
|
|
|
|
|
|
|
brightnessExporter
|
|
|
|
:: RealFrac b
|
|
|
|
=> XPQuery
|
|
|
|
-> [Fulfillment]
|
|
|
|
-> [IODependency_]
|
|
|
|
-> BrightnessConfig a b
|
|
|
|
-> Maybe SesClient
|
|
|
|
-> SometimesIO
|
|
|
|
brightnessExporter q ful deps bc@BrightnessConfig {bcName = n} cl =
|
2022-12-26 14:45:49 -05:00
|
|
|
Sometimes (T.append n " DBus Interface") q [Subfeature root "exporter"]
|
2022-06-17 00:37:12 -04:00
|
|
|
where
|
2022-07-08 20:01:35 -04:00
|
|
|
root = DBusRoot_ (exportBrightnessControls' bc) tree cl
|
2022-07-09 01:02:37 -04:00
|
|
|
tree = listToAnds (Bus ful xmonadBusName) $ fmap DBusIO deps
|
2021-11-11 00:11:15 -05:00
|
|
|
|
2022-12-30 17:15:50 -05:00
|
|
|
exportBrightnessControls'
|
|
|
|
:: (MonadUnliftIO m, RealFrac b)
|
|
|
|
=> BrightnessConfig a b
|
|
|
|
-> SesClient
|
|
|
|
-> m ()
|
2022-12-28 12:19:44 -05:00
|
|
|
exportBrightnessControls' bc cl = io $ do
|
2022-07-09 17:08:10 -04:00
|
|
|
let ses = toClient cl
|
2021-11-07 13:35:08 -05:00
|
|
|
maxval <- bcGetMax bc -- assume the max value will never change
|
2021-11-21 00:42:40 -05:00
|
|
|
let bounds = (bcMinRaw bc, maxval)
|
2022-07-09 17:08:10 -04:00
|
|
|
let autoMethod' m f = autoMethod m $ emitBrightness bc ses =<< f bc bounds
|
2021-11-07 13:35:08 -05:00
|
|
|
let funget = bcGet bc
|
2022-12-30 14:58:23 -05:00
|
|
|
export
|
|
|
|
ses
|
|
|
|
(bcPath bc)
|
|
|
|
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]
|
2021-11-20 19:35:24 -05:00
|
|
|
}
|
2022-12-30 14:58:23 -05:00
|
|
|
where
|
|
|
|
sig =
|
|
|
|
I.Signal
|
|
|
|
{ I.signalName = memCur
|
|
|
|
, I.signalArgs =
|
|
|
|
[ I.SignalArg
|
|
|
|
{ I.signalArgName = "brightness"
|
|
|
|
, I.signalArgType = TypeInt32
|
|
|
|
}
|
|
|
|
]
|
|
|
|
}
|
2021-11-07 13:35:08 -05:00
|
|
|
|
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)]}
|
2021-11-07 13:35:08 -05:00
|
|
|
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
|
2021-11-07 13:35:08 -05:00
|
|
|
|
|
|
|
bodyGetBrightness :: Num a => [Variant] -> Maybe a
|
|
|
|
bodyGetBrightness [b] = fromIntegral <$> (fromVariant b :: Maybe Int32)
|
2022-12-30 14:58:23 -05:00
|
|
|
bodyGetBrightness _ = Nothing
|
2021-11-07 13:35:08 -05:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
2022-12-30 14:58:23 -05:00
|
|
|
-- DBus Members
|
2021-11-07 13:35:08 -05:00
|
|
|
|
|
|
|
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"
|