Yampa-0.10.2: Library for programming hybrid systems.

Copyright(c) Antony Courtney and Henrik Nilsson, Yale University, 2003
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerivan.perez@keera.co.uk
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell98

FRP.Yampa

Contents

Description

Domain-specific language embedded in Haskell for programming hybrid (mixed discrete-time and continuous-time) systems. Yampa is based on the concepts of Functional Reactive Programming (FRP) and is structured using arrow combinators.

You can find examples, tutorials and documentation on Yampa here:

www.haskell.org/haskellwiki/Yampa

Structuring a hybrid system in Yampa is done based on two main concepts:

  • Signal Functions: SF. Yampa is based on the concept of Signal Functions, which are functions from a typed input signal to a typed output signal. Conceptually, signals are functions from Time to Value, where time are the real numbers and, computationally, a very dense approximation (Double) is used.
  • Events: Event. Values that may or may not occur (and would probably occur rarely). It is often used for incoming network messages, mouse clicks, etc. Events are used as values carried by signals.

A complete Yampa system is defined as one Signal Function from some type a to a type b. The execution of this signal transformer with specific input can be accomplished by means of two functions: reactimate (which needs an initialization action, an input sensing action and an actuation/consumer action and executes until explicitly stopped), and react (which executes only one cycle).

This will be the last version of Yampa to include mergeable records, point2 and point3, vector2 and vector3, and other auxiliary definitions. The internals have now changed. Although not all will be exposed in the next version, below is the new project structure. Please, take a look and let us know if you think there are any potential problems with it.

Main Yampa modules:

Minimal Complete FRP Definition

Different FRP aspects

Internals

Geometry:

Old legacy code:

CHANGELOG:

  • Adds (most) documentation.
  • New version using GADTs.

ToDo:

  • Specialize def. of repeatedly. Could have an impact on invaders.
  • New defs for accs using SFAcc
  • Make sure opt worked: e.g.
    repeatedly >>> count >>> arr (fmap sqr)
  • Introduce SFAccHld.
  • See if possible to unify AccHld wity Acc??? They are so close.
  • Introduce SScan. BUT KEEP IN MIND: Most if not all opts would have been possible without GADTs???
  • Look into pairs. At least pairing of SScan ought to be interesting.
  • Would be nice if we could get rid of first & second with impunity thanks to Id optimizations. That's a clear win, with or without an explicit pair combinator.
  • delayEventCat is a bit complicated ...

Random ideas:

  • What if one used rules to optimize
  • (arr :: SF a ()) to (constant ())
  • (arr :: SF a a) to identity But inspection of invader source code seem to indicate that these are not very common cases at all.
  • It would be nice if it was possible to come up with opt. rules that are invariant of how signal function expressions are parenthesized. Right now, we have e.g. arr f >>> (constant c >>> sf) being optimized to cpAuxA1 f (cpAuxC1 c sf) whereas it clearly should be possible to optimize to just cpAuxC1 c sf What if we didn't use SF' but SFComp :: tfun -> SF' a b -> SF' b c -> SF' a c ???
  • The transition function would still be optimized in (pretty much) the current way, but it would still be possible to look "inside" composed signal functions for lost optimization opts. Seems to me this could be done without too much extra effort/no dupl. work. E.g. new cpAux, the general case:
     cpAux sf1 sf2 = SFComp tf sf1 sf2
         where
             tf dt a = (cpAux sf1' sf2', c)
                 where
                     (sf1', b) = (sfTF' sf1) dt a
                     (sf2', c) = (sfTF' sf2) dt b
  • The ONLY change was changing the constructor from SF' to SFComp and adding sf1 and sf2 to the constructor app.!
  • An optimized case: cpAuxC1 b sf1 sf2 = SFComp tf sf1 sf2 So cpAuxC1 gets an extra arg, and we change the constructor. But how to exploit without writing 1000s of rules??? Maybe define predicates on SFComp to see if the first or second sf are "interesting", and if so, make "reassociate" and make a recursive call? E.g. we're in the arr case, and the first sf is another arr, so we'd like to combine the two.
  • It would also be intersting, then, to know when to STOP playing this game, due to the overhead involved.
  • Why don't we have a SWITCH constructor that indicates that the structure will change, and thus that it is worthwile to keep looking for opt. opportunities, whereas a plain SF' would indicate that things NEVER are going to change, and thus we can just as well give up?

