sodium-0.6.0.1: Sodium Reactive Programming (FRP) System

Safe HaskellSafe-Inferred

FRP.Sodium.Context

Description

Generalization of the Sodium API to allow for parallel processing.

Synopsis

Documentation

class (Applicative (Reactive r), Monad (Reactive r), MonadFix (Reactive r), Functor (Event r), Applicative (Behavior r)) => Context r whereSource

Associated Types

data Reactive r :: * -> *Source

A monad for transactional reactive operations. Execute it from IO using sync.

data Event 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.

Methods

sync :: Reactive r a -> IO aSource

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.

ioReactive :: IO a -> Reactive r aSource

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 (values b) handler

never :: Event r aSource

An event that never fires.

merge :: Event r a -> Event r a -> Event r aSource

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 aSource

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.

changes :: Behavior r a -> Event r aSource

An event that gives the updates for the behavior. It doesn't do any equality comparison as the name might imply.

values :: Behavior r a -> Event r aSource

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.

snapshotWith :: (a -> b -> c) -> Event r a -> Behavior r b -> Event r cSource

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 holds.

switchE :: Behavior r (Event r a) -> Event r aSource

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 aSource

Execute the specified Reactive action inside an event.

sample :: Behavior r a -> Reactive r aSource

Obtain the current value of a behavior.

coalesce :: (a -> a -> a) -> Event r a -> Event r aSource

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 :: Context r => Event r a -> Event r aSource

Throw away all event occurrences except for the first one.

Instances

type Behaviour r a = Behavior r aSource

A time-varying value, British spelling.

newBehaviorSource

Arguments

:: 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.

newBehaviourSource

Arguments

:: 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 aSource

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 aSource

Only keep event occurrences for which the predicate returns true.

snapshot :: Context r => Event r a -> Behavior r b -> Event r bSource

Variant of snapshotWith that throws away the event's value and captures the behavior's.

gate :: Context r => Event r a -> Behavior r Bool -> Event r aSource

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.

collect :: Context r => (a -> s -> (b, s)) -> s -> Behavior r a -> Reactive r (Behavior r b)Source

Transform a behavior 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.

accum :: Context r => a -> Event r (a -> a) -> Reactive r (Behavior r a)Source

Accumulate state changes given in the input event.

count :: Context r => Event r a -> Reactive r (Behavior r Int)Source

Count event occurrences, giving a behavior that starts with 0 before the first occurrence.