elerea-0.1.0: A minimalistic FRP library

FRP.Elerea.Internal

Contents

Description

This is the core module of Elerea, which contains the signal implementation and the primitive constructors.

The basic idea is to create a dataflow network whose structure closely resembles the user's definitions by turning each combinator into a mutable variable (an IORef). In other words, each signal is represented by a variable. Such a variable contains information about the operation to perform and (depending on the operation) references to other signals. For instance, a pointwise function application created by the <*> operator contains an SNA node, which holds two references: one to the function signal and another to the argument signal.

In order to have a pure(-looking) applicative interface, the library relies on unsafePerformIO to create the references on demand. In contrast, the execution of the network is explicitly marked as an IO operation. The core library exposes a single function to animate the network called superstep, which takes a signal and a time interval, and mutates all the variables the signal depends on. It is supposed to be called repeatedly in a loop that also takes care of user input.

To ensure consistency, a superstep has two phases: evaluation and finalisation. During evaluation, each signal affected is sampled at the current point of time (sample), advanced by the desired time (advance), and both of these pieces of data are stored in its reference. If the value of a signal is requested multiple times, the sample is simply reused, and no further aging is performed. After successfully sampling the top-level signal, the finalisation process throws away the intermediate samples and marks the aged signals as the current ones, ready to be sampled again. Evaluation is done by the signalValue function, while finalisation is done by commit. Since these functions are invoked recursively on a data structure with existential types, their types also need to be explicity quantified.

As a bonus, applicative nodes are automatically collapsed into lifted functions of up to five arguments. This optimisation significantly reduces the number of nodes in the network.

Synopsis

Implementation

Some type synonyms

type Time = DoubleSource

Time is continuous. Nothing fancy.

type Sink a = a -> IO ()Source

Sinks are used when feeding input into peripheral-bound signals.

The data structures behind signals

newtype Signal a Source

A signal is represented as a transactional structural node.

Constructors

S (IORef (SignalTrans a)) 

Instances

Functor Signal 
Applicative Signal

The Applicative instance with run-time optimisation. The <*> operator tries to move all the pure parts to its left side in order to flatten the structure, hence cutting down on book-keeping costs. Since applicatives are used with pure functions and lifted values most of the time, one can gain a lot by merging these nodes.

Eq (Signal a)

The equality test checks whether to signals are physically the same.

Fractional t => Fractional (Signal t) 
Num t => Num (Signal t) 
Show (Signal a)

The Show instance is only defined for the sake of Num...

data SignalTrans a Source

A node can have two states: stable (freshly created or finalised) or mutating (in the process of aging).

Constructors

Cur (SignalNode a)

Cur s is simply the signal s

Tra a (SignalNode a)

Tra x s is an already sampled signal, where x is the current value and s is the new version of the signal

data SignalNode a Source

The possible structures of a node are defined by the SignalNode type. Note that the SNLx nodes are only needed to optimise applicatives, they can all be expressed in terms of SNK and SNA.

Constructors

SNK a

SNK x: constantly x

SNF (Time -> a)

SNF f: time function f (absolute time)

SNS a (DTime -> a -> a)

SNS x t: stateful generator, where x is current state and t is the update function

forall t . SNT (Signal t) a (DTime -> t -> a -> a)

SNT s x t: stateful transfer function, which also depends on an input signal s

forall t . SNA (Signal (t -> a)) (Signal t)

SNA sf sx: pointwise function application

SNE (Signal a) (Signal Bool) (Signal (Signal a))

SNE s e ss: latcher that starts out as s and becomes the current value of ss at every moment when e is true

SNR (IORef a)

SNR r: opaque reference to connect peripherals

forall t . SNL1 (t -> a) (Signal t)

SNL1 f: fmap f

forall t1 t2 . SNL2 (t1 -> t2 -> a) (Signal t1) (Signal t2)

SNL2 f: liftA2 f

forall t1 t2 t3 . SNL3 (t1 -> t2 -> t3 -> a) (Signal t1) (Signal t2) (Signal t3)

SNL3 f: liftA3 f

forall t1 t2 t3 t4 . SNL4 (t1 -> t2 -> t3 -> t4 -> a) (Signal t1) (Signal t2) (Signal t3) (Signal t4)

SNL4 f: liftA4 f

forall t1 t2 t3 t4 t5 . SNL5 (t1 -> t2 -> t3 -> t4 -> t5 -> a) (Signal t1) (Signal t2) (Signal t3) (Signal t4) (Signal t5)

SNL5 f: liftA5 f

debugLog :: String -> IO a -> IO aSource

You can uncomment the verbose version of this function to see the applicative optimisations in action.

Internal functions to run the network

createSignal :: SignalNode a -> Signal aSource

This function is really just a shorthand to create a reference to a given node.

signalValue :: forall a. Signal a -> DTime -> IO aSource

Sampling and aging the signal and all of its dependencies, at the same time. We don't need the aged signal in the current superstep, only the current value, so we sample before propagating the changes, which might require the fresh sample because of recursive definitions.

commit :: forall a. Signal a -> IO ()Source

Finalising the aged signals for the next round.

advance :: SignalNode a -> DTime -> IO (SignalNode a)Source

Aging the signal. Stateful signals have their state forced to prevent building up big thunks, and the latcher also does its job here. The other nodes are structurally static.

sample :: SignalNode a -> DTime -> IO aSource

Sampling the signal at the current moment. This is where static nodes propagate changes to those they depend on. Note the latcher rule (SNE): the signal is sampled before latching takes place, therefore even if the change is instantaneous, its effect cannot be observed at the moment of latching. This is needed to prevent dependency loops and make recursive definitions involving latching possible. The stateful signals SNS and SNT are similar, although it is only the transfer function where it matters that the input signal cannot affect the current output, only the next one.

timeRef :: IORef TimeSource

The actual variable that keeps track of global time.

Userland primitives

superstepSource

Arguments

:: Signal a

the top-level signal

-> DTime

the amount of time to advance

-> IO a

the value of the signal before the update

Advancing the whole network that the given signal depends on by the amount of time given in the second argument. Note that the shared time signal is also advanced, so this function should only be used for sampling the top level.

time :: Signal TimeSource

The global time.

statelessSource

Arguments

:: (Time -> a)

the function to wrap

-> Signal a 

A pure time function.

statefulSource

Arguments

:: a

initial state

-> (DTime -> a -> a)

state transformation

-> Signal a 

A pure stateful signal.

transferSource

Arguments

:: a

initial state

-> (DTime -> t -> a -> a)

state updater function

-> Signal t

input signal

-> Signal a 

A stateful transfer function. The current input can only affect the next output, i.e. there is an implicit delay.

latcherSource

Arguments

:: Signal a

s: initial behaviour

-> Signal Bool

e: latch control signal

-> Signal (Signal a)

ss: signal of potential future behaviours

-> Signal a 

Reactive signal that starts out as s and can change its behaviour to the one supplied in ss whenever e is true. The change can only be observed in the next instant.

externalSource

Arguments

:: a

initial value

-> IO (Signal a, Sink a)

the signal and an IO function to feed it

A signal that can be directly fed through the sink function returned. This can be used to attach the network to the outer world.