Synopsis

Documentation

class RandomGen g where

The class RandomGen provides a common interface to random number generators.

Minimal complete definition

next, split

Methods

next :: g -> (Int, g)

The next operation returns an Int that is uniformly distributed in the range returned by genRange (including both end points), and a new generator.

genRange :: g -> (Int, Int)

The genRange operation yields the range of values returned by the generator.

It is required that:

The second condition ensures that genRange cannot examine its argument, and hence the value it returns can be determined only by the instance of RandomGen. That in turn allows an implementation to make a single call to genRange to establish a generator's range, without being concerned that the generator returned by (say) next might have a different range to the generator passed to next.

The default definition spans the full range of Int.

split :: g -> (g, g)

The split operation allows one to obtain two distinct random number generators. This is very useful in functional programs (for example, when passing a random number generator down to recursive calls), but very little work has been done on statistically robust implementations of split ([System.Random, System.Random] are the only examples we know of).

Instances

class Random a where

With a source of random number supply in hand, the Random class allows the programmer to extract random values of a variety of types.

Minimal complete definition: randomR and random.

Minimal complete definition

randomR, random

Methods

randomR :: RandomGen g => (a, a) -> g -> (a, g)

Takes a range (lo,hi) and a random number generator g, and returns a random value uniformly distributed in the closed interval [lo,hi], together with a new generator. It is unspecified what happens if lo>hi. For continuous types there is no requirement that the values lo and hi are ever produced, but they may be, depending on the implementation and the interval.

random :: RandomGen g => g -> (a, g)

The same as randomR, but using a default range determined by the type:

  • For bounded types (instances of Bounded, such as Char), the range is normally the whole type.
  • For fractional types, the range is normally the semi-closed interval [0,1).
  • For Integer, the range is (arbitrarily) the range of Int.

randomRs :: RandomGen g => (a, a) -> g -> [a]

Plural variant of randomR, producing an infinite list of random values instead of returning a new generator.

randoms :: RandomGen g => g -> [a]

Plural variant of random, producing an infinite list of random values instead of returning a new generator.

randomRIO :: (a, a) -> IO a

A variant of randomR that uses the global random number generator (see System.Random).

randomIO :: IO a

A variant of random that uses the global random number generator (see System.Random).

Basic definitions

type Time = Double Source

Time is used both for time intervals (duration), and time w.r.t. some agreed reference point in time.

type DTime = Double Source

DTime is the time type for lengths of sample intervals. Conceptually, DTime = R+ = { x in R | x > 0 }. Don't assume Time and DTime have the same representation.

data SF a b Source

Signal function that transforms a signal carrying values of some type a into a signal carrying values of some type b. You can think of it as (Signal a -> Signal b). A signal is, conceptually, a function from Time to value.

Instances

data Event a Source

A single possible event occurrence, that is, a value that may or may not occur. Events are used to represent values that are not produced continuously, such as mouse clicks (only produced when the mouse is clicked, as opposed to mouse positions, which are always defined).

Constructors

NoEvent 
Event a 

Instances

Functor Event 
Eq a => Eq (Event a) 
Ord a => Ord (Event a) 
Show a => Show (Event a) 
NFData a => NFData (Event a) 
Forceable a => Forceable (Event a) 

Lifting

arrPrim :: (a -> b) -> SF a b Source

Lifts a pure function into a signal function (applied pointwise).

arrEPrim :: (Event a -> b) -> SF (Event a) b Source

Lifts a pure function into a signal function applied to events (applied pointwise).

Signal functions

Basic signal functions

identity :: SF a a Source

Identity: identity = arr id

