definitive-reactive-1.0: A simple Reactive library.

Safe HaskellNone

Data.Reactive

Contents

Synopsis

Reactive Modules

module IO.Time

Reactive Events

data Event t a Source

An event (a list of time-value pairs of increasing times)

Instances

Functor (Event t) 
Ord t => Applicative (Event t) 
Ord t => Monad (Event t) 
Ord t => Foldable (Event t) 
Ord t => Traversable (Event t) 
Ord t => Unit (Event t) 
(Ord t, Show t, Show a) => Show (Event t a) 
Ord t => Semigroup (Event t a) 
Ord t => Monoid (Event t a) 
Stream (Future t a) (Event t a) 

i'event :: Iso (Event t a) (Event t' b) (EventRep t a) (EventRep t' b)Source

headE :: Event t a -> aSource

data Reactive t a Source

A reactive variable, consisting of an initial value and an Event of changes

Constructors

Reactive a (Event t a) 

Instances

Contructing events

atTimes :: [t] -> Event t ()Source

mkEvent :: [(t, a)] -> Event t aSource

withTime :: Ord t => Event t a -> Event t (Time t, a)Source

times :: Ord t => Event t a -> Event t (Time t)Source

times' :: (Ord t, Monoid t) => Event t a -> Event t tSource

mapFutures :: (Future t a -> Future t' b) -> Event t a -> Event t' bSource

Combining events

(//) :: Ord t => Event t a -> Event t b -> Event t (a, Event t b)Source

The 'splice' operator. Occurs when a occurs.

 by t: a // b = (a,before t: b)

(<|*>) :: Ord t => Reactive t (a -> b) -> Event t a -> Event t bSource

(<*|>) :: Ord t => Event t (a -> b) -> Reactive t a -> Event t bSource

The 'over' operator. Occurs only when a occurs.

 by t: a <|*> (bi,b) = a <*> (minBound,bi):b

Filtering events

groupE :: (Eq a, Ord t) => Event t a -> Event t (Event t a)Source

Group the occurences of an event by equality. Occurs when the first occurence of a group occurs.

mask :: Ord t => Event t Bool -> Event t a -> Event t aSource

Real-world event synchronization

realize :: Event Seconds (IO ()) -> IO ()Source

Sinks an action event into the Real World. Actions are evaluated as closely to their specified time as possible. However, they are all executed in order, even if it means delaying the next action further than its required time. For real-time realization of events, see the realizeRT function

realtime :: Event Seconds (IO ()) -> Event Seconds (IO ())Source

Creates a real-time action event (an event that skips frames as needed) from an ordinary event.

realizeRT :: Event Seconds (IO ()) -> IO ()Source

Sinks a frame event into the real-world, skipping frames if they come too late, thus always performing the frame closest to the current time.

react :: IO a -> (Event Seconds a -> IO (Event Seconds (IO ()))) -> IO ()Source

react2 :: IO a -> IO b -> (Event Seconds a -> Event Seconds b -> IO (Event Seconds (IO ()))) -> IO ()Source

react3 :: IO a -> IO b -> IO c -> (Event Seconds a -> Event Seconds b -> Event Seconds c -> IO (Event Seconds (IO ()))) -> IO ()Source

Future values

data Future t a Source

A Future value (a value with a timestamp)

Instances

Functor (Future t) 
Ord t => Applicative (Future t) 
Ord t => Monad (Future t) 
Foldable (Future t) 
Traversable (Future t) 
Ord t => Unit (Future t) 
Ord t => Bounded (Future t a) 
Ord t => Eq (Future t a) 
Ord t => Ord (Future t a) 
(Eq t, Show t, Show a) => Show (Future t a) 
(Ord t, Semigroup a) => Semigroup (Future t a) 
(Ord t, Monoid a) => Monoid (Future t a) 
Ord t => Orderable (Future t a) 
Stream (Future t a) (Event t a) 

i'future :: Iso (Future t a) (Future t' b) (Time t, a) (Time t', b)Source

l'time :: Lens (Time t) (Time t') (Future t a) (Future t' a)Source

l'value :: Lens a b (Future t a) (Future t b)Source