Yampa-0.11.1: Library for programming hybrid systems.

Safe HaskellNone
LanguageHaskell98

FRP.Yampa.Core

Contents

Description

Minimal FRP core.

For documentation purposes only, to serve as a minimal FRP implementation. Based on Antony Courtney's thesis "Modeling User Interfaces in a Functional Language", page 48 (see https://www.antonycourtney.com/pubs/ac-thesis.pdf, page 61).

Notes:

  • While time is defined as "core", it is not a primitive in Yampa, and it is actually defined as the integral of 1 over time.
  • This does not include derivative.
  • This does not include parallel switching combinators (see Switches).
Synopsis

Signal function

data SF a b Source #

Signal function that transforms a signal carrying values of some type a into a signal carrying values of some type b. You can think of it as (Signal a -> Signal b). A signal is, conceptually, a function from Time to value.

Instances
Arrow SF Source #

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

Instance details

Defined in FRP.Yampa.InternalCore

Methods

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

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

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

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

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

ArrowChoice SF Source #

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

Instance details

Defined in FRP.Yampa.InternalCore

Methods

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

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

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

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

ArrowLoop SF Source #

Creates a feedback loop without delay.

Instance details

Defined in FRP.Yampa.InternalCore

Methods

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

Category SF Source #

Composition and identity for SFs.

Instance details

Defined in FRP.Yampa.InternalCore

Methods

id :: SF a a #

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

Stateless combinators

iPre :: a -> SF a a Source #

Initialized delay operator.

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

arr :: Arrow a => (b -> c) -> a b c #

Lift a function to an arrow.

(>>>) :: Category cat => cat a b -> cat b c -> cat a c infixr 1 #

Left-to-right composition

first :: Arrow a => a b c -> a (b, d) (c, d) #

Send the first component of the input through the argument arrow, and copy the rest unchanged to the output.

Stateful combinators

loop :: ArrowLoop a => a (b, d) (c, d) -> a b c #

Instantly loops an SF, making the second output also the second input, using the fix combinator. This introduces a instant loop; without delays, that may lead to an infinite loop.

integral :: VectorSpace a s => SF a a Source #

Integration using the rectangle rule.

Switching upon certain events

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
Monad Event Source #

Monad instance

Instance details

Defined in FRP.Yampa.Event

Methods

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

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

return :: a -> Event a #

fail :: String -> Event a #

Functor Event Source #

Functor instance (could be derived).

Instance details

Defined in FRP.Yampa.Event

Methods

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

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

Applicative Event Source #

Applicative instance (similar to Maybe).

Instance details

Defined in FRP.Yampa.Event

Methods

pure :: a -> Event a #

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

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

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

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

Alternative Event Source #

Alternative instance

Instance details

Defined in FRP.Yampa.Event

Methods

empty :: Event a #

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

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

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

Eq a => Eq (Event a) Source #

Eq instance (equivalent to derived instance)

Instance details

Defined in FRP.Yampa.Event

Methods

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

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

Ord a => Ord (Event a) Source #

Ord instance (equivalent to derived instance)

Instance details

Defined in FRP.Yampa.Event

Methods

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

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

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

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

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

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

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

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

Defined in FRP.Yampa.Event

Methods

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

show :: Event a -> String #

showList :: [Event a] -> ShowS #

NFData a => NFData (Event a) Source #

NFData instance

Instance details

Defined in FRP.Yampa.Event

Methods

rnf :: Event a -> () #

Forceable a => Forceable (Event a) Source #

Forceable instance

Instance details

Defined in FRP.Yampa.Event

Methods

force :: Event a -> Event a Source #

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!

Time

Note: The function time is actually the integral of 1 over time. So, it's not really necessary.

type Time = Double Source #

Time is used both for time intervals (duration), and time w.r.t. some agreed reference point in time.

time :: SF a Time Source #

Alternative name for localTime.