reactive-banana-0.4.0.0: Small but solid library for functional reactive programming (FRP).

Reactive.Banana.Model

Contents

Synopsis

Synopsis

Combinators for building event networks and their semantics.

Core Combinators

class (Functor (Event f), Functor (Behavior f), Applicative (Behavior f)) => FRP f whereSource

The FRP class defines the primitive API for functional reactive programming. Each instance f defines two type constructors Event f and Behavior f and corresponding combinators.

Event f a represents a stream of events as they occur in time. Semantically, you can think of Event f a as an infinite list of values that are tagged with their corresponding time of occurence,

 type Event f a = [(Time,a)]

Behavior f a represents a value that varies in time. Think of it as

 type Behavior f a = Time -> a

While these type synonyms are the way you should think about Behavior and Event, they are a bit vague for formal manipulation. To remedy this, the library provides a very simple model implementation, called Model. This model is authoritative: every instance of the FRP class must give the same results as the model when observed with the interpret function. Note that this must also hold for recursive and partial definitions (at least in spirit, I'm not going to split hairs over _|_ vs \_ -> _|_).

Concerning time and space complexity, the model is not authoritative, however. Implementations are free to be much more efficient.

Minimal complete definition of the FRP class: One of filter or filterApply and one of accumB or stepper.

Methods

never :: Event f aSource

Event that never occurs. Think of it as never = [].

union :: Event f a -> Event f a -> Event f aSource

Merge two event streams of the same type. In case of simultaneous occurrences, the left argument comes first. Think of it as

 union ((timex,x):xs) ((timey,y):ys)
    | timex <= timey = (timex,x) : union xs ((timey,y):ys)
    | timex >  timey = (timey,y) : union ((timex,x):xs) ys

apply :: Behavior f (a -> b) -> Event f a -> Event f bSource

Apply a time-varying function to a stream of events. Think of it as

 apply bf ex = [(time, bf time x) | (time, x) <- ex]

filterE :: (a -> Bool) -> Event f a -> Event f aSource

Allow all events that fulfill the predicate, discard the rest. Think of it as

 filterE p es = [(time,a) | (time,a) <- es, p a]

filterApply :: Behavior f (a -> Bool) -> Event f a -> Event f aSource

Allow all events that fulfill the time-varying predicate, discard the rest. It's a slight generalization of filterE.

stepper :: a -> Event f a -> Behavior f aSource

Construct a time-varying function from an initial value and a stream of new values. Think of it as

 stepper x0 ex = \time -> last (x0 : [x | (timex,x) <- ex, timex < time])

Note that the smaller-than-sign in the comparision timex < time means that the value of the behavior changes "slightly after" the event occurrences. This allows for recursive definitions.

Also note that in the case of simultaneous occurrences, only the last one is kept.

accumB :: a -> Event f (a -> a) -> Behavior f aSource

The accumB function is similar to a strict left fold, foldl'. It starts with an initial value and combines it with incoming events. For example, think

 accumB "x" [(time1,(++"y")),(time2,(++"z"))]
    = stepper "x" [(time1,"xy"),(time2,"xyz")]

Note that the value of the behavior changes "slightly after" the events occur. This allows for recursive definitions.

accumE :: a -> Event f (a -> a) -> Event f aSource

The accumE function accumulates a stream of events. Example:

 accumE "x" [(time1,(++"y")),(time2,(++"z"))]
    = [(time1,"xy"),(time2,"xyz")]

Note that the output events are simultaneous with the input events, there is no "delay" like in the case of accumB.

Instances

data family Event f :: * -> *Source

data family Behavior f :: * -> *Source

Further combinators that Haddock can't document properly.

 instance FRP f => Monoid (Event f a)

The combinators never and union turn Event into a monoid.

 instance FPR f => Applicative (Behavior f)

Behavior is an applicative functor. In particular, we have the following functions.

 pure :: FRP f => a -> Behavior f a

The constant time-varying value. Think of it as pure x = \time -> x.

 (<*>) :: FRP f => Behavior f (a -> b) -> Behavior f a -> Behavior f b

Combine behaviors in applicative style. Think of it as bf <*> bx = \time -> bf time $ bx time.

whenE :: FRP f => Behavior f Bool -> Event f a -> Event f aSource

Variant of filterApply.

mapAccum :: FRP f => acc -> Event f (acc -> (x, acc)) -> (Event f x, Behavior f acc)Source

Efficient combination of accumE and accumB.

Model implementation

data Model Source

The type index Model represents the model implementation. You are encouraged to look at the source code! (If there is no link to the source code at every type signature, then you have to run cabal with --hyperlink-source flag.)

interpretTime :: (Event Model a -> Event Model b) -> [(Time, a)] -> [(Time, b)]Source

Interpreter that corresponds to your mental model.

interpret :: (Event Model a -> Event Model b) -> [a] -> [[b]]Source

Slightly simpler interpreter that does not mention Time. Returns lists of event values that occur simultaneously.