Yampa-0.13.5: Elegant Functional Reactive Programming Language for 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
LanguageHaskell2010

FRP.Yampa

Description

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

Yampa has been used to write professional Haskell cross-platform games for iOS, Android, desktop and web. There is a library for testing Yampa applications that allows you to use Temporal Logic and QuickCheck to test your games. You can also use a time-travel debugger to connect to your application running live and debug it step by step.

Documentation

You can find many examples, tutorials and documentation here:

https://github.com/ivanperez-keera/Yampa

https://github.com/ivanperez-keera/Yampa/tree/develop/yampa/examples

https://wiki.haskell.org/Yampa

Yampa at a glance

A Yampa network is structured as a Signal Function: a pure transformation from a time-varying input to that produces a time-varying output. The Yampa language provides signal function primitives, as well as SF combinators. Primitives and combinators guarantee that SFs are well-formed and efficient.

For example, a game could take the changing mouse position (continuous-time signal) and mouse clicks (discrete-time signal), combine them as part of some game logic, and produce an animation with sound (continuously changing picture).

Signal and SF separation

To create a Yampa system, you need to think about three things:

  • How to obtain the input signals coming into your system. This typically requires polling some input device or consuming a queue of input events.
  • How to consume the output signals produced by your system. This typically requires taking output samples or chunks and rendering them or playing them.
  • How to transform the input signal into the output signal. This requires thinking about the transformation applied as time progresses towards the future, possibly switching from one transformation to another as the program evolves.

The first two aspects lie outside Yampa, and they determine the backends that your system uses. Yampa is backend-agnostic, and you can connect it to SDL, SDL2, OpenGL, Gloss, Diagrams, HTML5 Canvas. In addition, you can use it with any input device you want, and it has been used with Nintendo wiimotes, Microsoft Kinects and LeapMotions.

The last aspect is what defines Yampa as a language. You define a pure Signal Function (SF) using primitives and combinators. You can find a series of primitive SFs in FRP.Yampa.Basic. For example, the function constant allows you to ignore the input signal and produce a constant output, the function arr allows you to apply a pure function to every input value at every time, ignoring previous history. Signal Functions can transform signals taking their history into account. For example, the function integral integrates the input signal.

Execution

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). You can also use the function embed to try your signal functions with lists of input samples in GHCi.

For a simple example of an SDL application that creates a moving picture around the mouse position, see:

https://github.com/ivanperez-keera/Yampa/blob/develop/yampa/examples/yampa-game/MainCircleMouse.hs

Hybrid systems

Signals can change in continuous or in discrete time (known as Events). Events represent 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. The module FRP.Yampa.Event allows you to manipulate events, the module FRP.Yampa.EventS deals with event signal functions, and the FRP.Yampa.Hybrid allows you to go from a continuous-time domain to a discrete domain, and vice-versa.

Vector Spaces

Yampa uses vector spaces in time-aware primitives like integral. However, Yampa does not enforce the use of a particular vector space implementation, meaning you could use integral for example with other vector types like V2, V1, etc. from the library linear. For an example, see this gist.

Library Overview

Synopsis

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

Instances details
Arrow SF Source #

Signal Functions as Arrows. See "The Yampa Arcade", by Courtney, Nilsson and Peterson.

Instance details

Defined in FRP.Yampa.InternalCore

Methods

arr :: (b -> c) -> SF b c #

first :: SF b c -> SF (b, d) (c, d) #

second :: SF b c -> SF (d, b) (d, c) #

(***) :: SF b c -> SF b' c' -> SF (b, b') (c, c') #

(&&&) :: SF b c -> SF b c' -> SF b (c, c') #

ArrowChoice SF Source #

Choice of which SF to run based on the value of a signal.

Instance details

Defined in FRP.Yampa.InternalCore

Methods

left :: SF b c -> SF (Either b d) (Either c d) #

right :: SF b c -> SF (Either d b) (Either d c) #

(+++) :: SF b c -> SF b' c' -> SF (Either b b') (Either c c') #

(|||) :: SF b d -> SF c d -> SF (Either b c) d #

ArrowLoop SF Source #

Creates a feedback loop without delay.

Instance details

Defined in FRP.Yampa.InternalCore

Methods

