elerea-2.3.0: A minimalistic FRP library

FRP.Elerea.Legacy.Internal

Contents

Description

This is the core module of Elerea, which contains the signal implementation and the atomic 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 for the most part, the library relies on unsafePerformIO to create the references of stateless signals, while stateful signals have to be obtained from a special SignalMonad, which is just a wrapping of IO that doesn't allow any other action to be performed.

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 three phases: sampling, aging and finalisation. Each signal reachable from the top-level signal passed to superstep is sampled at the current point of time (sample), and the sample is stored along with the old signal in its reference. If the value of a signal is requested multiple times, the sample is simply reused. After successfully sampling the top-level signal, the network is traversed again to advance by the desired time (advance), and when that's completed, the finalisation process throws away the intermediate samples and marks the aged signals as the current ones, ready to be sampled again. If there is a dependency loop, the system tries to use the sampleDelayed function instead of sample to get a useful value at the problematic spot instead of entering an infinite loop. Evaluation is initiated by the signalValue function (which is used in both the sampling and the aging phase to calculate samples and retrieve the cached values if they are requested again), aging is performed by age, 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 DTime = 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 SignalMonad a Source

A restricted monad to create stateful signals in.

Constructors

SM 

Fields

createSignal :: IO a
 

signalDebug :: Show a => a -> SignalMonad ()Source

A printing function that can be used in the SignalMonad. Provided for debugging purposes.

newtype Signal a Source

A signal is conceptually a time-varying value.

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.

Bounded t => Bounded (Signal t) 
Enum t => Enum (Signal t) 
Eq (Signal a)

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

Floating t => Floating (Signal t) 
Fractional t => Fractional (Signal t) 
Integral t => Integral (Signal t) 
Num t => Num (Signal t) 
Ord t => Ord (Signal t) 
Real t => Real (Signal t) 
Show (Signal a)

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

data SignalTrans a Source

A node can have four states that distinguish various stages of sampling and aging.

Constructors

Ready (SignalNode a)

Ready s is simply the signal s that was not sampled yet

Sampling (SignalNode a)

Sampling s is signal s after its current value was requested, but not yet delivered

Sampled a (SignalNode a)

Sampled x s is signal s paired with its current value x

Aged a (SignalNode a)

Aged x s is the aged version of signal s paired with its current value x

data SignalNode a Source

The possible structures of a node are defined by the SignalNode type. Note that the SNFx 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

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

SNH (Signal (Signal a)) (IORef (Signal a))

SNH ss r: the higher-order signal ss collapsed into a signal cached in reference r; r is used during the aging phase

SNM (Signal Bool) (Signal (SignalMonad a))

SNM b sm: signal generator that executes the monad carried by sm whenever b is true, and outputs the result (or undefined when b is false)

SNE (IORef a)

SNE r: opaque reference to connect peripherals

SND a (Signal a)

SND s: the s signal delayed by one superstep

forall t . SNKA (Signal a) (Signal t)

SNKA s l: equivalent to s while aging signal l

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

SNF1 f: fmap f

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

SNF2 f: liftA2 f

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

SNF3 f: liftA3 f

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

SNF4 f: liftA4 f

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

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

unimp :: String -> aSource

Error message for unimplemented instance functions.

Internal functions to run the network

makeSignal :: SignalNode a -> SignalMonad (Signal a)Source

Creating a reference within the SignalMonad. Used for stateful signals.

makeSignalUnsafe :: SignalNode a -> Signal aSource

Creating a reference as a pure value. Used for stateless signals.

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

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

age :: forall a. Signal a -> DTime -> IO ()Source

Aging the network of signals the given signal depends on.

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

Finalising aged signals for the next round.

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

Aging the signal. Stateful signals have their state forced to prevent building up big thunks. 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. Transfer functions (SNT) work without delay, i.e. the effects of their input signals can be observed in the same superstep.

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

Sampling the signal with some kind of delay in order to resolve dependency loops. Transfer functions simply return their previous output (delays can be considered a special case, because they always do that, so sampleDelayed is never called with them), while other types of signals are always handled by the sample function, so it is not possible to create a working stateful loop composed of solely stateless combinators.

Userland combinators

superstepSource

Arguments

:: Signal a

the top-level signal

-> DTime

the amount of time to advance

-> IO a

the current value of the signal

Advancing the whole network that the given signal depends on by the amount of time given in the second argument.

statefulSource

Arguments

:: a

initial state

-> (DTime -> a -> a)

state transformation

-> SignalMonad (Signal a) 

A pure stateful signal. The initial state is the first output.

transferSource

Arguments

:: a

initial internal state

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

state updater function

-> Signal t

input signal

-> SignalMonad (Signal a) 

A stateful transfer function. The current input affects the current output, i.e. the initial state given in the first argument is considered to appear before the first output, and can only be directly observed by the sampleDelayed function.

samplerSource

Arguments

:: Signal (Signal a)

signal to flatten

-> Signal a 

A continuous sampler that flattens a higher-order signal by outputting its current snapshots.

generatorSource

Arguments

:: Signal Bool

control (trigger) signal

-> Signal (SignalMonad a)

a stream of monads to potentially run

-> Signal (Maybe a) 

A reactive signal that takes the value to output from a monad carried by its input when a boolean control signal is true, otherwise it outputs Nothing. It is possible to create new signals in the monad and also to print debug messages.

toMaybe :: Bool -> a -> Maybe aSource

A helper function to wrap any value in a Maybe depending on a boolean condition.

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.

delaySource

Arguments

:: a

initial output

-> Signal a

the signal to delay

-> SignalMonad (Signal a) 

The delay transfer function emits the value of a signal from the previous superstep, starting with the filler value given in the first argument. It has to be a primitive, otherwise it could not be used to prevent automatic delays.

keepAliveSource

Arguments

:: Signal a

the actual output

-> Signal t

a signal guaranteed to age when this one is sampled

-> Signal a 

Dependency injection to allow aging signals whose output is not necessarily needed to produce the current sample of the first argument. It's equivalent to (flip . liftA2 . flip) const, as it evaluates its second argument first.