Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Monadic Stream Functions are synchronized stream functions with side effects.
MSFs are defined by a function unMSF :: MSF m a b -> a -> m (b, MSF m a b)
that executes one step of a simulation, and produces an output in a
monadic context, and a continuation to be used for future steps.
MSFs are a generalisation of the implementation mechanism used by Yampa, Wormholes and other FRP and reactive implementations.
When combined with different monads, they produce interesting effects. For
example, when combined with the Maybe
monad, they become transformations
that may stop producing outputs (and continuations). The Either
monad
gives rise to MSFs that end with a result (akin to Tasks in Yampa, and
Monadic FRP).
Flattening, that is, going from some structure MSF (t m) a b
to MSF m a b
for a specific transformer t
often gives rise to known FRP constructs.
For instance, flattening with EitherT
gives rise to switching, and
flattening with ListT
gives rise to parallelism with broadcasting.
MSFs can be used to implement many FRP variants, including Arrowized FRP, Classic FRP, and plain reactive programming. Arrowized and applicative syntax are both supported.
For a very detailed introduction to MSFs, see: http://dl.acm.org/citation.cfm?id=2976010 (mirror: http://www.cs.nott.ac.uk/~psxip1/#FRPRefactored).
- data MSF m a b = MSF {}
- arrM :: Monad m => (a -> m b) -> MSF m a b
- liftS :: (Monad m2, MonadBase m1 m2) => (a -> m1 b) -> MSF m2 a b
- liftMSFPurer :: (Monad m2, Monad m1) => (forall c. m1 c -> m2 c) -> MSF m1 a b -> MSF m2 a b
- liftMSFTrans :: (MonadTrans t, Monad m, Monad (t m)) => MSF m a b -> MSF (t m) a b
- liftMSFBase :: (Monad m2, MonadBase m1 m2) => MSF m1 a b -> MSF m2 a b
- performOnFirstSample :: Monad m => m (MSF m a b) -> MSF m a b
- iPre :: Monad m => a -> MSF m a a
- delay :: Monad m => a -> MSF m a a
- switch :: Monad m => MSF m a (b, Maybe c) -> (c -> MSF m a b) -> MSF m a b
- feedback :: Monad m => c -> MSF m (a, c) (b, c) -> MSF m a b
- embed :: Monad m => MSF m a b -> [a] -> m [b]
- reactimate :: Monad m => MSF m () () -> m ()
- reactimateB :: Monad m => MSF m () Bool -> m ()
Definitions
Stepwise, side-effectful MSFs without implicit knowledge of time.
MSFs should be applied to streams or executed indefinitely or until they
terminate. See reactimate
and reactimateB
for details. In general,
calling the value constructor MSF
or the function unMSF
is discouraged.
Lifting
arrM :: Monad m => (a -> m b) -> MSF m a b Source #
Apply the same monadic transformation to every element of the input stream.
Generalisation of arr from Arrow to stream functions with monads.
Monadic lifting from one monad into another
Purer monads
liftMSFPurer :: (Monad m2, Monad m1) => (forall c. m1 c -> m2 c) -> MSF m1 a b -> MSF m2 a b Source #
Lifting purer monadic actions (in an arbitrary way)
Monad stacks
liftMSFTrans :: (MonadTrans t, Monad m, Monad (t m)) => MSF m a b -> MSF (t m) a b Source #
Lift inner monadic actions in monad stacks.
liftMSFBase :: (Monad m2, MonadBase m1 m2) => MSF m1 a b -> MSF m2 a b Source #
Lift innermost monadic actions in a monad stacks (generalisation of
liftIO
).
MSFs within monadic actions
performOnFirstSample :: Monad m => m (MSF m a b) -> MSF m a b Source #
Extract MSF from a monadic action.
Runs a monadic action that produces an MSF on the first iteration/step, and uses that MSF as the main signal function for all inputs (including the first one).
Delays and signal overwriting
Switching
switch :: Monad m => MSF m a (b, Maybe c) -> (c -> MSF m a b) -> MSF m a b Source #
Switching applies one MSF until it produces a Just
output, and then
"turns on" a continuation and runs it.
A more advanced and comfortable approach to switching is givin by Exceptions in Control.Monad.Trans.MSF.Except
Feedback loops
feedback :: Monad m => c -> MSF m (a, c) (b, c) -> MSF m a b Source #
Well-formed looped connection of an output component as a future input.
Execution/simulation
embed :: Monad m => MSF m a b -> [a] -> m [b] Source #
Apply a monadic stream function to a list.
Because the result is in a monad, it may be necessary to traverse the whole list to evaluate the value in the results to WHNF. For example, if the monad is the maybe monad, this may not produce anything if the MSF produces Nothing at any point, so the output stream cannot consumed progressively.
To explore the output progressively, use liftMSF and (>>>), together with some action that consumes/actuates on the output.
This is called "runSF" in Liu, Cheng, Hudak, "Causal Commutative Arrows and Their Optimization"
reactimate :: Monad m => MSF m () () -> m () Source #
Run an MSF indefinitely passing a unit-carrying input stream.