dunai-core-0.5.1.0: Generalised reactive framework supporting classic, arrowized and monadic FRP. (Core library fork.)

Safe HaskellSafe
LanguageHaskell2010

Data.MonadicStreamFunction.Core

Contents

Description

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).

Synopsis

Definitions

data MSF m a b Source #

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.

Constructors

MSF 

Fields

Instances
Monad m => Arrow (MSF m) Source #

Arrow instance for MSFs.

Instance details

Defined in Data.MonadicStreamFunction.Core

Methods

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

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

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

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

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

(Monad m, MonadPlus m) => ArrowZero (MSF m) #

Instance of ArrowZero for Monadic Stream Functions (MSF). The monad must be an instance of MonadPlus.

Instance details

Defined in Data.MonadicStreamFunction.Instances.ArrowPlus

Methods

zeroArrow :: MSF m b c #

(Monad m, MonadPlus m) => ArrowPlus (MSF m) #

Instance of ArrowPlus for Monadic Stream Functions (MSF). The monad must be an instance of MonadPlus.

Instance details

Defined in Data.MonadicStreamFunction.Instances.ArrowPlus

Methods

(<+>) :: MSF m b c -> MSF m b c -> MSF m b c #

Monad m => ArrowChoice (MSF m) #

ArrowChoice instance for MSFs.

Instance details

Defined in Data.MonadicStreamFunction.Instances.ArrowChoice

Methods

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

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

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

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

MonadFix m => ArrowLoop (MSF m) #

ArrowLoop instance for MSFs. The monad must be an instance of MonadFix.

Instance details

Defined in Data.MonadicStreamFunction.Instances.ArrowLoop

Methods

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

Monad m => Category (MSF m :: * -> * -> *) Source #

Instance definition for Category. Defines id and ..

Instance details

Defined in Data.MonadicStreamFunction.Core

Methods

id :: MSF m a a #

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

Functor m => Functor (MSF m a) Source #

Functor instance for MSFs.

Instance details

Defined in Data.MonadicStreamFunction.Core

Methods

fmap :: (a0 -> b) -> MSF m a a0 -> MSF m a b #

(<$) :: a0 -> MSF m a b -> MSF m a a0 #

Monad m => Applicative (MSF m a) Source #

Applicative instance for MSFs.

Instance details

Defined in Data.MonadicStreamFunction.Core

Methods

pure :: a0 -> MSF m a a0 #

(<*>) :: MSF m a (a0 -> b) -> MSF m a a0 -> MSF m a b #

liftA2 :: (a0 -> b -> c) -> MSF m a a0 -> MSF m a b -> MSF m a c #

(*>) :: MSF m a a0 -> MSF m a b -> MSF m a b #

(<*) :: MSF m a a0 -> MSF m a b -> MSF m a a0 #

(Monad m, MonadPlus m) => Alternative (MSF m a) # 
Instance details

Defined in Data.MonadicStreamFunction.Instances.ArrowPlus

Methods

empty :: MSF m a a0 #

(<|>) :: MSF m a a0 -> MSF m a a0 -> MSF m a a0 #

some :: MSF m a a0 -> MSF m a [a0] #

many :: MSF m a a0 -> MSF m a [a0] #

(Monad m, Floating b) => Floating (MSF m a b) #

Floating instance for MSFs.

Instance details

Defined in Data.MonadicStreamFunction.Instances.Num

Methods

pi :: MSF m a b #

exp :: MSF m a b -> MSF m a b #

log :: MSF m a b -> MSF m a b #

sqrt :: MSF m a b -> MSF m a b #

(**) :: MSF m a b -> MSF m a b -> MSF m a b #

logBase :: MSF m a b -> MSF m a b -> MSF m a b #

sin :: MSF m a b -> MSF m a b #

cos :: MSF m a b -> MSF m a b #

tan :: MSF m a b -> MSF m a b #

asin :: MSF m a b -> MSF m a b #

acos :: MSF m a b -> MSF m a b #

atan :: MSF m a b -> MSF m a b #

sinh :: MSF m a b -> MSF m a b #

cosh :: MSF m a b -> MSF m a b #

tanh :: MSF m a b -> MSF m a b #

asinh :: MSF m a b -> MSF m a b #

acosh :: MSF m a b -> MSF m a b #

atanh :: MSF m a b -> MSF m a b #

log1p :: MSF m a b -> MSF m a b #

expm1 :: MSF m a b -> MSF m a b #

log1pexp :: MSF m a b -> MSF m a b #

log1mexp :: MSF m a b -> MSF m a b #

(Monad m, Fractional b) => Fractional (MSF m a b) #

Fractional instance for MSFs.

Instance details

Defined in Data.MonadicStreamFunction.Instances.Num

Methods

(/) :: MSF m a b -> MSF m a b -> MSF m a b #

recip :: MSF m a b -> MSF m a b #

fromRational :: Rational -> MSF m a b #

(Monad m, Num b) => Num (MSF m a b) #

Num instance for MSFs.

Instance details

Defined in Data.MonadicStreamFunction.Instances.Num

Methods

(+) :: MSF m a b -> MSF m a b -> MSF m a b #

(-) :: MSF m a b -> MSF m a b -> MSF m a b #

(*) :: MSF m a b -> MSF m a b -> MSF m a b #

negate :: MSF m a b -> MSF m a b #

abs :: MSF m a b -> MSF m a b #

signum :: MSF m a b -> MSF m a b #

fromInteger :: Integer -> MSF m a b #

(Monad m, VectorSpace v) => VectorSpace (MSF m a v) Source #

Vector-space instance for MSFs.

Instance details

Defined in Data.MonadicStreamFunction.Instances.VectorSpace

Methods

(^/) :: MSF m a v -> Groundfield (MSF m a v) -> MSF m a v Source #

(Monad m, RModule v) => RModule (MSF m a v) Source #

R-module instance for MSFs.

Instance details

Defined in Data.MonadicStreamFunction.Instances.VectorSpace

Associated Types

type Groundring (MSF m a v) :: * Source #

Methods

zeroVector :: MSF m a v Source #

(*^) :: Groundring (MSF m a v) -> MSF m a v -> MSF m a v Source #

(^*) :: MSF m a v -> Groundring (MSF m a v) -> MSF m a v Source #

negateVector :: MSF m a v -> MSF m a v Source #

(^+^) :: MSF m a v -> MSF m a v -> MSF m a v Source #

(^-^) :: MSF m a v -> MSF m a v -> MSF m a v Source #

type Groundring (MSF m a v) Source # 
Instance details

Defined in Data.MonadicStreamFunction.Instances.VectorSpace

type Groundring (MSF m a v) = Groundring v

Monadic computations and MSFs

Lifting point-wise computations

arrM :: Monad m => (a -> m b) -> MSF m a b Source #

Apply a monadic transformation to every element of the input stream.

Generalisation of arr from Arrow to monadic functions.

liftS :: (Monad m2, MonadBase m1 m2) => (a -> m1 b) -> MSF m2 a b Source #

Monadic lifting from one monad into another

Lifting MSFs

Lifting across 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).

Generic MSF Lifting

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)

Delays

iPre Source #

Arguments

:: Monad m 
=> a

First output

-> MSF m a a 

Delay a signal by one sample.

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

See iPre.

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 given by Exceptions in 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.