bearriver-0.14.1: FRP Yampa replacement implemented with Monadic Stream Functions.
Safe HaskellSafe-Inferred
LanguageHaskell2010

FRP.BearRiver

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.

type SF m = MSF (ClockInfo m) Source #

Extensible signal function (signal function with a notion of time, but which can be extended with actions). 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.

type ClockInfo m = ReaderT DTime m Source #

Information on the progress of time.

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

Event a 
NoEvent 

Instances

Instances details
MonadFail Event Source #

MonadFail instance

Instance details

Defined in FRP.BearRiver

Methods

fail :: String -> Event a #

Alternative Event Source #

Alternative instance

Instance details

Defined in FRP.BearRiver

Methods

empty :: Event a #

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

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

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

Applicative Event Source #

The type Event is isomorphic to Maybe. The Applicative instance of Event is analogous to the Applicative instance of Maybe, where the lack of a value (i.e., NoEvent) causes (<*>) to produce no value (NoEvent).

Instance details

Defined in FRP.BearRiver

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 #

Functor Event Source #

The type Event is isomorphic to Maybe. The Functor instance of Event is analogous to the Functo instance of Maybe, where the given function is applied to the value inside the Event, if any.

Instance details

Defined in FRP.BearRiver

Methods

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

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

Monad Event Source #

The type Event is isomorphic to Maybe. The Monad instance of Event is analogous to the Monad instance of Maybe, where the lack of a value (i.e., NoEvent) causes bind to produce no value (NoEvent).

Instance details

Defined in FRP.BearRiver

Methods

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

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

return :: a -> Event a #

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

Defined in FRP.BearRiver

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

Methods

rnf :: Event a -> () #

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

Defined in FRP.BearRiver

Methods

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

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

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

Defined in FRP.BearRiver

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 #

Lifting

arrPrim :: Monad m => (a -> b) -> SF m a b Source #

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

arrEPrim :: Monad m => (Event a -> b) -> SF m (Event a) b Source #

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

Signal functions

Basic signal functions

identity :: Monad m => SF m 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 :: Monad m => b -> SF m 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 :: Monad m => SF m a Time Source #

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

time :: Monad m => SF m a Time Source #

Alternative name for localTime.

Initialization

(-->) :: Monad m => b -> SF m a b -> SF m 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.

(-:>) :: Monad m => b -> SF m a b -> SF m 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.

(>--) :: Monad m => a -> SF m a b -> SF m 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.

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

initially :: Monad m => a -> SF m a a Source #

Simple, stateful signal processing

sscan :: Monad m => (b -> a -> b) -> b -> SF m 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 :: Monad m => (c -> a -> Maybe (c, b)) -> c -> b -> SF m 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.

never :: Monad m => SF m a (Event b) Source #

Event source that never occurs.

now :: Monad m => b -> SF m 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

:: Monad m 
=> Time

The time q after which the event should be produced

-> b

Value to produce at that time

-> SF m a (Event b) 

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

repeatedly :: Monad m => Time -> b -> SF m 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 :: Monad m => [(Time, b)] -> SF m 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 :: Monad m => [(Time, b)] -> SF m 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.

Events

mapEventS :: Monad m => MSF m a b -> MSF m (Event a) (Event b) Source #

Apply an MSF to every input. Freezes temporarily if the input is NoEvent, and continues as soon as an Event is received.

Relation to other types

Hybrid SF m combinators

edge :: Monad m => SF m Bool (Event ()) Source #

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

iEdge :: Monad m => Bool -> SF m 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 occurring at time 0 will be detected).

edgeTag :: Monad m => a -> SF m Bool (Event a) Source #

Like edge, but parameterized on the tag value.

From Yampa

edgeJust :: Monad m => SF m (Maybe a) (Event a) Source #

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

From Yampa

edgeBy :: Monad m => (a -> a -> Maybe b) -> a -> SF m 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).

edgeFrom :: Monad m => Bool -> SF m Bool (Event ()) Source #

Stateful event suppression

notYet :: Monad m => SF m (Event a) (Event a) Source #

Suppression of initial (at local time 0) event.

once :: Monad m => SF m (Event a) (Event a) Source #

Suppress all but the first event.

