reenact-0.9: A reimplementation of the Reactive library.

Safe HaskellNone

Control.Reactive

Contents

Description

Synopsis

Types

data Event a Source

A stream of values.

 type Event a = [(Time, a)]

Instances

Functor Event

Event is a functor: fmap transforms each value.

Monoid (Event a)

Event is a monoid: mempty is the event that never occurs, mappend interleaves values.

data Reactive a Source

A time-varying value.

 type Reactive a = Time -> a

Instances

Functor Reactive

Reactive is a functor: fmap transforms the value at each point in time.

Applicative Reactive

Reactive is an applicative functor: pure is a constant value and fr <*> xr applies the function fr t to the value xr t.

Enum a => Enum (Reactive a) 
Eq (Reactive b) 
Floating b => Floating (Reactive b) 
Fractional b => Fractional (Reactive b) 
Integral a => Integral (Reactive a) 
Num a => Num (Reactive a) 
Ord b => Ord (Reactive b) 
(Num a, Ord a) => Real (Reactive a) 
IsString a => IsString (Reactive a) 
Monoid a => Monoid (Reactive a)

Reactive has a lifted is a monoid: mempty is the constant empty value and mappend combines values according to mappend on values.

VectorSpace v => VectorSpace (Reactive v) 
AdditiveGroup v => AdditiveGroup (Reactive v) 

Basic combinators

Event to reactive

stepper :: a -> Event a -> Reactive aSource

Step between values.

maybeStepper :: Event a -> Reactive (Maybe a)Source

Switch between time-varying values.

switcher :: Reactive a -> Event (Reactive a) -> Reactive a r switcher e = RJoin (r stepper e) r switcher e = join (r stepper e)

Step between values without initial.

sampleAndHold2 :: b -> Reactive b -> Event a -> Reactive bSource

Switch between the values of a time-varying value when an event occurs.

sampleAndHold :: Reactive b -> Event a -> Reactive b sampleAndHold r e = r switcher (pure $ r sample e) sampleAndHold r e = (liftA2 change) r (maybeStepper $ sample r e) where change a Nothing = a change a (Just b) = b

Reactive to event

apply :: Reactive (a -> b) -> Event a -> Event bSource

Apply the values of an event to a time-varying function.

 r `apply` e = r `snapshotWith ($)` e

filter' :: Reactive (a -> Bool) -> Event a -> Event aSource

Filter an event based on a time-varying predicate.

 r `filter'` e = justE $ (partial <$> r) `apply` e

gate :: Reactive Bool -> Event a -> Event aSource

Filter an event based on a time-varying toggle.

 r `gate` e = (const <$> r) `filter'` e

sample :: Reactive b -> Event a -> Event bSource

Sample a time-varying value.

 r `snapshot` e = snapshotWith const

snapshot :: Reactive a -> Event b -> Event (a, b)Source

Sample a time-varying value with the value of the trigger.

 r `snapshot` e = snapshotWith (,)

snapshotWith :: (a -> b -> c) -> Reactive a -> Event b -> Event cSource

Sample a time-varying value with the value of the trigger, using the given function to combine.

 r `snapshotWith f` e = (f <$> r) `apply` e

Merging and splitting values

justE :: Event (Maybe a) -> Event aSource

Discard empty values.

splitE :: Event (Either a b) -> (Event a, Event b)Source

Partition values of different types. See also partitionE.

 let (x, y) in eitherE x y = splitE e  ≡  e

eitherE :: Event a -> Event b -> Event (Either a b)Source

Interleave values of different types.

Past-dependent values

Buffering events

lastE :: Event a -> Event aSource

Delay by one value.

delayE :: Int -> Event a -> Event aSource

Delay by n values.

recallEWith :: (b -> b -> a) -> Event b -> Event aSource

Pack with last value. Similar to withPrevEWith in reactive but flipped.

diffE :: Num a => Event a -> Event aSource

Difference of successive values.

bufferE :: Int -> Event a -> Event [a]Source

Buffer up to n values. When the buffer is full, old elements will be rotated out.

 bufferE n e = [[e1],[e1,e2]..[e1..en],[e2..en+1]..]

gatherE :: Int -> Event a -> Event [a]Source

Gather event values into chunks of regular size.

 gatherE n e = [[e1..en],[en+1..e2n]..]

scatterE :: Event [a] -> Event aSource

Separate chunks of values.

 scatterE [e1,e2..] = [e1] <> [e2] ..

Accumulating values

accumE :: a -> Event (a -> a) -> Event aSource

Event accumulator.

 a `accumE` e = (a `accumR` e) `sample` e
 a `accumR` e = a `stepper` (a `accumE` e)

accumR :: a -> Event (a -> a) -> Reactive aSource

Reactive accumulator.

 a `accumE` e = (a `accumR` e) `sample` e
 a `accumR` e = a `stepper` (a `accumE` e)

