Copyright | (c) 2015 Schell Scivally |
---|---|
License | MIT |
Maintainer | Schell Scivally <schell@takt.com> |
Safe Haskell | None |
Language | Haskell2010 |
An event stream is simply a stream of Maybe a
. This kind of stream is
considered to be only defined at those occurances of Just a
. Events
describe things that happen at a specific time, place or any collection of
inputs.
For example, you can think of the event stream
as an occurrence of VarT
IO
Double
(Event
())()
at a specific
value of Double
. It is possible that this Double
is time, or it could be
the number of ice cream sandwiches eaten by a particular cat.
In varying
we use event streams to dynamically update the network while it
is running. For more info on switching and sequencing streams with events
please check out Spline
, which lets you chain together
sequences of values and events using a familiar do-notation.
Synopsis
- type Event = Maybe
- event :: a -> Event a
- noevent :: Event a
- use :: (Functor f, Functor e) => a -> f (e b) -> f (e a)
- onTrue :: Monad m => VarT m Bool (Event ())
- onUnique :: (Monad m, Eq a) => VarT m a (Event a)
- onWhen :: Applicative m => (a -> Bool) -> VarT m a (Event a)
- foldStream :: Monad m => (a -> t -> a) -> a -> VarT m (Event t) a
- startingWith :: Monad m => a -> VarT m (Event a) a
- startWith :: Monad m => a -> VarT m (Event a) a
- bothE :: Monad m => (a -> b -> c) -> VarT m a (Event a) -> VarT m a (Event b) -> VarT m a (Event c)
- anyE :: Monad m => [VarT m a (Event b)] -> VarT m a (Event b)
- filterE :: Monad m => (b -> Bool) -> VarT m a (Event b) -> VarT m a (Event b)
- takeE :: Monad m => Int -> VarT m a (Event b) -> VarT m a (Event b)
- dropE :: Monad m => Int -> VarT m a (Event b) -> VarT m a (Event b)
- once :: Monad m => b -> VarT m a (Event b)
- always :: Monad m => b -> VarT m a (Event b)
- never :: Monad m => VarT m b (Event c)
- before :: (Monad m, Num t, Ord t) => t -> VarT m t (Event t)
- after :: (Monad m, Num t, Ord t) => t -> VarT m t (Event t)
- switch :: Monad m => VarT m a (Event (VarT m a b)) -> VarT m a (Event b)
- onlyWhen :: Monad m => VarT m a b -> (a -> Bool) -> VarT m a (Event b)
- onlyWhenE :: Monad m => VarT m a b -> VarT m a (Event c) -> VarT m a (Event b)
Event constructors (synonyms of Maybe)
Generating events from value streams
onWhen :: Applicative m => (a -> Bool) -> VarT m a (Event a) Source #
Triggers an
when the condition is met.Event
a
Folding and gathering event streams
foldStream :: Monad m => (a -> t -> a) -> a -> VarT m (Event t) a Source #
Like a left fold over all the stream's produced values.
startingWith :: Monad m => a -> VarT 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
>>>
:{
let v = onWhen (== 3) >>> startingWith 0 in testVarOver v [0, 1, 2, 3, 4]>>>
:}
0 0 0 3 3
startWith :: Monad m => a -> VarT 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
>>>
:{
let v = onWhen (== 3) >>> startingWith 0 in testVarOver v [0, 1, 2, 3, 4]>>>
:}
0 0 0 3 3
Combining multiple event streams
bothE :: Monad m => (a -> b -> c) -> VarT m a (Event a) -> VarT m a (Event b) -> VarT m a (Event c) Source #
Combine two Event
streams. Produces an event only when both streams proc
at the same time.
List-like operations on event streams
filterE :: Monad m => (b -> Bool) -> VarT m a (Event b) -> VarT m a (Event b) Source #
Inhibit all Event
s that don't pass the predicate.
takeE :: Monad m => Int -> VarT m a (Event b) -> VarT m a (Event b) Source #
Stream through some number of successful Event
s and then inhibit
forever.
dropE :: Monad m => Int -> VarT m a (Event b) -> VarT m a (Event b) Source #
Inhibit the first n occurences of an Event
.
Primitive event streams
once :: Monad m => b -> VarT m a (Event b) Source #
Produce the given event value once and then inhibit forever.
before :: (Monad m, Num t, Ord t) => t -> VarT m t (Event t) Source #
Emits events before accumulating t of input dt. Note that as soon as we have accumulated >= t we stop emitting events and therefore an event will never be emitted exactly at time == t.
after :: (Monad m, Num t, Ord t) => t -> VarT m t (Event t) Source #
Emits events after t input has been accumulated. Note that event emission is not guaranteed to begin exactly at t, since it depends on the input.
Switching
switch :: Monad m => VarT m a (Event (VarT m a b)) -> VarT m a (Event b) Source #
Higher-order switching. Use an event stream of value streams and produces event values of the latest produced value stream. Switches to a new value stream each time one is produced. The currently used value stream maintains local state until the outer event stream produces a new value stream.
In this example we're sequencing the value streams we'd like to use and then switching them when the outer event stream fires.
>>>
import Control.Varying.Spline
>>>
:{
let v :: VarT IO () (Event Int) v = switch $ flip outputStream Nothing $ do step $ Just $ 1 >>> accumulate (+) 0 step Nothing step Nothing step $ Just 5 step Nothing in testVarOver v [(), (), (), (), ()] -- testing over five frames>>>
:}
Just 1 Just 2 Just 3 Just 5 Just 5