loop :: SF (b, d) (c, d) -> SF b c #

Functor (SF a) Source #

Functor instance for applied SFs.

Instance details

Defined in FRP.Yampa.InternalCore

Methods

fmap :: (a0 -> b) -> SF a a0 -> SF a b #

(<$) :: a0 -> SF a b -> SF a a0 #

Applicative (SF a) Source #

Applicative Functor instance (allows classic-frp style signals and composition using applicative style).

Instance details

Defined in FRP.Yampa.InternalCore

Methods

pure :: a0 -> SF a a0 #

(<*>) :: SF a (a0 -> b) -> SF a a0 -> SF a b #

liftA2 :: (a0 -> b -> c) -> SF a a0 -> SF a b -> SF a c #

(*>) :: SF a a0 -> SF a b -> SF a b #

(<*) :: SF a a0 -> SF a b -> SF a a0 #

Category SF Source #

Composition and identity for SFs.

Instance details

Defined in FRP.Yampa.InternalCore

Methods

id :: forall (a :: k). SF a a #

(.) :: forall (b :: k) (c :: k) (a :: k). SF b c -> SF a b -> SF a c #

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

Instances details
Monad Event Source #

Monad instance

Instance details

Defined in FRP.Yampa.Event

Methods

(>>=) :: Event a -> (a -> Event b) -> Event b #

(>>) :: Event a -> Event b -> Event b #

return :: a -> Event a #

Functor Event Source #

Functor instance (could be derived).

Instance details

Defined in FRP.Yampa.Event

Methods

fmap :: (a -> b) -> Event a -> Event b #

(<$) :: a -> Event b -> Event a #

MonadFail Event Source # 
Instance details

Defined in FRP.Yampa.Event

Methods

fail :: String -> Event a #

Applicative Event Source #

Applicative instance (similar to Maybe).

Instance details

Defined in FRP.Yampa.Event

Methods

pure :: a -> Event a #

(<*>) :: Event (a -> b) -> Event a -> Event b #

liftA2 :: (a -> b -> c) -> Event a -> Event b -> Event c #

(*>) :: Event a -> Event b -> Event b #

(<*) :: Event a -> Event b -> Event a #

Alternative Event Source #

Alternative instance

Instance details

Defined in FRP.Yampa.Event

Methods

empty :: Event a #

(<|>) :: Event a -> Event a -> Event a #

some :: Event a -> Event [a] #

many :: Event a -> Event [a] #

Eq a => Eq (Event a) Source #

Eq instance (equivalent to derived instance)

Instance details

Defined in FRP.Yampa.Event

Methods

(==) :: Event a -> Event a -> Bool #

(/=) :: Event a -> Event a -> Bool #

Ord a => Ord (Event a) Source #

Ord instance (equivalent to derived instance)

Instance details

Defined in FRP.Yampa.Event

Methods

compare :: Event a -> Event a -> Ordering #

(<) :: Event a -> Event a -> Bool #

(<=) :: Event a -> Event a -> Bool #

(>) :: Event a -> Event a -> Bool #

(>=) :: Event a -> Event a -> Bool #

max :: Event a -> Event a -> Event a #

min :: Event a -> Event a -> Event a #

Show a => Show (Event a) Source # 
Instance details

Defined in FRP.Yampa.Event

Methods

showsPrec :: Int -> Event a -> ShowS #

show :: Event a -> String #

showList :: [Event a] -> ShowS #

NFData a => NFData (Event a) Source #

NFData instance

Instance details

Defined in FRP.Yampa.Event

Methods

rnf :: 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.

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

Output pre-insert operator.

Insert a sample in the output, and from that point on, behave like the given sf.

(>--) :: 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 #

Applies a function point-wise, using the last output as next input. This creates a well-formed loop based on a pure, auxiliary function.

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

Generic version of sscan, in which the auxiliary function produces an internal accumulator and an "held" output.

Applies a function point-wise, using the last known Just output to form the output, and next input accumulator. If the output is Nothing, the last known accumulators are used. This creates a well-formed loop based on a pure, auxiliary function.

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.

maybeToEvent :: Maybe a -> Event a Source #

Convert a maybe value into a event (Event is isomorphic to Maybe).

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).