Using identity is preferred over lifting id, since the arrow combinators know how to optimise certain networks based on the transformations being applied.

constant :: b -> SF a b Source

Identity: constant b = arr (const b)

Using constant is preferred over lifting const, since the arrow combinators know how to optimise certain networks based on the transformations being applied.

localTime :: SF a Time Source

Outputs the time passed since the signal function instance was started.

time :: SF a Time Source

Alternative name for localTime.

Initialization

(-->) :: b -> SF a b -> SF a b infixr 0 Source

Initialization operator (cf. Lustre/Lucid Synchrone).

The output at time zero is the first argument, and from that point on it behaves like the signal function passed as second argument.

(>--) :: a -> SF a b -> SF a b infixr 0 Source

Input initialization operator.

The input at time zero is the first argument, and from that point on it behaves like the signal function passed as second argument.

(-=>) :: (b -> b) -> SF a b -> SF a b infixr 0 Source

Transform initial output value.

Applies a transformation f only to the first output value at time zero.

(>=-) :: (a -> a) -> SF a b -> SF a b infixr 0 Source

Transform initial input value.

Applies a transformation f only to the first input value at time zero.

initially :: a -> SF a a Source

Override initial value of input signal.

Simple, stateful signal processing

sscan :: (b -> a -> b) -> b -> SF a b Source

sscanPrim :: (c -> a -> Maybe (c, b)) -> c -> b -> SF a b Source

Events

Basic event sources

never :: SF a (Event b) Source

Event source that never occurs.

now :: b -> SF a (Event b) Source

Event source with a single occurrence at time 0. The value of the event is given by the function argument.

after Source

Arguments

:: Time

The time q after which the event should be produced

-> b

Value to produce at that time

-> SF a (Event b) 

Event source with a single occurrence at or as soon after (local) time q as possible.

repeatedly :: Time -> b -> SF a (Event b) Source

Event source with repeated occurrences with interval q. Note: If the interval is too short w.r.t. the sampling intervals, the result will be that events occur at every sample. However, no more than one event results from any sampling interval, thus avoiding an "event backlog" should sampling become more frequent at some later point in time.

afterEach :: [(Time, b)] -> SF a (Event b) Source

Event source with consecutive occurrences at the given intervals. Should more than one event be scheduled to occur in any sampling interval, only the first will in fact occur to avoid an event backlog.

afterEachCat :: [(Time, b)] -> SF a (Event [b]) Source

Event source with consecutive occurrences at the given intervals. Should more than one event be scheduled to occur in any sampling interval, the output list will contain all events produced during that interval.

delayEvent :: Time -> SF (Event a) (Event a) Source

Delay for events. (Consider it a triggered after, hence basic.)

delayEventCat :: Time -> SF (Event a) (Event [a]) Source

Delay an event by a given delta and catenate events that occur so closely so as to be inseparable.

edge :: SF Bool (Event ()) Source

A rising edge detector. Useful for things like detecting key presses. It is initialised as up, meaning that events occuring at time 0 will not be detected.

iEdge :: Bool -> SF Bool (Event ()) Source

A rising edge detector that can be initialized as up (True, meaning that events occurring at time 0 will not be detected) or down (False, meaning that events ocurring at time 0 will be detected).

edgeTag :: a -> SF Bool (Event a) Source

Like edge, but parameterized on the tag value.

edgeJust :: SF (Maybe a) (Event a) Source

Edge detector particularized for detecting transtitions on a Maybe signal from Nothing to Just.

edgeBy :: (a -> a -> Maybe b) -> a -> SF a (Event b) Source

Edge detector parameterized on the edge detection function and initial state, i.e., the previous input sample. The first argument to the edge detection function is the previous sample, the second the current one.

Stateful event suppression

notYet :: SF (Event a) (Event a) Source

Suppression of initial (at local time 0) event.

once :: SF (Event a) (Event a) Source

Suppress all but the first event.

takeEvents :: Int -> SF (Event a) (Event a) Source

Suppress all but the first n events.

dropEvents :: Int -> SF (Event a) (Event a) Source

