sodium-0.1.0.0: Sodium Reactive Programming (FRP) System

Safe HaskellSafe-Infered

FRP.Sodium

Contents

Description

Sodium Reactive Programming (FRP) system.

The p type parameter determines the partition that your FRP is running on. A thread is automatically created for each partition used in the system based on the unique concrete p type, which must be an instance of Typeable. FRP processing runs on this thread, but synchronously will block the calling thread while it waits for FRP processing to complete.

The cross and crossE functions are used to move events and behaviours between partitions. The separation thus created allows your FRP logic to be partitioned so that the different partitions can run in parallel, with more relaxed guarantees of consistency between partitions.

Some functions are pure, and others need to run under the Reactive monad via synchronously or asynchronously.

In addition to the functions supplied here, note that you can use

  • Functor on Event and Behaviour
  • Applicative on behaviour, e.g. let bsum = (+) <$> ba <*> bb
  • Applicative pure is used to give a constant Behaviour.
  • Recursive do (via DoRec) to make state loops with the rec keyword.

Here's an example of recursive do to write state-keeping loops. Note that attachWith will capture the old value of the state s.

 {-# LANGUAGE DoRec #-}
 -- | Accumulate on input event, outputting the new state each time.
 accumE :: (a -> s -> s) -> s -> Event p a -> Reactive p (Event p s) 
 accumE f z ea = do
     rec
         let es = attachWith f ea s
         s <- hold z es
     return es

Synopsis

Running FRP code

synchronously :: Typeable p => Reactive p a -> IO aSource

Run the specified FRP transaction, blocking the caller until all resulting processing is complete and all callbacks have been called.

asynchronously :: Typeable p => Reactive p () -> IO ()Source

Fire an FRP transaction off without waiting for it to complete. It will be queued for executing on the FRP thread for the selected partition.

newEvent :: Typeable p => IO (Event p a, a -> Reactive p ())Source

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

listen :: Event p a -> (a -> Reactive p ()) -> Reactive p (IO ())Source

Listen for firings of this event. The returned IO () is an IO action that unregisters the listener. This is the observer pattern.

listenIO :: Event p a -> (a -> IO ()) -> Reactive p (IO ())Source

Variant of listen that takes an IO action.

listenValue :: Behaviour p a -> (a -> Reactive p ()) -> Reactive p (IO ())Source

Listen to the value of this behaviour with a guaranteed initial callback giving the current value, followed by callbacks for any updates.

listenValueIO :: Behaviour p a -> (a -> IO ()) -> Reactive p (IO ())Source

Variant of listenValue that takes an IO action.

FRP language

data Event p a Source

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

Instances

never :: Event p aSource

An event that never fires.

merge :: Typeable p => Event p a -> Event p a -> Event p aSource

Merge two streams of events of the same type.

justE :: Typeable p => Event p (Maybe a) -> Event p aSource

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

filterE :: Typeable p => (a -> Bool) -> Event p a -> Event p aSource

Only keep event occurrences for which the predicate is true.

data Behaviour p a Source

A time-varying value, British spelling.

type Behavior p a = Behaviour p aSource

A time-varying value, American spelling.

hold :: a -> Event p a -> Reactive p (Behaviour p a)Source

Create a behaviour with the specified initial value, that gets updated by the values coming through the event. The 'current value' of the behaviour 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.

valueEvent :: Typeable p => Behaviour p a -> Event p aSource

An event that fires once for the current value of the behaviour, and then for all changes that occur after that.

attachWith :: Typeable p => (a -> b -> c) -> Event p a -> Behaviour p b -> Event p cSource

Sample the behaviour at the time of the event firing. Note that the 'current value' of the behaviour 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.

attach :: Typeable p => Event p a -> Behaviour p b -> Event p (a, b)Source

Variant of attachWith defined as attachWith (,)

tag :: Typeable p => Event p a -> Behaviour p b -> Event p bSource

Variant of attachWith that throws away the event's value and captures the behaviour's.

gate :: Typeable p => Event p a -> Behaviour p Bool -> Event p aSource

Let event occurrences through only when the behaviour's value is True. Note that the behaviour'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 :: Typeable p => (a -> s -> (b, s)) -> s -> Event p a -> Reactive p (Event p 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 :: Typeable p => (a -> s -> (b, s)) -> s -> Behaviour p a -> Reactive p (Behaviour p b)Source

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

accumE :: Typeable p => (a -> s -> s) -> s -> Event p a -> Reactive p (Event p s)Source

Accumulate on input event, outputting the new state each time.

countE :: Typeable p => Event p a -> Reactive p (Event p Int)Source

Count event occurrences, starting at 0.

count :: Typeable p => Event p a -> Reactive p (Behaviour p Int)Source

Count event occurrences, giving a behaviour.

switchE :: Typeable p => Behaviour p (Event p a) -> Event p aSource

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

switch :: Typeable p => Behaviour p (Behaviour p a) -> Reactive p (Behaviour p a)Source

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

once :: Typeable p => Event p a -> Reactive p (Event p a)Source

Throw away all event occurrences except for the first one.

execute :: Typeable p => Event p (Reactive p a) -> Event p aSource

Execute the specified Reactive action inside an event.

sample :: Behaviour p a -> Reactive p aSource

Obtain the current value of a behaviour.

Partitions

crossE :: (Typeable p, Typeable q) => Event p a -> Reactive p (Event q a)Source

Cross the specified event over to a different partition.

cross :: (Typeable p, Typeable q) => Behaviour p a -> Reactive p (Behaviour q a)Source

Cross the specified behaviour over to a different partition.