Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
TODO: Proper haddock docs
Synopsis
- data Cell m a b = Data s => Cell {}
- step :: Monad m => Cell m a b -> a -> m (b, Cell m a b)
- steps :: Monad m => Cell m a b -> [a] -> m ([b], Cell m a b)
- sumC :: (Monad m, Num a, Data a) => Cell m a a
- liveCell :: Functor m => Cell m () () -> LiveProgram m
- toLiveCell :: Functor m => LiveProgram m -> Cell m () ()
- newtype Composition state1 state2 = Composition (state1, state2)
- getState2 :: Composition state1 state2 -> state2
- type Sensor a = Cell IO () a
- type SF a b = forall m. Cell m a b
- type Actuator b = Cell IO b ()
- buildLiveProg :: Sensor a -> SF a b -> Actuator b -> LiveProgram IO
- stepRate :: Num a => a
- integrate :: (Data a, Fractional a, Monad m) => Cell m a a
- localTime :: (Data a, Fractional a, Monad m) => Cell m b a
- hoistCell :: (forall x. m1 x -> m2 x) -> Cell m1 a b -> Cell m2 a b
- runReaderC :: r -> Cell (ReaderT r m) a b -> Cell m a b
- liftCell :: (Monad m, MonadTrans t) => Cell m a b -> Cell (t m) a b
- transformOutput :: (Monad m1, Monad m2) => (forall s. m1 (b1, s) -> m2 (b2, s)) -> Cell m1 a b1 -> Cell m2 a b2
- newtype Parallel s1 s2 = Parallel (s1, s2)
- arrM :: Functor m => (a -> m b) -> Cell m a b
- constM :: Functor m => m b -> Cell m a b
- sine :: MonadFix m => Double -> Cell m () Double
- asciiArt :: Double -> String
- printEverySecond :: Cell IO String ()
- printSine :: Double -> LiveProgram IO
- data Choice stateL stateR = Choice {
- choiceLeft :: stateL
- choiceRight :: stateR
Documentation
The basic building block of a live program.
toLiveCell :: Functor m => LiveProgram m -> Cell m () () Source #
newtype Composition state1 state2 Source #
Composition (state1, state2) |
Instances
(Data state1, Data state2) => Data (Composition state1 state2) Source # | |
Defined in LiveCoding.Cell 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 #
buildLiveProg :: Sensor a -> SF a b -> Actuator b -> LiveProgram IO Source #
transformOutput :: (Monad m1, Monad m2) => (forall s. m1 (b1, s) -> m2 (b2, s)) -> Cell m1 a b1 -> Cell m2 a b2 Source #
newtype Parallel s1 s2 Source #
Parallel (s1, s2) |
Instances
(Data s1, Data s2) => Data (Parallel s1 s2) Source # | |
Defined in LiveCoding.Cell 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) # |
data Choice stateL stateR Source #
Choice | |
|
Instances
(Data stateL, Data stateR) => Data (Choice stateL stateR) Source # | |
Defined in LiveCoding.Cell 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) # |