Suppress first n events.

Pointwise functions on events

noEvent :: Event a Source

Make the NoEvent constructor available. Useful e.g. for initialization, ((-->) & friends), and it's easily available anyway (e.g. mergeEvents []).

noEventFst :: (Event a, b) -> (Event c, b) Source

Suppress any event in the first component of a pair.

noEventSnd :: (a, Event b) -> (a, Event c) Source

Suppress any event in the second component of a pair.

event :: a -> (b -> a) -> Event b -> a Source

An event-based version of the maybe function.

fromEvent :: Event a -> a Source

Extract the value from an event. Fails if there is no event.

isEvent :: Event a -> Bool Source

Tests whether the input represents an actual event.

isNoEvent :: Event a -> Bool Source

Negation of isEvent.

tag :: Event a -> b -> Event b infixl 8 Source

Tags an (occurring) event with a value ("replacing" the old value).

tagWith :: b -> Event a -> Event b Source

Tags an (occurring) event with a value ("replacing" the old value). Same as tag with the arguments swapped.

attach :: Event a -> b -> Event (a, b) infixl 8 Source

Attaches an extra value to the value of an occurring event.

lMerge :: Event a -> Event a -> Event a infixl 6 Source

Left-biased event merge (always prefer left event, if present).

rMerge :: Event a -> Event a -> Event a infixl 6 Source

Right-biased event merge (always prefer right event, if present).

merge :: Event a -> Event a -> Event a infixl 6 Source

Unbiased event merge: simultaneous occurrence is an error.

mergeBy :: (a -> a -> a) -> Event a -> Event a -> Event a Source

Event merge parameterized by a conflict resolution function.

mapMerge :: (a -> c) -> (b -> c) -> (a -> b -> c) -> Event a -> Event b -> Event c Source

A generic event merge-map utility that maps event occurrences, merging the results. The first three arguments are mapping functions, the third of which will only be used when both events are present. Therefore, mergeBy = mapMerge id id

mergeEvents :: [Event a] -> Event a Source

Merge a list of events; foremost event has priority.

catEvents :: [Event a] -> Event [a] Source

Collect simultaneous event occurrences; no event if none.

joinE :: Event a -> Event b -> Event (a, b) infixl 7 Source

Join (conjunction) of two events. Only produces an event if both events exist.

splitE :: Event (a, b) -> (Event a, Event b) Source

Split event carrying pairs into two events.

filterE :: (a -> Bool) -> Event a -> Event a Source

Filter out events that don't satisfy some predicate.

mapFilterE :: (a -> Maybe b) -> Event a -> Event b Source

Combined event mapping and filtering. Note: since Event is a Functor, see fmap for a simpler version of this function with no filtering.

gate :: Event a -> Bool -> Event a infixl 8 Source

Enable/disable event occurences based on an external condition.

Switching

Basic switchers

switch :: SF a (b, Event c) -> (c -> SF a b) -> SF a b Source

Basic switch.

By default, the first signal function is applied.

Whenever the second value in the pair actually is an event, the value carried by the event is used to obtain a new signal function to be applied *at that time and at future times*.

Until that happens, the first value in the pair is produced in the output signal.

Important note: at the time of switching, the second signal function is applied immediately. If that second SF can also switch at time zero, then a double (nested) switch might take place. If the second SF refers to the first one, the switch might take place infinitely many times and never be resolved.

Remember: The continuation is evaluated strictly at the time of switching!

dSwitch :: SF a (b, Event c) -> (c -> SF a b) -> SF a b Source

Switch with delayed observation.

By default, the first signal function is applied.

Whenever the second value in the pair actually is an event, the value carried by the event is used to obtain a new signal function to be applied *at future times*.

Until that happens, the first value in the pair is produced in the output signal.

Important note: at the time of switching, the second signal function is used immediately, but the current input is fed by it (even though the actual output signal value at time 0 is discarded).

If that second SF can also switch at time zero, then a double (nested) -- switch might take place. If the second SF refers to the first one, the switch might take place infinitely many times and never be resolved.

