reactive-0.10.3: Simple foundation for functional reactive programmingSource codeContentsIndex
FRP.Reactive.Internal.Behavior
Stabilityexperimental
Maintainerconal@conal.net
Description
Representation of reactive behaviors
Synopsis
newtype BehaviorG tr tf a = Beh {
unBeh :: (ReactiveG tr :. Fun tf) a
}
beh :: ReactiveG tr (Fun tf a) -> BehaviorG tr tf a
unb :: BehaviorG tr tf a -> ReactiveG tr (Fun tf a)
Documentation
newtype 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).
Constructors
Beh
unBeh :: (ReactiveG tr :. Fun tf) a
show/hide Instances
beh :: ReactiveG tr (Fun tf a) -> BehaviorG tr tf aSource
Wrap a reactive time fun as a behavior.
unb :: BehaviorG tr tf a -> ReactiveG tr (Fun tf a)Source
Unwrap a behavior.
Produced by Haddock version 2.4.2