Applicative-based definition: tag = ($>)

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.

Applicative-based definition: tagWith = (<$)

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.

Applicative-based definition: mergeBy f le re = (f $ le * re) | le | re

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

Applicative-based definition: mapMerge lf rf lrf le re = (f $ le * re) | (lf $ le) | (rf $ re)

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

Merge a list of events; foremost event has priority.

Foldable-based definition: mergeEvents :: Foldable t => t (Event a) -> Event a mergeEvents = asum

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

Collect simultaneous event occurrences; no event if none.

Traverable-based definition: catEvents :: Foldable t => t (Event a) -> Event (t a) carEvents e = if (null e) then NoEvent else (sequenceA e)

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

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

Applicative-based definition: joinE = liftA2 (,)

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.

Uses the given SF until an event comes in the input, in which case the SF in the event is turned on, until the next event comes in the input, and so on.

See https://wiki.haskell.org/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.

Uses the given SF until an event comes in the input, in which case the SF in the event is turned on, until the next event comes in the input, and so on.

Uses decoupled switch (dSwitch).

See https://wiki.haskell.org/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.

Applies the first SF until the input signal and the output signal, when passed to the second SF, produce an event, in which case the original SF and the event are used to build an new SF to switch into.

See https://wiki.haskell.org/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.

Applies the first SF until the input signal and the output signal, when passed to the second SF, produce an event, in which case the original SF and the event are used to build an new SF to switch into.

The switch is decoupled (dSwitch).

See https://wiki.haskell.org/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) with broadcasting. 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 #

Decoupled 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 #

Recurring parallel switch with broadcasting.

Uses the given collection of SFs, until an event comes in the input, in which case the function in the Event is used to transform the collections of SF to be used with rpSwitch again, until the next event comes in the input, and so on.

Broadcasting is used to decide which subpart of the input goes to each SF in the collection.

See rpSwitch.

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

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

Decoupled recurring parallel switch with broadcasting.

Uses the given collection of SFs, until an event comes in the input, in which case the function in the Event is used to transform the collections of SF to be used with rpSwitch again, until the next event comes in the input, and so on.

Broadcasting is used to decide which subpart of the input goes to each SF in the collection.

This is the decoupled version of rpSwitchB.

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

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 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)

Initial signal function collection.

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

Recurring parallel switch parameterized on the routing function.

Uses the given collection of SFs, until an event comes in the input, in which case the function in the Event is used to transform the collections of SF to be used with rpSwitch again, until the next event comes in the input, and so on.

The routing function is used to decide which subpart of the input goes to each SF in the collection.

This is the parallel version of rSwitch.

drpSwitch 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)

Initial signal function collection.

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

Recurring parallel switch with delayed observation parameterized on the routing function.

Uses the given collection of SFs, until an event comes in the input, in which case the function in the Event is used to transform the collections of SF to be used with rpSwitch again, until the next event comes in the input, and so on.

The routing function is used to decide which subpart of the input goes to each SF in the collection.

This is the parallel version of drSwitch.

Discrete to continuous-time signal functions

Wave-form generation

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

Zero-order hold.

Converts a discrete-time signal into a continuous-time signal, by holding the last value until it changes in the input signal. The given parameter may be used for time zero, and until the first event occurs in the input signal, so hold is always well-initialized.

>>> embed (hold 1) (deltaEncode 0.1 [NoEvent, NoEvent, Event 2, NoEvent, Event 3, NoEvent])
[1,1,2,2,3,3]

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

Zero-order hold with a delay.

Converts a discrete-time signal into a continuous-time signal, by holding the last value until it changes in the input signal. The given parameter is used for time zero (until the first event occurs in the input signal), so dHold shifts the discrete input by an infinitesimal delay.

>>> embed (dHold 1) (deltaEncode 0.1 [NoEvent, NoEvent, Event 2, NoEvent, Event 3, NoEvent])
[1,1,1,2,2,3]

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

Tracks input signal when available, holding the last value when the input is Nothing.

This behaves similarly to hold, but there is a conceptual difference, as it takes a signal of input Maybe a (for some a) and not Event.

>>> embed (trackAndHold 1) (deltaEncode 0.1 [Nothing, Nothing, Just 2, Nothing, Just 3, Nothing])
[1,1,2,2,3,3]

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.

