elerea-2.1.0: A minimalistic FRP library

FRP.Elerea.Param

Description

This version differs from the simple one in providing an extra argument to the sampling action that will be globally distributed to every node and can be used to update the state. For instance, it can hold the time step between the two samplings, but it could also encode all the external input to the system.

The interface of this module differs from the old Elerea in the following ways:

  • the delta time argument is generalised to an arbitrary type, so it is possible to do without external altogether in case someone wants to do so;
  • there is no sampler any more, it is substituted by join, as signals are monads;
  • generator has been conceptually simplified, so it's a more basic primitive now;
  • there is no automatic delay in order to preserve semantic soundness (e.g. the monad laws for signals);
  • all signals are aged regardless of whether they are sampled (i.e. their behaviour doesn't depend on the context any more);
  • the user needs to cache the results of applicative operations to be reused in multiple places explicitly using the memo combinator;
  • the input can be retrieved as an explicit signal within the SignalGen monad, and also overridden for parts of the network.

Synopsis

Documentation

data Signal a Source

A signal can be thought of as a function of type Nat -> a, and its Monad instance agrees with that intuition. Internally, is represented by a sampling computation.

Instances

Monad Signal 
Functor Signal 
Applicative Signal 
Bounded t => Bounded (Signal t) 
Enum t => Enum (Signal t) 
Eq (Signal a)

Equality test is impossible.

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 SignalGen p a Source

A signal generator is the only source of stateful signals. Internally, computes a signal structure and adds the new variables to an existing update pool.

startSource

Arguments

:: SignalGen p (Signal a)

the generator of the top-level signal

-> IO (p -> IO a)

the computation to sample the signal

Embedding a signal into an IO environment. Repeated calls to the computation returned cause the whole network to be updated, and the current sample of the top-level signal is produced as a result. The computation accepts a global parameter that will be distributed to all signals. For instance, this can be the time step, if we want to model continuous-time signals.

externalSource

Arguments

:: a

initial value

-> IO (Signal a, a -> IO ())

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. Note that this is optional, as all the input of the network can be fed in through the global parameter, although that is not really convenient for many signals.

externalMultiSource

Arguments

:: IO (SignalGen p (Signal [a]), a -> IO ())

a generator for the event signal and the associated sink

An event-like signal that can be fed through the sink function returned. The signal carries a list of values fed in since the last sampling, i.e. it is constantly [] if the sink is never invoked. The order of elements is reversed, so the last value passed to the sink is the head of the list. Note that unlike external this function only returns a generator to be used within the expression constructing the top-level stream, and this generator can only be used once.

delaySource

Arguments

:: a

initial output

-> Signal a

the signal to delay

-> SignalGen p (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.

generatorSource

Arguments

:: Signal (SignalGen p a)

a stream of generators to potentially run

-> SignalGen p (Signal a) 

A reactive signal that takes the value to output from a monad carried by its input. It is possible to create new signals in the monad.

memoSource

Arguments

:: Signal a

signal to memoise

-> SignalGen p (Signal a) 

Memoising combinator. It can be used to cache results of applicative combinators in case they are used in several places. Other than that, it is equivalent to return.

untilSource

Arguments

:: Signal Bool

the boolean input signal

-> SignalGen p (Signal Bool)

a one-shot signal true only the first time the input is true

A signal that is true exactly once: the first time the input signal is true. Afterwards, it is constantly false, and it holds no reference to the input signal.

input :: SignalGen p (Signal p)Source

The common input signal that is fed through the function returned by start, unless we are in an embedded generator.

embed :: Signal p' -> SignalGen p' a -> SignalGen p aSource

Embed a generator with an overridden input signal.

statefulSource

Arguments

:: a

initial state

-> (p -> a -> a)

state transformation

-> SignalGen p (Signal a) 

A pure stateful signal. The initial state is the first output, and every following output is calculated from the previous one and the value of the global parameter (which might have been overridden by embed). It is equivalent to the following expression:

  stateful x0 f = mfix $ sig -> input >>= i -> delay x0 (f <$> i <*> sig)

transferSource

Arguments

:: a

initial internal state

-> (p -> t -> a -> a)

state updater function

-> Signal t

input signal

-> SignalGen p (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 never be observed. Every output is derived from the current value of the input signal, the global parameter (which might have been overridden by embed) and the previous output. It is equivalent to the following expression:

  transfer x0 f s = mfix $ sig -> input >>= i -> liftA3 f i s <$> delay x0 sig

noise :: MTRandom a => SignalGen p (Signal a)Source

A random signal.

getRandom :: MTRandom a => SignalGen p aSource

A random source within the SignalGen monad.

debug :: String -> SignalGen p ()Source

A printing action within the SignalGen monad.