Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Cell m a b
- toCell :: Functor m => Cell m a b -> Cell m a b
- 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 :: Monad m => Cell m () () -> LiveProgram m
- toLiveCell :: Functor m => LiveProgram m -> Cell m () ()
- data Composition state1 state2 = Composition {}
- type Sensor a = Cell IO () a
- type SF a b = forall m. Cell m a b
- type Actuator b = Cell IO b ()
- buildProg :: 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
- liftCell :: (Monad m, MonadTrans t) => Cell m a b -> Cell (t m) a b
- data Parallel stateP1 stateP2 = Parallel {}
- arrM :: (a -> m b) -> Cell m a b
- constM :: m b -> Cell m a b
- constC :: Monad 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.
You can build cells directly, by using constructors,
or through the Functor
, Applicative
, or Arrow
type classes.
The Cell
constructor is the main way build a cell,
but for efficiency purposes there is an additional constructor.
forall s.Data s => Cell | A cell consists of an internal state, and an effectful state transition function. |
ArrM | Effectively a cell with trivial state. Added to improve performance and keep state types simpler. |
|
steps :: Monad m => Cell m a b -> [a] -> m ([b], Cell m a b) Source #
Execute a cell for several steps. The number of steps is determined by the length of the list of inputs.
liveCell :: Monad m => Cell m () () -> LiveProgram m Source #
Convert a cell with no inputs and outputs to a live program. Semantically, this is an isomorphism.
toLiveCell :: Functor m => LiveProgram m -> Cell m () () Source #
The inverse to liveCell
.
data Composition state1 state2 Source #
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 :: forall r r'. (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) # |
hoistCell :: (forall x. m1 x -> m2 x) -> Cell m1 a b -> Cell m2 a b Source #
Hoist a Cell
along a monad morphism.
liftCell :: (Monad m, MonadTrans t) => Cell m a b -> Cell (t m) a b Source #
Lift a Cell
into a monad transformer.
data Parallel stateP1 stateP2 Source #
Instances
(Data stateP1, Data stateP2) => Data (Parallel stateP1 stateP2) Source # | |
Defined in LiveCoding.Cell gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Parallel stateP1 stateP2 -> c (Parallel stateP1 stateP2) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Parallel stateP1 stateP2) # toConstr :: Parallel stateP1 stateP2 -> Constr # dataTypeOf :: Parallel stateP1 stateP2 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Parallel stateP1 stateP2)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Parallel stateP1 stateP2)) # gmapT :: (forall b. Data b => b -> b) -> Parallel stateP1 stateP2 -> Parallel stateP1 stateP2 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parallel stateP1 stateP2 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parallel stateP1 stateP2 -> r # gmapQ :: (forall d. Data d => d -> u) -> Parallel stateP1 stateP2 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Parallel stateP1 stateP2 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Parallel stateP1 stateP2 -> m (Parallel stateP1 stateP2) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Parallel stateP1 stateP2 -> m (Parallel stateP1 stateP2) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Parallel stateP1 stateP2 -> m (Parallel stateP1 stateP2) # |
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 :: forall r r'. (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) # |