grapefruit-frp-0.1.0.2: Functional Reactive Programming core

Safe HaskellNone

FRP.Grapefruit.Signal.Discrete

Contents

Description

This module is about discrete signals.

For a general introduction to signals, see the documentation of FRP.Grapefruit.Signal.

Synopsis

Discrete signal type

data DSignal era val Source

The type of discrete signals.

A discrete signal is a sequence of values assigned to discrete times. A pair of a time and a corresponding value is called an occurrence. You can think of DSignal era val as being equivalent to Map (Time era) val where Time era is the type of all times of the given era. However, an occurence at the starting time of the era is not possible. In contrast to Map, a discrete signal may cover infinitely many values.

Discrete signals can describe sequences of events. For example, the sequence of all key presses could be described by a discrete signal of characters. Discrete signals are also used in conjunction with sampling.

The discrete signal instances of Functor and Monoid provide the following method definitions:

        fmap    = map
        mempty  = empty
        mappend = union
        mconcat = unions

Instances

Empty signal

empty :: DSignal era valSource

A signal with no occurrences.

Combination

Union

union :: DSignal era val -> DSignal era val -> DSignal era valSource

Constructs the left-biased union of two discrete signals.

union is equivalent to unionWith const.

unionWith :: (val -> val -> val) -> DSignal era val -> DSignal era val -> DSignal era valSource

Constructs the union of two discrete signals, combining simultaneously occuring values via a combining function.

unionWith is equivalent to transUnion id id.

transUnion :: (val1 -> val') -> (val2 -> val') -> (val1 -> val2 -> val') -> DSignal era val1 -> DSignal era val2 -> DSignal era val'Source

Union with conversion and combination.

At each time, a signal dSignal1 or a signal dSignal2 has an occurence, the signal

        transUnion conv1 conv2 comb dSignal1 dSignal2

has an occurence, too. The value of this occurence is formed as follows:

conv1 val1
if dSignal1 has an occurence of value val1 and dSignal2 has no occurence
conv2 val2
if dSignal2 has an occurence of value val2 and dSignal1 has no occurence
comb val1 val2
if dSignal1 has an occurence of value val1 and dSignal2 has an occurence of value val2

unions :: [DSignal era val] -> DSignal era valSource

Repeated left-biased union.

unions is equivalent to foldl union empty and unionsWith const.

unionsWith :: (val -> val -> val) -> [DSignal era val] -> DSignal era valSource

Repeated union with a combining function.

unionsWith comb is equivalent to foldl (unionWith comb) empty.

Difference

difference :: DSignal era val1 -> DSignal era val2 -> DSignal era val1Source

Constructs the difference of two discrete signals.

difference is equivalent to differenceWith (\_ _ -> Nothing).

differenceWith :: (val1 -> val2 -> Maybe val1) -> DSignal era val1 -> DSignal era val2 -> DSignal era val1Source

Constructs a kind of difference of two discrete signals where occurences may be modified instead of being dropped.

At each time, a signal dSignal1 has an occurence of a value val1, the signal differenceWith comb dSignal1 dSignal has

an occurence of val1
if dSignal2 has no occurence
an occurence of val'
if dSignal2 has an occurence of a value val2 and comb val1 val2 = Just val'
no occurence
if dSignal2 has an occurence of a value val2 and comb val1 val2 = Nothing

Intersection

intersection :: DSignal era val1 -> DSignal era val2 -> DSignal era val1Source

Constructs the left-biased intersection of two discrete signals.

intersection is equivalent to intersectionWith const.

intersectionWith :: (val1 -> val2 -> val') -> DSignal era val1 -> DSignal era val2 -> DSignal era val'Source

Constructs the intersection of two discrete signals, combining values via a combining function.

Mapping and filtering

map :: (val -> val') -> DSignal era val -> DSignal era val'Source

Converts each value occuring in a discrete signal by applying a function to it.

filter :: (val -> Bool) -> DSignal era val -> DSignal era valSource

Drops all occurence of a discrete signal whose values do not fulfill a given predicate.

catMaybes :: DSignal era (Maybe val) -> DSignal era valSource

Converts all occurences with values of the form Just val into occurences with value val and drops all occurences with value Nothing.

mapMaybe :: (val -> Maybe val') -> DSignal era val -> DSignal era val'Source

The combination of map and catMaybes.

mapMaybe fun is equivalent to catMaybes . map fun.

Stateful signals

scan :: accu -> (accu -> val -> accu) -> DSignal era val -> DSignal era accuSource

Accumulates the values of a discrete signal, starting with a given initial value.

Applying scan init fun to a discrete signal replaces its occurence values val_1, val_2 and so on by the values init `fun` val_1, (init `fun` val_1) `fun` val_2 and so on.

scan1 :: (val -> val -> val) -> DSignal era val -> DSignal era valSource

Accumulates the values of a discrete signal, starting with the first occuring value.

Applying scan1 init fun to a discrete signal replaces its occurence values val_1, val_2, val_3 and so on by the values val_1, val_1 `fun` val_2, (val_1 `fun` val_2) `fun` val_3 and so on.

stateful :: state -> DSignal era (state -> (val, state)) -> DSignal era valSource

Constructs a discrete signal by repeatedly applying state transformers.

Applying stateful init to a discrete signal replaces its occurence values trans_1, trans_2, trans_3 and so on by the values fst . trans_1 $ init, fst . trans_2 $ snd . trans_1 $ init, fst . trans_3 $ snd . trans_2 $ snd . trans_1 $ init and so on.

Connectors

consumer :: (val -> IO ()) -> Consumer DSignal valSource

Converts an event handler into a discrete signal consumer.

If a discrete signal is consumed with such a consumer, the handler is called at each occurence with the occuring value as its argument.

producer :: ((val -> IO ()) -> Setup) -> Producer DSignal valSource

Converts an event handler registration into a discrete signal producer.

Applying the argument of producer to an event handler has to yield a setup which makes the handler be called with a certain value everytime the produced signal shall have an occurence of this value.