scc-0.2: Streaming component combinatorsSource codeContentsIndex
Control.Concurrent.SCC.Foundation
Contents
Classes
Types
Flow-control functions
Utility functions
Description
Module Foundation defines the pipe computations and their basic building blocks.
Synopsis
class Monad m => ParallelizableMonad m where
parallelize :: m a -> m b -> m (a, b)
data Pipe context m r
data Source context x
data Sink context x
pipe :: forall context x m r1 r2. Monad m => Producer context m x r1 -> Consumer context m x r2 -> Pipe context m (r1, r2)
pipeD :: forall c x m r1 r2. Monad m => String -> Producer c m x r1 -> Consumer c m x r2 -> Pipe c m (r1, r2)
pipeP :: forall c x m r1 r2. ParallelizableMonad m => Producer c m x r1 -> Consumer c m x r2 -> Pipe c m (r1, r2)
get :: forall context x m r. (Monad m, Typeable x) => Source context x -> Pipe context m (Maybe x)
getSuccess :: forall context x m. (Monad m, Typeable x) => Source context x -> (x -> Pipe context m ()) -> Pipe context m ()
canPut :: forall context x m r. (Monad m, Typeable x) => Sink context x -> Pipe context m Bool
put :: forall context x m r. (Monad m, Typeable x) => Sink context x -> x -> Pipe context m Bool
liftPipe :: forall context m r. Monad m => m r -> Pipe context m r
runPipes :: forall m r. Monad m => (forall context. Pipe context m r) -> m r
cond :: a -> a -> Bool -> a
whenNull :: forall a m. Monad m => m [a] -> [a] -> m [a]
pour :: forall c x m. (Monad m, Typeable x) => Source c x -> Sink c x -> Pipe c m ()
tee :: (Monad m, Typeable x) => Source c x -> Sink c x -> Sink c x -> Pipe c m [x]
getList :: forall x c m. (Monad m, Typeable x) => Source c x -> Pipe c m [x]
putList :: forall x c m. (Monad m, Typeable x) => [x] -> Sink c x -> Pipe c m [x]
consumeAndSuppress :: forall x c m. (Monad m, Typeable x) => Source c x -> Pipe c m ()
Classes
class Monad m => ParallelizableMonad m whereSource
Methods
parallelize :: m a -> m b -> m (a, b)Source
show/hide Instances
Types
data Pipe context m r Source
Pipe represents the type of monadic computations that can be split into co-routining computations using function pipe. The context type parameter delimits the scope of the computation.
show/hide Instances
Monad m => Monad (Pipe context m)
ParallelizableMonad m => ParallelizableMonad (Pipe context m)
data Source context x Source
A Source is the read-only end of a Pipe communication channel.
data Sink context x Source
A Sink is the write-only end of a Pipe communication channel.
Flow-control functions
pipe :: forall context x m r1 r2. Monad m => Producer context m x r1 -> Consumer context m x r2 -> Pipe context m (r1, r2)Source
The pipe function splits the computation into two concurrent parts, producer and consumer. The producer is given a Sink to put values into, and consumer a Source to get those values from. Once producer and consumer both complete, pipe returns their paired results.
pipeD :: forall c x m r1 r2. Monad m => String -> Producer c m x r1 -> Consumer c m x r2 -> Pipe c m (r1, r2)Source
The pipeD function is same as pipe, with an additional description argument.
pipeP :: forall c x m r1 r2. ParallelizableMonad m => Producer c m x r1 -> Consumer c m x r2 -> Pipe c m (r1, r2)Source
The pipeP function is equivalent to pipe, except the producer and consumer are run in parallel if resources allow.
get :: forall context x m r. (Monad m, Typeable x) => Source context x -> Pipe context m (Maybe x)Source
Function get tries to get a value from the given Source argument. The intervening Pipe computations suspend all the way to the pipe function invocation that created the source. The result of get is Nothing iff the argument source is empty.
getSuccessSource
:: forall context x m . (Monad m, Typeable x)
=> Source context x
-> x -> Pipe context m ()Success continuation
-> Pipe context m ()
canPut :: forall context x m r. (Monad m, Typeable x) => Sink context x -> Pipe context m BoolSource
Function canPut checks if the argument sink accepts values, i.e., whether a put operation would succeed on the sink.
put :: forall context x m r. (Monad m, Typeable x) => Sink context x -> x -> Pipe context m BoolSource
Function put tries to put a value into the given sink. The intervening Pipe computations suspend up to the pipe invocation that has created the argument sink. The result of put indicates whether the operation succeded.
liftPipe :: forall context m r. Monad m => m r -> Pipe context m rSource
Function liftPipe lifts a value of the underlying monad type into a Pipe computation.
runPipes :: forall m r. Monad m => (forall context. Pipe context m r) -> m rSource
Function runPipes runs the given computation involving pipes and returns the final result. The context argument ensures that no suspended computation can escape its scope.
Utility functions
cond :: a -> a -> Bool -> aSource
A utility function wrapping if-then-else, useful for handling monadic truth values
whenNull :: forall a m. Monad m => m [a] -> [a] -> m [a]Source
A utility function, useful for handling monadic list values where empty list means success
pour :: forall c x m. (Monad m, Typeable x) => Source c x -> Sink c x -> Pipe c m ()Source
pour copies all data from the source argument into the sink argument, as long as there is anything to copy and the sink accepts it.
tee :: (Monad m, Typeable x) => Source c x -> Sink c x -> Sink c x -> Pipe c m [x]Source
tee is similar to pour except it distributes every input value from the source arguments into both sink1 and sink2.
getList :: forall x c m. (Monad m, Typeable x) => Source c x -> Pipe c m [x]Source
getList returns the list of all values generated by the source.
putList :: forall x c m. (Monad m, Typeable x) => [x] -> Sink c x -> Pipe c m [x]Source
putList puts entire list into its sink argument, as long as the sink accepts it. The remainder that wasn't accepted by the sink is the result value.
consumeAndSuppress :: forall x c m. (Monad m, Typeable x) => Source c x -> Pipe c m ()Source
consumeAndSuppress consumes the entire source ignoring the values it generates.
Produced by Haddock version 2.3.0