The output has an infinitesimal delay (1 sample), and the value at time zero is undefined.

iPre :: a -> SF a a Source #

Initialized delay operator.

Creates an SF that delays the input signal, introducing an infinitesimal delay (one sample), using the given argument to fill in the initial output at time zero.

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.

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

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

impulseIntegral :: VectorSpace a k => SF (a, Event a) a Source #

Integrate the first input signal and add the discrete accumulation (sum) of the second, discrete, input signal.

count :: Integral b => SF (Event a) (Event b) Source #

Count the occurrences of input events.

>>> embed count (deltaEncode 1 [Event 'a', NoEvent, Event 'b'])
[Event 1,NoEvent,Event 2]

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.

iterFrom :: (a -> a -> DTime -> b -> b) -> b -> SF a b Source #

Integrate using an auxiliary function that takes the current and the last input, the time between those samples, and the last output, and returns a new output.

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.

class RandomGen g where #

RandomGen is an interface to pure pseudo-random number generators.

StdGen is the standard RandomGen instance provided by this library.

Since: random-1.0.0

Minimal complete definition

split, (genWord32 | genWord64 | next, genRange)

Methods

next :: g -> (Int, g) #

Returns an Int that is uniformly distributed over the range returned by genRange (including both end points), and a new generator. Using next is inefficient as all operations go via Integer. See here for more details. It is thus deprecated.

Since: random-1.0.0

genWord8 :: g -> (Word8, g) #

Returns a Word8 that is uniformly distributed over the entire Word8 range.

Since: random-1.2.0

genWord16 :: g -> (Word16, g) #

Returns a Word16 that is uniformly distributed over the entire Word16 range.

Since: random-1.2.0

genWord32 :: g -> (Word32, g) #

Returns a Word32 that is uniformly distributed over the entire Word32 range.

Since: random-1.2.0

genWord64 :: g -> (Word64, g) #

Returns a Word64 that is uniformly distributed over the entire Word64 range.

Since: random-1.2.0

genWord32R :: Word32 -> g -> (Word32, g) #

genWord32R upperBound g returns a Word32 that is uniformly distributed over the range [0, upperBound].

Since: random-1.2.0

genWord64R :: Word64 -> g -> (Word64, g) #

genWord64R upperBound g returns a Word64 that is uniformly distributed over the range [0, upperBound].

Since: random-1.2.0

genShortByteString :: Int -> g -> (ShortByteString, g) #

genShortByteString n g returns a ShortByteString of length n filled with pseudo-random bytes.

Since: random-1.2.0

genRange :: g -> (Int, Int) #

Yields the range of values returned by next.

It is required that:

  • If (a, b) = genRange g, then a < b.
  • genRange must not examine its argument so the value it returns is determined only by the instance of RandomGen.

The default definition spans the full range of Int.

Since: random-1.0.0

split :: g -> (g, g) #

Returns two distinct pseudo-random number generators.

Implementations should take care to ensure that the resulting generators are not correlated. Some pseudo-random number generators are not splittable. In that case, the split implementation should fail with a descriptive error message.

Since: random-1.0.0

Instances

Instances details
RandomGen StdGen 
Instance details

Defined in System.Random.Internal

RandomGen SMGen 
Instance details

Defined in System.Random.Internal

RandomGen SMGen 
Instance details

Defined in System.Random.Internal

RandomGen g => RandomGen (StateGen g) 
Instance details

Defined in System.Random.Internal

class Random a where #

The class of types for which random values can be generated. Most instances of Random will produce values that are uniformly distributed on the full range, but for those types without a well-defined "full range" some sensible default subrange will be selected.

Random exists primarily for backwards compatibility with version 1.1 of this library. In new code, use the better specified Uniform and UniformRange instead.

Since: random-1.0.0

Minimal complete definition

Nothing

Methods

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

Takes a range (lo,hi) and a pseudo-random number generator g, and returns a pseudo-random value uniformly distributed over the closed interval [lo,hi], together with a new generator. It is unspecified what happens if lo>hi, but usually the values will simply get swapped.

>>> let gen = mkStdGen 2021
>>> fst $ randomR ('a', 'z') gen
't'
>>> fst $ randomR ('z', 'a') gen
't'

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.

