uni-util-2.3.0.2: Utilities for the uniform workbench

Safe HaskellNone
LanguageHaskell98

Util.Sources

Contents

Description

We implement the Source type and combinators for it.

Synopsis

Documentation

data Source x d Source #

Instances
HasSource (Source x d) x d Source # 
Instance details

Defined in Util.Sources

Methods

toSource :: Source x d -> Source x d Source #

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 extra Source #

attachClient :: Client d -> Source x d -> IO x Source #

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

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

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

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

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

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

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

Fold a Source so that it can carry state around.

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

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

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

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

A Source combinator which "flattens" lists of updates.

newtype SimpleSource x Source #

Constructors

SimpleSource (Source x x) 
Instances
Monad SimpleSource Source # 
Instance details

Defined in Util.Sources

Functor SimpleSource Source # 
Instance details

Defined in Util.Sources

Methods

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

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

Applicative SimpleSource Source # 
Instance details

Defined in Util.Sources

HasMapIO SimpleSource Source # 
Instance details

Defined in Util.Sources

Methods

mapIO :: (a -> IO b) -> SimpleSource a -> SimpleSource b Source #

HasSimpleSource (SimpleSource x) x Source # 
Instance details

Defined in Util.Sources

HasSource (SimpleSource x) x x Source # 
Instance details

Defined in Util.Sources

Methods

toSource :: SimpleSource x -> Source x x Source #

class HasSource hasSource x d | hasSource -> x, hasSource -> d where Source #

Minimal complete definition

toSource

Methods

toSource :: hasSource -> Source x d Source #

Instances
HasSource (SimpleSource x) x x Source # 
Instance details

Defined in Util.Sources

Methods

toSource :: SimpleSource x -> Source x x Source #

HasSource (SimpleBroadcaster x) x x Source # 
Instance details

Defined in Util.Broadcaster

HasKey x key => HasSource (VariableSet x) [x] (VariableSetUpdate x) Source # 
Instance details

Defined in Util.VariableSet

HasSource (Source x d) x d Source # 
Instance details

Defined in Util.Sources

Methods

toSource :: Source x d -> Source x d Source #

HasSource (Broadcaster x d) x d Source # 
Instance details

Defined in Util.Broadcaster

Methods

toSource :: Broadcaster x d -> Source x d Source #

HasSource (GeneralBroadcaster x d) x d Source # 
Instance details

Defined in Util.Broadcaster

Ord key => HasSource (KeyedChanges key delta) [delta] delta Source # 
Instance details

Defined in Util.KeyedChanges

Methods

toSource :: KeyedChanges key delta -> Source [delta] delta Source #

Ord key => HasSource (VariableMap key elt) (VariableMapData key elt) (VariableMapUpdate key elt) Source #

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.

Instance details

Defined in Util.VariableMap

Methods

toSource :: VariableMap key elt -> Source (VariableMapData key elt) (VariableMapUpdate key elt) Source #

class HasSimpleSource hasSource x | hasSource -> x where Source #

Minimal complete definition

toSimpleSource

Methods

toSimpleSource :: hasSource -> SimpleSource x Source #

Instances
HasSimpleSource (SimpleSource x) x Source # 
Instance details

Defined in Util.Sources

HasSimpleSource (SimpleBroadcaster x) x Source # 
Instance details

Defined in Util.Broadcaster

readContents :: HasSource source x d => source -> IO x Source #

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 x Source #

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 x Source #

replaces the first value of the SimpleSource.

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

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 a Source #

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 d Source #

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 a Source #

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 x2 Source #

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

Orphan instances

HasSource hasSource x d => CanAddSinks hasSource x d Source # 
Instance details

Methods

addNewSink :: hasSource -> (d -> IO ()) -> IO (x, Sink d) Source #

addNewSinkGeneral :: hasSource -> (d -> IO ()) -> SinkID -> IO (x, Sink d) Source #

addNewSinkVeryGeneral :: hasSource -> (d -> IO ()) -> SinkID -> ParallelExec -> IO (x, Sink d) Source #

addNewSinkWithInitial :: hasSource -> (x -> IO ()) -> (d -> IO ()) -> SinkID -> ParallelExec -> IO (x, Sink d) Source #

addNewQuickSink :: hasSource -> (d -> IO ()) -> IO (x, Sink d) Source #

addNewQuickSinkGeneral :: hasSource -> (d -> IO ()) -> SinkID -> IO (x, Sink d) Source #

addOldSink :: hasSource -> Sink d -> IO x Source #