Control.Concurrent.SCC.Sequential
Contents
- Sink and Source types
- Sink and Source constructors
- Operations on sinks and sources
- Component types
- Component constructors
- Coercible class
- Splitter isomorphism
- I/O components
- Generic components
- Character stream components
- Consumer, producer, and transducer combinators
- Splitter combinators
- Flow-control combinators
- Section-based combinators
- Parser support
- Parsing XML
- XML splitters
Description
This module exports all of the SCC libraries. The exported combinators run their components by sequentially interleaving them.
- data Sink m a x
- data Source m a x
- type SinkFunctor a x = EitherFunctor a (Request [x] [x])
- type SourceFunctor a x = EitherFunctor a (Request (Ticker x) ([x], Either x (Ticker x)))
- class (Functor a, Functor d) => AncestorFunctor a d
- pipe :: forall m a a1 a2 x r1 r2. (Monad m, Functor a, a1 ~ SinkFunctor a x, a2 ~ SourceFunctor a x) => (Sink m a1 x -> Coroutine a1 m r1) -> (Source m a2 x -> Coroutine a2 m r2) -> Coroutine a m (r1, r2)
- pipeP :: forall m a a1 a2 x r1 r2. (MonadParallel m, Functor a, a1 ~ SinkFunctor a x, a2 ~ SourceFunctor a x) => (Sink m a1 x -> Coroutine a1 m r1) -> (Source m a2 x -> Coroutine a2 m r2) -> Coroutine a m (r1, r2)
- pipeG :: forall m a a1 a2 x r1 r2. (Monad m, Functor a, a1 ~ SinkFunctor a x, a2 ~ SourceFunctor a x) => PairBinder m -> (Sink m a1 x -> Coroutine a1 m r1) -> (Source m a2 x -> Coroutine a2 m r2) -> Coroutine a m (r1, r2)
- nullSink :: forall m a x. Monad m => Sink m a x
- nullSource :: forall m a x. Monad m => Source m a x
- get :: forall m a d x. (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m (Maybe x)
- getWith :: forall m a d x. (Monad m, AncestorFunctor a d) => (x -> Coroutine d m ()) -> Source m a x -> Coroutine d m ()
- peek :: forall m a d x. (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m (Maybe x)
- put :: forall m a d x. (Monad m, AncestorFunctor a d) => Sink m a x -> x -> Coroutine d m ()
- tryPut :: forall m a d x. (Monad m, AncestorFunctor a d) => Sink m a x -> x -> Coroutine d m Bool
- liftSink :: forall m a d x. (Monad m, AncestorFunctor a d) => Sink m a x -> Sink m d x
- liftSource :: forall m a d x. (Monad m, AncestorFunctor a d) => Source m a x -> Source m d x
- pour :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => Source m a1 x -> Sink m a2 x -> Coroutine d m ()
- tee :: forall m a1 a2 a3 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d) => Source m a1 x -> Sink m a2 x -> Sink m a3 x -> Coroutine d m ()
- teeSink :: forall m a1 a2 a3 x. (Monad m, AncestorFunctor a1 a3, AncestorFunctor a2 a3) => Sink m a1 x -> Sink m a2 x -> Sink m a3 x
- teeSource :: forall m a1 a2 a3 x. (Monad m, AncestorFunctor a1 a3, AncestorFunctor a2 a3) => Sink m a1 x -> Source m a2 x -> Source m a3 x
- getList :: forall m a d x. (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m [x]
- putList :: forall m a d x. (Monad m, AncestorFunctor a d) => [x] -> Sink m a x -> Coroutine d m [x]
- putQueue :: forall m a d x. (Monad m, AncestorFunctor a d) => Seq x -> Sink m a x -> Coroutine d m [x]
- getTicked :: forall m a d x. (Monad m, AncestorFunctor a d) => Ticker x -> Source m a x -> Coroutine d m [x]
- getWhile :: forall m a d x. (Monad m, AncestorFunctor a d) => (x -> Bool) -> Source m a x -> Coroutine d m [x]
- getUntil :: forall m a d x. (Monad m, AncestorFunctor a d) => (x -> Bool) -> Source m a x -> Coroutine d m ([x], Maybe x)
- pourTicked :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => Ticker x -> Source m a1 x -> Sink m a2 x -> Coroutine d m ()
- pourWhile :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m ()
- pourUntil :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m (Maybe x)
- mapSink :: forall m a x y. Monad m => (x -> y) -> Sink m a y -> Sink m a x
- mapStream :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()
- mapMaybeStream :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Maybe y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()
- concatMapStream :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> [y]) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()
- mapStreamChunks :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => ([x] -> [y]) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()
- foldStream :: forall m a d x acc. (Monad m, AncestorFunctor a d) => (acc -> x -> acc) -> acc -> Source m a x -> Coroutine d m acc
- mapAccumStream :: forall m a1 a2 d x y acc. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (acc -> x -> (acc, y)) -> acc -> Source m a1 x -> Sink m a2 y -> Coroutine d m acc
- concatMapAccumStream :: forall m a1 a2 d x y acc. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (acc -> x -> (acc, [y])) -> acc -> Source m a1 x -> Sink m a2 y -> Coroutine d m acc
- partitionStream :: forall m a1 a2 a3 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Sink m a3 x -> Coroutine d m ()
- mapMStream :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Coroutine d m y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()
- mapMStream_ :: forall m a d x. (Monad m, AncestorFunctor a d) => (x -> Coroutine d m ()) -> Source m a x -> Coroutine d m ()
- mapMStreamChunks_ :: forall m a d x. (Monad m, AncestorFunctor a d) => ([x] -> Coroutine d m ()) -> Source m a x -> Coroutine d m ()
- filterMStream :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Coroutine d m Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m ()
- foldMStream :: forall m a d x acc. (Monad m, AncestorFunctor a d) => (acc -> x -> Coroutine d m acc) -> acc -> Source m a x -> Coroutine d m acc
- foldMStream_ :: forall m a d x acc. (Monad m, AncestorFunctor a d) => (acc -> x -> Coroutine d m acc) -> acc -> Source m a x -> Coroutine d m ()
- unfoldMStream :: forall m a d x acc. (Monad m, AncestorFunctor a d) => (acc -> Coroutine d m (Maybe (x, acc))) -> acc -> Sink m a x -> Coroutine d m acc
- unmapMStream_ :: forall m a d x. (Monad m, AncestorFunctor a d) => Coroutine d m (Maybe x) -> Sink m a x -> Coroutine d m ()
- unmapMStreamChunks_ :: forall m a d x. (Monad m, AncestorFunctor a d) => Coroutine d m [x] -> Sink m a x -> Coroutine d m ()
- zipWithMStream :: forall m a1 a2 a3 d x y z. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d) => (x -> y -> Coroutine d m z) -> Source m a1 x -> Source m a2 y -> Sink m a3 z -> Coroutine d m ()
- parZipWithMStream :: forall m a1 a2 a3 d x y z. (MonadParallel m, AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d) => (x -> y -> Coroutine d m z) -> Source m a1 x -> Source m a2 y -> Sink m a3 z -> Coroutine d m ()
- newtype Performer m r = Performer {
- perform :: m r
- type OpenConsumer m a d x r = AncestorFunctor a d => Source m a x -> Coroutine d m r
- newtype Consumer m x r = Consumer {
- consume :: forall a d. OpenConsumer m a d x r
- type OpenProducer m a d x r = AncestorFunctor a d => Sink m a x -> Coroutine d m r
- newtype Producer m x r = Producer {
- produce :: forall a d. OpenProducer m a d x r
- type OpenTransducer m a1 a2 d x y r = (AncestorFunctor a1 d, AncestorFunctor a2 d) => Source m a1 x -> Sink m a2 y -> Coroutine d m r
- newtype Transducer m x y = Transducer {
- transduce :: forall a1 a2 d. OpenTransducer m a1 a2 d x y ()
- type OpenSplitter m a1 a2 a3 a4 d x b r = (AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d, AncestorFunctor a4 d) => Source m a1 x -> Sink m a2 x -> Sink m a3 x -> Sink m a4 b -> Coroutine d m r
- newtype Splitter m x b = Splitter {
- split :: forall a1 a2 a3 a4 d. OpenSplitter m a1 a2 a3 a4 d x b ()
- data Boundary y
- data Markup y x
- type Parser m x b = Transducer m x (Markup b x)
- class Branching c m x r | c -> m x where
- combineBranches :: (forall d. PairBinder m -> (forall a d'. AncestorFunctor d d' => OpenConsumer m a d' x r) -> (forall a d'. AncestorFunctor d d' => OpenConsumer m a d' x r) -> forall a. OpenConsumer m a d x r) -> PairBinder m -> c -> c -> c
- isolateConsumer :: forall m x r. Monad m => (forall d. Functor d => Source m d x -> Coroutine d m r) -> Consumer m x r
- isolateProducer :: forall m x r. Monad m => (forall d. Functor d => Sink m d x -> Coroutine d m r) -> Producer m x r
- isolateTransducer :: forall m x y. Monad m => (forall d. Functor d => Source m d x -> Sink m d y -> Coroutine d m ()) -> Transducer m x y
- isolateSplitter :: forall m x b. Monad m => (forall d. Functor d => Source m d x -> Sink m d x -> Sink m d x -> Sink m d b -> Coroutine d m ()) -> Splitter m x b
- oneToOneTransducer :: Monad m => (x -> y) -> Transducer m x y
- statelessTransducer :: Monad m => (x -> [y]) -> Transducer m x y
- statefulTransducer :: Monad m => (state -> x -> (state, [y])) -> state -> Transducer m x y
- statelessSplitter :: Monad m => (x -> Bool) -> Splitter m x b
- statefulSplitter :: Monad m => (state -> x -> (state, Bool)) -> state -> Splitter m x ()
- class Coercible x y where
- coerce :: Monad m => Transducer m x y
- adaptConsumer :: Monad m => Consumer m y r -> Consumer m x r
- adaptProducer :: Monad m => Producer m x r -> Producer m y r
- adaptSplitter :: forall m x y b. (Monad m, Coercible x y, Coercible y x) => Splitter m x b -> Splitter m y b
- fromFile :: String -> Producer IO Char ()
- fromHandle :: Handle -> Producer IO Char ()
- fromStdIn :: Producer IO Char ()
- fromBinaryHandle :: Handle -> Int -> Producer IO ByteString ()
- appendFile :: String -> Consumer IO Char ()
- toFile :: String -> Consumer IO Char ()
- toHandle :: Handle -> Consumer IO Char ()
- toStdOut :: Consumer IO Char ()
- toBinaryHandle :: Handle -> Consumer IO ByteString ()
- fromList :: forall m x. Monad m => [x] -> Producer m x ()
- suppress :: forall m x y. Monad m => Consumer m x ()
- erroneous :: forall m x. Monad m => String -> Consumer m x ()
- toList :: forall m x. Monad m => Consumer m x [x]
- parse :: forall m x y. Monad m => Transducer m x (Markup y x)
- unparse :: forall m x b. Monad m => Transducer m (Markup b x) x
- parseSubstring :: forall m x y. (Monad m, Eq x) => [x] -> Parser m x OccurenceTag
- data OccurenceTag
- count :: forall m x. Monad m => Transducer m x Integer
- toString :: forall m x. (Monad m, Show x) => Transducer m x String
- group :: forall m x. Monad m => Transducer m x [x]
- concatenate :: forall m x. Monad m => Transducer m [x] x
- concatSeparate :: forall m x. Monad m => [x] -> Transducer m [x] x
- everything :: forall m x. Monad m => Splitter m x ()
- nothing :: forall m x. Monad m => Splitter m x ()
- marked :: forall m x y. (Monad m, Eq y) => Splitter m (Markup y x) ()
- markedContent :: forall m x y. (Monad m, Eq y) => Splitter m (Markup y x) ()
- markedWith :: forall m x y. (Monad m, Eq y) => (y -> Bool) -> Splitter m (Markup y x) ()
- contentMarkedWith :: forall m x y. (Monad m, Eq y) => (y -> Bool) -> Splitter m (Markup y x) ()
- one :: forall m x. Monad m => Splitter m x ()
- substring :: forall m x. (Monad m, Eq x) => [x] -> Splitter m x ()
- lowercase :: forall m. Monad m => Transducer m Char Char
- uppercase :: forall m. Monad m => Transducer m Char Char
- whitespace :: forall m. Monad m => Splitter m Char ()
- letters :: forall m. Monad m => Splitter m Char ()
- digits :: forall m. Monad m => Splitter m Char ()
- line :: forall m. Monad m => Splitter m Char ()
- nonEmptyLine :: forall m. Monad m => Splitter m Char ()
- consumeBy :: forall m x y r. Monad m => Consumer m x r -> Transducer m x y
- prepend :: forall m x r. Monad m => Producer m x r -> Transducer m x x
- append :: forall m x r. Monad m => Producer m x r -> Transducer m x x
- substitute :: forall m x y r. Monad m => Producer m y r -> Transducer m x y
- class PipeableComponentPair m w c1 c2 c3 | c1 c2 -> c3, c1 c3 -> c2, c2 c3 -> c2, c1 -> m w, c2 -> m w, c3 -> m
- (>->) :: (Monad m, PipeableComponentPair m w c1 c2 c3) => c1 -> c2 -> c3
- class (Monad m, CompatibleSignature c1 t1 m x y, CompatibleSignature c2 t2 m x y, CompatibleSignature c3 t3 m x y) => JoinableComponentPair t1 t2 t3 m x y c1 c2 c3 | c1 c2 -> c3, c1 -> t1 m, c2 -> t2 m, c3 -> t3 m x y, t1 m x y -> c1, t2 m x y -> c2, t3 m x y -> c3 where
- sequence :: c1 -> c2 -> c3
- join :: (Monad m, JoinableComponentPair t1 t2 t3 m x y c1 c2 c3) => c1 -> c2 -> c3
- sNot :: forall m x b. Monad m => Splitter m x b -> Splitter m x b
- (>&) :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (b1, b2)
- (>|) :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (Either b1 b2)
- (&&) :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (b1, b2)
- (||) :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (Either b1 b2)
- ifs :: (Monad m, Branching c m x ()) => Splitter m x b -> c -> c -> c
- wherever :: Monad m => Transducer m x x -> Splitter m x b -> Transducer m x x
- unless :: Monad m => Transducer m x x -> Splitter m x b -> Transducer m x x
- select :: forall m x b. Monad m => Splitter m x b -> Transducer m x x
- while :: Monad m => Transducer m x x -> Splitter m x b -> Transducer m x x
- nestedIn :: Monad m => Splitter m x b -> Splitter m x b -> Splitter m x b
- foreach :: (Monad m, Branching c m x ()) => Splitter m x b -> c -> c -> c
- having :: (Monad m, Coercible x y) => Splitter m x b1 -> Splitter m y b2 -> Splitter m x b1
- havingOnly :: (Monad m, Coercible x y) => Splitter m x b1 -> Splitter m y b2 -> Splitter m x b1
- followedBy :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (b1, b2)
- even :: forall m x b. Monad m => Splitter m x b -> Splitter m x b
- first :: forall m x b. Monad m => Splitter m x b -> Splitter m x b
- uptoFirst :: forall m x b. Monad m => Splitter m x b -> Splitter m x b
- prefix :: forall m x b. Monad m => Splitter m x b -> Splitter m x b
- last :: forall m x b. Monad m => Splitter m x b -> Splitter m x b
- lastAndAfter :: forall m x b. Monad m => Splitter m x b -> Splitter m x b
- suffix :: forall m x b. Monad m => Splitter m x b -> Splitter m x b
- startOf :: forall m x b. Monad m => Splitter m x b -> Splitter m x (Maybe b)
- endOf :: forall m x b. Monad m => Splitter m x b -> Splitter m x (Maybe b)
- (...) :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x b1
- splitterToMarker :: forall m x b. Monad m => Splitter m x b -> Transducer m x (Either (x, Bool) b)
- parseRegions :: forall m x b. Monad m => Splitter m x b -> Parser m x b
- parseNestedRegions :: forall m x b. Monad m => Splitter m x (Boundary b) -> Parser m x b
- parseEachNestedRegion :: Monad m => Splitter m x (Boundary b) -> Transducer m x y -> Transducer m x (Markup b y)
- xmlTokens :: Monad m => Splitter m Char (Boundary XMLToken)
- parseXMLTokens :: MonadParallel m => Transducer m Char (Markup XMLToken Text)
- expandXMLEntity :: String -> String
- data XMLToken
- xmlElement :: Monad m => Splitter m (Markup XMLToken Text) ()
- xmlElementContent :: Monad m => Splitter m (Markup XMLToken Text) ()
- xmlElementName :: Monad m => Splitter m (Markup XMLToken Text) ()
- xmlAttribute :: Monad m => Splitter m (Markup XMLToken Text) ()
- xmlAttributeName :: Monad m => Splitter m (Markup XMLToken Text) ()
- xmlAttributeValue :: Monad m => Splitter m (Markup XMLToken Text) ()
- xmlElementHavingTagWith :: forall m b. MonadParallel m => Splitter m (Markup XMLToken Text) b -> Splitter m (Markup XMLToken Text) b
Sink and Source types
type SinkFunctor a x = EitherFunctor a (Request [x] [x])Source
type SourceFunctor a x = EitherFunctor a (Request (Ticker x) ([x], Either x (Ticker x)))Source
class (Functor a, Functor d) => AncestorFunctor a d
Class of functors that can be lifted.
Instances
| (d' ~ Parent d, Functor a, ChildFunctor d, AncestorFunctor a d') => AncestorFunctor a d | |
| Functor a => AncestorFunctor a a |
Sink and Source constructors
pipe :: forall m a a1 a2 x r1 r2. (Monad m, Functor a, a1 ~ SinkFunctor a x, a2 ~ SourceFunctor a x) => (Sink m a1 x -> Coroutine a1 m r1) -> (Source m a2 x -> Coroutine a2 m r2) -> Coroutine a m (r1, r2)Source
pipeP :: forall m a a1 a2 x r1 r2. (MonadParallel m, Functor a, a1 ~ SinkFunctor a x, a2 ~ SourceFunctor a x) => (Sink m a1 x -> Coroutine a1 m r1) -> (Source m a2 x -> Coroutine a2 m r2) -> Coroutine a m (r1, r2)Source
pipeG :: forall m a a1 a2 x r1 r2. (Monad m, Functor a, a1 ~ SinkFunctor a x, a2 ~ SourceFunctor a x) => PairBinder m -> (Sink m a1 x -> Coroutine a1 m r1) -> (Source m a2 x -> Coroutine a2 m r2) -> Coroutine a m (r1, r2)Source
A generic version of pipe. The first argument is used to combine two computation steps.
nullSink :: forall m a x. Monad m => Sink m a xSource
A disconnected sink that ignores all values put into it.
nullSource :: forall m a x. Monad m => Source m a xSource
An empty source whose get always returns Nothing.
Operations on sinks and sources
Singleton operations
get :: forall m a d x. (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m (Maybe x)Source
getWith :: forall m a d x. (Monad m, AncestorFunctor a d) => (x -> Coroutine d m ()) -> Source m a x -> Coroutine d m ()Source
Invokes its first argument with the value it gets from the source, if there is any to get.
peek :: forall m a d x. (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m (Maybe x)Source
tryPut :: forall m a d x. (Monad m, AncestorFunctor a d) => Sink m a x -> x -> Coroutine d m BoolSource
Like put, but returns a Bool that determines if the sink is still active.
Lifting functions
liftSink :: forall m a d x. (Monad m, AncestorFunctor a d) => Sink m a x -> Sink m d xSource
Converts a Sink on the ancestor functor a into a sink on the descendant functor d.
liftSource :: forall m a d x. (Monad m, AncestorFunctor a d) => Source m a x -> Source m d xSource
Converts a Source on the ancestor functor a into a source on the descendant functor d.
Bulk operations
Fetching and moving data
pour :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => Source m a1 x -> Sink m a2 x -> Coroutine d m ()Source
Copies all data from the source argument into the sink argument.
tee :: forall m a1 a2 a3 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d) => Source m a1 x -> Sink m a2 x -> Sink m a3 x -> Coroutine d m ()Source
teeSink :: forall m a1 a2 a3 x. (Monad m, AncestorFunctor a1 a3, AncestorFunctor a2 a3) => Sink m a1 x -> Sink m a2 x -> Sink m a3 xSource
teeSource :: forall m a1 a2 a3 x. (Monad m, AncestorFunctor a1 a3, AncestorFunctor a2 a3) => Sink m a1 x -> Source m a2 x -> Source m a3 xSource
getList :: forall m a d x. (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m [x]Source
getList returns the list of all values generated by the source.
putList :: forall m a d x. (Monad m, AncestorFunctor a d) => [x] -> Sink m a x -> Coroutine d m [x]Source
putList puts an entire list into its sink argument. If the coroutine fed by the sink dies, the remainder of
the argument list is returned.
putQueue :: forall m a d x. (Monad m, AncestorFunctor a d) => Seq x -> Sink m a x -> Coroutine d m [x]Source
getTicked :: forall m a d x. (Monad m, AncestorFunctor a d) => Ticker x -> Source m a x -> Coroutine d m [x]Source
Consumes values from the source as long as the ticker accepts them.
getWhile :: forall m a d x. (Monad m, AncestorFunctor a d) => (x -> Bool) -> Source m a x -> Coroutine d m [x]Source
Consumes values from the source as long as each satisfies the predicate, then returns their list.
getUntil :: forall m a d x. (Monad m, AncestorFunctor a d) => (x -> Bool) -> Source m a x -> Coroutine d m ([x], Maybe x)Source
Consumes values from the source until one of them satisfies the predicate or the source is emptied, then returns the pair of the list of preceding values and maybe the one value that satisfied the predicate. The latter is not consumed.
pourTicked :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => Ticker x -> Source m a1 x -> Sink m a2 x -> Coroutine d m ()Source
Like pour, copies data from the source to the sink, but only as long as it satisfies the predicate.
pourWhile :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m ()Source
Like pour, copies data from the source to the sink, but only as long as it satisfies the predicate.
pourUntil :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m (Maybe x)Source
Like pour, copies data from the source to the sink, but only until one value satisfies the predicate. That
value is returned rather than copied.
Stream transformations
mapStream :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()Source
mapMaybeStream :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Maybe y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()Source
mapMaybeStream is to mapStream like mapMaybe is to map.
concatMapStream :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> [y]) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()Source
concatMapStream is to mapStream like concatMap is to map.
mapStreamChunks :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => ([x] -> [y]) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()Source
Like mapStream except it runs the argument function on whole chunks read from the input.
foldStream :: forall m a d x acc. (Monad m, AncestorFunctor a d) => (acc -> x -> acc) -> acc -> Source m a x -> Coroutine d m accSource
mapAccumStream :: forall m a1 a2 d x y acc. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (acc -> x -> (acc, y)) -> acc -> Source m a1 x -> Sink m a2 y -> Coroutine d m accSource
mapAccumStream is similar to mapAccumL except it reads the values from a Source instead of a list
and writes the mapped values into a Sink instead of returning another list.
concatMapAccumStream :: forall m a1 a2 d x y acc. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (acc -> x -> (acc, [y])) -> acc -> Source m a1 x -> Sink m a2 y -> Coroutine d m accSource
concatMapAccumStream is a love child of concatMapStream and mapAccumStream: it threads the accumulator like
the latter, but its argument function returns not a single value, but a list of values to write into the sink.
partitionStream :: forall m a1 a2 a3 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Sink m a3 x -> Coroutine d m ()Source
Monadic stream transformations
mapMStream :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Coroutine d m y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()Source
mapMStream is similar to mapM. It draws the values from a Source instead of a list, writes the
mapped values to a Sink, and returns a Coroutine.
mapMStream_ :: forall m a d x. (Monad m, AncestorFunctor a d) => (x -> Coroutine d m ()) -> Source m a x -> Coroutine d m ()Source
mapMStream_ is similar to mapM_ except it draws the values from a Source instead of a list and
works with Coroutine instead of an arbitrary monad.
mapMStreamChunks_ :: forall m a d x. (Monad m, AncestorFunctor a d) => ([x] -> Coroutine d m ()) -> Source m a x -> Coroutine d m ()Source
Like mapMStream_ except it runs the argument function on whole chunks read from the input.
filterMStream :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Coroutine d m Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m ()Source
foldMStream :: forall m a d x acc. (Monad m, AncestorFunctor a d) => (acc -> x -> Coroutine d m acc) -> acc -> Source m a x -> Coroutine d m accSource
foldMStream is similar to foldM except it draws the values from a Source instead of a list and
works with Coroutine instead of an arbitrary monad.
foldMStream_ :: forall m a d x acc. (Monad m, AncestorFunctor a d) => (acc -> x -> Coroutine d m acc) -> acc -> Source m a x -> Coroutine d m ()Source
A variant of foldMStream that discards the final result value.
unfoldMStream :: forall m a d x acc. (Monad m, AncestorFunctor a d) => (acc -> Coroutine d m (Maybe (x, acc))) -> acc -> Sink m a x -> Coroutine d m accSource
unfoldMStream is a version of unfoldr that writes the generated values into a Sink instead of
returning a list.
unmapMStream_ :: forall m a d x. (Monad m, AncestorFunctor a d) => Coroutine d m (Maybe x) -> Sink m a x -> Coroutine d m ()Source
unmapMStream_ is opposite of mapMStream_; it takes a Sink instead of a Source argument and writes the
generated values into it.
unmapMStreamChunks_ :: forall m a d x. (Monad m, AncestorFunctor a d) => Coroutine d m [x] -> Sink m a x -> Coroutine d m ()Source
Like unmapMStream_ but writing whole chunks of generated data into the argument sink.
zipWithMStream :: forall m a1 a2 a3 d x y z. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d) => (x -> y -> Coroutine d m z) -> Source m a1 x -> Source m a2 y -> Sink m a3 z -> Coroutine d m ()Source
zipWithMStream is similar to zipWithM except it draws the values from two Source arguments
instead of two lists, sends the results into a Sink, and works with Coroutine instead of an arbitrary monad.
parZipWithMStream :: forall m a1 a2 a3 d x y z. (MonadParallel m, AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d) => (x -> y -> Coroutine d m z) -> Source m a1 x -> Source m a2 y -> Sink m a3 z -> Coroutine d m ()Source
parZipWithMStream is equivalent to zipWithMStream, but it consumes the two sources in parallel.
Component types
A coroutine that has no inputs nor outputs - and therefore may not suspend at all, which means it's not really a coroutine.
Instances
| Monad m => PipeableComponentPair m x (Producer m x ()) (Consumer m x ()) (Performer m ()) | |
| Monad m => JoinableComponentPair TransducerType (PerformerType r) TransducerType m [x] [y] (Transducer m x y) (Performer m r) (Transducer m x y) | |
| Monad m => JoinableComponentPair (PerformerType r) TransducerType TransducerType m [x] [y] (Performer m r) (Transducer m x y) (Transducer m x y) | |
| Monad m => JoinableComponentPair (PerformerType r1) (PerformerType r2) (PerformerType r2) m () () (Performer m r1) (Performer m r2) (Performer m r2) | |
| Monad m => JoinableComponentPair (PerformerType r1) (ProducerType r2) (ProducerType r2) m () [x] (Performer m r1) (Producer m x r2) (Producer m x r2) | |
| Monad m => JoinableComponentPair (ProducerType r1) (PerformerType r2) (ProducerType r2) m () [x] (Producer m x r1) (Performer m r2) (Producer m x r2) | |
| Monad m => JoinableComponentPair (PerformerType r1) (ConsumerType r2) (ConsumerType r2) m [x] () (Performer m r1) (Consumer m x r2) (Consumer m x r2) | |
| Monad m => JoinableComponentPair (ConsumerType r1) (PerformerType r2) (ConsumerType r2) m [x] () (Consumer m x r1) (Performer m r2) (Consumer m x r2) | |
| (AnyListOrUnit x, AnyListOrUnit y) => CompatibleSignature (Performer m r) (PerformerType r) m x y | |
| (AnyListOrUnit x, AnyListOrUnit y) => CompatibleSignature (Performer m r) (PerformerType r) m x y |
type OpenConsumer m a d x r = AncestorFunctor a d => Source m a x -> Coroutine d m rSource
A coroutine that consumes values from a Source.
Constructors
| Consumer | |
Fields
| |
Instances
| Monad m => PipeableComponentPair m x (Producer m x ()) (Consumer m x ()) (Performer m ()) | |
| Monad m => PipeableComponentPair m y (Transducer m x y) (Consumer m y r) (Consumer m x r) | |
| Monad m => JoinableComponentPair TransducerType (ConsumerType ()) TransducerType m [x] [y] (Transducer m x y) (Consumer m x ()) (Transducer m x y) | |
| Monad m => JoinableComponentPair (ConsumerType ()) TransducerType TransducerType m [x] [y] (Consumer m x ()) (Transducer m x y) (Transducer m x y) | |
| Monad m => JoinableComponentPair (ProducerType ()) (ConsumerType ()) TransducerType m [x] [y] (Producer m y ()) (Consumer m x ()) (Transducer m x y) | |
| Monad m => JoinableComponentPair (ConsumerType ()) (ProducerType ()) TransducerType m [x] [y] (Consumer m x ()) (Producer m y ()) (Transducer m x y) | |
| Monad m => JoinableComponentPair (PerformerType r1) (ConsumerType r2) (ConsumerType r2) m [x] () (Performer m r1) (Consumer m x r2) (Consumer m x r2) | |
| Monad m => JoinableComponentPair (ConsumerType r1) (PerformerType r2) (ConsumerType r2) m [x] () (Consumer m x r1) (Performer m r2) (Consumer m x r2) | |
| Monad m => JoinableComponentPair (ConsumerType ()) (ConsumerType ()) (ConsumerType ()) m [x] () (Consumer m x ()) (Consumer m x ()) (Consumer m x ()) | |
| Monad m => Branching (Consumer m x r) m x r | |
| AnyListOrUnit y => CompatibleSignature (Consumer m x r) (ConsumerType r) m [x] y | |
| AnyListOrUnit y => CompatibleSignature (Consumer m x r) (ConsumerType r) m [x] y |
type OpenProducer m a d x r = AncestorFunctor a d => Sink m a x -> Coroutine d m rSource
A coroutine that produces values and puts them into a Sink.
Constructors
| Producer | |
Fields
| |
Instances
| Monad m => PipeableComponentPair m x (Producer m x ()) (Consumer m x ()) (Performer m ()) | |
| Monad m => PipeableComponentPair m x (Producer m x r) (Transducer m x y) (Producer m y r) | |
| Monad m => JoinableComponentPair TransducerType (ProducerType ()) TransducerType m [x] [y] (Transducer m x y) (Producer m y ()) (Transducer m x y) | |
| Monad m => JoinableComponentPair (ProducerType ()) TransducerType TransducerType m [x] [y] (Producer m y ()) (Transducer m x y) (Transducer m x y) | |
| Monad m => JoinableComponentPair (ProducerType ()) (ConsumerType ()) TransducerType m [x] [y] (Producer m y ()) (Consumer m x ()) (Transducer m x y) | |
| Monad m => JoinableComponentPair (ConsumerType ()) (ProducerType ()) TransducerType m [x] [y] (Consumer m x ()) (Producer m y ()) (Transducer m x y) | |
| Monad m => JoinableComponentPair (PerformerType r1) (ProducerType r2) (ProducerType r2) m () [x] (Performer m r1) (Producer m x r2) (Producer m x r2) | |
| Monad m => JoinableComponentPair (ProducerType r1) (PerformerType r2) (ProducerType r2) m () [x] (Producer m x r1) (Performer m r2) (Producer m x r2) | |
| Monad m => JoinableComponentPair (ProducerType r1) (ProducerType r2) (ProducerType r2) m () [x] (Producer m x r1) (Producer m x r2) (Producer m x r2) | |
| AnyListOrUnit y => CompatibleSignature (Producer m x r) (ProducerType r) m y [x] | |
| AnyListOrUnit y => CompatibleSignature (Producer m x r) (ProducerType r) m y [x] |
type OpenTransducer m a1 a2 d x y r = (AncestorFunctor a1 d, AncestorFunctor a2 d) => Source m a1 x -> Sink m a2 y -> Coroutine d m rSource
newtype Transducer m x y Source
The Transducer type represents coroutines that transform a data stream. Execution of transduce must continue
consuming the given Source and feeding the Sink as
long as there is any data in the source.
Constructors
| Transducer | |
Fields
| |
Instances
| Monad m => JoinableComponentPair TransducerType TransducerType TransducerType m [x] [y] (Transducer m x y) (Transducer m x y) (Transducer m x y) | |
| Monad m => PipeableComponentPair m y (Transducer m x y) (Transducer m y z) (Transducer m x z) | |
| Monad m => PipeableComponentPair m x (Producer m x r) (Transducer m x y) (Producer m y r) | |
| Monad m => PipeableComponentPair m y (Transducer m x y) (Consumer m y r) (Consumer m x r) | |
| Monad m => JoinableComponentPair TransducerType (PerformerType r) TransducerType m [x] [y] (Transducer m x y) (Performer m r) (Transducer m x y) | |
| Monad m => JoinableComponentPair TransducerType (ProducerType ()) TransducerType m [x] [y] (Transducer m x y) (Producer m y ()) (Transducer m x y) | |
| Monad m => JoinableComponentPair TransducerType (ConsumerType ()) TransducerType m [x] [y] (Transducer m x y) (Consumer m x ()) (Transducer m x y) | |
| Monad m => Category (Transducer m) | |
| Monad m => JoinableComponentPair (PerformerType r) TransducerType TransducerType m [x] [y] (Performer m r) (Transducer m x y) (Transducer m x y) | |
| Monad m => JoinableComponentPair (ProducerType ()) TransducerType TransducerType m [x] [y] (Producer m y ()) (Transducer m x y) (Transducer m x y) | |
| Monad m => JoinableComponentPair (ConsumerType ()) TransducerType TransducerType m [x] [y] (Consumer m x ()) (Transducer m x y) (Transducer m x y) | |
| Monad m => JoinableComponentPair (ProducerType ()) (ConsumerType ()) TransducerType m [x] [y] (Producer m y ()) (Consumer m x ()) (Transducer m x y) | |
| Monad m => JoinableComponentPair (ConsumerType ()) (ProducerType ()) TransducerType m [x] [y] (Consumer m x ()) (Producer m y ()) (Transducer m x y) | |
| Monad m => Branching (Transducer m x y) m x () | |
| CompatibleSignature (Transducer m x y) TransducerType m [x] [y] | |
| CompatibleSignature (Transducer m x y) TransducerType m [x] [y] |
type OpenSplitter m a1 a2 a3 a4 d x b r = (AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d, AncestorFunctor a4 d) => Source m a1 x -> Sink m a2 x -> Sink m a3 x -> Sink m a4 b -> Coroutine d m rSource
The Splitter type represents coroutines that distribute the input stream acording to some criteria. A splitter
should distribute only the original input data, and feed it into the sinks in the same order it has been read from
the source. Furthermore, the input source should be entirely consumed and fed into the first two sinks. The third
sink can be used to supply extra information at arbitrary points in the input.
A splitter can be used in two ways: as a predicate to determine which portions of its input stream satisfy a certain property, or as a chunker to divide the input stream into chunks. In the former case, the predicate is considered true for exactly those parts of the input that are written to its true sink. In the latter case, a chunk is a contiguous section of the input stream that is written exclusively to one sink, either true or false. Anything written to the third sink also terminates the chunk.
Constructors
| Splitter | |
Fields
| |
Type of values in a markup-up stream. The Content constructor wraps the actual data.
type Parser m x b = Transducer m x (Markup b x)Source
A parser is a transducer that marks up its input.
class Branching c m x r | c -> m x whereSource
Branching is a type class representing all types that can act as consumers, namely Consumer,
Transducer, and Splitter.
Methods
combineBranches :: (forall d. PairBinder m -> (forall a d'. AncestorFunctor d d' => OpenConsumer m a d' x r) -> (forall a d'. AncestorFunctor d d' => OpenConsumer m a d' x r) -> forall a. OpenConsumer m a d x r) -> PairBinder m -> c -> c -> cSource
combineBranches is used to combine two values of Branch class into one, using the given Consumer binary
combinator.
Component constructors
isolateConsumer :: forall m x r. Monad m => (forall d. Functor d => Source m d x -> Coroutine d m r) -> Consumer m x rSource
Creates a proper Consumer from a function that is, but can't be proven to be, an OpenConsumer.
isolateProducer :: forall m x r. Monad m => (forall d. Functor d => Sink m d x -> Coroutine d m r) -> Producer m x rSource
Creates a proper Producer from a function that is, but can't be proven to be, an OpenProducer.
isolateTransducer :: forall m x y. Monad m => (forall d. Functor d => Source m d x -> Sink m d y -> Coroutine d m ()) -> Transducer m x ySource
Creates a proper Transducer from a function that is, but can't be proven to be, an OpenTransducer.
isolateSplitter :: forall m x b. Monad m => (forall d. Functor d => Source m d x -> Sink m d x -> Sink m d x -> Sink m d b -> Coroutine d m ()) -> Splitter m x bSource
Creates a proper Splitter from a function that is, but can't be proven to be, an OpenSplitter.
oneToOneTransducer :: Monad m => (x -> y) -> Transducer m x ySource
Function oneToOneTransducer takes a function that maps one input value to one output value each, and lifts it
into a Transducer.
statelessTransducer :: Monad m => (x -> [y]) -> Transducer m x ySource
Function statelessTransducer takes a function that maps one input value into a list of output values, and
lifts it into a Transducer.
statefulTransducer :: Monad m => (state -> x -> (state, [y])) -> state -> Transducer m x ySource
Function statefulTransducer constructs a Transducer from a state-transition function and the initial
state. The transition function may produce arbitrary output at any transition step.
statelessSplitter :: Monad m => (x -> Bool) -> Splitter m x bSource
Function statelessSplitter takes a function that assigns a Boolean value to each input item and lifts it into
a Splitter.
statefulSplitter :: Monad m => (state -> x -> (state, Bool)) -> state -> Splitter m x ()Source
Function statefulSplitter takes a state-converting function that also assigns a Boolean value to each input
item and lifts it into a Splitter.
Coercible class
class Coercible x y whereSource
Two streams of Coercible types can be unambigously converted one to another.
Methods
coerce :: Monad m => Transducer m x ySource
A Transducer that converts a stream of one type to another.
adaptConsumer :: Monad m => Consumer m y r -> Consumer m x rSource
adaptProducer :: Monad m => Producer m x r -> Producer m y rSource
Splitter isomorphism
adaptSplitter :: forall m x y b. (Monad m, Coercible x y, Coercible y x) => Splitter m x b -> Splitter m y bSource
Adjusts the argument splitter to split the stream of a data type Isomorphic to the type it was meant to split.
I/O components
I/O producers
fromFile :: String -> Producer IO Char ()Source
Reads the named file and feeds the given sink from its contents.
fromHandle :: Handle -> Producer IO Char ()Source
Feeds the given sink from the open text file handle.
fromStdIn :: Producer IO Char ()Source
Producer fromStdIn feeds the given sink from the standard input.
fromBinaryHandle :: Handle -> Int -> Producer IO ByteString ()Source
Feeds the given sink from the open binary file handle. The argument chunkSize determines the size of the chunks read from the handle.
I/O consumers
toFile :: String -> Consumer IO Char ()Source
Creates the named text file and writes the entire given source to it.
toHandle :: Handle -> Consumer IO Char ()Source
Copies the given source into the open text file handle.
toStdOut :: Consumer IO Char ()Source
Consumer toStdOut copies the given source into the standard output.
toBinaryHandle :: Handle -> Consumer IO ByteString ()Source
Copies the given source into the open binary file handle.
Generic components
fromList :: forall m x. Monad m => [x] -> Producer m x ()Source
Produces the contents of the given list argument.
Generic consumers
suppress :: forall m x y. Monad m => Consumer m x ()Source
The suppress consumer suppresses all input it receives. It is equivalent to substitute []
erroneous :: forall m x. Monad m => String -> Consumer m x ()Source
The erroneous consumer reports an error if any input reaches it.
toList :: forall m x. Monad m => Consumer m x [x]Source
Collects the entire input source into a list.
Generic transducers
parse :: forall m x y. Monad m => Transducer m x (Markup y x)Source
Transducer parse prepares input content for subsequent parsing.
unparse :: forall m x b. Monad m => Transducer m (Markup b x) xSource
Transducer unparse removes all markup from its input and passes the content through.
parseSubstring :: forall m x y. (Monad m, Eq x) => [x] -> Parser m x OccurenceTagSource
Performs the same task as the substring splitter, but instead of splitting it outputs the input as in order to distinguish overlapping strings.
Markup x
OccurenceTag
data OccurenceTag Source
Used by parseSubstring to distinguish between overlapping substrings.
Instances
count :: forall m x. Monad m => Transducer m x IntegerSource
The count transducer counts all its input values and outputs the final tally.
toString :: forall m x. (Monad m, Show x) => Transducer m x StringSource
Converts each input value x to show x.
List stream transducers
The following laws hold:
-
group>>>concatenate==id -
concatenate==concatSeparate[]
group :: forall m x. Monad m => Transducer m x [x]Source
Transducer group collects all its input values into a single list.
concatenate :: forall m x. Monad m => Transducer m [x] xSource
Transducer concatenate flattens the input stream of lists of values into the output stream of values.
concatSeparate :: forall m x. Monad m => [x] -> Transducer m [x] xSource
Same as concatenate except it inserts the given separator list between every two input lists.
Generic splitters
everything :: forall m x. Monad m => Splitter m x ()Source
Splitter everything feeds its entire input into its true sink.
nothing :: forall m x. Monad m => Splitter m x ()Source
Splitter nothing feeds its entire input into its false sink.
marked :: forall m x y. (Monad m, Eq y) => Splitter m (Markup y x) ()Source
Splitter marked passes all marked-up input sections to its true sink, and all unmarked input to its
false sink.
markedContent :: forall m x y. (Monad m, Eq y) => Splitter m (Markup y x) ()Source
Splitter markedContent passes the content of all marked-up input sections to its true sink, while the
outermost tags and all unmarked input go to its false sink.
markedWith :: forall m x y. (Monad m, Eq y) => (y -> Bool) -> Splitter m (Markup y x) ()Source
Splitter markedWith passes input sections marked-up with the appropriate tag to its true sink, and the
rest of the input to its false sink. The argument select determines if the tag is appropriate.
contentMarkedWith :: forall m x y. (Monad m, Eq y) => (y -> Bool) -> Splitter m (Markup y x) ()Source
Splitter contentMarkedWith passes the content of input sections marked-up with the appropriate tag to
its true sink, and the rest of the input to its false sink. The argument select determines if the tag is
appropriate.
one :: forall m x. Monad m => Splitter m x ()Source
Splitter one feeds all input values to its true sink, treating every value as a separate section.
substring :: forall m x. (Monad m, Eq x) => [x] -> Splitter m x ()Source
Splitter substring feeds to its true sink all input parts that match the contents of the given list
argument. If two overlapping parts of the input both match the argument, both are sent to true and each is preceded
by an edge.
Character stream components
lowercase :: forall m. Monad m => Transducer m Char CharSource
The lowercase transforms all uppercase letters in the input to lowercase, leaving the rest unchanged.
uppercase :: forall m. Monad m => Transducer m Char CharSource
The uppercase transforms all lowercase letters in the input to uppercase, leaving the rest unchanged.
whitespace :: forall m. Monad m => Splitter m Char ()Source
Splitter whitespace feeds all white-space characters into its true sink, all others into false.
letters :: forall m. Monad m => Splitter m Char ()Source
Splitter letters feeds all alphabetical characters into its true sink, all other characters into
| false.
digits :: forall m. Monad m => Splitter m Char ()Source
Splitter digits feeds all digits into its true sink, all other characters into false.
line :: forall m. Monad m => Splitter m Char ()Source
The sectioning splitter line feeds line-ends into its false sink, and line contents into true. A single
line-end can be formed by any of the character sequences "\n", "\r", "\r\n", or "\n\r".
nonEmptyLine :: forall m. Monad m => Splitter m Char ()Source
Splitter nonEmptyLine feeds line-ends into its false sink, and all other characters into true.
Consumer, producer, and transducer combinators
consumeBy :: forall m x y r. Monad m => Consumer m x r -> Transducer m x ySource
Converts a Consumer into a Transducer with no output.
prepend :: forall m x r. Monad m => Producer m x r -> Transducer m x xSource
Combinator prepend converts the given producer to a Transducer that passes all its
input through unmodified, except for prepending the output of the argument producer to it. The following law holds:
prepend prefix = join (substitute prefix) Control.Category.id
append :: forall m x r. Monad m => Producer m x r -> Transducer m x xSource
Combinator append converts the given producer to a Transducer that passes all its
input through unmodified, finally appending the output of the argument producer to it. The following law holds:
append suffix = join Control.Category.id (substitute suffix)
substitute :: forall m x y r. Monad m => Producer m y r -> Transducer m x ySource
The substitute combinator converts its argument producer to a Transducer that
produces the same output, while consuming its entire input and ignoring it.
class PipeableComponentPair m w c1 c2 c3 | c1 c2 -> c3, c1 c3 -> c2, c2 c3 -> c2, c1 -> m w, c2 -> m w, c3 -> mSource
Class PipeableComponentPair applies to any two components that can be combined into a third component with the
following properties:
- The input of the result, if any, becomes the input of the first component.
- The output produced by the first child component is consumed by the second child component.
- The result output, if any, is the output of the second component.
Instances
| Monad m => PipeableComponentPair m x (Producer m x ()) (Consumer m x ()) (Performer m ()) | |
| Monad m => PipeableComponentPair m y (Transducer m x y) (Transducer m y z) (Transducer m x z) | |
| Monad m => PipeableComponentPair m x (Producer m x r) (Transducer m x y) (Producer m y r) | |
| Monad m => PipeableComponentPair m y (Transducer m x y) (Consumer m y r) (Consumer m x r) |
(>->) :: (Monad m, PipeableComponentPair m w c1 c2 c3) => c1 -> c2 -> c3Source
Class PipeableComponentPair applies to any two components that can be combined into a third component with the
following properties:
- The input of the result, if any, becomes the input of the first component.
- The output produced by the first child component is consumed by the second child component.
- The result output, if any, is the output of the second component.
class (Monad m, CompatibleSignature c1 t1 m x y, CompatibleSignature c2 t2 m x y, CompatibleSignature c3 t3 m x y) => JoinableComponentPair t1 t2 t3 m x y c1 c2 c3 | c1 c2 -> c3, c1 -> t1 m, c2 -> t2 m, c3 -> t3 m x y, t1 m x y -> c1, t2 m x y -> c2, t3 m x y -> c3 whereSource
Class JoinableComponentPair applies to any two components that can be combined into a third component with the
following properties:
- if both argument components consume input, the input of the combined component gets distributed to both components in parallel, and
- if both argument components produce output, the output of the combined component is a concatenation of the complete output from the first component followed by the complete output of the second component.
Methods
sequence :: c1 -> c2 -> c3Source
The sequence combinator makes sure its first argument has completed before using the second one.
Instances
| Monad m => JoinableComponentPair TransducerType TransducerType TransducerType m [x] [y] (Transducer m x y) (Transducer m x y) (Transducer m x y) | |
| Monad m => JoinableComponentPair TransducerType (PerformerType r) TransducerType m [x] [y] (Transducer m x y) (Performer m r) (Transducer m x y) | |
| Monad m => JoinableComponentPair TransducerType (ProducerType ()) TransducerType m [x] [y] (Transducer m x y) (Producer m y ()) (Transducer m x y) | |
| Monad m => JoinableComponentPair TransducerType (ConsumerType ()) TransducerType m [x] [y] (Transducer m x y) (Consumer m x ()) (Transducer m x y) | |
| Monad m => JoinableComponentPair (PerformerType r) TransducerType TransducerType m [x] [y] (Performer m r) (Transducer m x y) (Transducer m x y) | |
| Monad m => JoinableComponentPair (ProducerType ()) TransducerType TransducerType m [x] [y] (Producer m y ()) (Transducer m x y) (Transducer m x y) | |
| Monad m => JoinableComponentPair (ConsumerType ()) TransducerType TransducerType m [x] [y] (Consumer m x ()) (Transducer m x y) (Transducer m x y) | |
| Monad m => JoinableComponentPair (ProducerType ()) (ConsumerType ()) TransducerType m [x] [y] (Producer m y ()) (Consumer m x ()) (Transducer m x y) | |
| Monad m => JoinableComponentPair (ConsumerType ()) (ProducerType ()) TransducerType m [x] [y] (Consumer m x ()) (Producer m y ()) (Transducer m x y) | |
| Monad m => JoinableComponentPair (PerformerType r1) (PerformerType r2) (PerformerType r2) m () () (Performer m r1) (Performer m r2) (Performer m r2) | |
| Monad m => JoinableComponentPair (PerformerType r1) (ProducerType r2) (ProducerType r2) m () [x] (Performer m r1) (Producer m x r2) (Producer m x r2) | |
| Monad m => JoinableComponentPair (ProducerType r1) (PerformerType r2) (ProducerType r2) m () [x] (Producer m x r1) (Performer m r2) (Producer m x r2) | |
| Monad m => JoinableComponentPair (ProducerType r1) (ProducerType r2) (ProducerType r2) m () [x] (Producer m x r1) (Producer m x r2) (Producer m x r2) | |
| Monad m => JoinableComponentPair (PerformerType r1) (ConsumerType r2) (ConsumerType r2) m [x] () (Performer m r1) (Consumer m x r2) (Consumer m x r2) | |
| Monad m => JoinableComponentPair (ConsumerType r1) (PerformerType r2) (ConsumerType r2) m [x] () (Consumer m x r1) (Performer m r2) (Consumer m x r2) | |
| Monad m => JoinableComponentPair (ConsumerType ()) (ConsumerType ()) (ConsumerType ()) m [x] () (Consumer m x ()) (Consumer m x ()) (Consumer m x ()) |
join :: (Monad m, JoinableComponentPair t1 t2 t3 m x y c1 c2 c3) => c1 -> c2 -> c3Source
The join combinator may apply the components in any order.
Splitter combinators
sNot :: forall m x b. Monad m => Splitter m x b -> Splitter m x bSource
The sNot (streaming not) combinator simply reverses the outputs of the argument splitter. In other words, data
that the argument splitter sends to its true sink goes to the false sink of the result, and vice versa.
Pseudo-logic flow combinators
Combinators >& and >| are only pseudo-logic. While the laws of double negation and De Morgan's laws
hold, sAnd and sOr are in general not commutative, associative, nor idempotent. In the special case when all
argument splitters are stateless, such as those produced by statelessSplitter,
these combinators do satisfy all laws of Boolean algebra.
(>&) :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (b1, b2)Source
The >& combinator sends the true sink output of its left operand to the input of its right operand for further
splitting. Both operands' false sinks are connected to the false sink of the combined splitter, but any input
value to reach the true sink of the combined component data must be deemed true by both splitters.
(>|) :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (Either b1 b2)Source
A >| combinator's input value can reach its false sink only by going through both argument splitters' false
sinks.
Zipping logic combinators
The && and || combinators run the argument splitters in parallel and combine their logical outputs using
the corresponding logical operation on each output pair, in a manner similar to Data.List.zipWith. They fully
satisfy the laws of Boolean algebra.
(&&) :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (b1, b2)Source
Combinator && is a pairwise logical conjunction of two splitters run in parallel on the same input.
(||) :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (Either b1 b2)Source
Combinator || is a pairwise logical disjunction of two splitters run in parallel on the same input.
Flow-control combinators
The following combinators resemble the common flow-control programming language constructs. Combinators
wherever, unless, and select are just the special cases of the combinator ifs.
wherever :: Monad m => Transducer m x x -> Splitter m x b -> Transducer m x xSource
unless :: Monad m => Transducer m x x -> Splitter m x b -> Transducer m x xSource
select :: forall m x b. Monad m => Splitter m x b -> Transducer m x xSource
Recursive
while :: Monad m => Transducer m x x -> Splitter m x b -> Transducer m x xSource
The recursive combinator while feeds the true sink of the argument splitter back to itself, modified by the
argument transducer. Data fed to the splitter's false sink is passed on unmodified.
nestedIn :: Monad m => Splitter m x b -> Splitter m x b -> Splitter m x bSource
The recursive combinator nestedIn combines two splitters into a mutually recursive loop acting as a single
splitter. The true sink of one of the argument splitters and false sink of the other become the true and false sinks
of the loop. The other two sinks are bound to the other splitter's source. The use of nestedIn makes sense only on
hierarchically structured streams. If we gave it some input containing a flat sequence of values, and assuming both
component splitters are deterministic and stateless, an input value would either not loop at all or it would loop
forever.
Section-based combinators
All combinators in this section use their Control.Concurrent.SCC.Splitter argument to determine the structure
of the input. Every contiguous portion of the input that gets passed to one or the other sink of the splitter is
treated as one section in the logical structure of the input stream. What is done with the section depends on the
combinator, but the sections, and therefore the logical structure of the input stream, are determined by the
argument splitter alone.
foreach :: (Monad m, Branching c m x ()) => Splitter m x b -> c -> c -> cSource
The foreach combinator is similar to the combinator ifs in that it combines a splitter and two transducers into
another transducer. However, in this case the transducers are re-instantiated for each consecutive portion of the
input as the splitter chunks it up. Each contiguous portion of the input that the splitter sends to one of its two
sinks gets transducered through the appropriate argument transducer as that transducer's whole input. As soon as the
contiguous portion is finished, the transducer gets terminated.
having :: (Monad m, Coercible x y) => Splitter m x b1 -> Splitter m y b2 -> Splitter m x b1Source
The having combinator combines two pure splitters into a pure splitter. One splitter is used to chunk the input
into contiguous portions. Its false sink is routed directly to the false sink of the combined splitter. The
second splitter is instantiated and run on each portion of the input that goes to first splitter's true sink. If
the second splitter sends any output at all to its true sink, the whole input portion is passed on to the true
sink of the combined splitter, otherwise it goes to its false sink.
havingOnly :: (Monad m, Coercible x y) => Splitter m x b1 -> Splitter m y b2 -> Splitter m x b1Source
The havingOnly combinator is analogous to the having combinator, but it succeeds and passes each chunk of the
input to its true sink only if the second splitter sends no part of it to its false sink.
followedBy :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (b1, b2)Source
Combinator followedBy treats its argument Splitters as patterns components and returns a Splitter that
matches their concatenation. A section of input is considered true by the result iff its prefix is considered
true by argument s1 and the rest of the section is considered true by s2. The splitter s2 is started anew
after every section split to true sink by s1.
first and its variants
first :: forall m x b. Monad m => Splitter m x b -> Splitter m x bSource
The result of combinator first behaves the same as the argument splitter up to and including the first portion of
the input which goes into the argument's true sink. All input following the first true portion goes into the
false sink.
uptoFirst :: forall m x b. Monad m => Splitter m x b -> Splitter m x bSource
The result of combinator uptoFirst takes all input up to and including the first portion of the input which goes
into the argument's true sink and feeds it to the result splitter's true sink. All the rest of the input goes
into the false sink. The only difference between first and uptoFirst combinators is in where they direct the
false portion of the input preceding the first true part.
prefix :: forall m x b. Monad m => Splitter m x b -> Splitter m x bSource
The prefix combinator feeds its true sink only the prefix of the input that its argument feeds to its true
sink. All the rest of the input is dumped into the false sink of the result.
last and its variants
last :: forall m x b. Monad m => Splitter m x b -> Splitter m x bSource
The result of the combinator last is a splitter which directs all input to its false sink, up to the last
portion of the input which goes to its argument's true sink. That portion of the input is the only one that goes to
the resulting component's true sink. The splitter returned by the combinator last has to buffer the previous two
portions of its input, because it cannot know if a true portion of the input is the last one until it sees the end of
the input or another portion succeeding the previous one.
lastAndAfter :: forall m x b. Monad m => Splitter m x b -> Splitter m x bSource
The result of the combinator lastAndAfter is a splitter which directs all input to its false sink, up to the
last portion of the input which goes to its argument's true sink. That portion and the remainder of the input is
fed to the resulting component's true sink. The difference between last and lastAndAfter combinators is where
they feed the false portion of the input, if any, remaining after the last true part.
suffix :: forall m x b. Monad m => Splitter m x b -> Splitter m x bSource
The suffix combinator feeds its true sink only the suffix of the input that its argument feeds to its true
sink. All the rest of the input is dumped into the false sink of the result.
positional splitters
startOf :: forall m x b. Monad m => Splitter m x b -> Splitter m x (Maybe b)Source
Splitter startOf issues an empty true section at the beginning of every section considered true by its
argument splitter, otherwise the entire input goes into its false sink.
endOf :: forall m x b. Monad m => Splitter m x b -> Splitter m x (Maybe b)Source
Splitter endOf issues an empty true section at the end of every section considered true by its argument
splitter, otherwise the entire input goes into its false sink.
(...) :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x b1Source
Combinator ... tracks the running balance of difference between the number of preceding starts of sections
considered true according to its first argument and the ones according to its second argument. The combinator
passes to true all input values for which the difference balance is positive. This combinator is typically used
with startOf and endOf in order to count entire input sections and ignore their lengths.
Parser support
splitterToMarker :: forall m x b. Monad m => Splitter m x b -> Transducer m x (Either (x, Bool) b)Source
parseRegions :: forall m x b. Monad m => Splitter m x b -> Parser m x bSource
Converts a splitter into a parser.
parseNestedRegions :: forall m x b. Monad m => Splitter m x (Boundary b) -> Parser m x bSource
Converts a boundary-marking splitter into a parser.
parseEachNestedRegion :: Monad m => Splitter m x (Boundary b) -> Transducer m x y -> Transducer m x (Markup b y)Source
Converts a boundary-marking splitter into a parser.
Parsing XML
xmlTokens :: Monad m => Splitter m Char (Boundary XMLToken)Source
This splitter splits XML markup from data content. It is used by parseXMLTokens.
parseXMLTokens :: MonadParallel m => Transducer m Char (Markup XMLToken Text)Source
The XML token parser. This parser converts plain text to parsed text, which is a precondition for using the remaining XML components.
expandXMLEntity :: String -> StringSource
Converts an XML entity name into the text value it represents: expandXMLEntity "lt" = "<".
XML splitters
xmlElement :: Monad m => Splitter m (Markup XMLToken Text) ()Source
Splits all top-level elements with all their content to true, all other input to false.
xmlElementContent :: Monad m => Splitter m (Markup XMLToken Text) ()Source
Splits the content of all top-level elements to true, their tags and intervening input to false.
xmlElementName :: Monad m => Splitter m (Markup XMLToken Text) ()Source
Splits every element name, including the names of nested elements and names in end tags, to true, all the rest of input to false.
xmlAttribute :: Monad m => Splitter m (Markup XMLToken Text) ()Source
Splits every attribute specification to true, everything else to false.
xmlAttributeName :: Monad m => Splitter m (Markup XMLToken Text) ()Source
Splits every attribute name to true, all the rest of input to false.
xmlAttributeValue :: Monad m => Splitter m (Markup XMLToken Text) ()Source
Splits every attribute value, excluding the quote delimiters, to true, all the rest of input to false.
xmlElementHavingTagWith :: forall m b. MonadParallel m => Splitter m (Markup XMLToken Text) b -> Splitter m (Markup XMLToken Text) bSource
Similiar to (, except it runs the argument splitter
only on each element's start tag, not on the entire element with its content.
Control.Concurrent.SCC.Combinators.having element)