Safe Haskell | None |
---|---|
Language | Haskell2010 |
Util.Sink
Description
Very primitive concurrency, this implements a sink, which passes messages along until the receiver is no longer interested.
Synopsis
- class HasInvalidate source where
- invalidate :: source -> IO ()
- data SinkID
- newSinkID :: IO SinkID
- data Sink x
- newSink :: (x -> IO ()) -> IO (Sink x)
- newSinkGeneral :: SinkID -> (x -> IO ()) -> IO (Sink x)
- newParallelSink :: (x -> IO ()) -> IO (Sink x)
- newParallelDelayedSink :: IO (Sink x, (x -> IO ()) -> IO ())
- putSink :: Sink x -> x -> IO Bool
- putSinkMultiple :: Sink x -> [x] -> IO Bool
- coMapSink :: (y -> x) -> Sink x -> Sink y
- coMapSink' :: (y -> Maybe x) -> Sink x -> Sink y
- coMapIOSink' :: (y -> IO (Maybe x)) -> Sink x -> Sink y
- class CanAddSinks sinkSource x delta | sinkSource -> x, sinkSource -> delta where
- addNewSink :: sinkSource -> (delta -> IO ()) -> IO (x, Sink delta)
- addNewSinkGeneral :: sinkSource -> (delta -> IO ()) -> SinkID -> IO (x, Sink delta)
- addNewSinkVeryGeneral :: sinkSource -> (delta -> IO ()) -> SinkID -> ParallelExec -> IO (x, Sink delta)
- addNewSinkWithInitial :: sinkSource -> (x -> IO ()) -> (delta -> IO ()) -> SinkID -> ParallelExec -> IO (x, Sink delta)
- addNewQuickSink :: sinkSource -> (delta -> IO ()) -> IO (x, Sink delta)
- addNewQuickSinkGeneral :: sinkSource -> (delta -> IO ()) -> SinkID -> IO (x, Sink delta)
- addOldSink :: sinkSource -> Sink delta -> IO x
- addNewAction :: CanAddSinks sinkSource x delta => sinkSource -> (delta -> IO Bool) -> IO x
- data ParallelExec
- newParallelExec :: IO ParallelExec
- parallelExec :: ParallelExec -> IO () -> IO ()
- parallelExecVSem :: VSem
Documentation
class HasInvalidate source where Source #
The HasInvalidate class represents information sources which can be told "No more, I'm not interested."
Methods
invalidate :: source -> IO () Source #
Instances
HasInvalidate SinkID Source # | |
HasInvalidate (Sink x) Source # | Or we can do so with HasInvalidate |
Instances
HasInvalidate (Sink x) Source # | Or we can do so with HasInvalidate |
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 Bool Source #
Put a value into the sink, returning False if the sink id has been invalidated.
putSinkMultiple :: Sink x -> [x] -> IO Bool Source #
Put a list of values into the sink, returning False if the sink id has been invalidated
coMapSink' :: (y -> Maybe x) -> Sink x -> Sink y Source #
Another version which allows a transformation function to filter certain elements
coMapIOSink' :: (y -> IO (Maybe x)) -> Sink x -> Sink y Source #
A version which allows an IO action, which had better not take too long.
class CanAddSinks sinkSource x delta | sinkSource -> x, sinkSource -> delta where Source #
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.
Minimal complete definition
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 x Source #
Instances
HasSource hasSource x d => CanAddSinks hasSource x d Source # | |
Defined in Util.Sources 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 # |
addNewAction :: CanAddSinks sinkSource x delta => sinkSource -> (delta -> IO Bool) -> IO x Source #
Add an action to a sinkSource which is performed until the action returns False.
data ParallelExec Source #
parallelExec :: ParallelExec -> IO () -> IO () Source #