foldpE :: (a -> b -> b) -> b -> Event a -> Event bSource

Create a past-dependent event.

 scanlE f z x = foldpE (flip f) f z x

foldpR :: (a -> b -> b) -> b -> Event a -> Reactive bSource

Create a past-dependent reactive. This combinator corresponds to scanl on streams.

 scanlR f z x = foldpR (flip f) f z x

scanlE :: (a -> b -> a) -> a -> Event b -> Event aSource

Create a past-dependent event. This combinator corresponds to scanl on streams.

 scanlE f z x = foldpE (flip f) f z x

scanlR :: (a -> b -> a) -> a -> Event b -> Reactive aSource

Create a past-dependent reactive. This combinator corresponds to scanl on streams.

 scanlR f z x = foldpR (flip f) f z x

mapAccum :: a -> Event (a -> (b, a)) -> (Event b, Reactive a)Source

Efficient combination of accumE and accumR.

Special accumulators

firstE :: Event a -> Event aSource

Get just the first value.

restE :: Event a -> Event aSource

Get all but the first value.

countE :: Enum b => Event a -> Event bSource

Count values.

countR :: Enum b => Event a -> Reactive bSource

Count values.

monoidE :: Monoid a => Event a -> Event aSource

Create a past-dependent event using a Monoid instance.

monoidR :: Monoid a => Event a -> Reactive aSource

Create a past-dependent event using a Monoid instance.

Lifted monoids

sumE :: Num a => Event a -> Event aSource

productE :: Num a => Event a -> Event aSource

sumR :: Num a => Event a -> Reactive aSource

Toggles and switches

tickE :: Event a -> Event ()Source

Throw away values of the event.

This is of course just () <$ x but it is useful to fix the type in some cases.

Time

pulse :: DiffTime -> Event ()Source

  An event occuring at the specified interval.

time :: Fractional a => Reactive aSource

A generalized time behaviour.

integral :: Fractional b => Event a -> Reactive b -> Reactive bSource

Integrates a behaviour.

 integral pulse behavior

Record and playback

data TransportControl t Source

Constructors

Play

Play from the current position.

Reverse

Play in reverse from the current position.

Pause

Stop playing, and retain current position.

Stop

Stop and reset position.

transport :: (Ord t, Fractional t) => Event (TransportControl t) -> Event a -> Reactive t -> Reactive tSource

Generates a cursor that moves forward or backward continuously.

The cursor may be started, stopped, moved by sending a TransportControl event.

 transport control pulse speed

record :: Ord t => Reactive t -> Event a -> Reactive [(t, a)]Source

Record a list of values.

playback :: Ord t => Reactive t -> Reactive [(t, a)] -> Event aSource

Play back a list of values.

This function will sample the time behaviour at an arbitrary small interval. To get precise control of how time is sampled, use playback' instead.

playback' :: Ord t => Event b -> Reactive t -> Reactive [(t, a)] -> Event [(t, a)]Source

Play back a list of values.

Special functions

seqE :: Event a -> Event b -> Event bSource

Run both and behave as the second event.

Creating events and reactives

From standard library

getCharE :: Event CharSource

Event version of getChar.

putCharE :: Event Char -> Event CharSource

Event version of putChar.

getLineE :: Event StringSource

Event version of getLine.

From channels

readChanE :: Chan a -> Event aSource

Event reading from a channel.

writeChanE :: Chan a -> Event a -> Event aSource

Event writing to a channel.

From IO

getE :: IO a -> Event aSource

Event reading from external world. The computation should be blocking and is polled exactly once per value.

This function can be used with standard I/O functions.

pollE :: IO (Maybe a) -> Event aSource

Event reading from external world. The computation should be non-blocking and may be polled repeatedly for each value.

This function should be used with non-effectful functions, typically functions that observe the current value of some external property. You should not use this function with standard I/O functions as this may lead to non-deterministic reads (i.e. loss of data).

putE :: (a -> IO ()) -> Event a -> Event aSource

Event writing to the external world.

This function can be used with standard I/O functions.

Run events

run :: Event a -> IO ()Source

Run the given event once.

runLoop :: Event a -> IO ()Source

Run the given event for ever.

runLoopUntil :: Event (Maybe a) -> IO aSource

Run the given event until the first Just x value, then return x.

Utility

type Source a = Event aSource

type Sink a = Event a -> Event ()Source

newSource :: IO (a -> IO (), Source a)Source

Creates a new source and a computation that writes it.

newSink :: IO (IO (Maybe a), Sink a)Source

Creates a new sink and a computation that reads from it.

notify :: String -> Event a -> Event aSource

Behaves like the original event but writes a given message to the standard output for each value.

showing :: Show a => String -> Event a -> Event aSource

Behaves like the original event but writes its value, prepended by the given message, for each value.

runEvent :: Show a => Event a -> IO ()Source