Animas-0.2: Updated version of Yampa: a library for programming hybrid systems.

Portabilitynon-portable (GHC extensions)
Stabilityprovisional
Maintaineredwardamsden@gmail.com

FRP.Animas

Contents

Description

 

Synopsis

Re-exported modules

Random-number classes

class RandomGen g where

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

Minimal complete definition: next and 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.

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

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.

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.

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

Convenience operators

(#) :: (a -> b) -> (b -> c) -> a -> cSource

Reverse composition

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

Duplicate a value into a pair

swap :: (a, b) -> (b, a)Source

Swap the values in a pair

Datatypes

type Time = DoubleSource

Time representation for signal functions

data SF a b Source

A signal function

data Event a Source

Event type

Constructors

NoEvent 
Event a 

Instances

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

Pure signal functions

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

Lifts a function to a pure signal function. Use arr from the Arrow class, rather than this function.

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

Lifts a function with an event input to a pure signal function on events. Use arr from the Arrow class, rather than this function.

identity :: SF a aSource

The identity signal function. Use in place of

 arr id

constant :: b -> SF a bSource

The constant signal function. Use

 constant x

in place of

 arr $ const x

Time signal functions

localTime :: SF a TimeSource

The time of this part of the signal graph. Note that if a signal function is switched in, the time is relative to the moment of switching, not the moment that animation started.

time :: SF a TimeSource

identical to localTime

Initialization

These operators provide means of specifying the initial input or output of a signal function, overriding the signal function for the first cycle of animation

(-->) :: b -> SF a b -> SF a bSource

Override the output value for a signal function at the first instant it is processed

(>--) :: a -> SF a b -> SF a bSource

Override the input value for a signal function at the first instant it is processed.

(-=>) :: (b -> b) -> SF a b -> SF a bSource

Apply a function to the output at the first instant of a signal function

(>=-) :: (a -> a) -> SF a b -> SF a bSource

Apply a function to the input at the first instant of a signal function

initiallySource

Arguments

:: a

Value at first instant

-> SF a a 

Output a value at the first instant, and forever after pass the input value through

Accumulator-based signal functions

sscanSource

Arguments

:: (b -> a -> b)

Function from accumulator and input to accumulator

-> b

Initial accumulator value

-> SF a b

Accumulating scan signal function

Signal function: apply a function to an accumulator at each instant. Note that the output value is the value of the accumulator at each instant.

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

Events

Basic event producers

never :: SF a (Event b)Source

Never produce an event

nowSource

Arguments

:: b

Value for event

-> SF a (Event b)

Signal function producing

Produce an event immediately (at the moment of switching in or animation) and never again.

afterSource

Arguments

:: Time

Time to wait before producing event

-> b

Value for event

-> SF a (Event b)

Signal function producing event after specified period

Produce an event delayed by some time.

repeatedlySource

Arguments

:: Time

Time between events

-> b

Value for all events

-> SF a (Event b)

Signal function producing repeated event

Produce event every so often (but not immediately)

afterEachSource

Arguments

:: [(Time, b)]

Time since previous event or start and value for event

-> SF a (Event b) 

Takes a list of time delays and values to a signal function producing events.

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

edge :: SF Bool (Event ())Source

Produce an event whenever the input goes from False to True

edgeTagSource

Arguments

:: a

Value for events

-> SF Bool (Event a) 

Produce an event carrying a specified value whenever the input goes from False to True

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

Produce the value carried by the Maybe whenever the input goes from Nothing to Just

edgeBySource

Arguments

:: (a -> a -> Maybe b)

Comparison function. An event will occur at any instant where the value of this function is Just.

-> a

initial "previous" instant.

-> SF a (Event b)

Signal function comparing instants

Compare the input at the current and previous instant and produce an event based on the comparison

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

Suppress all but the first event passing through

noEvent :: Event aSource

Not an event

noEventFstSource

Arguments

:: (Event a, b)

Input pair

-> (Event c, b)

No event pair

Force the first item of a pair to not be an event

noEventSndSource

Arguments

:: (a, Event b)

Input pair

-> (a, Event c)

No event pair

Force the second item of a pair to not be an event

Event manipulation

delayEventSource

Arguments

:: Time

Time to delay events

-> SF (Event a) (Event a)

Signal function delaying events

Delay events passing through

takeEventsSource

Arguments

:: Int

Number of events to permit

-> SF (Event a) (Event a)

Signal function only permitting that many events

Only permit a certain number of events

dropEventsSource

Arguments

:: Int

Number of events to suppress initially

-> SF (Event a) (Event a)

Signal function suppressing That many events initially

Suppress a certain number of initial events

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

Suppress a possible event at the instant of animation or switching in

Stateful event processing

old_hold :: a -> SF (Event a) aSource

For backwards compatibility only.

holdSource

Arguments

:: a

Initial value

-> SF (Event a) a

Signal function which constantly outputs the value of the last event.

Output the initial value or the value of the last event.

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

Decoupled version of hold. Begins outputting event value the instant after the event occurence.

trackAndHoldSource

Arguments

:: a

Initial value

-> SF (Maybe a) a

Output the initial value or the value of the most recent Just

Hold the value of a Maybe input.

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

For backwards compatability only.

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

For backwards compatibility only.

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

For backwards compatibility only.

accumSource

Arguments

:: a

Initial accumulator value.

-> SF (Event (a -> a)) (Event a)

Signal function from events carrying functions to events with the value of those functions applied to the accumulator

Apply a function carried by an event to an accumulator, producing an event with the new value of the accumulator.

accumHoldSource

Arguments

:: a

Initial value of accumulator

-> SF (Event (a -> a)) a

Signal function from events carrying functions to events with the value of those functions applied to the accumulator

As with accum but output the value of the accumulator.

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

Decoupled version of accumHold. Updated accumulator values begin output at the instant after the updating event.

accumBySource

Arguments

:: (b -> a -> b)

Function from accumulator and event value to accumulator.

-> b

Initial accumulator value

-> SF (Event a) (Event b)

Signal function processing events with accumulator function

Provide a function and initial accumulator to process events, produce each new accumulator vale as an event.

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

As in accumBy but produce the accumulator value as a continuous signal.

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

Decoupled version of accumHoldBy. Output signal changes at the instant after an event.

accumFilterSource

Arguments

:: (c -> a -> (c, Maybe b))

Function from accumulator value and event value to new accumulator value and possible event value.

-> c

Initial accumulator value.

-> SF (Event a) (Event b)

Signal function filtering events.

Filter events with an accumulator.

Unlifted event functions

eventSource

Arguments

:: a

Default value

-> (b -> a)

Function from event value

-> Event b

Event

-> a

Return value

Apply a function to an event, or return a default value

fromEvent :: Event a -> aSource

Extract a value from an event. This function will produce an error if applied to a NoEvent function

isEvent :: Event a -> BoolSource

Predicate: is a value an event occurence

isNoEvent :: Event a -> BoolSource

Predicate: is a value not an event occurence

tagSource

Arguments

:: Event a

Possible event occurence

-> b

Replacement value

-> Event b 

Replace a possible event occurence with a new occurence carrying a replacement value

tagWith :: b -> Event a -> Event bSource

See above

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

Pair a value with an event occurrence's value, creating a new event occurrence

lMerge :: Event a -> Event a -> Event aSource

If both inputs are event occurrences, produce the left event.

rMerge :: Event a -> Event a -> Event aSource

If both inputs are event occurences, produce the right event.

merge :: Event a -> Event a -> Event aSource

If both inputs are event occurences, produce an error.

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

If both inputs are event occurences, merge them with the supplied function

mapMergeSource

Arguments

:: (a -> c)

Function for occurences in first source

-> (b -> c)

Function for occurences in second source

-> (a -> b -> c)

Function for occurences in both sources

-> Event a

First source

-> Event b

Second source

-> Event c

Merged/mapped events

Apply functions to an event occurences from two sources

mergeEvents :: [Event a] -> Event aSource

Produce the event occurence closest to the head of the list, if one exists.

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

From a list of event sources produce an event occurence with a list of values of occurrences

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

If there is an occurence from both sources, produce an occurence with both values.

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

Create a pair of event occurences from a single event occurence with a pair of values

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

Apply a predicate to event occurences and forward them only if it matches

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

Apply a Maybe function to event occurences, producing events only for Just values.

gate :: Event a -> Bool -> Event aSource

Only pass through events if some external condition is true.

Switches

Switches provide run-time modification of the signal network. Most switching combinators provided two varieties: an "instantaneous" version and a "decoupled version". The difference lies in which signal function is used to produce the value at the instant of switching. For an instantaneous switch, the signal function being switched in is used to produce the value. For a decoupled switch, that signal function is used to produce the value at the next instant, while the signal function being switched out is still used to produce the value at the instant of switching. This is useful for (among other things) ensuring that looped signal functions are well-founded recursively. Decoupled varieties of switches are prefixed with a "d".

Event-based switches

switchSource

Arguments

:: SF a (b, Event c)

Signal function which may eventually produce an event.

-> (c -> SF a b)

Function producing a signal function from the event value

-> SF a b

Signal function which may switch to a new signal function.

Switch in a new signal function produced from an event, at the instant of that event.

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

Decoupled version of switch.

rSwitchSource

Arguments

:: SF a b

Initial signal function

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

Signal function which may be changed by an event carrying a new signal function

Switches in new signal functions carried by input events.

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

Decoupled version of rswitch

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

Continuation based switching (undocumented)

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

Decoupled version of kswitch

Parallel switches (collections of signal functions)

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

Broadcast the same output to a collection of signal functions, producing a collection of outputs.

pSwitchBSource

Arguments

:: Functor col 
=> col (SF a b)

Initial collection of signal functions

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

Produces collection update events based on the input and output of the parallel SF.

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

Produces the SF to replace the initial parallel sf upon event output from the SF above

-> SF a (col b) 

Take a single input and broadcast it to a collection of functions, until an event is triggered, then switch into another SF producing a collection of outputs

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

pSwitchB, but switched output is visible on the sample frame after the event occurs

rpSwitchBSource

Arguments

:: Functor col 
=> col (SF a b)

Initial collection of signal functions

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

Signal function taking input to broadcast and mutating events and producing the output of the collection of SFs

Broadcast intput to a collection of signal functions, and transform that collection with mutator functions carried in events

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

rpSwitchB, but switched output is visible on the sample frame after the event occurs

parSource

Arguments

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

Routing function, pair input values with signal functions

-> col (SF b c)

Collection of signal functions

-> SF a (col c) 

Route input to a static collection of signal functions

pSwitchSource

Arguments

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

Routing function, pair output with SFs in the collection

-> col (SF b c)

Initial collection of SFs

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

Switching event SF, takes input and output of parallel SF and produces a switching event

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

Takes collection of SFs and value of switching event and produces SF to switch into

-> SF a (col c) 

Like par, but takes an extra SF which looks at the input and output of the parallel switching combinator and switches in a new SF at that point

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

pSwitch, but the output from the switched-in signal function is visible | in the sample frame after the event.

rpSwitchSource

Arguments

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

Routing function

-> col (SF b c)

Initial collection of signal functions

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

Signal function accepting events which mutate the collection

Dynamic collections of signal functions with a routing function

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

rpSwitch, but the output of a switched-in SF is visible in the sample frame after the switch

Delays

old_pre :: SF a aSource

For backwards compatibility only.

old_iPre :: a -> SF a aSource

For backwards compatibility only.

pre :: SF a aSource

Uninitialized one-instant delay.

iPreSource

Arguments

:: a

Value of delayed function at first instant

-> SF a a

One-instant delay

Iniitialized one-instant delay

delaySource

Arguments

:: Time

Time offset to delay signal by

-> a

Initial value until time offset is reached

-> SF a a

delayed signal function

Delay a (non-event) signal by a specific time offsent. For events please use delayEvent.

Calculus

integral :: VectorSpace a s => SF a aSource

Integrate a signal with respect to time.

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

Looping

See also the loop combinator from the ArrowLoop class.

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

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

Randomized signal functions

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

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

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

Animation

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

reactimate :: IO a -> (Bool -> IO (DTime, Maybe a)) -> (Bool -> b -> IO Bool) -> SF a b -> IO ()Source

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

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

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

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

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

data Step a b Source

A step in evaluating a signal function

initStepSource

Arguments

:: a

Value at time 0

-> SF a b

Signal function to animate

-> (b, Step a b)

Output at time 0, next step

Initialize a signal function for stepping through

stepSource

Arguments

:: DTime

Time offset

-> a

Value at new time

-> Step a b

Step to evaluate

-> (b, Step a b)

output value at this time, and next step

Go to the next step of a signal function