Yampa-0.9.5: Library for programming hybrid systems.

Portabilitynon-portable (GHC extensions)
Stabilityprovisional
Maintainernilsson@cs.yale.edu
Safe HaskellNone

FRP.Yampa

Contents

Description

New version using GADTs.

ToDo:

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

Random ideas:

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

Synopsis

Documentation

class RandomGen g where

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

Methods

next :: g -> (Int, g)

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

genRange :: g -> (Int, Int)

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

It is required that:

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

The default definition spans the full range of Int.

split :: g -> (g, g)

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

Instances

class Random a where

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

Minimal complete definition: randomR and random.

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

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

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

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

type Time = DoubleSource

Time is used both for time intervals (duration), and time w.r.t. some agreed reference point in time. Conceptually, Time = R, i.e. time can be 0 or even negative.

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.

data Event a Source

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

Constructors

NoEvent 
Event a 

Instances

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

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

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

Signal functions

Basic signal functions

constant :: b -> SF a bSource

Initialization

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

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

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

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

initially :: a -> SF a aSource

Simple, stateful signal processing

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

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

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.

afterSource

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

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

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

Stateful event suppression

Pointwise functions on events

noEvent :: Event aSource

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

An event-based version of the maybe function.

fromEvent :: Event a -> aSource

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

isEvent :: Event a -> BoolSource

Tests whether the input represents an actual event.

isNoEvent :: Event a -> BoolSource

Negation of isEvent.

tag :: Event a -> b -> Event bSource

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

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

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

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

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

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

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

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

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

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

Unbiased event merge: simultaneous occurrence is an error.

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

Event merge parameterized by a conflict resolution function.

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

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

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

Collects simultaneous event occurrences; no event if none.

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

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

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

Split event carrying pairs into two events.

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

Filter out events that don't satisfy some predicate.

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

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 aSource

Enable/disable event occurences based on an external condition.

Switching

Basic switchers

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

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

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

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

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

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

Parallel composition and switching

Parallel composition and switching over collections with broadcasting

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

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

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

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

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

Parallel composition and switching over collections with general routing

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

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

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

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

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

Discrete to continuous-time signal functions

Wave-form generation

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

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

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

Accumulators

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

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

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

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

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

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

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

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

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

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

Delays

Basic delays

old_iPre :: a -> SF a aSource

pre :: SF a aSource

iPre :: a -> SF a aSource

Timed delays

delay :: Time -> a -> SF a aSource

State keeping combinators

Loops with guaranteed well-defined feedback

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

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

Integration and differentiation

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

Noise (random signal) sources and stochastic event sources

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

Reactimation

reactimateSource

Arguments

:: IO a

IO initialization action

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

IO input sensing action

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

IO actuaction (output processing) action

-> SF a b

Signal function

-> IO () 

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

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

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

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

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

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

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

Embedding

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