Copyright | (c) Atze van der Ploeg 2015 |
---|---|
License | BSD-style |
Maintainer | atzeus@gmail.org |
Stability | provisional |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
Utility FRPNow functions
- step :: a -> Event (Behavior a) -> Behavior a
- cstep :: a -> Event x -> a -> Behavior a
- when :: Behavior Bool -> Behavior (Event ())
- change :: Eq a => Behavior a -> Behavior (Event a)
- edge :: Behavior Bool -> Behavior (Event ())
- tryGetEv :: Event a -> Behavior (Maybe a)
- hasOccured :: Event x -> Behavior Bool
- first :: Event a -> Event a -> Behavior (Event a)
- cmpTime :: Event a -> Event b -> Behavior (Event (EvOrd a b))
- data EvOrd l r
- = Simul l r
- | LeftEarlier l
- | RightEarlier r
- prev :: Eq a => a -> Behavior a -> Behavior (Behavior a)
- foldB :: Eq a => (b -> a -> b) -> b -> Behavior a -> Behavior (Behavior b)
- sampleUntil :: Eq a => Behavior a -> Event () -> Behavior (Event [a])
- planB :: Event (Behavior a) -> Behavior (Event a)
- snapshot :: Behavior a -> Event () -> Behavior (Event a)
- (<@>) :: Behavior (a -> b) -> Event a -> Behavior (Event b)
- class Monad b => Plan b where
- class Monad n => Sample n where
- traceChanges :: (Eq a, Show a) => String -> Behavior a -> Now ()
Behavior construction
step :: a -> Event (Behavior a) -> Behavior a Source
Start with a constant and then switch
Defined as:
step a s = pure a `switch` s
cstep :: a -> Event x -> a -> Behavior a Source
Start with a constant, and switch to another constant when the event arrives.
Defined as:
cstep x e y = pure x `switch` (pure y <$ e)
Getting events from behaviors
when :: Behavior Bool -> Behavior (Event ()) Source
Like whenJust
but on behaviors of type Bool
instead of Maybe
.
Gives the event that the input behavior is True
change :: Eq a => Behavior a -> Behavior (Event a) Source
Gives at any point in time the event that the input behavior changes, and the new value of the input behavior.
edge :: Behavior Bool -> Behavior (Event ()) Source
The resulting behavior gives at any point in time, the event that the input behavior next becomes true. I.e. the next event that there is an edge from False to True. If the input behavior is True already, the event gives the time that it is True again, after first being False for a period of time.
Events and their ordering
tryGetEv :: Event a -> Behavior (Maybe a) Source
Convert an event into a behavior that gives
Nothing
if the event has not occured yet, and Just
the value of the event if the event has already occured.
hasOccured :: Event x -> Behavior Bool Source
The resulting behavior states wheter the input event has already occured.
first :: Event a -> Event a -> Behavior (Event a) Source
Gives the first of two events.
If either of the events lies in the future, then the result will be the first of these events. If both events have already occured, the left event is returned.
cmpTime :: Event a -> Event b -> Behavior (Event (EvOrd a b)) Source
Compare the time of two events.
The resulting behavior gives an event, occuring at the same time as the earliest input event, of which the value indicates if the event where simultanious, or if one was earlier.
If at the time of sampling both event lie in the past, then the result is that they are simulatinous.
The outcome of a cmpTime
: the events occur simultanious, left is earlier or right is earlier.
Simul l r | |
LeftEarlier l | |
RightEarlier r |
Fold and state
prev :: Eq a => a -> Behavior a -> Behavior (Behavior a) Source
Gives the previous value of the behavior, starting with given value.
This cannot be used to prevent immediate feedback loop! Use delay
instead!
foldB :: Eq a => (b -> a -> b) -> b -> Behavior a -> Behavior (Behavior b) Source
A (left) fold over a behavior.
The inital value of the resulting behavior is f i x
where i
the initial value given, and x
is the current value of the behavior.
sampleUntil :: Eq a => Behavior a -> Event () -> Behavior (Event [a]) Source
When sampled at a point in time t, the behavior gives an event with the list of all values of the input behavior between time t and the time that the argument event occurs (including the value when the event occurs).
Sample behaviors on events
planB :: Event (Behavior a) -> Behavior (Event a) Source
Plan to sample the behavior carried by the event as soon as possible.
If the resulting behavior is sampled after the event occurs, then the behavior carried by the event will be sampled now.
snapshot :: Behavior a -> Event () -> Behavior (Event a) Source
Obtain the value of the behavior at the time the event occurs
If the event has already occured when sampling the resulting behavior, we sample not the past, but the current value of the input behavior.
(<@>) :: Behavior (a -> b) -> Event a -> Behavior (Event b) Source
Like snapshot
, but feeds the result of the event to the
value of the given behavior at that time.
Type classes for uniform interface
class Monad n => Sample n where Source
A type class for behavior-like monads, such Now
and the monads from Control.FRPNow.BehaviorEnd