Safe Haskell | None |
---|
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.
- data Event a
- type EvReqs e = Set e
- type EvOccs e = Set e
- data React e alpha
- exper :: e -> React e e
- interpret :: Monad m => (EvReqs e -> m (EvOccs e)) -> React e a -> m a
- newtype Sig e a b = Sig (React e (ISig e a b))
- data ISig e a b
- interpretSig :: Monad m => (EvReqs e -> m (EvOccs e)) -> (a -> m r) -> Sig e a b -> m b
- first :: Ord e => React e a -> React e b -> React e (React e a, React e b)
- parR :: Ord e => React e a -> React e b -> React e (React e a, React e b)
- update :: Ord e => React e a -> EvOccs e -> React e a
- repeat :: React e a -> Sig e a b
- spawn :: Sig e t t1 -> Sig e (ISig e t t1) b
- map :: (t -> a) -> Sig e t b -> Sig e a b
- imap :: (t -> a) -> ISig e t b -> ISig e a b
- scanl :: (a -> t -> a) -> a -> Sig e t t1 -> Sig e a t1
- iscanl :: (a -> t -> a) -> a -> Sig e t t1 -> ISig e a t1
- break :: (a -> Bool) -> Sig e a b -> Sig e a (ISig e a b)
- ibreak :: (a -> Bool) -> ISig e a b -> ISig e a (ISig e a b)
- foldl :: (a -> b -> a) -> a -> Sig e b r -> React e a
- ifoldl :: (a -> b -> a) -> a -> ISig e b r -> React e a
- find :: (a -> Bool) -> Sig t a t1 -> React t (Maybe a)
- at :: Ord t => Sig t a t1 -> React t b -> React t (Maybe a)
- until :: Ord e => Sig e a t -> React e b -> Sig e a (Sig e a t, React e b)
- iuntil :: Ord t => ISig t a b -> React t alpha -> ISig t a (ISig t a b, React t alpha)
- (<^>) :: Ord e => Sig e (t -> a) b -> Sig e t t1 -> Sig e a (ISig e (t -> a) b, ISig e t t1)
- pairs :: Ord e => ISig e t1 b -> ISig e t2 t -> ISig e (t1, t2) (ISig e t1 b, ISig e t2 t)
- bothStart :: Ord t4 => Sig t4 t t1 -> Sig t4 t2 t3 -> React t4 (ISig t4 t t1, ISig t4 t2 t3)
- indexBy :: (Show a, Ord e) => Sig e a l -> Sig e b r -> Sig e a ()
- iindexBy :: Ord e => ISig e a b -> Sig e t t1 -> Sig e a ()
- emitAll :: ISig e a b -> Sig e a b
- emit :: a -> Sig e a ()
- always :: a -> Sig e a b
- waitFor :: React e b -> Sig e a b
- hold :: Sig e a b
- res :: Sig t t1 b -> React t b
- ires :: ISig t t1 b -> React t b
- cur :: Sig t a t1 -> Maybe a
- icur :: ISig t a t1 -> Maybe a
- done :: React t a -> Maybe a
- done' :: React t c -> c
- cons :: Ord e => ISig e a l -> ISig e [a] r -> ISig e [a] ()
- parList :: Ord e => Sig e (ISig e a l) r -> Sig e [a] ()
- iparList :: Ord e => Sig e (ISig e a l) r -> ISig e [a] ()
- memo :: Ord e => React e a -> React e a
- memoSig :: Ord e => Sig e a b -> Sig e a b
- imemoSig :: Ord e => ISig e a b -> ISig e a b
Basic definitions
A reactive computation
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.
A signal computation is a reactive computation of an initialized signal
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
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.
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.
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.
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.
(<^>) :: 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.
Conversion
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.
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.
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.