Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- blucontrol :: BlucontrolConstraints mc mp ma => ConfigControl mc mp ma -> IO (StM mc (StM mp (StM ma ())))
- type BlucontrolConstraints mc mp ma = (CompatibleValues (PreparedValue mp) (ApplicableValue ma), ControlConstraint mc (StM mp (StM ma ())), MonadBaseControl IO mp, MonadBaseControl IO ma, MonadApplyValue ma, MonadControl mc, MonadPrepareValue mp)
- data ConfigControl mc mp ma = ConfigControl {
- runControl :: forall a. mc a -> IO (StM mc a)
- runPrepareValue :: forall a. mp a -> IO (StM mp a)
- runApplyValue :: forall a. ma a -> IO (StM ma a)
- class MonadBaseControl IO m => MonadControl m where
- type ControlConstraint m a :: Constraint
- doInbetween :: ControlConstraint m a => a -> m ()
- (!>) :: (forall a. t1 m a -> m (StT t1 a)) -> (forall a. t2 (t1 m) a -> t1 m (StT t2 a)) -> forall a. ControlConcatT t1 t2 m a -> m (StT t1 (StT t2 a))
- class Monad m => MonadPrepareValue m where
- type PreparedValue m
- preparedValue :: m (PreparedValue m)
- class Monad m => MonadApplyValue m where
- type ApplicableValue m
- applyValue :: ApplicableValue m -> m ()
- class Default a where
- def :: a
main
For most configurations blucontrol
should be called directly from the main
function in
$XDG_CONFIG_HOME/blucontrol/blucontrol.hs
blucontrol :: BlucontrolConstraints mc mp ma => ConfigControl mc mp ma -> IO (StM mc (StM mp (StM ma ()))) Source #
type BlucontrolConstraints mc mp ma = (CompatibleValues (PreparedValue mp) (ApplicableValue ma), ControlConstraint mc (StM mp (StM ma ())), MonadBaseControl IO mp, MonadBaseControl IO ma, MonadApplyValue ma, MonadControl mc, MonadPrepareValue mp) Source #
ConfigControl
will set the monads in which calculation and application of values will take
place.
data ConfigControl mc mp ma Source #
ConfigControl | |
|
Control
Modules with instances of MonadControl
can be found under Blucontrol.Monad.Control.*
.
class MonadBaseControl IO m => MonadControl m where Source #
type ControlConstraint m a :: Constraint Source #
Give a constraint to allow doInbetween
to handle a polymorphic argument.
This is usfeul to allow arguments wrapped in monadic state StM
from running
PrepareValue
and ApplyValue
.
:: ControlConstraint m a | |
=> a | the returned value from the last call of |
-> m () | the side effect to be run inbetween recoloring |
This function will be called after recoloring the screen.
Instances
To compose instances of MonadControl
avoid function composition, as it won't compose
doInbetween
.
Use !>
instead.
(!>) :: (forall a. t1 m a -> m (StT t1 a)) -> (forall a. t2 (t1 m) a -> t1 m (StT t2 a)) -> forall a. ControlConcatT t1 t2 m a -> m (StT t1 (StT t2 a)) infixr 5 Source #
Prepare value
Modules with instances of MonadPrepareValue
can be found under Blucontrol.Monad.PrepareValue.*
.
class Monad m => MonadPrepareValue m where Source #
type PreparedValue m Source #
preparedValue :: m (PreparedValue m) Source #
Calculate a value. This is a monadic function, to allow the value to be dependent on side effects like time and location.
Instances
ApplyValue
Modules with instances of MonadApplyValue
can be found under Blucontrol.Monad.ApplyValue.*
.
class Monad m => MonadApplyValue m where Source #
type ApplicableValue m Source #
applyValue :: ApplicableValue m -> m () Source #
Apply a value. This is a monadic function, to allow application to external programs like an X display server.
Instances
MonadBaseControl IO m => MonadApplyValue (ApplyValueXT m) Source # | |
Defined in Blucontrol.Monad.ApplyValue.X type ApplicableValue (ApplyValueXT m) Source # applyValue :: ApplicableValue (ApplyValueXT m) -> ApplyValueXT m () Source # | |
(MonadBaseControl IO m, Show c) => MonadApplyValue (ApplyValuePrintT c m) Source # | |
Defined in Blucontrol.Monad.ApplyValue.Print type ApplicableValue (ApplyValuePrintT c m) Source # applyValue :: ApplicableValue (ApplyValuePrintT c m) -> ApplyValuePrintT c m () Source # |
other
A class for types with a default value.
Nothing