Safe Haskell | None |
---|---|
Language | Haskell98 |
- data Event a
- data Behavior a :: * -> *
- class Monad m => MonadMoment m where
- apply :: Behavior (a -> b) -> Event a -> Event b
- (<@>) :: Behavior (a -> b) -> Event a -> Event b
- union :: Event a -> Event a -> Event a
- filterE :: (a -> Bool) -> Event a -> Event a
- filterJust :: Event (Maybe a) -> Event a
- accumB :: MonadMoment m => a -> Event (a -> a) -> m (Behavior a)
- accumE :: MonadMoment m => a -> Event (a -> a) -> m (Event a)
- mapAccum :: MonadMoment m => acc -> Event (acc -> (x, acc)) -> m (Event x, Behavior acc)
- stepper :: MonadMoment m => a -> Event a -> m (Behavior a)
- valueBLater :: MonadMoment m => Behavior a -> m a
- collect :: Event a -> Event (T [] a)
- spill :: Event (T [] a) -> Event a
Documentation
Behavior a
represents a value that varies in time.
Semantically, you can think of it as a function
type Behavior a = Time -> a
Functor Behavior | The function fmap :: (a -> b) -> Behavior a -> Behavior b fmap f b = \time -> f (b time) |
Applicative Behavior | The function pure :: a -> Behavior a pure x = \time -> x The combinator (<*>) :: Behavior (a -> b) -> Behavior a -> Behavior b fx <*> bx = \time -> fx time $ bx time |
class Monad m => MonadMoment m where #
An instance of the MonadMoment
class denotes a computation
that happens at one particular moment in time.
Unlike the Moment
monad, it need not be pure anymore.
liftMoment :: Moment a -> m a #
valueBLater :: MonadMoment m => Behavior a -> m a #
Obtain the value of the Behavior
at a given moment in time.
Semantically, it corresponds to
valueBLater b = \time -> b time
Note: To allow for more recursion, the value is returned lazily
and not available for pattern matching immediately.
It can be used safely with most combinators like stepper
.
If that doesn't work for you, please use valueB
instead.