elerea-1.2.0: A minimalistic FRP library

FRP.Elerea.Experimental.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.

Synopsis

Documentation

data Signal p 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 p) 
Functor (Signal p) 
Applicative (Signal p) 
Bounded t => Bounded (Signal p t) 
Enum t => Enum (Signal p t) 
Eq (Signal p a)

Equality test is impossible.

Floating t => Floating (Signal p t) 
Fractional t => Fractional (Signal p t) 
Integral t => Integral (Signal p t) 
Num t => Num (Signal p t) 
Ord t => Ord (Signal p t) 
Real t => Real (Signal p t) 
Show (Signal p 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 p 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 p 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.

delaySource

Arguments

:: a

initial output

-> Signal p a

the signal to delay

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

stateful :: a -> (p -> a -> a) -> SignalGen p (Signal p a)Source

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.

transfer :: a -> (p -> t -> a -> a) -> Signal p t -> SignalGen p (Signal p a)Source

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 and the previous output.

memoSource

Arguments

:: Signal p a

signal to memoise

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

generatorSource

Arguments

:: Signal p (SignalGen p a)

a stream of generators to potentially run

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

debug :: String -> SignalGen p ()Source

A printing action within the SignalGen monad.