Remember: The continuation is evaluated strictly at the time of switching!

rSwitch :: SF a b -> SF (a, Event (SF a b)) b Source

Recurring switch.

See http://www.haskell.org/haskellwiki/Yampa#Switches for more information on how this switch works.

drSwitch :: SF a b -> SF (a, Event (SF a b)) b Source

Recurring switch with delayed observation.

See http://www.haskell.org/haskellwiki/Yampa#Switches for more information on how this switch works.

kSwitch :: SF a b -> SF (a, b) (Event c) -> (SF a b -> c -> SF a b) -> SF a b Source

Call-with-current-continuation switch.

See http://www.haskell.org/haskellwiki/Yampa#Switches for more information on how this switch works.

dkSwitch :: SF a b -> SF (a, b) (Event c) -> (SF a b -> c -> SF a b) -> SF a b Source

kSwitch with delayed observation.

See http://www.haskell.org/haskellwiki/Yampa#Switches for more information on how this switch works.

Parallel composition and switching

Parallel composition and switching over collections with broadcasting

parB :: Functor col => col (SF a b) -> SF a (col b) Source

Spatial parallel composition of a signal function collection. Given a collection of signal functions, it returns a signal function that broadcasts its input signal to every element of the collection, to return a signal carrying a collection of outputs. See par.

For more information on how parallel composition works, check http://haskell.cs.yale.edu/wp-content/uploads/2011/01/yampa-arcade.pdf

pSwitchB :: Functor col => col (SF a b) -> SF (a, col b) (Event c) -> (col (SF a b) -> c -> SF a (col b)) -> SF a (col b) Source

Parallel switch (dynamic collection of signal functions spatially composed in parallel). See pSwitch.

For more information on how parallel composition works, check http://haskell.cs.yale.edu/wp-content/uploads/2011/01/yampa-arcade.pdf

dpSwitchB :: Functor col => col (SF a b) -> SF (a, col b) (Event c) -> (col (SF a b) -> c -> SF a (col b)) -> SF a (col b) Source

Delayed parallel switch with broadcasting (dynamic collection of signal functions spatially composed in parallel). See dpSwitch.

For more information on how parallel composition works, check http://haskell.cs.yale.edu/wp-content/uploads/2011/01/yampa-arcade.pdf

rpSwitchB :: Functor col => col (SF a b) -> SF (a, Event (col (SF a b) -> col (SF a b))) (col b) Source

drpSwitchB :: Functor col => col (SF a b) -> SF (a, Event (col (SF a b) -> col (SF a b))) (col b) Source

Parallel composition and switching over collections with general routing

par Source

Arguments

:: Functor col 
=> (forall sf. a -> col sf -> col (b, sf))

Determines the input to each signal function in the collection. IMPORTANT! The routing function MUST preserve the structure of the signal function collection.

-> col (SF b c)

Signal function collection.

-> SF a (col c) 

Spatial parallel composition of a signal function collection parameterized on the routing function.

pSwitch Source

Arguments

:: Functor col 
=> (forall sf. a -> col sf -> col (b, sf))

Routing function: determines the input to each signal function in the collection. IMPORTANT! The routing function has an obligation to preserve the structure of the signal function collection.

-> col (SF b c)

Signal function collection.

-> SF (a, col c) (Event d)

Signal function generating the switching event.

-> (col (SF b c) -> d -> SF a (col c))

Continuation to be invoked once event occurs.

-> SF a (col c) 

Parallel switch parameterized on the routing function. This is the most general switch from which all other (non-delayed) switches in principle can be derived. The signal function collection is spatially composed in parallel and run until the event signal function has an occurrence. Once the switching event occurs, all signal function are "frozen" and their continuations are passed to the continuation function, along with the event value.

dpSwitch Source

Arguments

:: Functor col 
=> (forall sf. a -> col sf -> col (b, sf))

Routing function. Its purpose is to pair up each running signal function in the collection maintained by dpSwitch with the input it is going to see at each point in time. All the routing function can do is specify how the input is distributed.

