euphoria-0.6.0.1: Dynamic network FRP with events and continuous values

Safe HaskellNone
LanguageHaskell98

FRP.Euphoria.Update

Description

Signals for incremental updates.

Synopsis

Documentation

data Update a Source

Update a represents a stream of events, just like an Event. Unlike an Event, you cannot observe individual event ocurrences; you first specify a time interval, and you will receive data made by combining together all occurrences in that interval. The type a represents those combined data.

A typical usage is to update external objects in batch. For example, suppose you have (data :: Discrete String) which you want to display on a GUI window. The simplest way to do this would be to use changesD to obtain a event stream of all changes to data, then use fmap to construct a stream of update actions of type Event (IO ()), which will be executed one by one. However, this becomes wasteful if data changes more frequently than you want to update the window, for example you only update the window once in a few network steps. This is because all but the last update operation will be immediately overwritten and have no effect.

A better way here is to create an Update (IO ()) which gives no more than 1 operation when sampled, corresponding to the last change of the underlying data. To do this you first apply updateUseLast to the event stream of changes, then use fmap to construct an Update (IO ()).

Note: there is no way to construct a Signal, Event, or Discrete that depends on an Update. The only way to extract information from an Update is startUpdateNetwork.

Note: in the current implementation, if you use an Update twice, an unbounded amount of computation can be duplicated. Please avoid doing so.

Constructors

forall s . Monoid s => Update (s -> a) (Event s) 

updateUseAll :: Monoid a => Event a -> Update a Source

Convert an Event to an Update by combining the occurrences, i.e. without doing any shortcut.

updateUseLast :: Event a -> Update (Maybe a) Source

Create an Update that ignores all but the latest occurrences.

updateUseAllIO :: Monoid a => Event (IO a) -> Update (IO a) Source

Do the same thing as updateUseAll but use (>>) in place of mappend.

discreteToUpdate :: MonadSignalGen m => Discrete a -> m (Update (Maybe a)) Source

discreteToUpdate d = fmap updateUseLast (preservesD d)

mappendUpdateIO :: Monoid a => Update (IO a) -> Update (IO a) -> Update (IO a) Source

Do the same thing as mappend but use (>>) in place of mappend.

startUpdateNetwork :: SignalGen (Update a) -> IO (IO a, IO ()) Source

Execute a network whose output is represented with an Update. It returns 2 actions, a sampling action and a stepping action. The stepping action executes one cycle of the network, updating its internal state. The sampling action first steps the network, then observes the final Update value. It returns the combined value corresponding to the interval between now and the last time the sampling action was executed.

startUpdateNetworkWithValue :: SignalGen (Update a, Signal b) -> IO (IO (a, b), IO b) Source

Execute a network that has both a continuous output and an accumulated updates.

newtype IOMonoid a Source

Constructors

IOMonoid 

Fields

unIOMonoid :: IO a
 

Instances