Copyright | (c) Antony Courtney and Henrik Nilsson Yale University 2003 |
---|---|
License | BSD-style (see the LICENSE file in the distribution) |
Maintainer | ivan.perez@keera.co.uk |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell98 |
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, screenshots, tutorials and documentation here:
https://github.com/ivanperez-keera/Yampa
https://github.com/ivanperez-keera/Yampa/tree/master/examples
https://wiki.haskell.org/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).
Main Yampa modules:
- FRP.Yampa -- This exports all FRP-related functions
- FRP.Yampa.Task
Minimal Complete FRP Definition:
Different FRP aspects:
- FRP.Yampa.Basic
- FRP.Yampa.Conditional
- FRP.Yampa.Delays
- FRP.Yampa.Event
- FRP.Yampa.EventS -- Event consuming/producing SFs. To be renamed.
- FRP.Yampa.Hybrid -- Hybrid (discrete/continuous) SFs
- FRP.Yampa.Integration
- FRP.Yampa.Loop
- FRP.Yampa.Random
- FRP.Yampa.Scan
- FRP.Yampa.Switches
- FRP.Yampa.Time
- FRP.Yampa.Simulation -- Reactimation/evaluation
Internals:
- FRP.Yampa.InternalCore -- Module not exposed.
Geometry:
- FRP.Yampa.Geometry
- FRP.Yampa.AffineSpace
- FRP.Yampa.VectorSpace
- FRP.Yampa.Point2
- FRP.Yampa.Point3
- FRP.Yampa.Vector2
- FRP.Yampa.Vector3
Old legacy code:
- FRP.Yampa.Diagnostics
- FRP.Yampa.Forceable
- FRP.Yampa.Internals -- No longer in use
- FRP.Yampa.MergeableRecord
- FRP.Yampa.Miscellany
- FRP.Yampa.Utilities
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. Also, please let us know if you see any problems with the new project structure.
- module Control.Arrow
- module FRP.Yampa.VectorSpace
- class RandomGen g where
- class Random a where
- type Time = Double
- type DTime = Double
- data SF a b
- data Event a
- arrPrim :: (a -> b) -> SF a b
- arrEPrim :: (Event a -> b) -> SF (Event a) b
- identity :: SF a a
- constant :: b -> SF a b
- localTime :: SF a Time
- time :: SF a Time
- (-->) :: b -> SF a b -> SF a b
- (-:>) :: b -> SF a b -> SF a b
- (>--) :: a -> SF a b -> SF a b
- (-=>) :: (b -> b) -> SF a b -> SF a b
- (>=-) :: (a -> a) -> SF a b -> SF a b
- initially :: a -> SF a a
- sscan :: (b -> a -> b) -> b -> SF a b
- sscanPrim :: (c -> a -> Maybe (c, b)) -> c -> b -> SF a b
- never :: SF a (Event b)
- now :: b -> SF a (Event b)
- after :: Time -> b -> SF a (Event b)
- repeatedly :: Time -> b -> SF a (Event b)
- afterEach :: [(Time, b)] -> SF a (Event b)
- afterEachCat :: [(Time, b)] -> SF a (Event [b])
- delayEvent :: Time -> SF (Event a) (Event a)
- delayEventCat :: Time -> SF (Event a) (Event [a])
- edge :: SF Bool (Event ())
- iEdge :: Bool -> SF Bool (Event ())
- edgeTag :: a -> SF Bool (Event a)
- edgeJust :: SF (Maybe a) (Event a)
- edgeBy :: (a -> a -> Maybe b) -> a -> SF a (Event b)
- maybeToEvent :: Maybe a -> Event a
- notYet :: SF (Event a) (Event a)
- once :: SF (Event a) (Event a)
- takeEvents :: Int -> SF (Event a) (Event a)
- dropEvents :: Int -> SF (Event a) (Event a)
- noEvent :: Event a
- noEventFst :: (Event a, b) -> (Event c, b)
- noEventSnd :: (a, Event b) -> (a, Event c)
- event :: a -> (b -> a) -> Event b -> a
- fromEvent :: Event a -> a
- isEvent :: Event a -> Bool
- isNoEvent :: Event a -> Bool
- tag :: Event a -> b -> Event b
- tagWith :: b -> Event a -> Event b
- attach :: Event a -> b -> Event (a, b)
- lMerge :: Event a -> Event a -> Event a
- rMerge :: Event a -> Event a -> Event a
- merge :: Event a -> Event a -> Event a
- mergeBy :: (a -> a -> a) -> Event a -> Event a -> Event a
- mapMerge :: (a -> c) -> (b -> c) -> (a -> b -> c) -> Event a -> Event b -> Event c
- mergeEvents :: [Event a] -> Event a
- catEvents :: [Event a] -> Event [a]
- joinE :: Event a -> Event b -> Event (a, b)
- splitE :: Event (a, b) -> (Event a, Event b)
- filterE :: (a -> Bool) -> Event a -> Event a
- mapFilterE :: (a -> Maybe b) -> Event a -> Event b
- gate :: Event a -> Bool -> Event a
- switch :: SF a (b, Event c) -> (c -> SF a b) -> SF a b
- dSwitch :: SF a (b, Event c) -> (c -> SF a b) -> SF a b
- rSwitch :: SF a b -> SF (a, Event (SF a b)) b
- drSwitch :: SF a b -> SF (a, Event (SF a b)) b
- kSwitch :: SF a b -> SF (a, b) (Event c) -> (SF a b -> c -> SF a b) -> SF a b
- dkSwitch :: SF a b -> SF (a, b) (Event c) -> (SF a b -> c -> SF a b) -> SF a b
- parB :: Functor col => col (SF a b) -> SF a (col b)
- 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)
- 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)
- rpSwitchB :: Functor col => col (SF a b) -> SF (a, Event (col (SF a b) -> col (SF a b))) (col b)
- drpSwitchB :: Functor col => col (SF a b) -> SF (a, Event (col (SF a b) -> col (SF a b))) (col b)
- par :: Functor col => (forall sf. a -> col sf -> col (b, sf)) -> col (SF b c) -> SF a (col c)
- pSwitch :: 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)
- 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)
- 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)
- 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)
- hold :: a -> SF (Event a) a
- dHold :: a -> SF (Event a) a
- trackAndHold :: a -> SF (Maybe a) a
- accum :: a -> SF (Event (a -> a)) (Event a)
- accumHold :: a -> SF (Event (a -> a)) a
- dAccumHold :: a -> SF (Event (a -> a)) a
- accumBy :: (b -> a -> b) -> b -> SF (Event a) (Event b)
- accumHoldBy :: (b -> a -> b) -> b -> SF (Event a) b
- dAccumHoldBy :: (b -> a -> b) -> b -> SF (Event a) b
- accumFilter :: (c -> a -> (c, Maybe b)) -> c -> SF (Event a) (Event b)
- pre :: SF a a
- iPre :: a -> SF a a
- delay :: Time -> a -> SF a a
- pause :: b -> SF a Bool -> SF a b -> SF a b
- loopPre :: c -> SF (a, c) (b, c) -> SF a b
- loopIntegral :: VectorSpace c s => SF (a, c) (b, c) -> SF a b
- integral :: VectorSpace a s => SF a a
- imIntegral :: VectorSpace a s => a -> SF a a
- impulseIntegral :: VectorSpace a k => SF (a, Event a) a
- count :: Integral b => SF (Event a) (Event b)
- derivative :: VectorSpace a s => SF a a
- iterFrom :: (a -> a -> DTime -> b -> b) -> b -> SF a b
- noise :: (RandomGen g, Random b) => g -> SF a b
- noiseR :: (RandomGen g, Random b) => (b, b) -> g -> SF a b
- occasionally :: RandomGen g => g -> Time -> b -> SF a (Event b)
- reactimate :: Monad m => m a -> (Bool -> m (DTime, Maybe a)) -> (Bool -> b -> m Bool) -> SF a b -> m ()
- data ReactHandle a b
- reactInit :: IO a -> (ReactHandle a b -> Bool -> b -> IO Bool) -> SF a b -> IO (ReactHandle a b)
- react :: ReactHandle a b -> (DTime, Maybe a) -> IO Bool
- embed :: SF a b -> (a, [(DTime, Maybe a)]) -> [b]
- embedSynch :: SF a b -> (a, [(DTime, Maybe a)]) -> SF Double b
- deltaEncode :: Eq a => DTime -> [a] -> (a, [(DTime, Maybe a)])
- deltaEncodeBy :: (a -> a -> Bool) -> DTime -> [a] -> (a, [(DTime, Maybe a)])
- (#) :: (a -> b) -> (b -> c) -> a -> c
- dup :: a -> (a, a)
Documentation
module Control.Arrow
module FRP.Yampa.VectorSpace
The class RandomGen
provides a common interface to random number
generators.
The next
operation returns an Int
that is uniformly distributed
in the range returned by genRange
(including both end points),
and a new generator.
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
.
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).
With a source of random number supply in hand, the Random
class allows the
programmer to extract random values of a variety of types.
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:
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.
A variant of randomR
that uses the global random number generator
(see System.Random).
A variant of random
that uses the global random number generator
(see System.Random).
Basic definitions
Time is used both for time intervals (duration), and time w.r.t. some agreed reference point in time.
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.
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.
Arrow SF Source # | Signal Functions as Arrows. See "The Yampa Arcade", by Courtney, Nilsson and Peterson. |
ArrowChoice SF Source # | Choice of which SF to run based on the value of a signal. |
ArrowLoop SF Source # | Creates a feedback loop without delay. |
Category * SF Source # | Composition and identity for SFs. |
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).
Monad Event Source # | Monad instance |
Functor Event Source # | Functor instance (could be derived). |
Applicative Event Source # | Applicative instance (similar to |
Alternative Event Source # | Alternative instance |
Eq a => Eq (Event a) Source # | Eq instance (equivalent to derived instance) |
Ord a => Ord (Event a) Source # | Ord instance (equivalent to derived instance) |
Show a => Show (Event a) Source # | |
NFData a => NFData (Event a) Source # | NFData instance |
Forceable a => Forceable (Event a) Source # | Forceable instance |
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: 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.
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.
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
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.
:: 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.
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 #
Stateful event suppression
Pointwise functions on events
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.
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.
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 (,)
filterE :: (a -> Bool) -> Event a -> Event a Source #
Filter out events that don't satisfy some predicate.
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
:: 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.
:: 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.
:: 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 |
-> 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 |
-> 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.
:: 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
.
:: 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
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).
Delays
Basic delays
Uninitialized delay operator.
The output has an infinitesimal delay (1 sample), and the value at time zero is undefined.
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.
Execution/simulation
Reactimation
:: Monad m | |
=> m a | Initialization action |
-> (Bool -> m (DTime, Maybe a)) | Input sensing action |
-> (Bool -> b -> m Bool) | Actuaction (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.
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.