Safe Haskell | None |
---|
- module Algebra.Time
- data Event t a
- _event :: Iso (Event t a) (Event t' b) [Future t a] [Future t' b]
- headE :: Event t a -> a
- data Reactive t a = Reactive a (Event t a)
- atTimes :: [t] -> Event t ()
- mkEvent :: [(t, a)] -> Event t a
- withTime :: Ord t => Event t a -> Event t (Time t, a)
- times :: Ord t => Event t a -> Event t (Time t)
- times' :: (Ord t, Monoid t) => Event t a -> Event t t
- mapFutures :: (Future t a -> Future t' b) -> Event t a -> Event t' b
- (//) :: Ord t => Event t a -> Event t b -> Event t (a, Event t b)
- (<|*>) :: Ord t => Reactive t (a -> b) -> Event t a -> Event t b
- (<*|>) :: Ord t => Event t (a -> b) -> Reactive t a -> Event t b
- groupE :: (Eq a, Ord t) => Event t a -> Event t (Event t a)
- mask :: Ord t => Event t Bool -> Event t a -> Event t a
- realize :: Event Seconds (IO ()) -> IO ()
- realtime :: Event Seconds (IO ()) -> Event Seconds (IO ())
- realizeRT :: Event Seconds (IO ()) -> IO ()
- eventMay :: IO (Maybe a) -> IO (Event Seconds a)
- event :: IO a -> IO (Event Seconds a)
- react :: IO a -> (Event Seconds a -> IO (Event Seconds (IO ()))) -> IO ()
- react2 :: IO a -> IO b -> (Event Seconds a -> Event Seconds b -> IO (Event Seconds (IO ()))) -> IO ()
- react3 :: IO a -> IO b -> IO c -> (Event Seconds a -> Event Seconds b -> Event Seconds c -> IO (Event Seconds (IO ()))) -> IO ()
- data Future t a
- _future :: Iso (Future t a) (Future t' b) (Time t, a) (Time t', b)
- _time :: Lens (Time t) (Time t') (Future t a) (Future t' a)
- _value :: Lens a b (Future t a) (Future t b)
- futureIO :: IO a -> IO (Future Seconds a)
Reactive Modules
module Algebra.Time
Reactive Events
An event (a list of time-value pairs of increasing times)
Contructing events
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 => 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.
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.
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
A Future value (a value with a timestamp)
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 => 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 => Orderable (Future t a) | |
(Ord t, Monoid a) => Monoid (Future t a) | |
(Ord t, Semigroup a) => Semigroup (Future t a) |