There is no requirement to follow the Ord instance and the concept of range can be defined on per type basis. For example product types will treat their values independently:

>>> fst $ randomR (('a', 5.0), ('z', 10.0)) $ mkStdGen 2021
('t',6.240232662366563)

In case when a lawful range is desired uniformR should be used instead.

Since: random-1.0.0

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 floating point types, the range is normally the closed interval [0,1].
  • For Integer, the range is (arbitrarily) the range of Int.

Since: random-1.0.0

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

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

Since: random-1.0.0

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

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

Since: random-1.0.0

Instances

Instances details
Random Bool 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Bool, Bool) -> g -> (Bool, g) #

random :: RandomGen g => g -> (Bool, g) #

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

randoms :: RandomGen g => g -> [Bool] #

Random Char 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Char, Char) -> g -> (Char, g) #

random :: RandomGen g => g -> (Char, g) #

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

randoms :: RandomGen g => g -> [Char] #

Random Double

Note - random produces values in the closed range [0,1].

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Double, Double) -> g -> (Double, g) #

random :: RandomGen g => g -> (Double, g) #

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

randoms :: RandomGen g => g -> [Double] #

Random Float

Note - random produces values in the closed range [0,1].

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Float, Float) -> g -> (Float, g) #

random :: RandomGen g => g -> (Float, g) #

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

randoms :: RandomGen g => g -> [Float] #

Random Int 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int, Int) -> g -> (Int, g) #

random :: RandomGen g => g -> (Int, g) #

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

randoms :: RandomGen g => g -> [Int] #

Random Int8 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int8, Int8) -> g -> (Int8, g) #

random :: RandomGen g => g -> (Int8, g) #

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

randoms :: RandomGen g => g -> [Int8] #

Random Int16 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int16, Int16) -> g -> (Int16, g) #

random :: RandomGen g => g -> (Int16, g) #

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

randoms :: RandomGen g => g -> [Int16] #

Random Int32 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int32, Int32) -> g -> (Int32, g) #

random :: RandomGen g => g -> (Int32, g) #

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

randoms :: RandomGen g => g -> [Int32] #

Random Int64 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Int64, Int64) -> g -> (Int64, g) #

random :: RandomGen g => g -> (Int64, g) #

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

randoms :: RandomGen g => g -> [Int64] #

Random Integer

Note - random generates values in the Int range

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Integer, Integer) -> g -> (Integer, g) #

random :: RandomGen g => g -> (Integer, g) #

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

randoms :: RandomGen g => g -> [Integer] #

Random Word 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word, Word) -> g -> (Word, g) #

random :: RandomGen g => g -> (Word, g) #

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

randoms :: RandomGen g => g -> [Word] #

Random Word8 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word8, Word8) -> g -> (Word8, g) #

random :: RandomGen g => g -> (Word8, g) #

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

randoms :: RandomGen g => g -> [Word8] #

Random Word16 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word16, Word16) -> g -> (Word16, g) #

random :: RandomGen g => g -> (Word16, g) #

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

randoms :: RandomGen g => g -> [Word16] #

Random Word32 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word32, Word32) -> g -> (Word32, g) #

random :: RandomGen g => g -> (Word32, g) #

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

randoms :: RandomGen g => g -> [Word32] #

Random Word64 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Word64, Word64) -> g -> (Word64, g) #

random :: RandomGen g => g -> (Word64, g) #

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

randoms :: RandomGen g => g -> [Word64] #

Random CChar 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CChar, CChar) -> g -> (CChar, g) #

random :: RandomGen g => g -> (CChar, g) #

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

randoms :: RandomGen g => g -> [CChar] #

Random CSChar 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CSChar, CSChar) -> g -> (CSChar, g) #

random :: RandomGen g => g -> (CSChar, g) #

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

randoms :: RandomGen g => g -> [CSChar] #

Random CUChar 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUChar, CUChar) -> g -> (CUChar, g) #

random :: RandomGen g => g -> (CUChar, g) #

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

randoms :: RandomGen g => g -> [CUChar] #

Random CShort 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CShort, CShort) -> g -> (CShort, g) #

