varying-0.1.0.0: Automaton based varying values, event streams and tweening.

Safe HaskellNone
LanguageHaskell2010

Control.Varying.Event

Contents

Description

 

Synopsis

Documentation

data Event a Source

An Event is just like a Maybe.

Constructors

Event a 
NoEvent 

Transforming event values.

toMaybe :: Event a -> Maybe a Source

Turns an Event into a Maybe.

isEvent :: Event a -> Bool Source

Returns True when the Event contains a sample and False otherwise.

Combining events and values

latchWith :: Monad m => (b -> c -> d) -> Var m a (Event b) -> Var m a (Event c) -> Var m a (Event d) Source

Holds the last value of one event stream while waiting for another event stream to produce a value. Once both streams have produced a value combine the two using the given combine function.

orE :: Monad m => Var m a b -> Var m a (Event b) -> Var m a b Source

Produces values from the first unless the second produces event values and if so, produces the values of those events.

tagOn :: Monad m => Var m a b -> Var m a (Event c) -> Var m a (Event b) Source

Injects the values of the vb into the events of ve.

tagM :: Monad m => (b -> m c) -> Var m a (Event b) -> Var m a (Event c) Source

Injects a monadic computation into the events of vb, providing a way to perform side-effects inside an Event inside a Var.

ringM :: Monad m => (c -> m ()) -> (b -> m c) -> Var m a (Event b) -> Var m a (Event c) Source

Injects a monadic computation into an event stream, using the event values of type b as a parameter to produce an event stream of type c. After the first time an event is generated the result of the previous event is used in a clean up function.

This is like tagM but performs a cleanup function first.

Generating events from values

use :: (Functor f, Functor e) => a -> f (e b) -> f (e a) Source

Populates a varying Event with a value. This is meant to be used with the various 'on...' event triggers. For example use 1 onTrue produces values of `Event 1` when the input value is True.

onTrue :: Monad m => Var m Bool (Event ()) Source

Triggers an `Event ()` when the input value is True.

onJust :: Monad m => Var m (Maybe a) (Event a) Source

Triggers an `Event a` when the input is `Just a`.

onUnique :: (Monad m, Eq a) => Var m a (Event a) Source

Triggers an `Event a` when the input is a unique value.

onWhen :: Applicative m => (a -> Bool) -> Var m a (Event a) Source

Triggers an `Event a` when the condition is met.

toEvent :: Monad m => Var m a b -> Var m a (Event b) Source

Wraps all produced values of the given var with events.

Using events

collect :: Monad m => Var m (Event a) [a] Source

Collect all produced values into a list.

hold :: Monad m => Var m a (Event b) -> b -> Var m a b Source

Produces the initial value until the given Var produces an event. After an event is produced that event's value will be produced until the next event produced by the given Var.

holdWith :: Monad m => b -> Var m a (Event b) -> Var m a b Source

Flipped version of hold.

startingWith :: Monad m => a -> Var m (Event a) a Source

Produces the given value until the input events produce a value, then produce that value until a new input event produces. This always holds the last produced value, starting with the given value. time ~> after 3 ~> startingWith 0 This is similar to hold except that it takes events from its input value instead of another Var.

startWith :: Monad m => a -> Var m (Event a) a Source

Produces the given value until the input events produce a value, then produce that value until a new input event produces. This always holds the last produced value, starting with the given value. time ~> after 3 ~> startingWith 0 This is similar to hold except that it takes events from its input value instead of another Var.

Temporal operations

between :: Monad m => Var m a (Event b) -> Var m a (Event c) -> Var m a (Event ()) Source

Produce events after the first until the second. After a successful cycle it will start over.

until :: Monad m => Var m a b -> Var m a (Event c) -> Var m a (Event b) Source

Produce events with the initial varying value until the input event stream ve produces its first event, then never produce any events.

after :: Monad m => Var m a b -> Var m a (Event c) -> Var m a (Event b) Source

Produce events with the initial value only after the input stream has produced one event.

beforeWith :: Monad m => Var m a b -> (Var m a (Event b), b -> Var m a (Event b)) -> Var m a (Event b) Source

Like before, but use the value produced by the switching stream to create a stream to switch to.

beforeOne :: Monad m => Var m a b -> Var m a (Event b) -> Var m a (Event b) Source

Like before, but sample the value of the second stream once before inhibiting.

before :: Monad m => Var m a b -> Var m a (Event c) -> Var m a (Event b) Source

Produce events with the initial varying value only before the second stream has produced one event.

filterE :: Monad m => (b -> Bool) -> Var m a (Event b) -> Var m a (Event b) Source

Inhibit all events that don't pass the predicate.

takeE :: Monad m => Int -> Var m a (Event b) -> Var m a (Event b) Source

Stream through some number of successful events and then inhibit forever.

once :: Monad m => b -> Var m a (Event b) Source

Produce the given value once and then inhibit forever.

always :: Monad m => b -> Var m a (Event b) Source

Produces events with the initial value forever.

never :: Monad m => Var m b (Event c) Source

TODO: | Produce events of a stream only when both streams produce events. | Combine simultaneous events.

Never produces any event values.

Switching and chaining events

andThen :: Monad m => Var m a (Event b) -> Var m a b -> Var m a b Source

Produces the first Vars Event values until that stops producing, then switches to the second Var.

andThenWith :: Monad m => Var m a (Event b) -> (Maybe b -> Var m a b) -> Var m a b Source

Switches from one event stream when that stream stops producing. A new stream is created using the last produced value (or Nothing) and used as the second stream.

andThenE :: Monad m => Var m a (Event b) -> Var m a (Event b) -> Var m a (Event b) Source

Switches from one event stream to another once the first stops producing.

switchByMode :: (Monad m, Eq b) => Var m a b -> (b -> Var m a c) -> Var m a c Source

Switches using a mode signal. Signals maintain state for the duration of the mode.

Combining event streams

combineWith :: Monad m => (b -> c -> d) -> Var m a (Event b) -> Var m a (Event c) -> Var m a (Event d) Source

Combine two events streams into one event stream. Like combine but uses a combining function instead of (,).

combine :: Monad m => Var m a (Event b) -> Var m a (Event c) -> Var m a (Event (b, c)) Source

Combine two event streams into an event stream of tuples. A tuple is only produced when both event streams produce a value.