-> col (SF b c)

Initial collection of signal functions.

-> SF (a, col c) (Event d)

Signal function that observes the external input signal and the output signals from the collection in order to produce a switching event.

-> (col (SF b c) -> d -> SF a (col c))

The fourth argument is a function that is invoked when the switching event occurs, yielding a new signal function to switch into based on the collection of signal functions previously running and the value carried by the switching event. This allows the collection to be updated and then switched back in, typically by employing dpSwitch again.

-> SF a (col c) 

Parallel switch with delayed observation parameterized on the routing function.

The collection argument to the function invoked on the switching event is of particular interest: it captures the continuations of the signal functions running in the collection maintained by dpSwitch at the time of the switching event, thus making it possible to preserve their state across a switch. Since the continuations are plain, ordinary signal functions, they can be resumed, discarded, stored, or combined with other signal functions.

rpSwitch :: Functor col => (forall sf. a -> col sf -> col (b, sf)) -> col (SF b c) -> SF (a, Event (col (SF b c) -> col (SF b c))) (col c) Source

drpSwitch :: Functor col => (forall sf. a -> col sf -> col (b, sf)) -> col (SF b c) -> SF (a, Event (col (SF b c) -> col (SF b c))) (col c) Source

Discrete to continuous-time signal functions

Wave-form generation

hold :: a -> SF (Event a) a Source

Zero-order hold.

dHold :: a -> SF (Event a) a Source

Zero-order hold with delay.

Identity: dHold a0 = hold a0 >>> iPre a0).

trackAndHold :: a -> SF (Maybe a) a Source

Tracks input signal when available, holds last value when disappears.

!!! DANGER!!! Event used inside arr! Probably OK because arr will not be !!! optimized to arrE. But still. Maybe rewrite this using, say, scan? !!! or switch? Switching (in hold) for every input sample does not !!! seem like such a great idea anyway.

Accumulators

accum :: a -> SF (Event (a -> a)) (Event a) Source

Given an initial value in an accumulator, it returns a signal function that processes an event carrying transformation functions. Every time an Event is received, the function inside it is applied to the accumulator, whose new value is outputted in an Event.

accumHold :: a -> SF (Event (a -> a)) a Source

Zero-order hold accumulator (always produces the last outputted value until an event arrives).

dAccumHold :: a -> SF (Event (a -> a)) a Source

Zero-order hold accumulator with delayed initialization (always produces the last outputted value until an event arrives, but the very initial output is always the given accumulator).

accumBy :: (b -> a -> b) -> b -> SF (Event a) (Event b) Source

Accumulator parameterized by the accumulation function.

accumHoldBy :: (b -> a -> b) -> b -> SF (Event a) b Source

Zero-order hold accumulator parameterized by the accumulation function.

dAccumHoldBy :: (b -> a -> b) -> b -> SF (Event a) b Source

Zero-order hold accumulator parameterized by the accumulation function with delayed initialization (initial output sample is always the given accumulator).

accumFilter :: (c -> a -> (c, Maybe b)) -> c -> SF (Event a) (Event b) Source

Accumulator parameterized by the accumulator function with filtering, possibly discarding some of the input events based on whether the second component of the result of applying the accumulation function is Nothing or Just x for some x.

Delays

Basic delays

pre :: SF a a Source

Uninitialized delay operator.

iPre :: a -> SF a a Source

Initialized delay operator.

Timed delays

delay :: Time -> a -> SF a a Source

Delay a signal by a fixed time t, using the second parameter to fill in the initial t seconds.

Variable delay

pause :: b -> SF a Bool -> SF a b -> SF a b Source

Given a value in an accumulator (b), a predicate signal function (sfC), and a second signal function (sf), pause will produce the accumulator b if sfC input is True, and will transform the signal using sf otherwise. It acts as a pause with an accumulator for the moments when the transformation is paused.

State keeping combinators

Loops with guaranteed well-defined feedback

loopPre :: c -> SF (a, c) (b, c) -> SF a b Source

