Yampa-0.11.1: Library for programming hybrid systems.

Copyright(c) Antony Courtney and Henrik Nilsson Yale University 2003
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainernilsson@cs.yale.edu
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

FRP.Yampa.Event

Description

Events in Yampa represent discrete time-signals, meaning those that do not change continuously. Examples of event-carrying signals would be mouse clicks (in between clicks it is assumed that there is no click), some keyboard events, button presses on wiimotes or window-manager events.

The type Event is isomorphic to Maybe (Event a = NoEvent | Event a) but, semantically, a Maybe-carrying signal could change continuously, whereas an Event-carrying signal should not: for two events in subsequent samples, there should be an small enough sampling frequency such that we sample between those two samples and there are no Events between them. Nevertheless, no mechanism in Yampa will check this or misbehave if this assumption is violated.

Events are essential for many other Yampa constructs, like switches (see switch for details).

Synopsis

Documentation

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 #

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.

maybeToEvent :: Maybe a -> Event a Source #

Convert a maybe value into a event (Event is isomorphic to Maybe).

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

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

Event merge parameterized by a conflict resolution function.

Applicative-based definition: mergeBy f le re = (f $ le * re) | le | re

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 (,)

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 infixl 8 Source #

Enable/disable event occurences based on an external condition.