| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Blucontrol
Synopsis
- blucontrol :: (ControlConstraint m (StM g (StM r ())), MonadControl m, MonadBaseControl IO g, MonadBaseControl IO r, MonadGamma g, MonadRecolor r) => ConfigControl m g r -> IO ()
- data ConfigControl m g r = ConfigControl {
- runControl :: forall a. m a -> IO a
- runGamma :: forall a. g a -> IO (StM g a)
- runRecolor :: forall a. r a -> g (StM r a)
- data Trichromaticity = Trichromaticity {
- red :: Chromaticity
- green :: Chromaticity
- blue :: Chromaticity
- class RGB c where
- toRGB :: c -> Trichromaticity
- class MonadBaseControl IO m => MonadControl m where
- type ControlConstraint m a :: Constraint
- doInbetween :: ControlConstraint m a => a -> m ()
- (!>) :: (t1 m a -> m a) -> (t2 (t1 m) a -> t1 m a) -> ControlConcatT t1 t2 m a -> m a
- class Monad m => MonadGamma m where
- gamma :: m Trichromaticity
- class Monad m => MonadRecolor m where
- recolor :: Trichromaticity -> 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 :: (ControlConstraint m (StM g (StM r ())), MonadControl m, MonadBaseControl IO g, MonadBaseControl IO r, MonadGamma g, MonadRecolor r) => ConfigControl m g r -> IO () Source #
ConfigControl will set the monads in which recoloring and calculation of the gamma values
will take place.
data ConfigControl m g r Source #
Constructors
| ConfigControl | |
Fields
| |
RGB
RGB values are represented by Trichromaticity.
data Trichromaticity Source #
combination of Chromaticitys for the colors red, green and blue
Constructors
| Trichromaticity | |
Fields
| |
Instances
An alternative way, which avoids declaring Trichromaticity directly, uses the RGB type
class.
convertible to 8-bit RGB values
Methods
toRGB :: c -> Trichromaticity Source #
Instances
| RGB Trichromaticity Source # | |
Defined in Blucontrol.RGB Methods | |
| RGB Temperature Source # | |
Defined in Blucontrol.RGB.Temperature Methods toRGB :: Temperature -> Trichromaticity Source # | |
Control
Modules with instances of MonadControl can be found under Blucontrol.Control.*.
class MonadBaseControl IO m => MonadControl m where Source #
Associated Types
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
MonadGamma and MonadRecolor.
Methods
Arguments
| :: 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.
(!>) :: (t1 m a -> m a) -> (t2 (t1 m) a -> t1 m a) -> ControlConcatT t1 t2 m a -> m a infixr 5 Source #
Gamma
Modules with instances of MonadGamma can be found under Blucontrol.Gamma.*.
class Monad m => MonadGamma m where Source #
Methods
gamma :: m Trichromaticity Source #
Calculate a Trichromaticity.
This is a monadic function, to allow the value to be dependent on side effects like time and
location.
Instances
| (Monad m, RGB c) => MonadGamma (GammaConstT c m) Source # | |
Defined in Blucontrol.Gamma.Const Methods gamma :: GammaConstT c m Trichromaticity Source # | |
| MonadBase IO m => MonadGamma (GammaLinearT Trichromaticity m) Source # | |
Defined in Blucontrol.Gamma.Linear Methods gamma :: GammaLinearT Trichromaticity m Trichromaticity Source # | |
| MonadBase IO m => MonadGamma (GammaLinearT Temperature m) Source # | |
Defined in Blucontrol.Gamma.Linear Methods gamma :: GammaLinearT Temperature m Trichromaticity Source # | |
Recolor
Modules with instances of MonadRecolor can be found under Blucontrol.Recolor.*.
class Monad m => MonadRecolor m where Source #
Instances
| MonadBaseControl IO m => MonadRecolor (RecolorPrintT m) Source # | |
Defined in Blucontrol.Recolor.Print Methods recolor :: Trichromaticity -> RecolorPrintT m () Source # | |
| MonadBaseControl IO m => MonadRecolor (RecolorXT m) Source # | |
Defined in Blucontrol.Recolor.X Methods recolor :: Trichromaticity -> RecolorXT m () Source # | |
other
A class for types with a default value.
Minimal complete definition
Nothing