drClickOn-0.1: Monadic FRP

Safe HaskellNone

Control.MonadicFRP

Contents

Description

Monadic FRP basic definitions and composition functions.

See the paper Monadic Functional Reactive Programming by Atze van der Ploeg. Haskell Symposium '13. http://homepages.cwi.nl/~ploeg/papers/monfrp.pdf.

An example can be found at https://github.com/cwi-swat/monadic-frp.

Notice that currently Monadic FRP relies on a closed union (ADT) of basic events, which has the following downsides:

  • Reactive level sharing requires an explicit call to a memoization function.
  • Reactive level recursion is problematic.

A function preprended with i indices a initialized signal variant of an signal computation function.

Synopsis

Basic definitions

data Event a Source

Constructors

Request 
Occurred a 

Instances

Ord a => Eq (Event a) 
Ord a => Ord (Event a) 
Show a => Show (Event a) 

type EvReqs e = Set eSource

An alias for a set of event requests

type EvOccs e = Set eSource

An alias for a set of event occurances

data React e alpha Source

A reactive computation

Constructors

Done alpha 
Await (EvReqs e) (EvOccs e -> React e alpha) 

Instances

exper :: e -> React e eSource

Request a single event

interpret :: Monad m => (EvReqs e -> m (EvOccs e)) -> React e a -> m aSource

The interpreter for reactive computations. The first argument is a function that answers event requests in the monad m, the second is the reactive computation.

newtype Sig e a b Source

A signal computation is a reactive computation of an initialized signal

Constructors

Sig (React e (ISig e a b)) 

Instances

Monad (Sig e a) 
Functor (Sig e a) 

data ISig e a b Source

An initialized signal

Constructors

a :| (Sig e a b) 
End b 

Instances

Monad (ISig e a) 

interpretSig :: Monad m => (EvReqs e -> m (EvOccs e)) -> (a -> m r) -> Sig e a b -> m bSource

The interpreter for signal computations taking three arguments:

  • a function that answers event requests in the monad m
  • a function that processes the emitted values in the monad m
  • the signal computation.

first :: Ord e => React e a -> React e b -> React e (React e a, React e b)Source

Run two reactive computations in parallel until either completes, and return the new state of both.

Notice that flip first == first

parR :: Ord e => React e a -> React e b -> React e (React e a, React e b)Source

Alias for first

update :: Ord e => React e a -> EvOccs e -> React e aSource

Call the continuation function of a reactive computation if it awaits at least one of the event occurences.

Repetition

repeat :: React e a -> Sig e a bSource

Repeat the given reactive computation indefinitely, each time emitting its result.

spawn :: Sig e t t1 -> Sig e (ISig e t t1) bSource

Repeat the given signal computation indefinitely, each time emitting its initialized signal result.

Transformation

map :: (t -> a) -> Sig e t b -> Sig e a bSource

Transform the emmited values of a signal computation by applying the function to each of them.

imap :: (t -> a) -> ISig e t b -> ISig e a bSource

Transform the emmited values of an initialized signal computation by applying the function to each of them.

scanl :: (a -> t -> a) -> a -> Sig e t t1 -> Sig e a t1Source

The list function scanl is similar to foldl, but returns a list of successive reduced values instead of a single value. the signal variant works analogously.

iscanl :: (a -> t -> a) -> a -> Sig e t t1 -> ISig e a t1Source

break :: (a -> Bool) -> Sig e a b -> Sig e a (ISig e a b)Source

Run the signal computation as long as the given predicate does not hold on the emitted values. Once a value is emmited on which the predicate holds, the rest of the signal computation is returned.

ibreak :: (a -> Bool) -> ISig e a b -> ISig e a (ISig e a b)Source

foldl :: (a -> b -> a) -> a -> Sig e b r -> React e aSource

|foldl| on signal computations behaves the same as waiting for the signal computation to end and then applying the fold on the list of emitted values.

ifoldl :: (a -> b -> a) -> a -> ISig e b r -> React e aSource

find :: (a -> Bool) -> Sig t a t1 -> React t (Maybe a)Source

Find the first emmited value on which the predicate hold.

at :: Ord t => Sig t a t1 -> React t b -> React t (Maybe a)Source

Sample the form of the signal computation at the time the reactive computation completes

until :: Ord e => Sig e a t -> React e b -> Sig e a (Sig e a t, React e b)Source

Run the signal computation until the reactive computation completes, and return the new state of both computations.

iuntil :: Ord t => ISig t a b -> React t alpha -> ISig t a (ISig t a b, React t alpha)Source

(<^>) :: Ord e => Sig e (t -> a) b -> Sig e t t1 -> Sig e a (ISig e (t -> a) b, ISig e t t1)Source

Apply the values from the second signal computation to the values from the first signal computation over time. When one ends, the new state of both is returned.

pairs :: Ord e => ISig e t1 b -> ISig e t2 t -> ISig e (t1, t2) (ISig e t1 b, ISig e t2 t)Source

Emitted the pairs of the emitted values from both signal computations over time. When one ends, the new state of both is returned.

bothStart :: Ord t4 => Sig t4 t t1 -> Sig t4 t2 t3 -> React t4 (ISig t4 t t1, ISig t4 t2 t3)Source

Wait for both signal computation to become initialized, and then return both their initizialized signals.

indexBy :: (Show a, Ord e) => Sig e a l -> Sig e b r -> Sig e a ()Source

Sample the former signal computation each time the later emits a value.

iindexBy :: Ord e => ISig e a b -> Sig e t t1 -> Sig e a ()Source

Conversion

emitAll :: ISig e a b -> Sig e a bSource

Convert a initialized signal to a signal computation

emit :: a -> Sig e a ()Source

Emit a single value in the signal computation mondad

always :: a -> Sig e a bSource

A signal that alway has the given form.

waitFor :: React e b -> Sig e a bSource

Convert a reactive computation to a signal computation.

hold :: Sig e a bSource

The reactive computation that never completes.

res :: Sig t t1 b -> React t bSource

Convert the result of a signal computation to a reactive computation.

ires :: ISig t t1 b -> React t bSource

Convert the result of an initialized signal a reactive computation.

cur :: Sig t a t1 -> Maybe aSource

Give the current value of a signal computation, if any.

icur :: ISig t a t1 -> Maybe aSource

the head of an initalized signal, if any.

done :: React t a -> Maybe aSource

Return the result of a reactive computation if it is done

done' :: React t c -> cSource

Version of done that throws an error if it the result is not done.

Dynamic lists

cons :: Ord e => ISig e a l -> ISig e [a] r -> ISig e [a] ()Source

Cons the values from the first signal computation to the values form the latter signal computation over time.

parList :: Ord e => Sig e (ISig e a l) r -> Sig e [a] ()Source

Run the initialized signals from the given signal computation in parallel, and emit the lists of the current form of all alive initialized signals.

iparList :: Ord e => Sig e (ISig e a l) r -> ISig e [a] ()Source

Memoization

memo :: Ord e => React e a -> React e aSource

Memoize the continuation function of the reactive computation, and the continuation function of all next states.

memoSig :: Ord e => Sig e a b -> Sig e a bSource

Memoize the reactive computation of the initialized signal, and memoize the signal computation of the tail (if any).

imemoSig :: Ord e => ISig e a b -> ISig e a bSource