essence-of-live-coding-0.2.0.1: General purpose live coding framework

Safe HaskellSafe
LanguageHaskell2010

LiveCoding.Cell

Description

TODO: Proper haddock docs

Synopsis

Documentation

data Cell m a b Source #

The basic building block of a live program.

Constructors

Data s => Cell 

Fields

ArrM

Added to improve performance and keep state types simpler

Fields

Instances
Monad m => Arrow (Cell m) Source # 
Instance details

Defined in LiveCoding.Cell

Methods

arr :: (b -> c) -> Cell m b c #

first :: Cell m b c -> Cell m (b, d) (c, d) #

second :: Cell m b c -> Cell m (d, b) (d, c) #

(***) :: Cell m b c -> Cell m b' c' -> Cell m (b, b') (c, c') #

(&&&) :: Cell m b c -> Cell m b c' -> Cell m b (c, c') #

Monad m => ArrowChoice (Cell m) Source # 
Instance details

Defined in LiveCoding.Cell

Methods

left :: Cell m b c -> Cell m (Either b d) (Either c d) #

right :: Cell m b c -> Cell m (Either d b) (Either d c) #

(+++) :: Cell m b c -> Cell m b' c' -> Cell m (Either b b') (Either c c') #

(|||) :: Cell m b d -> Cell m c d -> Cell m (Either b c) d #

MonadFix m => ArrowLoop (Cell m) Source # 
Instance details

Defined in LiveCoding.Cell

Methods

loop :: Cell m (b, d) (c, d) -> Cell m b c #

Monad m => Category (Cell m :: Type -> Type -> Type) Source # 
Instance details

Defined in LiveCoding.Cell

Methods

id :: Cell m a a #

(.) :: Cell m b c -> Cell m a b -> Cell m a c #

toCell :: Functor m => Cell m a b -> Cell m a b Source #

Converts every Cell to the Cell constructor.

step :: Monad m => Cell m a b -> a -> m (b, Cell m a b) Source #

steps :: Monad m => Cell m a b -> [a] -> m ([b], Cell m a b) Source #

sumC :: (Monad m, Num a, Data a) => Cell m a a Source #

liveCell :: Functor m => Cell m () () -> LiveProgram m Source #

toLiveCell :: Functor m => LiveProgram m -> Cell m () () Source #

newtype Composition state1 state2 Source #

Constructors

Composition (state1, state2) 
Instances
(Data state1, Data state2) => Data (Composition state1 state2) Source # 
Instance details

Defined in LiveCoding.Cell

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Composition state1 state2 -> c (Composition state1 state2) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Composition state1 state2) #

toConstr :: Composition state1 state2 -> Constr #

dataTypeOf :: Composition state1 state2 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Composition state1 state2)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Composition state1 state2)) #

gmapT :: (forall b. Data b => b -> b) -> Composition state1 state2 -> Composition state1 state2 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Composition state1 state2 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Composition state1 state2 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Composition state1 state2 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Composition state1 state2 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Composition state1 state2 -> m (Composition state1 state2) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Composition state1 state2 -> m (Composition state1 state2) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Composition state1 state2 -> m (Composition state1 state2) #

getState2 :: Composition state1 state2 -> state2 Source #

type Sensor a = Cell IO () a Source #

type SF a b = forall m. Cell m a b Source #

type Actuator b = Cell IO b () Source #

stepRate :: Num a => a Source #

integrate :: (Data a, Fractional a, Monad m) => Cell m a a Source #

localTime :: (Data a, Fractional a, Monad m) => Cell m b a Source #

hoistCell :: (forall x. m1 x -> m2 x) -> Cell m1 a b -> Cell m2 a b Source #

liftCell :: (Monad m, MonadTrans t) => Cell m a b -> Cell (t m) a b Source #

newtype Parallel s1 s2 Source #

Constructors

Parallel (s1, s2) 
Instances
(Data s1, Data s2) => Data (Parallel s1 s2) Source # 
Instance details

Defined in LiveCoding.Cell

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Parallel s1 s2 -> c (Parallel s1 s2) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Parallel s1 s2) #

toConstr :: Parallel s1 s2 -> Constr #

dataTypeOf :: Parallel s1 s2 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Parallel s1 s2)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Parallel s1 s2)) #

gmapT :: (forall b. Data b => b -> b) -> Parallel s1 s2 -> Parallel s1 s2 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parallel s1 s2 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parallel s1 s2 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Parallel s1 s2 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Parallel s1 s2 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Parallel s1 s2 -> m (Parallel s1 s2) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Parallel s1 s2 -> m (Parallel s1 s2) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Parallel s1 s2 -> m (Parallel s1 s2) #

arrM :: (a -> m b) -> Cell m a b Source #

constM :: m b -> Cell m a b Source #

constC :: Monad m => b -> Cell m a b Source #

data Choice stateL stateR Source #

Constructors

Choice 

Fields

Instances
(Data stateL, Data stateR) => Data (Choice stateL stateR) Source # 
Instance details

Defined in LiveCoding.Cell

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Choice stateL stateR -> c (Choice stateL stateR) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Choice stateL stateR) #

toConstr :: Choice stateL stateR -> Constr #

dataTypeOf :: Choice stateL stateR -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Choice stateL stateR)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Choice stateL stateR)) #

gmapT :: (forall b. Data b => b -> b) -> Choice stateL stateR -> Choice stateL stateR #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Choice stateL stateR -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Choice stateL stateR -> r #

gmapQ :: (forall d. Data d => d -> u) -> Choice stateL stateR -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Choice stateL stateR -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Choice stateL stateR -> m (Choice stateL stateR) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Choice stateL stateR -> m (Choice stateL stateR) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Choice stateL stateR -> m (Choice stateL stateR) #