reactive-0.8.8: Simple foundation for functional reactive programmingSource codeContentsIndex
FRP.Reactive.Behavior
Stabilityexperimental
Maintainerconal@conal.net
Description
Reactive behaviors (continuous time)
Synopsis
data BehaviorG tr tf a
type Behavior = BehaviorG ITime TimeT
time :: Behavior TimeT
stepper :: a -> Event a -> Behavior a
switcher :: Behavior a -> Event (Behavior a) -> Behavior a
snapshotWith :: (a -> b -> c) -> Event a -> Behavior b -> Event c
snapshot :: Event a -> Behavior b -> Event (a, b)
snapshot_ :: Event a -> Behavior b -> Event b
accumB :: a -> Event (a -> a) -> Behavior a
scanlB :: forall a. (Behavior a -> Behavior a -> Behavior a) -> Behavior a -> Event (Behavior a) -> Behavior a
monoidB :: Monoid a => Event (Behavior a) -> Behavior a
maybeB :: Event a -> Event b -> Behavior (Maybe a)
flipFlop :: Event a -> Event b -> Behavior Bool
countB :: Num n => Event a -> Behavior n
sumB :: VectorSpace v => Event v -> Behavior v
integral :: (VectorSpace v, Scalar v ~ TimeT) => Event () -> Behavior v -> Behavior v
Documentation
data BehaviorG tr tf a Source

Reactive behaviors. They can be understood in terms of a simple model (denotational semantics) as functions of time, namely at :: BehaviorG t a -> (t -> a).

The semantics of BehaviorG instances are given by corresponding instances for the semantic model (functions). See http://conal.net/blog/posts/simplifying-semantics-with-type-class-morphisms/.

  • Functor: at (fmap f r) == fmap f (at r), i.e., fmap f r at t == f (r at t).
  • Applicative: at (pure a) == pure a, and at (s <*> r) == at s <*> at t. That is, pure a at t == a, and (s <*> r) at t == (s at t) (r at t).
  • Monad: at (return a) == return a, and at (join rr) == join (at . at rr). That is, return a at t == a, and join rr at t == (rr at t) at t. As always, (r >>= f) == join (fmap f r). at (r >>= f) == at r >>= at . f.
  • Monoid: a typical lifted monoid. If o is a monoid, then Reactive o is a monoid, with mempty == pure mempty, and mappend == liftA2 mappend. That is, mempty at t == mempty, and (r mappend s) at t == (r at t) mappend (s at t).
show/hide Instances
type Behavior = BehaviorG ITime TimeTSource
Time-specialized behaviors. Note: The signatures of all of the behavior functions can be generalized. Is the interface generality worth the complexity?
time :: Behavior TimeTSource
The identity generalized behavior. Has value t at time t.
stepper :: a -> Event a -> Behavior aSource
Discretely changing behavior, based on an initial value and a new-value event.
switcher :: Behavior a -> Event (Behavior a) -> Behavior aSource
Switch between behaviors.
snapshotWith :: (a -> b -> c) -> Event a -> Behavior b -> Event cSource
Snapshots a behavior whenever an event occurs and combines the values using the combining function passed.
snapshot :: Event a -> Behavior b -> Event (a, b)Source
Snapshot a behavior whenever an event occurs. See also snapshotWith.
snapshot_ :: Event a -> Behavior b -> Event bSource
Like snapshot but discarding event data (often a is '()').
accumB :: a -> Event (a -> a) -> Behavior aSource
Behavior from an initial value and an updater event. See also accumE.
scanlB :: forall a. (Behavior a -> Behavior a -> Behavior a) -> Behavior a -> Event (Behavior a) -> Behavior aSource
Like scanl for behaviors. See also scanlE.
monoidB :: Monoid a => Event (Behavior a) -> Behavior aSource
Accumulate values from a monoid-valued event. Specialization of scanlB, using mappend and mempty. See also monoidE.
maybeB :: Event a -> Event b -> Behavior (Maybe a)Source
Start out blank (Nothing), latching onto each new a, and blanking on each b. If you just want to latch and not blank, then use mempty for the second event.
flipFlop :: Event a -> Event b -> Behavior BoolSource
Flip-flopping behavior. Turns true whenever first event occurs and false whenever the second event occurs.
countB :: Num n => Event a -> Behavior nSource
Count occurrences of an event. See also countE.
sumB :: VectorSpace v => Event v -> Behavior vSource
Like sum for behaviors.
integral :: (VectorSpace v, Scalar v ~ TimeT) => Event () -> Behavior v -> Behavior vSource
Euler integral.
Produced by Haddock version 2.3.0