dunai-0.1.0.0: Generalised reactive framework supporting classic, arrowized and monadic FRP.

Safe HaskellSafe
LanguageHaskell2010

Data.MonadicStreamFunction.Core

Contents

Description

Monadic Stream Functions are synchronized stream functions with side effects.

Synopsis

Documentation

data MStreamF m a b Source #

Constructors

MStreamF 

Fields

Instances

Monad m => Arrow (MStreamF m) Source # 

Methods

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

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

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

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

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

Monad m => Category * (MStreamF m) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

type Groundring (MStreamF m a v) Source # 
type Groundring (MStreamF m a v) = Groundring v

Lifts

liftMStreamF :: Monad m => (a -> m b) -> MStreamF m a b Source #

Monadic lifting from one monad into another

Purer monads

liftMStreamFPurer :: (Monad m2, Monad m1) => (forall c. m1 c -> m2 c) -> MStreamF m1 a b -> MStreamF m2 a b Source #

Lifting purer monadic actions (in an arbitrary way)

Monad stacks

liftMStreamFTrans :: (MonadTrans t, Monad m, Monad (t m)) => MStreamF m a b -> MStreamF (t m) a b Source #

Lifting inner monadic actions in monad stacks TODO Should be able to express this in terms of MonadBase

liftMStreamFBase :: (Monad m2, MonadBase m1 m2) => MStreamF m1 a b -> MStreamF m2 a b Source #

Lifting the innest monadic actions in a monad stacks (generalisation of liftIO)

MSFs within monadic actions

performOnFirstSample :: Monad m => m (MStreamF m a b) -> MStreamF m a b Source #

Extract MSF from a monadic action

Delays and signal overwriting

iPre :: Monad m => a -> MStreamF m a a Source #

delay :: Monad m => a -> MStreamF m a a Source #

Switching

switch :: Monad m => MStreamF m a (b, Maybe c) -> (c -> MStreamF m a b) -> MStreamF m a b Source #

Feedback loops

feedback :: Monad m => c -> MStreamF m (a, c) (b, c) -> MStreamF m a b Source #

Reactimating

embed :: Monad m => MStreamF 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 liftMStreamF 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 => MStreamF m () () -> m () Source #

Runs an MSF indefinitely passing a unit-carrying input stream.

reactimateB :: Monad m => MStreamF m () Bool -> m () Source #

Runs an MSF indefinitely passing a unit-carrying input stream.