takeEvents :: Monad m => Int -> SF m (Event a) (Event a) Source #

Suppress all but the first n events.

dropEvents :: Monad m => Int -> SF m (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 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) Source #

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

lMerge :: Event a -> Event a -> Event a Source #

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

rMerge :: Event a -> Event a -> Event a Source #

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

merge :: Event a -> Event a -> Event a Source #

Unbiased event merge: simultaneous occurrence is an error.

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

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

Enable/disable event occurences based on an external condition.

Switching

Basic switchers

switch :: Monad m => SF m a (b, Event c) -> (c -> SF m a b) -> SF m 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 :: Monad m => SF m a (b, Event c) -> (c -> SF m a b) -> SF m 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!

Parallel composition and switching

Parallel composition and switching over collections with broadcasting

parB :: Monad m => [SF m a b] -> SF m a [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 https://www.antonycourtney.com/pubs/hw03.pdf

dpSwitchB :: (Functor m, Monad m, Traversable col) => col (SF m a b) -> SF m (a, col b) (Event c) -> (col (SF m a b) -> c -> SF m a (col b)) -> SF m 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 https://www.antonycourtney.com/pubs/hw03.pdf

Parallel composition over collections

parC :: Monad m => SF m a b -> SF m [a] [b] Source #

Apply an SF to every element of a list.

Example:

>>> embed (parC integral) (deltaEncode 0.1 [[1, 2], [2, 4], [3, 6], [4.0, 8.0 :: Float]])
[[0.0,0.0],[0.1,0.2],[0.3,0.6],[0.6,1.2]]

The number of SFs or expected inputs is determined by the first input list, and not expected to vary over time.

If more inputs come in a subsequent list, they are ignored.

>>> embed (parC (arr (+1))) (deltaEncode 0.1 [[0], [1, 1], [3, 4], [6, 7, 8], [1, 1], [0, 0], [1, 9, 8]])
[[1],[2],[4],[7],[2],[1],[2]]

If less inputs come in a subsequent list, an exception is thrown.

>>> embed (parC (arr (+1))) (deltaEncode 0.1 [[0, 0], [1, 1], [3, 4], [6, 7, 8], [1, 1], [0, 0], [1, 9, 8]])
[[1,1],[2,2],[4,5],[7,8],[2,2],[1,1],[2,10]]

Discrete to continuous-time signal functions

Wave-form generation

hold :: Monad m => a -> SF m (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]

Accumulators

accumBy :: Monad m => (b -> a -> b) -> b -> SF m (Event a) (Event b) Source #

Accumulator parameterized by the accumulation function.

accumHoldBy :: Monad m => (b -> a -> b) -> b -> SF m (Event a) b Source #

Zero-order hold accumulator parameterized by the accumulation function.

State keeping combinators

Loops with guaranteed well-defined feedback

loopPre :: Monad m => c -> SF m (a, c) (b, c) -> SF m a b Source #

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

Integration and differentiation

integral :: (Monad m, Fractional s, VectorSpace a s) => SF m a a Source #

Integration using the rectangle rule.

integralFrom :: (Monad m, Fractional s, VectorSpace a s) => a -> SF m a a 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.

derivative :: (Monad m, Fractional s, VectorSpace a s) => SF m 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.

derivativeFrom :: (Monad m, Fractional s, VectorSpace a s) => a -> SF m a a Source #

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

Noise (random signal) sources and stochastic event sources

occasionally Source #

Arguments

:: MonadRandom m 
=> Time

The time q after which the event should be produced on average

-> b

Value to produce at time of event

-> SF m a (Event b) 

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

Execution/simulation

Reactimation

reactimate :: Monad m => m a -> (Bool -> m (DTime, Maybe a)) -> (Bool -> b -> m Bool) -> SF Identity a b -> m () Source #

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.

Debugging / Step by step simulation

evalAtZero :: SF Identity a b -> a -> (b, SF Identity a b) Source #

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 :: SF Identity a b -> DTime -> a -> (b, SF Identity a b) Source #

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 Identity a b -> a -> DTime -> (b, SF Identity 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 functions

Event handling

replaceOnce :: Monad m => a -> SF m a a Source #

Tuples

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