random :: RandomGen g => g -> (CShort, g) #

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

randoms :: RandomGen g => g -> [CShort] #

Random CUShort 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUShort, CUShort) -> g -> (CUShort, g) #

random :: RandomGen g => g -> (CUShort, g) #

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

randoms :: RandomGen g => g -> [CUShort] #

Random CInt 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CInt, CInt) -> g -> (CInt, g) #

random :: RandomGen g => g -> (CInt, g) #

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

randoms :: RandomGen g => g -> [CInt] #

Random CUInt 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUInt, CUInt) -> g -> (CUInt, g) #

random :: RandomGen g => g -> (CUInt, g) #

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

randoms :: RandomGen g => g -> [CUInt] #

Random CLong 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CLong, CLong) -> g -> (CLong, g) #

random :: RandomGen g => g -> (CLong, g) #

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

randoms :: RandomGen g => g -> [CLong] #

Random CULong 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CULong, CULong) -> g -> (CULong, g) #

random :: RandomGen g => g -> (CULong, g) #

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

randoms :: RandomGen g => g -> [CULong] #

Random CLLong 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CLLong, CLLong) -> g -> (CLLong, g) #

random :: RandomGen g => g -> (CLLong, g) #

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

randoms :: RandomGen g => g -> [CLLong] #

Random CULLong 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CULLong, CULLong) -> g -> (CULLong, g) #

random :: RandomGen g => g -> (CULLong, g) #

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

randoms :: RandomGen g => g -> [CULLong] #

Random CBool 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CBool, CBool) -> g -> (CBool, g) #

random :: RandomGen g => g -> (CBool, g) #

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

randoms :: RandomGen g => g -> [CBool] #

Random CFloat

Note - random produces values in the closed range [0,1].

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CFloat, CFloat) -> g -> (CFloat, g) #

random :: RandomGen g => g -> (CFloat, g) #

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

randoms :: RandomGen g => g -> [CFloat] #

Random CDouble

Note - random produces values in the closed range [0,1].

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CDouble, CDouble) -> g -> (CDouble, g) #

random :: RandomGen g => g -> (CDouble, g) #

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

randoms :: RandomGen g => g -> [CDouble] #

Random CPtrdiff 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CPtrdiff, CPtrdiff) -> g -> (CPtrdiff, g) #

random :: RandomGen g => g -> (CPtrdiff, g) #

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

randoms :: RandomGen g => g -> [CPtrdiff] #

Random CSize 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CSize, CSize) -> g -> (CSize, g) #

random :: RandomGen g => g -> (CSize, g) #

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

randoms :: RandomGen g => g -> [CSize] #

Random CWchar 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CWchar, CWchar) -> g -> (CWchar, g) #

random :: RandomGen g => g -> (CWchar, g) #

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

randoms :: RandomGen g => g -> [CWchar] #

Random CSigAtomic 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CSigAtomic, CSigAtomic) -> g -> (CSigAtomic, g) #

random :: RandomGen g => g -> (CSigAtomic, g) #

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

randoms :: RandomGen g => g -> [CSigAtomic] #

Random CIntPtr 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CIntPtr, CIntPtr) -> g -> (CIntPtr, g) #

random :: RandomGen g => g -> (CIntPtr, g) #

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

randoms :: RandomGen g => g -> [CIntPtr] #

Random CUIntPtr 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUIntPtr, CUIntPtr) -> g -> (CUIntPtr, g) #

random :: RandomGen g => g -> (CUIntPtr, g) #

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

randoms :: RandomGen g => g -> [CUIntPtr] #

Random CIntMax 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CIntMax, CIntMax) -> g -> (CIntMax, g) #

random :: RandomGen g => g -> (CIntMax, g) #

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

randoms :: RandomGen g => g -> [CIntMax] #

Random CUIntMax 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (CUIntMax, CUIntMax) -> g -> (CUIntMax, g) #

random :: RandomGen g => g -> (CUIntMax, g) #

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

randoms :: RandomGen g => g -> [CUIntMax] #

(Random a, Random b) => Random (a, b)

Note - randomR treats a and b types independently

Instance details

Defined in System.Random

Methods

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

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

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

randoms :: RandomGen g => g -> [(a, b)] #

