SimpleH-1.0: A light, clean and powerful Haskell utility library

Safe HaskellNone

SimpleH.Reactive

Contents

Synopsis

Reactive Modules

Reactive Events

data Event t a Source

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

Instances

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

_event :: Iso (Event t a) (Event t' b) [Future t a] [Future t' b]Source

headE :: Event t a -> aSource

data Reactive t a Source

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 (TimeVal t, a)Source

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

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.

 at 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.

 at 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

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

Sinks an action event into the Real World. Actions are evaluated as closely to their time as possible

Future values

data Future t a Source

A Future value (a value with a timestamp)

Instances

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

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

_time :: Lens (Time t) (Time t') (Future t a) (Future t' a)Source

_value :: Lens a b (Future t a) (Future t b)Source