uni-util-2.3.0.1: Utilities for the uniform workbench

Safe HaskellNone

Util.Sources

Description

We implement the Source type and combinators for it.

Synopsis

Documentation

data Source x d Source

Instances

HasSource (Source x d) x d 

data Client d Source

variableSource :: x -> IO (Source x d, (x -> (x, [d])) -> IO ())Source

data Updater x d Source

applyToUpdater :: Updater x d -> (x -> (x, [d], extra)) -> IO extraSource

map1 :: (x1 -> x2) -> Source x1 d -> Source x2 dSource

map1IO :: (x1 -> IO x2) -> Source x1 d -> Source x2 dSource

map2 :: (d1 -> d2) -> Source x d1 -> Source x d2Source

filter2 :: (d1 -> Maybe d2) -> Source x d1 -> Source x d2Source

filter2IO :: (d1 -> IO (Maybe d2)) -> Source x d1 -> Source x d2Source

foldSource :: (x -> state) -> (state -> d1 -> (state, d2)) -> Source x d1 -> Source (state, x) d2Source

foldSourceIO :: (x1 -> IO (state, x2)) -> (state -> d1 -> IO (state, d2)) -> Source x1 d1 -> Source (state, x2) d2Source

Fold a Source so that it can carry state around.

stepSource :: (x -> d2) -> (d1 -> d2) -> Source x d1 -> Source x d2Source

choose :: Source x1 d1 -> Source x2 d2 -> Source (x1, x2) (Either d1 d2)Source

seqSource :: Source x1 x1 -> (x1 -> Source x2 x2) -> Source x2 x2Source

flattenSource :: Source x [d] -> Source x dSource

A Source combinator which "flattens" lists of updates.

class HasSource hasSource x d | hasSource -> x, hasSource -> d whereSource

Methods

toSource :: hasSource -> Source x dSource

Instances

HasSource (SimpleSource x) x x 
HasSource (SimpleBroadcaster x) x x 
HasKey x key => HasSource (VariableSet x) [x] (VariableSetUpdate x) 
HasSource (Source x d) x d 
HasSource (Broadcaster x d) x d 
HasSource (GeneralBroadcaster x d) x d 
Ord key => HasSource (KeyedChanges key delta) [delta] delta 
Ord key => HasSource (VariableMap key elt) (VariableMapData key elt) (VariableMapUpdate key elt)

Unlike VariableSet, the contents of a variable map are not returned in concrete form but as the abstract data type VariableMapData. We provide functions for querying this.

class HasSimpleSource hasSource x | hasSource -> x whereSource

Methods

toSimpleSource :: hasSource -> SimpleSource xSource

readContents :: HasSource source x d => source -> IO xSource

Get the current contents of the source, but don't specify any other action.

mkHistorySource :: (x -> d) -> Source x d -> Source x (d, d)Source

For each update d, pairs it with its predecessor (given first). For the very first update, a value is given based on the initial x, mapped by the given function.

mkHistorySimpleSource :: x -> SimpleSource x -> SimpleSource (x, x)Source

Like mkHistorySource but for SimpleSource's; the x returns the initial value to compare with.

uniqSimpleSource :: Eq x => SimpleSource x -> SimpleSource xSource

filter out consecutive duplicates

pairSimpleSources :: SimpleSource x1 -> SimpleSource x2 -> SimpleSource (x1, x2)Source

Pair two SimpleSource's. This is probably better than using >>=, since it does not require reregistering with the second SimpleSource

sequenceSimpleSource :: [SimpleSource x] -> SimpleSource [x]Source

Does a similar job to pairSimpleSources, so that the sources run parallel.

change1 :: SimpleSource x -> x -> SimpleSource xSource

replaces the first value of the SimpleSource.

addNewSourceActions :: Source x d -> (x -> IO ()) -> (d -> IO ()) -> SinkID -> ParallelExec -> IO xSource

Run the specified actions for the source, using the given SinkID and in the ParallelExec thread. The x -> IO () action is guaranteed to be performed before any of the d -> IO () actions.

traceSimpleSource :: (a -> String) -> SimpleSource a -> SimpleSource aSource

Outputs information about what comes through the source, turning it into a String with the supplied function. (This is done once for each active client.)

traceSource :: (a -> String) -> (d -> String) -> Source a d -> Source a dSource

Outputs information about what comes through the source, turning it into a String with the supplied function. (This is done once for each active client.)

noLoopSimpleSource :: TSem -> ([String] -> a) -> SimpleSource a -> SimpleSource aSource

Used when we are worried that a SimpleSource recursively constructed by mapIOSeq, >>= and friends may actually try to call itself, and so loop forever. The Strings identify the SimpleSource, and so the [String] is effectively a backtrace of the TSems, revealing what chain of simple sources might have caused the loop.

foldSimpleSourceIO :: (x1 -> IO (state, x2)) -> (state -> x1 -> IO (state, x2)) -> SimpleSource x1 -> SimpleSource x2Source

Fold a Simple Source, so that it carries state. The state is recomputed for each client.