Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Generalization of the Sodium API to allow for parallel processing.
- class (Applicative (Reactive r), Monad (Reactive r), MonadFix (Reactive r), Functor (Event r), Applicative (Behavior r)) => Context r where
- data Reactive r :: * -> *
- data Event r :: * -> *
- data Behavior r :: * -> *
- sync :: Reactive r a -> IO a
- newEvent :: Reactive r (Event r a, a -> Reactive r ())
- listen :: Event r a -> (a -> IO ()) -> Reactive r (IO ())
- never :: Event r a
- merge :: Event r a -> Event r a -> Event r a
- filterJust :: Event r (Maybe a) -> Event r a
- hold :: a -> Event r a -> Reactive r (Behavior r a)
- updates :: Behavior r a -> Event r a
- value :: Behavior r a -> Event r a
- snapshot :: (a -> b -> c) -> Event r a -> Behavior r b -> Event r c
- switchE :: Behavior r (Event r a) -> Event r a
- switch :: Behavior r (Behavior r a) -> Reactive r (Behavior r a)
- execute :: Event r (Reactive r a) -> Event r a
- sample :: Behavior r a -> Reactive r a
- coalesce :: (a -> a -> a) -> Event r a -> Event r a
- once :: Event r a -> Event r a
- split :: Event r [a] -> Event r a
- class Context r => ContextIO r where
- executeAsyncIO :: Event r (IO a) -> Event r a
- executeSyncIO :: Event r (IO a) -> Event r a
- type Behaviour r a = Behavior r a
- newBehavior :: forall r a. Context r => a -> Reactive r (Behavior r a, a -> Reactive r ())
- newBehaviour :: forall r a. Context r => a -> Reactive r (Behavior r a, a -> Reactive r ())
- mergeWith :: Context r => (a -> a -> a) -> Event r a -> Event r a -> Event r a
- filterE :: Context r => (a -> Bool) -> Event r a -> Event r a
- gate :: Context r => Event r a -> Behavior r Bool -> Event r a
- collectE :: Context r => (a -> s -> (b, s)) -> s -> Event r a -> Reactive r (Event r b)
- collect :: Context r => (a -> s -> (b, s)) -> s -> Behavior r a -> Reactive r (Behavior r b)
- accum :: Context r => a -> Event r (a -> a) -> Reactive r (Behavior r a)
Documentation
class (Applicative (Reactive r), Monad (Reactive r), MonadFix (Reactive r), Functor (Event r), Applicative (Behavior r)) => Context r where Source
data Reactive r :: * -> * Source
A stream of events. The individual firings of events are called 'event occurrences'.
data Behavior r :: * -> * Source
A time-varying value, American spelling.
sync :: Reactive r a -> IO a Source
Execute the specified Reactive
within a new transaction, blocking the caller
until all resulting processing is complete and all callbacks have been called.
This operation is thread-safe, so it may be called from any thread.
State changes to hold
values occur after processing of the transaction is complete.
newEvent :: Reactive r (Event r a, a -> Reactive r ()) Source
Returns an event, and a push action for pushing a value into the event.
listen :: Event r a -> (a -> IO ()) -> Reactive r (IO ()) Source
Listen for firings of this event. The returned IO ()
is an IO action
that unregisters the listener. This is the observer pattern.
To listen to a Behavior
use listen (value b) handler
An event that never fires.
merge :: Event r a -> Event r a -> Event r a Source
Merge two streams of events of the same type.
In the case where two event occurrences are simultaneous (i.e. both within the same transaction), both will be delivered in the same transaction. If the event firings are ordered for some reason, then their ordering is retained. In many common cases the ordering will be undefined.
filterJust :: Event r (Maybe a) -> Event r a Source
Unwrap Just values, and discard event occurrences with Nothing values.
hold :: a -> Event r a -> Reactive r (Behavior r a) Source
Create a behavior with the specified initial value, that gets updated by the values coming through the event. The 'current value' of the behavior is notionally the value as it was 'at the start of the transaction'. That is, state updates caused by event firings get processed at the end of the transaction.
updates :: Behavior r a -> Event r a Source
An event that gives the updates for the behavior. If the behavior was created
with hold
, then updates
gives you an event equivalent to the one that was held.
value :: Behavior r a -> Event r a Source
An event that is guaranteed to fire once when you listen to it, giving
the current value of the behavior, and thereafter behaves like changes
,
firing for each update to the behavior's value.
snapshot :: (a -> b -> c) -> Event r a -> Behavior r b -> Event r c Source
Sample the behavior at the time of the event firing. Note that the 'current value'
of the behavior that's sampled is the value as at the start of the transaction
before any state changes of the current transaction are applied through hold
s.
switchE :: Behavior r (Event r a) -> Event r a Source
Unwrap an event inside a behavior to give a time-varying event implementation.
switch :: Behavior r (Behavior r a) -> Reactive r (Behavior r a) Source
Unwrap a behavior inside another behavior to give a time-varying behavior implementation.
execute :: Event r (Reactive r a) -> Event r a Source
Execute the specified Reactive
action inside an event.
sample :: Behavior r a -> Reactive r a Source
Obtain the current value of a behavior.
coalesce :: (a -> a -> a) -> Event r a -> Event r a Source
If there's more than one firing in a single transaction, combine them into one using the specified combining function.
If the event firings are ordered, then the first will appear at the left input of the combining function. In most common cases it's best not to make any assumptions about the ordering, and the combining function would ideally be commutative.
once :: Event r a -> Event r a Source
Throw away all event occurrences except for the first one.
split :: Event r [a] -> Event r a Source
Take each list item and put it into a new transaction of its own.
An example use case of this might be a situation where we are splitting a block of input data into frames. We obviously want each frame to have its own transaction so that state is updated separately each frame.
class Context r => ContextIO r where Source
executeAsyncIO :: Event r (IO a) -> Event r a Source
Execute the specified IO operation asynchronously on a separate thread, and signal the output event in a new transaction upon its completion.
Caveat: Where switch
or switchE
is used, when some reactive logic has been
switched away, we rely on garbage collection to actually disconnect this logic
from any input it may be listening to. With normal Sodium code, everything is
pure, so before garbage collection happens, the worst we will get is some wasted
CPU cycles. If you are using 'executeAsyncIO'/'executeSyncIO' inside a switch
or switchE
, however, it is possible that logic that has been switched away
hasn't been garbage collected yet. This logic could still run, and if it has
observable effects, you could see it running after it is supposed to have been
switched out. One way to avoid this is to pipe the source event for IO out of the
switch, run the 'executeAsyncIO'/'executeSyncIO' outside the switch, and pipe its
output back into the switch contents.
executeSyncIO :: Event r (IO a) -> Event r a Source
Execute the specified IO operation synchronously and fire the output event in the same transaction.
Caveat: See executeAsyncIO
.
:: forall r a . Context r | |
=> a | Initial behavior value |
-> Reactive r (Behavior r a, a -> Reactive r ()) |
Create a new Behavior
along with an action to push changes into it.
American spelling.
:: forall r a . Context r | |
=> a | Initial behavior value |
-> Reactive r (Behavior r a, a -> Reactive r ()) |
Create a new Behavior
along with an action to push changes into it.
British spelling.
mergeWith :: Context r => (a -> a -> a) -> Event r a -> Event r a -> Event r a Source
Merge two streams of events of the same type, combining simultaneous event occurrences.
In the case where multiple event occurrences are simultaneous (i.e. all
within the same transaction), they are combined using the same logic as
coalesce
.
filterE :: Context r => (a -> Bool) -> Event r a -> Event r a Source
Only keep event occurrences for which the predicate returns true.
gate :: Context r => Event r a -> Behavior r Bool -> Event r a Source
Let event occurrences through only when the behavior's value is True. Note that the behavior's value is as it was at the start of the transaction, that is, no state changes from the current transaction are taken into account.
collectE :: Context r => (a -> s -> (b, s)) -> s -> Event r a -> Reactive r (Event r b) Source
Transform an event with a generalized state loop (a mealy machine). The function is passed the input and the old state and returns the new state and output value.