Loop with an initial value for the signal being fed back.

loopIntegral :: VectorSpace c s => SF (a, c) (b, c) -> SF a b Source

Loop by integrating the second value in the pair and feeding the result back. Because the integral at time 0 is zero, this is always well defined.

Integration and differentiation

integral :: VectorSpace a s => SF a a Source

Integration using the rectangle rule.

derivative :: VectorSpace a s => SF a a Source

A very crude version of a derivative. It simply divides the value difference by the time difference. Use at your own risk.

imIntegral :: VectorSpace a s => a -> SF a a Source

"Immediate" integration (using the function's value at the current time)

Noise (random signal) sources and stochastic event sources

noise :: (RandomGen g, Random b) => g -> SF a b Source

Noise (random signal) with default range for type in question; based on "randoms".

noiseR :: (RandomGen g, Random b) => (b, b) -> g -> SF a b Source

Noise (random signal) with specified range; based on "randomRs".

occasionally :: RandomGen g => g -> Time -> b -> SF a (Event b) Source

Stochastic event source with events occurring on average once every t_avg seconds. However, no more than one event results from any one sampling interval in the case of relatively sparse sampling, thus avoiding an "event backlog" should sampling become more frequent at some later point in time.

Execution/simulation

Reactimation

reactimate Source

Arguments

:: IO a

IO initialization action

-> (Bool -> IO (DTime, Maybe a))

IO input sensing action

-> (Bool -> b -> IO Bool)

IO actuaction (output processing) action

-> SF a b

Signal function

-> IO () 

Convenience function to run a signal function indefinitely, using a IO actions to obtain new input and process the output.

This function first runs the initialization action, which provides the initial input for the signal transformer at time 0.

Afterwards, an input sensing action is used to obtain new input (if any) and the time since the last iteration. The argument to the input sensing function indicates if it can block. If no new input is received, it is assumed to be the same as in the last iteration.

After applying the signal function to the input, the actuation IO action is executed. The first argument indicates if the output has changed, the second gives the actual output). Actuation functions may choose to ignore the first argument altogether. This action should return True if the reactimation must stop, and False if it should continue.

Note that this becomes the program's main loop, which makes using this function incompatible with GLUT, Gtk and other graphics libraries. It may also impose a sizeable constraint in larger projects in which different subparts run at different time steps. If you need to control the main loop yourself for these or other reasons, use reactInit and react.

type ReactHandle a b = IORef (ReactState a b) Source

A reference to reactimate's state, maintained across samples.

reactInit :: IO a -> (ReactHandle a b -> Bool -> b -> IO Bool) -> SF a b -> IO (ReactHandle a b) Source

Initialize a top-level reaction handle.

react :: ReactHandle a b -> (DTime, Maybe a) -> IO Bool Source

Process a single input sample.

Embedding

embed :: SF a b -> (a, [(DTime, Maybe a)]) -> [b] Source

Given a signal function and a pair with an initial input sample for the input signal, and a list of sampling times, possibly with new input samples at those times, it produces a list of output samples.

This is a simplified, purely-functional version of reactimate.

embedSynch :: SF a b -> (a, [(DTime, Maybe a)]) -> SF Double b Source

Synchronous embedding. The embedded signal function is run on the supplied input and time stream at a given (but variable) ratio >= 0 to the outer time flow. When the ratio is 0, the embedded signal function is paused.

deltaEncode :: Eq a => DTime -> [a] -> (a, [(DTime, Maybe a)]) Source

Spaces a list of samples by a fixed time delta, avoiding unnecessary samples when the input has not changed since the last sample.

deltaEncodeBy :: (a -> a -> Bool) -> DTime -> [a] -> (a, [(DTime, Maybe a)]) Source

deltaEncode parameterized by the equality test.

Auxiliary definitions

(#) :: (a -> b) -> (b -> c) -> a -> c infixl 9 Source

Deprecated: Use Control.Arrow.(>>>) and Control.Arrow.(<<<).

dup :: a -> (a, a) Source