grapefruit-frp-0.1.0.1: Functional Reactive Programming core

Safe HaskellNone

FRP.Grapefruit.Signal

Contents

Description

Signals are the key concept of Functional Reactive Programming. They describe behavior over time. This module provides general support for signals. Individual kinds of signals are provided by the submodules FRP.Grapefruit.Signal.Disrete, FRP.Grapefruit.Signal.Segmented and FRP.Grapefruit.Signal.Continuous.

A signal type has kind * -> * -> *. Its first parameter denotes the time interval in which the signal is alive. This is called the era of the signal. An era is left-closed (contains a starting time) but right-open or right-unbounded (does not contain an ending time).

The era type parameter is not intended to be instantiated with concrete types. Instead, it is used to force equality of eras or independence of eras at compile time. Its use is very similar to that of the first type parameter of ST and the first parameter of STRef.

Synopsis

Signals

class Signal signal Source

The class of all signal types.

Switching

switch :: SSignal era (forall era'. SignalFun era' shape) -> SignalFun era shapeSource

This function generates a signal whose behavior switches between that of different other signals over time.

Since the result type SignalFun era shape is isomorphic to an n-ary function type, we can see switch as a function which takes a first argument, called the function signal, and n further arguments, called the argument signals, and yields a signal, called the result signal.

The result signal is composed of different sections. There is one section for each segment of the function signal. Such a section is formed as follows: For each argument signal, the part which corresponds to the time intervall of the functions signal’s segment is cut out of the argument signal. The value of the function signal is applied to the resulting n signal parts. The result of this application is the desired section of the result signal.

The signal functions which are applied to the parts of the argument signals use an universally quantified era parameter. This ensures that the results of these functions do not depend on signals from the outside but only on the parts of the argument signals. This is important since operations on signals require that their argument and result signals are of the same era. The usage of universial quantification in the type of switch corresponds to the usage of rank 2 polymorphism in the type of runST.

polySwitch :: SSignal era (PolySignalFun shape) -> SignalFun era shapeSource

Signal functions

data SignalFun era shape whereSource

A signal function is a function which maps a certain number of signals to one signal whereby all argument signals and the result signal have the same era.

The era parameter of SignalFun denotes the era of all argument signals and the result signal. The shape parameter is a phantom parameter which specifies the number of argument signals as well as the types of the argument signals and the result signal without their era parameters. It has the following form:

        signal_1 `Of` val_1 :-> ... :-> signal_n `Of` val_n :-> signal' `Of` val'

The data constructors OSF and SSF construct signal functions of zero and non-zero arity, respectively. (The O stands for “zero” and the S stands for “successor”.) A signal function is typically formed by an expression like

        SSF $ \signal_1 ->
        ...
        SSF $ \signal_n ->
        OSF $ signal'

where signal' is an expression that might use signal_1 to signal_n. Signal functions are usually applied like this:

        unOSF $ signalFun `sfApp` signal_1 `sfApp` ... `sfApp` signal_n

Constructors

OSF :: Signal signal => signal era val -> SignalFun era (signal `Of` val) 
SSF :: Signal signal => (signal era val -> SignalFun era shape) -> SignalFun era ((signal `Of` val) :-> shape) 

unOSF :: SignalFun era (signal `Of` val) -> signal era valSource

Converts a nullary signal function into its corresponding signal.

unSSF :: SignalFun era ((signal `Of` val) :-> shape) -> signal era val -> SignalFun era shapeSource

Converts a signal function of non-zero arity into a true function.

sfApp :: SignalFun era ((signal `Of` val) :-> shape) -> signal era val -> SignalFun era shapeSource

Applies a signal function to a signal.

sfApp is equivalent to unSSF.

data argShape :-> resultShape Source

The :-> operator is used to form signal function shapes for SignalFun. The shape argShape :-> resultShape stands for functions which map signals of shape argShape to signal functions of shape resultShape.

newtype PolySignalFun shape Source

Constructors

PolySignalFun (forall era. SignalFun era shape) 

Signal shapes

data Of signal val Source

Of is used to form signal shapes. Signal shapes are used as phantom types and denote a signal type except its era parameter.

A signal shape signal `Of` val stands for a signal of type signal era val where the era parameter is provided by an external source. Signal shapes are used as signal function shapes of nullary functions and as argument shapes for :->. In this case, the era parameter is the era parameter of SignalFun. Signal shapes are also used in records as defined by the module FRP.Grapefruit.Record of package grapefruit-records.

Sampling

class Sampler sampler Source

The class of all signals which can be seen as discrete sequences of values. Such signals can be used to sample signals of class Samplee.

class Samplee samplee Source

The class of all signals which assign a value to each time of their era. Such signals can be sampled by signals of class Sampler.

(<#>) :: (Sampler sampler, Samplee samplee) => sampler era (val -> val') -> samplee era val -> sampler era val'Source

Sampling of signals.

A signal sampler <#> samplee has a value at each time where sampler has a value. The value of sampler <#> samplee is formed by applying the value of sampler to the value, samplee has at this time.

This function has similarities with <*>.

(#>) :: (Sampler sampler, Samplee samplee) => sampler era dummy -> samplee era val -> sampler era valSource

Sampling of signals where the values of the sampler are ignored.

The following equation holds:

        sampler #> samplee = id <$ sampler <#> samplee

This function has similarities with *>.

(<#) :: (Sampler sampler, Samplee samplee) => sampler era val -> samplee era dummy -> sampler era valSource

Sampling of signals where the values of the samplee are ignored.

The following equation holds:

        sampler <# samplee = const <$> sampler <#> samplee

This function has similarities with <*.

Connectors

newtype Consumer signal val Source

A consumer says what to do with a given signal.

Constructors

Consumer (forall era. Circuit era (signal era val) ())

A consumer, represented by a circuit that consumes a signal.

consume :: Consumer signal val -> Circuit era (signal era val) ()Source

Yields a circuit which consumes a signal.

newtype Producer signal val Source

A producer says how to produce a certain signal.

Constructors

Producer (forall era. Circuit era () (signal era val))

A producer, represented by a circuit that produces a signal.

produce :: Producer signal val -> Circuit era () (signal era val)Source

Yields a circuit which produces a signal.