reactivity-0.3.2.4: An alternate implementation of push-pull FRP.

Safe HaskellTrustworthy
LanguageHaskell98

FRP.Reactivity.AlternateEvent

Contents

Synopsis

Documentation

newtype Event t Source #

Event streams are here presented using the publisher-subscriber model (push-based handling in contrast to the pull-based handling of MeasurementWrapper). Such an event is represented by a subscription function and a callback. The subscription function finishes fast allowing the caller to continue.

The motivation for introducing this data type is that, while the 'Measurement'/'MeasurementWrapper' system is fast, its intensive use of memory cells that need to be garbage collected means that it may not be fast enough for some purposes.

Constructors

Event 

Fields

Instances

Monad Event Source # 

Methods

(>>=) :: Event a -> (a -> Event b) -> Event b #

(>>) :: Event a -> Event b -> Event b #

return :: a -> Event a #

fail :: String -> Event a #

Functor Event Source # 

Methods

fmap :: (a -> b) -> Event a -> Event b #

(<$) :: a -> Event b -> Event a #

Applicative Event Source # 

Methods

pure :: a -> Event a #

(<*>) :: Event (a -> b) -> Event a -> Event b #

(*>) :: Event a -> Event b -> Event b #

(<*) :: Event a -> Event b -> Event a #

MonadIO Event Source # 

Methods

liftIO :: IO a -> Event a #

Alternative Event Source # 

Methods

empty :: Event a #

(<|>) :: Event a -> Event a -> Event a #

some :: Event a -> Event [a] #

many :: Event a -> Event [a] #

MonadPlus Event Source # 

Methods

mzero :: Event a #

mplus :: Event a -> Event a -> Event a #

EventStream Event Source # 

Methods

eventFromList :: [(t, POSIXTime)] -> Event t Source #

scan :: (t -> u -> (t, v)) -> t -> Event u -> Event v Source #

switch :: Event (Event t) -> Event t Source #

withRemainder :: Event t -> Event (t, Event t) Source #

channel :: IO (t -> IO (), Event t) Source #

adjoinTime :: Event t -> Event (t, POSIXTime) Source #

Monoid (Event t) Source # 

Methods

mempty :: Event t #

mappend :: Event t -> Event t -> Event t #

mconcat :: [Event t] -> Event t #

eFromML :: [Measurement t] -> Event t Source #

Extracts an Event from a list of measurements. No attempt has been made to sync up the time order of different calls to eFromML. For this reason, it is not true that "eFromML ml mplus eFromML ml2" equals "eFromML (ml merge ml2)"; please do any necessary syncing before calling eFromML.

runEvent :: Event t -> (t -> POSIXTime -> IO ()) -> IO () Source #

Run an event -- see .Basic module for a way to run with a Windows event loop.

A minimal set of combinators

class (Functor e, MonadPlus e) => EventStream e where Source #

Minimal complete definition

eventFromList, scan, switch, withRemainder, channel, adjoinTime

Methods

eventFromList :: [(t, POSIXTime)] -> e t Source #

Prooty self-explanatory.

scan :: (t -> u -> (t, v)) -> t -> e u -> e v Source #

The "scan" primitive is analogous to "scanl" for lists.

switch :: e (e t) -> e t Source #

A primitive like "switch" is the main way of implementing behaviors that can be switched in and out as required.

withRemainder :: e t -> e (t, e t) Source #

The main use of "withRemainder" is to implement manual aging of inputs. It helps prevent space and time leaks.

channel :: IO (t -> IO (), e t) Source #

Construct a channel in order to receive external events.

adjoinTime :: e t -> e (t, POSIXTime) Source #

Gets the current time along with every occurrence.

filterMaybes :: MonadPlus m => m (Maybe t) -> m t Source #

delay :: EventStream m => POSIXTime -> m t -> m t Source #

delays :: (EventStream e, MonadIO e) => e (t, POSIXTime) -> e t Source #

Optimizer rules

scan' :: (t1 -> Measurement t2 -> (t1, Measurement t)) -> t1 -> [Measurement t2] -> Event t Source #