uni-util-2.2.0.0: Utilities for the uniform workbench

Util.Sink

Description

Very primitive concurrency, this implements a sink, which passes messages along until the receiver is no longer interested.

Synopsis

Documentation

class HasInvalidate source whereSource

The HasInvalidate class represents information sources which can be told "No more, I'm not interested."

Methods

invalidate :: source -> IO ()Source

Instances

HasInvalidate SinkID 
HasInvalidate (Sink x)

Or we can do so with HasInvalidate

data Sink x Source

Instances

HasInvalidate (Sink x)

Or we can do so with HasInvalidate

newSink :: (x -> IO ()) -> IO (Sink x)Source

Creates a new sink with its own SinkID

newSinkGeneral :: SinkID -> (x -> IO ()) -> IO (Sink x)Source

Creates a new sink with a given SinkID. This allows us to invalidate lots of sinks just by invalidating one sinkID.

newParallelSink :: (x -> IO ()) -> IO (Sink x)Source

Creates a new sink which executes actions in a parallelExec thread.

newParallelDelayedSink :: IO (Sink x, (x -> IO ()) -> IO ())Source

Creates a new sink which executes actions in a parallelExec thread, but allow the function generating these actions to be specified later, via the returned command.

putSink :: Sink x -> x -> IO BoolSource

Put a value into the sink, returning False if the sink id has been invalidated.

putSinkMultiple :: Sink x -> [x] -> IO BoolSource

Put a list of values into the sink, returning False if the sink id has been invalidated

coMapSink :: (y -> x) -> Sink x -> Sink ySource

Convert a sink from one type to another

coMapSink' :: (y -> Maybe x) -> Sink x -> Sink ySource

Another version which allows a transformation function to filter certain elements

coMapIOSink' :: (y -> IO (Maybe x)) -> Sink x -> Sink ySource

A version which allows an IO action, which had better not take too long.

class CanAddSinks sinkSource x delta | sinkSource -> x, sinkSource -> delta whereSource

A class for things (in particular Source and SimpleSource) that can output via sinks. Each sink source is supposed to have a unique x, containing a representation of the current value, and delta, containing the (incremental) updates which are put in the sink. Only the addOrdSink function must be defined by instances.

Methods

addNewSink :: sinkSource -> (delta -> IO ()) -> IO (x, Sink delta)Source

addNewSinkGeneral :: sinkSource -> (delta -> IO ()) -> SinkID -> IO (x, Sink delta)Source

addNewSinkVeryGeneral :: sinkSource -> (delta -> IO ()) -> SinkID -> ParallelExec -> IO (x, Sink delta)Source

addNewSinkWithInitial :: sinkSource -> (x -> IO ()) -> (delta -> IO ()) -> SinkID -> ParallelExec -> IO (x, Sink delta)Source

addNewQuickSink :: sinkSource -> (delta -> IO ()) -> IO (x, Sink delta)Source

addNewQuickSinkGeneral :: sinkSource -> (delta -> IO ()) -> SinkID -> IO (x, Sink delta)Source

addOldSink :: sinkSource -> Sink delta -> IO xSource

Instances

HasSource hasSource x d => CanAddSinks hasSource x d 

addNewAction :: CanAddSinks sinkSource x delta => sinkSource -> (delta -> IO Bool) -> IO xSource

Add an action to a sinkSource which is performed until the action returns False.