| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Bludigon
Synopsis
- bludigon :: (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 -> m (StM g a)
- runRecolor :: forall a. r a -> g (StM r a)
- data Trichromaticity = Trichromaticity {
- red :: Chromaticity
- green :: Chromaticity
- blue :: Chromaticity
- data Temperature
- temperature :: Temperature -> Trichromaticity
- class MonadBaseControl IO m => MonadControl m where
- type ControlConstraint m a :: Constraint
- doInbetween :: ControlConstraint m a => a -> m ()
- 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 bludigon should be called directly from the main function in
$XDG_CONFIG_HOME/bludigon/bludigon.hs
bludigon :: (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 to declaring Trichromaticity directly is to use Temperature and the
conversion function temperature.
data Temperature Source #
Arbitrary precision temperature in Kelvin
Instances
temperature :: Temperature -> Trichromaticity Source #
Calculate a Trichromaticity from a Temperature.
Control
Modules with instances of MonadControl can be found under Bludigon.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
| MonadControl IO Source # | |
Defined in Bludigon.Control Associated Types type ControlConstraint IO a Source # Methods doInbetween :: ControlConstraint IO a => a -> IO () Source # | |
| MonadControl m => MonadControl (ControlPrintT m) Source # | |
Defined in Bludigon.Control.Print Associated Types type ControlConstraint (ControlPrintT m) a Source # Methods doInbetween :: ControlConstraint (ControlPrintT m) a => a -> ControlPrintT m () Source # | |
| MonadControl m => MonadControl (ControlWaitT m) Source # | |
Defined in Bludigon.Control.Wait Associated Types type ControlConstraint (ControlWaitT m) a Source # Methods doInbetween :: ControlConstraint (ControlWaitT m) a => a -> ControlWaitT m () Source # | |
Gamma
Modules with instances of MonadGamma can be found under Bludigon.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
| MonadBase IO m => MonadGamma (GammaLinearT m) Source # | |
Defined in Bludigon.Gamma.Linear Methods | |
| Monad m => MonadGamma (GammaConstT m) Source # | |
Defined in Bludigon.Gamma.Const Methods | |
Recolor
Modules with instances of MonadRecolor can be found under Bludigon.Recolor.*.
class Monad m => MonadRecolor m where Source #
Instances
| MonadBaseControl IO m => MonadRecolor (RecolorPrintT m) Source # | |
Defined in Bludigon.Recolor.Print Methods recolor :: Trichromaticity -> RecolorPrintT m () Source # | |
| MonadBaseControl IO m => MonadRecolor (RecolorXT m) Source # | |
Defined in Bludigon.Recolor.X Methods recolor :: Trichromaticity -> RecolorXT m () Source # | |
other
A class for types with a default value.
Minimal complete definition
Nothing