Copyright | (c) Antony Courtney and Henrik Nilsson Yale University 2003 |
---|---|
License | BSD-style (see the LICENSE file in the distribution) |
Maintainer | nilsson@cs.yale.edu |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
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 Event
s 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
- data Event a
- noEvent :: Event a
- noEventFst :: (Event a, b) -> (Event c, b)
- noEventSnd :: (a, Event b) -> (a, Event c)
- maybeToEvent :: Maybe a -> Event a
- 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
Documentation
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).
Instances
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 |
Defined in FRP.Yampa.Event | |
Forceable a => Forceable (Event a) Source # | Forceable instance |
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 #
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.