(Random a, Random b, Random c) => Random (a, b, c)

Note - randomR treats a, b and c types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c), (a, b, c)) -> g -> ((a, b, c), g) #

random :: RandomGen g => g -> ((a, b, c), g) #

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

randoms :: RandomGen g => g -> [(a, b, c)] #

(Random a, Random b, Random c, Random d) => Random (a, b, c, d)

Note - randomR treats a, b, c and d types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c, d), (a, b, c, d)) -> g -> ((a, b, c, d), g) #

random :: RandomGen g => g -> ((a, b, c, d), g) #

randomRs :: RandomGen g => ((a, b, c, d), (a, b, c, d)) -> g -> [(a, b, c, d)] #

randoms :: RandomGen g => g -> [(a, b, c, d)] #

(Random a, Random b, Random c, Random d, Random e) => Random (a, b, c, d, e)

Note - randomR treats a, b, c, d and e types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c, d, e), (a, b, c, d, e)) -> g -> ((a, b, c, d, e), g) #

random :: RandomGen g => g -> ((a, b, c, d, e), g) #

randomRs :: RandomGen g => ((a, b, c, d, e), (a, b, c, d, e)) -> g -> [(a, b, c, d, e)] #

randoms :: RandomGen g => g -> [(a, b, c, d, e)] #

(Random a, Random b, Random c, Random d, Random e, Random f) => Random (a, b, c, d, e, f)

Note - randomR treats a, b, c, d, e and f types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> g -> ((a, b, c, d, e, f), g) #

random :: RandomGen g => g -> ((a, b, c, d, e, f), g) #

randomRs :: RandomGen g => ((a, b, c, d, e, f), (a, b, c, d, e, f)) -> g -> [(a, b, c, d, e, f)] #

randoms :: RandomGen g => g -> [(a, b, c, d, e, f)] #

(Random a, Random b, Random c, Random d, Random e, Random f, Random g) => Random (a, b, c, d, e, f, g)

Note - randomR treats a, b, c, d, e, f and g types independently

Instance details

Defined in System.Random

Methods

randomR :: RandomGen g0 => ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> g0 -> ((a, b, c, d, e, f, g), g0) #

random :: RandomGen g0 => g0 -> ((a, b, c, d, e, f, g), g0) #

randomRs :: RandomGen g0 => ((a, b, c, d, e, f, g), (a, b, c, d, e, f, g)) -> g0 -> [(a, b, c, d, e, f, g)] #

randoms :: RandomGen g0 => g0 -> [(a, b, c, d, e, f, g)] #

Execution/simulation

Reactimation

reactimate Source #

Arguments

:: Monad m 
=> m a

Initialization action

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

Input sensing action

-> (Bool -> b -> m Bool)

Actuation (output processing) action

-> SF a b

Signal function

-> m () 

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.

data ReactHandle 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.

data FutureSF a b Source #

A wrapper around an initialized SF (continuation), needed for testing and debugging purposes.

evalAtZero Source #

Arguments

:: SF a b 
-> a

Input sample

-> (b, FutureSF a b)

Output x Continuation

Evaluate an SF, and return an output and an initialized SF.

WARN: Do not use this function for standard simulation. This function is intended only for debugging/testing. Apart from being potentially slower and consuming more memory, it also breaks the FRP abstraction by making samples discrete and step based.

evalAt Source #

Arguments

:: FutureSF a b 
-> DTime 
-> a

Input sample

-> (b, FutureSF a b)

Output x Continuation

Evaluate an initialized SF, and return an output and a continuation.

WARN: Do not use this function for standard simulation. This function is intended only for debugging/testing. Apart from being potentially slower and consuming more memory, it also breaks the FRP abstraction by making samples discrete and step based.

evalFuture :: SF a b -> a -> DTime -> (b, SF a b) Source #

Given a signal function and time delta, it moves the signal function into the future, returning a new uninitialized SF and the initial output.

While the input sample refers to the present, the time delta refers to the future (or to the time between the current sample and the next sample).

WARN: Do not use this function for standard simulation. This function is intended only for debugging/testing. Apart from being potentially slower and consuming more memory, it also breaks the FRP abstraction by making samples discrete and step based.

Auxiliary definitions

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

Duplicate an input.