reactive-0.10.3: 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 = BehaviorI TimeT
type Behaviour = Behavior
time :: Ord t => BehaviorI t t
stepper :: a -> EventI t a -> BehaviorI t a
switcher :: Ord tr => BehaviorG tr tf a -> EventG tr (BehaviorG tr tf a) -> BehaviorG tr tf a
snapshotWith :: Ord t => (a -> b -> c) -> BehaviorI t b -> EventI t a -> EventI t c
snapshot :: Ord t => BehaviorI t b -> EventI t a -> EventI t (a, b)
snapshot_ :: Ord t => BehaviorI t b -> EventI t a -> EventI t b
whenE :: Ord t => BehaviorI t Bool -> EventI t a -> EventI t a
accumB :: a -> EventI t (a -> a) -> BehaviorI t a
scanlB :: forall a b tr tf. Ord tr => (b -> BehaviorG tr tf a -> BehaviorG tr tf a) -> BehaviorG tr tf a -> EventG tr b -> BehaviorG tr tf a
monoidB :: (Ord tr, Monoid a) => EventG tr (BehaviorG tr tf a) -> BehaviorG tr tf a
maybeB :: Ord t => EventI t a -> EventI t b -> BehaviorI t (Maybe a)
flipFlop :: Ord t => EventI t a -> EventI t b -> BehaviorI t Bool
countB :: (Ord t, Num n) => EventI t a -> BehaviorI t n
sumB :: (Ord t, AdditiveGroup a) => EventI t a -> BehaviorI t a
integral :: (Scalar v ~ t, Ord t, VectorSpace v, Num t) => EventI t a -> BehaviorI t v -> BehaviorI t 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 = BehaviorI TimeTSource
Time-specialized behaviors. Note: The signatures of all of the behavior functions can be generalized. Is the interface generality worth the complexity?
type Behaviour = BehaviorSource
time :: Ord t => BehaviorI t tSource

The identity generalized behavior. Has value t at time t.

 time :: Behavior TimeT
stepper :: a -> EventI t a -> BehaviorI t aSource

Discretely changing behavior, based on an initial value and a new-value event.

stepper :: a -> Event a -> Behavior a
switcher :: Ord tr => BehaviorG tr tf a -> EventG tr (BehaviorG tr tf a) -> BehaviorG tr tf aSource

Switch between behaviors.

 switcher :: Behavior a -> Event (Behavior a) -> Behavior a
snapshotWith :: Ord t => (a -> b -> c) -> BehaviorI t b -> EventI t a -> EventI t cSource

Snapshots a behavior whenever an event occurs and combines the values using the combining function passed. Take careful note of the order of arguments and results.

 snapshotWith :: (a -> b -> c) -> Behavior b -> Event a -> Event c
snapshot :: Ord t => BehaviorI t b -> EventI t a -> EventI t (a, b)Source

Snapshot a behavior whenever an event occurs. See also snapshotWith. Take careful note of the order of arguments and results.

 snapshot :: Behavior b -> Event a -> Event (a,b)
snapshot_ :: Ord t => BehaviorI t b -> EventI t a -> EventI t bSource

Like snapshot but discarding event data (often a is '()').

 snapshot_ :: Behavior b -> Event a -> Event b
whenE :: Ord t => BehaviorI t Bool -> EventI t a -> EventI t aSource

Filter an event according to whether a reactive boolean is true.

 whenE :: Behavior Bool -> Event a -> Event a
accumB :: a -> EventI t (a -> a) -> BehaviorI t aSource

Behavior from an initial value and an updater event. See also accumE.

 accumB :: a -> Event (a -> a) -> Behavior a
scanlB :: forall a b tr tf. Ord tr => (b -> BehaviorG tr tf a -> BehaviorG tr tf a) -> BehaviorG tr tf a -> EventG tr b -> BehaviorG tr tf aSource

Like scanl for behaviors. See also scanlE.

 scanlB :: forall a. (Behavior a -> Behavior a -> Behavior a) -> Behavior a
        -> Event (Behavior a) -> Behavior a
monoidB :: (Ord tr, Monoid a) => EventG tr (BehaviorG tr tf a) -> BehaviorG tr tf aSource

Accumulate values from a monoid-valued event. Specialization of scanlB, using mappend and mempty. See also monoidE.

 monoidB :: Monoid a => Event (Behavior a) -> Behavior a
maybeB :: Ord t => EventI t a -> EventI t b -> BehaviorI t (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.

 maybeB :: Event a -> Event b -> Behavior (Maybe a)
flipFlop :: Ord t => EventI t a -> EventI t b -> BehaviorI t BoolSource

Flip-flopping behavior. Turns true whenever first event occurs and false whenever the second event occurs.

 flipFlop :: Event a -> Event b -> Behavior Bool
countB :: (Ord t, Num n) => EventI t a -> BehaviorI t nSource

Count occurrences of an event. See also countE.

 countB :: Num n => Event a -> Behavior n
sumB :: (Ord t, AdditiveGroup a) => EventI t a -> BehaviorI t aSource

Like sum for behaviors.

 sumB :: AdditiveGroup a => Event a -> Behavior a
integral :: (Scalar v ~ t, Ord t, VectorSpace v, Num t) => EventI t a -> BehaviorI t v -> BehaviorI t vSource

Euler integral.

 integral :: (VectorSpace v, Scalar v ~ TimeT) =>
             Event () -> Behavior v -> Behavior v
Produced by Haddock version 2.4.2