sodium-0.11.0.2: Sodium Reactive Programming (FRP) System

Safe HaskellNone
LanguageHaskell98

FRP.Sodium

Contents

Description

Sodium Reactive Programming (FRP) system.

See the examples directory for test cases and examples.

Some functions are pure, and others need to run under the Reactive monad via sync. An Event (Reactive a) can be flattened to an Event a using the execute primitive.

In addition to the explicit functions in the language, note that you can use

  • Functor on Event and Behavior
  • Applicative on behaviour, e.g. let bsum = (+) <$> ba <*> bb
  • Applicative pure is used to give a constant Behavior.
  • A Monoid instance on Event where mempty = never and mappend = merge
  • Recursive do (using the DoRec language extension) to make state loops with the rec keyword.
  • Data.Traversable.sequenceA is useful to convert [Behavior a] into Behavior [a].

Here's an example of recursive do to write state-keeping loops. Note that all holds are delayed, so snapshot will capture the old value of the state s.

{-# LANGUAGE DoRec #-}
-- | Accumulate state changes given in the input event.
accum :: Context r => a -> Event r (a -> a) -> Reactive r (Behavior r a)
accum z efa = do
    rec
        s <- hold z $ snapshot ($) efa s
    return s

Synopsis

Documentation

Running FRP code

type Reactive = Reactive Plain Source

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

sync :: Reactive 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 (Event a, a -> Reactive ()) Source

Returns an event, and a push action for pushing a value into the event.

newBehavior Source

Arguments

:: a

Initial behavior value

-> Reactive (Behavior a, a -> Reactive ()) 

Create a new Behavior along with an action to push changes into it. American spelling.

newBehaviour Source

Arguments

:: a

Initial behavior value

-> Reactive (Behavior a, a -> Reactive ()) 

Create a new Behavior along with an action to push changes into it. British spelling.

listen :: Event a -> (a -> IO ()) -> Reactive (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 or listen (updates b) handler

NOTE: The callback is called with the transaction held, so you cannot use sync inside a listener. You can delegate to another thread and have that start the new transaction. If you want to do more processing in the same transction, then you can use listenTrans but this is discouraged unless you really need to write a new primitive.

FRP core language

type Event = Event Plain Source

A stream of events. The individual firings of events are called 'event occurrences'.

type Behavior = Behavior Plain Source

A time-varying value, American spelling.

type Behaviour = Behavior Plain Source

A time-varying value, British spelling.

never :: Event a Source

An event that never fires.

merge :: Event a -> Event a -> Event 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 (Maybe a) -> Event a Source

Unwrap Just values, and discard event occurrences with Nothing values.

hold :: a -> Event a -> Reactive (Behavior 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 a -> Event 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 a -> Event 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 updates, firing for each update to the behavior's value.

snapshot :: (a -> b -> c) -> Event a -> Behavior b -> Event 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 holds.

switchE :: Behavior (Event a) -> Event a Source

Unwrap an event inside a behavior to give a time-varying event implementation.

switch :: Behavior (Behavior a) -> Reactive (Behavior a) Source

Unwrap a behavior inside another behavior to give a time-varying behavior implementation.

execute :: Event (Reactive a) -> Event a Source

Execute the specified Reactive action inside an event.

sample :: Behavior a -> Reactive a Source

Obtain the current value of a behavior.

coalesce :: (a -> a -> a) -> Event a -> Event 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 a -> Event a Source

Throw away all event occurrences except for the first one.

split :: Event [a] -> Event 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.

Derived FRP functions

mergeWith :: (a -> a -> a) -> Event a -> Event a -> Event 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 supplied function. The output event is guaranteed not to have more than one event occurrence per transaction.

The combine function should be commutative, because simultaneous events should be considered to be order-agnostic.

filterE :: (a -> Bool) -> Event a -> Event a Source

Only keep event occurrences for which the predicate is true.

gate :: Event a -> Behavior Bool -> Event 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 :: (a -> s -> (b, s)) -> s -> Event a -> Reactive (Event 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 :: (a -> s -> (b, s)) -> s -> Behavior a -> Reactive (Behavior 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 :: a -> Event (a -> a) -> Reactive (Behavior a) Source

Accumulate state changes given in the input event.

Deprecated

changes :: Behavior a -> Event a Source

Deprecated: renamed to updates

An event that gives the updates for the behavior. If the behavior was created with hold, then changes gives you an event equivalent to the one that was held.

values :: Behavior a -> Event a Source

Deprecated: renamed to value

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 a -> Behavior b -> Event c Source

Deprecated: renamed to snapshot

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.

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

Deprecated: removing it in the pursuit of minimalism, replace with: accum 0 (const (1+) $ e)

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