-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Streaming component combinators -- -- SCC is a layered library of Streaming Component Combinators. The -- lowest layer defines stream abstractions and nested producer-consumer -- coroutine pairs based on the Coroutine monad transformer. On top of -- that are streaming component types, a number of primitive streaming -- components and a set of component combinators. Finally, there is an -- executable that exposes all the framework functionality in a -- command-line shell. -- -- The original library design is based on paper -- http://conferences.idealliance.org/extreme/html/2006/Blazevic01/EML2006Blazevic01.html -- -- Mario Blažević, Streaming component combinators, Extreme Markup -- Languages, 2006. @package scc @version 0.6 -- | This module can be used to optimize any complex computation that can -- be broken down into parallelizable sub-computations. The computations -- in question may be pure values, monadic values, list or stream -- transformations or anything else provided that it's parallelizable and -- has a relatively predictable computation cost. Each elementary -- sub-computation needs to be packaged as a Component using the -- constructor atomic. Sub-computations can then be combined into -- larger computations using the other constructors. module Control.Concurrent.Configuration -- | A Component carries a value and metadata about the value. It -- can be configured to use a specific number of threads. data Component c Component :: String -> [AnyComponent] -> Int -> (Int -> Component c) -> Int -> Int -> c -> Component c -- | Readable component name. name :: Component c -> String -- | Returns the list of all children components. subComponents :: Component c -> [AnyComponent] -- | Returns the maximum number of threads that can be used by the -- component. maxUsableThreads :: Component c -> Int -- | Configures the component to use the specified number of threads. This -- function affects usedThreads, cost, and -- subComponents methods of the result, while name and -- maxUsableThreads remain the same. usingThreads :: Component c -> Int -> Component c -- | The number of threads that the component is configured to use. The -- default number is usually 1. usedThreads :: Component c -> Int -- | The cost of using the component as configured. The cost is a rough -- approximation of time it would take to do the job given the -- usedThreads. cost :: Component c -> Int -- | The content. with :: Component c -> c -- | Show details of the given component's configuration. showComponentTree :: Component c -> String -- | Function atomic takes the component name and its cost creates a -- single-threaded component with no subcomponents. atomic :: String -> Int -> c -> Component c -- | Applies a unary combinator to the component payload. The -- resulting component has the original one as its subComponents, -- and its cost is the sum of the original component's cost and -- the combinator cost. lift :: Int -> String -> (c1 -> c2) -> Component c1 -> Component c2 -- | Combines two components into one, applying combinator to their -- contents. The combinator takes a flag denoting if its arguments -- should run in parallel. The cost and usingThreads of the -- result assume the parallel execution of the argument components. liftParallelPair :: String -> (Bool -> c1 -> c2 -> c3) -> Component c1 -> Component c2 -> Component c3 -- | Combines two components into one, applying combinator to their -- contents. The cost and usingThreads of the result assume -- the sequential execution of the argument components. liftSequentialPair :: String -> (c1 -> c2 -> c3) -> Component c1 -> Component c2 -> Component c3 -- | Combines three components into one. The first component runs in -- parallel with the latter two, which are considered alternative to each -- other. parallelRouterAndBranches :: String -> (Bool -> c1 -> c2 -> c3 -> c4) -> Component c1 -> Component c2 -> Component c3 -> Component c4 -- | Builds a tree of recursive components. The combinator takes a list of -- pairs of a boolean flag denoting whether the level should be run in -- parallel and the value. recursiveComponentTree :: String -> (Bool -> c1 -> c2 -> c2) -> Component c1 -> Component c2 instance Functor Component -- | The Components module defines thin wrappers around the -- Transducer and Splitter primitives and combinators, -- relying on the Control.Concurrent.SCC.ComponentTypes module. module Control.Concurrent.SCC.Configurable -- | A Sink can be used to yield values from any nested -- Coroutine computation whose functor provably descends from the -- functor a. It's the write-only end of a communication channel -- created by pipe. data Sink m :: (* -> *) a x -- | A Source can be used to read values into any nested -- Coroutine computation whose functor provably descends from the -- functor a. It's the read-only end of a communication channel -- created by pipe. data Source m :: (* -> *) a x -- | Class of functors that can be lifted. class (Functor a, Functor d) => AncestorFunctor a :: (* -> *) d :: (* -> *) -- | 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. pipe :: (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) -- | The pipeP function is equivalent to pipe, except it runs -- the producer and the consumer in parallel. pipeP :: (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) -- | A generic version of pipe. The first argument is used to -- combine two computation steps. pipeG :: (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) -- | A disconnected sink that ignores all values put into it. nullSink :: Monad m => Sink m a x -- | An empty source whose get always returns Nothing. nullSource :: Monad m => Source m a x -- | Function get tries to get a value from the given Source -- argument. The intervening Coroutine computations suspend all -- the way to the pipe function invocation that created the -- source. The function returns Nothing if the argument source is -- empty. get :: (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m (Maybe x) -- | Invokes its first argument with the value it gets from the source, if -- there is any to get. getWith :: (Monad m, AncestorFunctor a d) => (x -> Coroutine d m ()) -> Source m a x -> Coroutine d m () -- | Function peek acts the same way as get, but doesn't -- actually consume the value from the source; sequential calls to -- peek will always return the same value. peek :: (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m (Maybe x) -- | This function puts a value into the given Sink. The intervening -- Coroutine computations suspend up to the pipe invocation -- that has created the argument sink. put :: (Monad m, AncestorFunctor a d) => Sink m a x -> x -> Coroutine d m () -- | Like put, but returns a Bool that determines if the sink is -- still active. tryPut :: (Monad m, AncestorFunctor a d) => Sink m a x -> x -> Coroutine d m Bool -- | Converts a Sink on the ancestor functor a into a sink on -- the descendant functor d. liftSink :: (Monad m, AncestorFunctor a d) => Sink m a x -> Sink m d x -- | Converts a Source on the ancestor functor a into a -- source on the descendant functor d. liftSource :: (Monad m, AncestorFunctor a d) => Source m a x -> Source m d x -- | Copies all data from the source argument into the sink -- argument. pour :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => Source m a1 x -> Sink m a2 x -> Coroutine d m () -- | tee is similar to pour except it distributes every input -- value from its source argument into its both sink arguments. tee :: (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 () -- | Every value put into a teeSink result sink goes into its -- both argument sinks: put (teeSink s1 s2) x is equivalent to -- put s1 x >> put s2 x. The putChunk method -- returns the list of values that couldn't fit into the second sink. teeSink :: (Monad m, AncestorFunctor a1 a3, AncestorFunctor a2 a3) => Sink m a1 x -> Sink m a2 x -> Sink m a3 x -- | The Source returned by teeSource writes every value read -- from its argument source into the argument sink before providing it -- back. teeSource :: (Monad m, AncestorFunctor a1 a3, AncestorFunctor a2 a3) => Sink m a1 x -> Source m a2 x -> Source m a3 x -- | getList returns the list of all values generated by the source. getList :: (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m [x] -- | 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. putList :: (Monad m, AncestorFunctor a d) => [x] -> Sink m a x -> Coroutine d m [x] -- | Like putList, except it puts the contents of the given -- Seq into the sink. putQueue :: (Monad m, AncestorFunctor a d) => Seq x -> Sink m a x -> Coroutine d m [x] -- | Consumes values from the source as long as the ticker -- accepts them. getTicked :: (Monad m, AncestorFunctor a d) => Ticker x -> Source m a x -> Coroutine d m [x] -- | Consumes values from the source as long as each satisfies the -- predicate, then returns their list. getWhile :: (Monad m, AncestorFunctor a d) => (x -> Bool) -> Source m a x -> Coroutine d m [x] -- | 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. getUntil :: (Monad m, AncestorFunctor a d) => (x -> Bool) -> Source m a x -> Coroutine d m ([x], Maybe x) -- | Like pour, copies data from the source to the -- sink, but only as long as it satisfies the predicate. pourTicked :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => Ticker x -> Source m a1 x -> Sink m a2 x -> Coroutine d m () -- | Like pour, copies data from the source to the -- sink, but only as long as it satisfies the predicate. pourWhile :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m () -- | 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. pourUntil :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m (Maybe x) -- | An equivalent of map that works on a Sink instead of a -- list. The argument function is applied to every value vefore it's -- written to the sink argument. mapSink :: Monad m => (x -> y) -> Sink m a y -> Sink m a x -- | mapStream is like pour that applies the function -- f to each argument before passing it into the sink. mapStream :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m () -- | mapMaybeStream is to mapStream like mapMaybe is -- to map. mapMaybeStream :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Maybe y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m () -- | concatMapStream is to mapStream like concatMap is -- to map. concatMapStream :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> [y]) -> Source m a1 x -> Sink m a2 y -> Coroutine d m () -- | Like mapStream except it runs the argument function on whole -- chunks read from the input. mapStreamChunks :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => ([x] -> [y]) -> Source m a1 x -> Sink m a2 y -> Coroutine d m () -- | Similar to foldl, but reads the values from a Source -- instead of a list. foldStream :: (Monad m, AncestorFunctor a d) => (acc -> x -> acc) -> acc -> Source m a x -> Coroutine d m acc -- | 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. mapAccumStream :: (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 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. concatMapAccumStream :: (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 -- | Equivalent to partition. Takes a Source instead of a -- list argument and partitions its contents into the two Sink -- arguments. partitionStream :: (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 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 :: (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_ 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. mapMStream_ :: (Monad m, AncestorFunctor a d) => (x -> Coroutine d m ()) -> Source m a x -> Coroutine d m () -- | Like mapMStream_ except it runs the argument function on whole -- chunks read from the input. mapMStreamChunks_ :: (Monad m, AncestorFunctor a d) => ([x] -> Coroutine d m ()) -> Source m a x -> Coroutine d m () -- | An equivalent of filterM. Draws the values from a Source -- instead of a list, writes the filtered values to a Sink, and -- returns a Coroutine. filterMStream :: (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 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 :: (Monad m, AncestorFunctor a d) => (acc -> x -> Coroutine d m acc) -> acc -> Source m a x -> Coroutine d m acc -- | A variant of foldMStream that discards the final result value. foldMStream_ :: (Monad m, AncestorFunctor a d) => (acc -> x -> Coroutine d m acc) -> acc -> Source m a x -> Coroutine d m () -- | unfoldMStream is a version of unfoldr that writes the -- generated values into a Sink instead of returning a list. unfoldMStream :: (Monad m, AncestorFunctor a d) => (acc -> Coroutine d m (Maybe (x, acc))) -> acc -> Sink m a x -> Coroutine d m acc -- | unmapMStream_ is opposite of mapMStream_; it takes a -- Sink instead of a Source argument and writes the -- generated values into it. unmapMStream_ :: (Monad m, AncestorFunctor a d) => Coroutine d m (Maybe x) -> Sink m a x -> Coroutine d m () -- | Like unmapMStream_ but writing whole chunks of generated data -- into the argument sink. unmapMStreamChunks_ :: (Monad m, AncestorFunctor a d) => Coroutine d m [x] -> Sink m a x -> Coroutine d m () -- | 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. zipWithMStream :: (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 is equivalent to zipWithMStream, but -- it consumes the two sources in parallel. parZipWithMStream :: (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 () -- | A coroutine that has no inputs nor outputs - and therefore may not -- suspend at all, which means it's not really a coroutine. newtype Performer m r Performer :: m r -> Performer m r perform :: Performer m r -> m r -- | A coroutine that consumes values from a Source. newtype Consumer m x r Consumer :: (forall a d. OpenConsumer m a d x r) -> Consumer m x r consume :: Consumer m x r -> forall a d. OpenConsumer m a d x r -- | A coroutine that produces values and puts them into a Sink. newtype Producer m x r Producer :: (forall a d. OpenProducer m a d x r) -> Producer m x r produce :: Producer m x r -> forall a d. OpenProducer m a d x r -- | 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. newtype Transducer m x y Transducer :: (forall a1 a2 d. OpenTransducer m a1 a2 d x y ()) -> Transducer m x y transduce :: Transducer m x y -> forall a1 a2 d. OpenTransducer m a1 a2 d x y () -- | 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. newtype Splitter m x b Splitter :: (forall a1 a2 a3 a4 d. OpenSplitter m a1 a2 a3 a4 d x b ()) -> Splitter m x b split :: Splitter m x b -> forall a1 a2 a3 a4 d. OpenSplitter m a1 a2 a3 a4 d x b () -- | A Boundary value is produced to mark either a Start and -- End of a region of data, or an arbitrary Point in data. -- A Point is semantically equivalent to a Start -- immediately followed by End. data Boundary y Start :: y -> Boundary y End :: y -> Boundary y Point :: y -> Boundary y -- | Type of values in a markup-up stream. The Content constructor -- wraps the actual data. data Markup y x Content :: x -> Markup y x Markup :: (Boundary y) -> Markup y x -- | A parser is a transducer that marks up its input. type Parser m x b = Transducer m x (Markup b x) -- | Branching is a type class representing all types that can act -- as consumers, namely Consumer, Transducer, and -- Splitter. class Branching c m :: (* -> *) x r | c -> m x combineBranches :: Branching c m x r => (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 -- | Creates a proper Consumer from a function that is, but can't be -- proven to be, an OpenConsumer. isolateConsumer :: Monad m => (forall d. Functor d => Source m d x -> Coroutine d m r) -> Consumer m x r -- | Creates a proper Producer from a function that is, but can't be -- proven to be, an OpenProducer. isolateProducer :: Monad m => (forall d. Functor d => Sink m d x -> Coroutine d m r) -> Producer m x r -- | Creates a proper Transducer from a function that is, but can't -- be proven to be, an OpenTransducer. isolateTransducer :: Monad m => (forall d. Functor d => Source m d x -> Sink m d y -> Coroutine d m ()) -> Transducer m x y -- | Creates a proper Splitter from a function that is, but can't be -- proven to be, an OpenSplitter. isolateSplitter :: 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 -- | Function oneToOneTransducer takes a function that maps one -- input value to one output value each, and lifts it into a -- Transducer. oneToOneTransducer :: Monad m => (x -> y) -> Transducer m x y -- | Function statelessTransducer takes a function that maps one -- input value into a list of output values, and lifts it into a -- Transducer. statelessTransducer :: Monad m => (x -> [y]) -> Transducer m x y -- | 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. statefulTransducer :: Monad m => (state -> x -> (state, [y])) -> state -> Transducer m x y -- | Function statelessSplitter takes a function that assigns a -- Boolean value to each input item and lifts it into a Splitter. statelessSplitter :: Monad m => (x -> Bool) -> Splitter m x b -- | Function statefulSplitter takes a state-converting function -- that also 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 () -- | A component that performs a computation with no inputs nor outputs is -- a PerformerComponent. type PerformerComponent m r = Component (Performer m r) -- | A component that consumes values from a Source is called -- ConsumerComponent. type ConsumerComponent m x r = Component (Consumer m x r) -- | A component that produces values and puts them into a Sink is -- called ProducerComponent. type ProducerComponent m x r = Component (Producer m x r) -- | The TransducerComponent type represents computations that -- transform a data stream. type TransducerComponent m x y = Component (Transducer m x y) -- | The SplitterComponent type represents computations that -- distribute data 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. If the two 'Sink c x' -- arguments of a splitter are the same, the splitter must act as an -- identity transform. type SplitterComponent m x b = Component (Splitter m x b) -- | The constant cost of each I/O-performing component. ioCost :: Int -- | A TransducerComponent that converts a stream of one type to -- another. coerce :: (Monad m, Coercible x y) => TransducerComponent m x y -- | Adjusts the argument consumer to consume the stream of a data type -- coercible to the type it was meant to consume. adaptConsumer :: (Monad m, Coercible x y) => ConsumerComponent m y r -> ConsumerComponent m x r -- | Adjusts the argument producer to produce the stream of a data type -- coercible from the type it was meant to produce. adaptProducer :: (Monad m, Coercible x y) => ProducerComponent m x r -> ProducerComponent m y r -- | Adjusts the argument splitter to split the stream of a data type -- isomorphic to the type it was meant to split. adaptSplitter :: (Monad m, Coercible x y, Coercible y x) => SplitterComponent m x b -> SplitterComponent m y b -- | ProducerComponent fromStdIn feeds the given sink from the -- standard input. fromStdIn :: ProducerComponent IO Char () -- | ProducerComponent fromFile opens the named file and feeds the -- given sink from its contents. fromFile :: String -> ProducerComponent IO Char () -- | ProducerComponent fromHandle feeds the given sink from the open -- file handle. fromHandle :: Handle -> ProducerComponent IO Char () -- | ConsumerComponent toStdOut copies the given source into the -- standard output. toStdOut :: ConsumerComponent IO Char () -- | ConsumerComponent toFile opens the named file and copies the -- given source into it. toFile :: String -> ConsumerComponent IO Char () -- | ConsumerComponent appendFile opens the name file and appends -- the given source to it. appendFile :: String -> ConsumerComponent IO Char () -- | ConsumerComponent toHandle copies the given source into the -- open file handle. toHandle :: Handle -> ConsumerComponent IO Char () -- | fromList produces the contents of the given list argument. fromList :: Monad m => [x] -> ProducerComponent m x () -- | ConsumerComponent toList copies the given source into a list. toList :: Monad m => ConsumerComponent m x [x] -- | The suppress consumer suppresses all input it receives. It is -- equivalent to substitute [] suppress :: Monad m => ConsumerComponent m x () -- | The erroneous consumer reports an error if any input reaches -- it. erroneous :: Monad m => String -> ConsumerComponent m x () -- | TransducerComponent id passes its input through unmodified. id :: Monad m => TransducerComponent m x x -- | TransducerComponent unparse removes all markup from its input -- and passes the content through. unparse :: Monad m => TransducerComponent m (Markup b x) x -- | TransducerComponent parse prepares input content for subsequent -- parsing. parse :: Monad m => TransducerComponent m x (Markup y x) -- | The lowercase transforms all uppercase letters in the input to -- lowercase, leaving the rest unchanged. lowercase :: Monad m => TransducerComponent m Char Char -- | The uppercase transforms all lowercase letters in the input to -- uppercase, leaving the rest unchanged. uppercase :: Monad m => TransducerComponent m Char Char -- | The count transducer counts all its input values and outputs -- the final tally. count :: Monad m => TransducerComponent m x Integer -- | Converts each input value x to show x. toString :: (Monad m, Show x) => TransducerComponent m x String -- | Performs the same task as the substring splitter, but instead -- of splitting it outputs the input as Markup x -- OccurenceTag in order to distinguish overlapping strings. parseSubstring :: (Monad m, Eq x) => [x] -> ParserComponent m x OccurenceTag -- | TransducerComponent group collects all its input values into a -- single list. group :: Monad m => TransducerComponent m x [x] -- | TransducerComponent concatenate flattens the input stream of -- lists of values into the output stream of values. concatenate :: Monad m => TransducerComponent m [x] x -- | Same as concatenate except it inserts the given separator list -- between every two input lists. concatSeparate :: Monad m => [x] -> TransducerComponent m [x] x -- | SplitterComponent everything feeds its entire input into its -- true sink. everything :: Monad m => SplitterComponent m x () -- | SplitterComponent nothing feeds its entire input into its -- false sink. nothing :: Monad m => SplitterComponent m x () -- | SplitterComponent marked passes all marked-up input sections to -- its true sink, and all unmarked input to its false sink. marked :: (Monad m, Eq y) => SplitterComponent m (Markup y x) () -- | SplitterComponent 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. markedContent :: (Monad m, Eq y) => SplitterComponent m (Markup y x) () -- | SplitterComponent 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. markedWith :: (Monad m, Eq y) => (y -> Bool) -> SplitterComponent m (Markup y x) () -- | SplitterComponent 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. contentMarkedWith :: (Monad m, Eq y) => (y -> Bool) -> SplitterComponent m (Markup y x) () -- | SplitterComponent one feeds all input values to its true -- sink, treating every value as a separate section. one :: Monad m => SplitterComponent m x () -- | SplitterComponent 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. substring :: (Monad m, Eq x) => [x] -> SplitterComponent m x () -- | SplitterComponent whitespace feeds all white-space characters -- into its true sink, all others into false. whitespace :: Monad m => SplitterComponent m Char () -- | SplitterComponent letters feeds all alphabetical characters -- into its true sink, all other characters into | false. letters :: Monad m => SplitterComponent m Char () -- | SplitterComponent digits feeds all digits into its true -- sink, all other characters into false. digits :: Monad m => SplitterComponent m Char () -- | SplitterComponent nonEmptyLine feeds line-ends into its -- false sink, and all other characters into true. nonEmptyLine :: Monad m => SplitterComponent m Char () -- | 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". line :: Monad m => SplitterComponent m Char () -- | Converts a ConsumerComponent into a TransducerComponent -- with no output. consumeBy :: Monad m => ConsumerComponent m x r -> TransducerComponent m x y -- | Class PipeableComponentPair applies to any two components -- that can be combined into a third component with the following -- properties: -- -- (>->) :: (MonadParallel m, PipeableComponentPair m w c1 c2 c3) => Component c1 -> Component c2 -> Component c3 -- | Class JoinableComponentPair applies to any two components -- that can be combined into a third component with the following -- properties: -- -- -- -- The join combinator may apply the components in any order. join :: (MonadParallel m, JoinableComponentPair t1 t2 t3 m x y c1 c2 c3) => Component c1 -> Component c2 -> Component c3 -- | The sequence combinator makes sure its first argument has -- completed before using the second one. sequence :: JoinableComponentPair t1 t2 t3 m x y c1 c2 c3 => Component c1 -> Component c2 -> Component c3 -- | Combinator prepend converts the given producer to transducer -- that passes all its input through unmodified, except | for prepending -- the output of the argument producer to it. | prepend -- prefix = join (substitute prefix) -- asis prepend :: Monad m => ProducerComponent m x r -> TransducerComponent m x x -- | Combinator append converts the given producer to transducer -- that passes all its input through unmodified, finally | appending to -- it the output of the argument producer. | append suffix -- = join asis (substitute suffix) append :: Monad m => ProducerComponent m x r -> TransducerComponent m x x -- | The substitute combinator converts its argument producer to a -- transducer that produces the same output, while | consuming its entire -- input and ignoring it. substitute :: Monad m => ProducerComponent m y r -> TransducerComponent m x y -- | 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. snot :: Monad m => SplitterComponent m x b -> SplitterComponent m x b -- | 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. (>&) :: MonadParallel m => SplitterComponent m x b1 -> SplitterComponent m x b2 -> SplitterComponent m x (b1, b2) -- | A >| combinator's input value can reach its false -- sink only by going through both argument splitters' false -- sinks. (>|) :: MonadParallel m => SplitterComponent m x b1 -> SplitterComponent m x b2 -> SplitterComponent m x (Either b1 b2) -- | Combinator && is a pairwise logical conjunction of two -- splitters run in parallel on the same input. (&&) :: MonadParallel m => SplitterComponent m x b1 -> SplitterComponent m x b2 -> SplitterComponent m x (b1, b2) -- | Combinator || is a pairwise logical disjunction of two -- splitters run in parallel on the same input. (||) :: MonadParallel m => SplitterComponent m x b1 -> SplitterComponent m x b2 -> SplitterComponent m x (Either b1 b2) -- | 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. while :: MonadParallel m => TransducerComponent m x x -> SplitterComponent m x b -> TransducerComponent m x x -- | 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. nestedIn :: MonadParallel m => SplitterComponent m x b -> SplitterComponent m x b -> SplitterComponent m x b -- | 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. foreach :: (MonadParallel m, Branching c m x ()) => SplitterComponent m x b -> Component c -> Component c -> Component c -- | 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. having :: (MonadParallel m, Coercible x y) => SplitterComponent m x b1 -> SplitterComponent m y b2 -> SplitterComponent m x b1 -- | 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. havingOnly :: (MonadParallel m, Coercible x y) => SplitterComponent m x b1 -> SplitterComponent m y b2 -> SplitterComponent m x b1 -- | Combinator followedBy treats its argument -- SplitterComponents as patterns components and returns a -- SplitterComponent 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. followedBy :: MonadParallel m => SplitterComponent m x b1 -> SplitterComponent m x b2 -> SplitterComponent m x (b1, b2) -- | The even combinator takes every input section that its argument -- splitter deems true, and feeds even ones into its -- true sink. The odd sections and parts of input that are -- false according to its argument splitter are fed to even -- splitter's false sink. even :: Monad m => SplitterComponent m x b -> SplitterComponent m x b -- | 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. first :: Monad m => SplitterComponent m x b -> SplitterComponent m x b -- | 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. uptoFirst :: Monad m => SplitterComponent m x b -> SplitterComponent m x b -- | 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. prefix :: Monad m => SplitterComponent m x b -> SplitterComponent m x b -- | 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. last :: Monad m => SplitterComponent m x b -> SplitterComponent m x b -- | 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. lastAndAfter :: Monad m => SplitterComponent m x b -> SplitterComponent m x b -- | 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. suffix :: Monad m => SplitterComponent m x b -> SplitterComponent m x b -- | SplitterComponent 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. startOf :: Monad m => SplitterComponent m x b -> SplitterComponent m x (Maybe b) -- | SplitterComponent 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. endOf :: MonadParallel m => SplitterComponent m x b -> SplitterComponent m x (Maybe b) -- | 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. (...) :: MonadParallel m => SplitterComponent m x b1 -> SplitterComponent m x b2 -> SplitterComponent m x b1 -- | Converts a splitter into a parser. parseRegions :: Monad m => SplitterComponent m x b -> ParserComponent m x b -- | Converts a boundary-marking splitter into a parser. parseNestedRegions :: MonadParallel m => SplitterComponent m x (Boundary b) -> ParserComponent m x b -- | This splitter splits XML markup from data content. It is used by -- parseXMLTokens. xmlTokens :: Monad m => SplitterComponent m Char (Boundary XMLToken) -- | The XML token parser. This parser converts plain text to parsed text, -- which is a precondition for using the remaining XML components. xmlParseTokens :: MonadParallel m => TransducerComponent m Char (Markup XMLToken Text) -- | Splits all top-level elements with all their content to true, -- all other input to false. xmlElement :: Monad m => SplitterComponent m (Markup XMLToken Text) () -- | Splits the content of all top-level elements to true, their -- tags and intervening input to false. xmlElementContent :: Monad m => SplitterComponent m (Markup XMLToken Text) () -- | Similiar to (Control.Concurrent.SCC.Combinators.having -- element), except it runs the argument splitter only on -- each element's start tag, not on the entire element with its content. xmlElementHavingTagWith :: MonadParallel m => SplitterComponent m (Markup XMLToken Text) b -> SplitterComponent m (Markup XMLToken Text) b -- | Splits every attribute specification to true, everything else -- to false. xmlAttribute :: Monad m => SplitterComponent m (Markup XMLToken Text) () -- | Splits every element name, including the names of nested elements and -- names in end tags, to true, all the rest of input to -- false. xmlElementName :: Monad m => SplitterComponent m (Markup XMLToken Text) () -- | Splits every attribute name to true, all the rest of input to -- false. xmlAttributeName :: Monad m => SplitterComponent m (Markup XMLToken Text) () -- | Splits every attribute value, excluding the quote delimiters, to -- true, all the rest of input to false. xmlAttributeValue :: Monad m => SplitterComponent m (Markup XMLToken Text) () -- | Converts an XML entity name into the text value it represents: -- expandXMLEntity "lt" = "<". expandXMLEntity :: String -> String instance CompatibleSignature (Transducer m x y) TransducerType m [x] [y] instance AnyListOrUnit y => CompatibleSignature (Producer m x r) (ProducerType r) m y [x] instance AnyListOrUnit y => CompatibleSignature (Consumer m x r) (ConsumerType r) m [x] y instance (AnyListOrUnit x, AnyListOrUnit y) => CompatibleSignature (Performer m r) (PerformerType r) m x y instance AnyListOrUnit () instance AnyListOrUnit [x] -- | This module exports all of the SCC libraries. The exported combinators -- run their components in parallel. module Control.Concurrent.SCC.Parallel -- | A Sink can be used to yield values from any nested -- Coroutine computation whose functor provably descends from the -- functor a. It's the write-only end of a communication channel -- created by pipe. data Sink m :: (* -> *) a x -- | A Source can be used to read values into any nested -- Coroutine computation whose functor provably descends from the -- functor a. It's the read-only end of a communication channel -- created by pipe. 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 of functors that can be lifted. class (Functor a, Functor d) => AncestorFunctor a :: (* -> *) d :: (* -> *) -- | 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. pipe :: (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) -- | The pipeP function is equivalent to pipe, except it runs -- the producer and the consumer in parallel. pipeP :: (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) -- | A generic version of pipe. The first argument is used to -- combine two computation steps. pipeG :: (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) -- | A disconnected sink that ignores all values put into it. nullSink :: Monad m => Sink m a x -- | An empty source whose get always returns Nothing. nullSource :: Monad m => Source m a x -- | Function get tries to get a value from the given Source -- argument. The intervening Coroutine computations suspend all -- the way to the pipe function invocation that created the -- source. The function returns Nothing if the argument source is -- empty. get :: (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m (Maybe x) -- | Invokes its first argument with the value it gets from the source, if -- there is any to get. getWith :: (Monad m, AncestorFunctor a d) => (x -> Coroutine d m ()) -> Source m a x -> Coroutine d m () -- | Function peek acts the same way as get, but doesn't -- actually consume the value from the source; sequential calls to -- peek will always return the same value. peek :: (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m (Maybe x) -- | This function puts a value into the given Sink. The intervening -- Coroutine computations suspend up to the pipe invocation -- that has created the argument sink. put :: (Monad m, AncestorFunctor a d) => Sink m a x -> x -> Coroutine d m () -- | Like put, but returns a Bool that determines if the sink is -- still active. tryPut :: (Monad m, AncestorFunctor a d) => Sink m a x -> x -> Coroutine d m Bool -- | Converts a Sink on the ancestor functor a into a sink on -- the descendant functor d. liftSink :: (Monad m, AncestorFunctor a d) => Sink m a x -> Sink m d x -- | Converts a Source on the ancestor functor a into a -- source on the descendant functor d. liftSource :: (Monad m, AncestorFunctor a d) => Source m a x -> Source m d x -- | Copies all data from the source argument into the sink -- argument. pour :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => Source m a1 x -> Sink m a2 x -> Coroutine d m () -- | tee is similar to pour except it distributes every input -- value from its source argument into its both sink arguments. tee :: (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 () -- | Every value put into a teeSink result sink goes into its -- both argument sinks: put (teeSink s1 s2) x is equivalent to -- put s1 x >> put s2 x. The putChunk method -- returns the list of values that couldn't fit into the second sink. teeSink :: (Monad m, AncestorFunctor a1 a3, AncestorFunctor a2 a3) => Sink m a1 x -> Sink m a2 x -> Sink m a3 x -- | The Source returned by teeSource writes every value read -- from its argument source into the argument sink before providing it -- back. teeSource :: (Monad m, AncestorFunctor a1 a3, AncestorFunctor a2 a3) => Sink m a1 x -> Source m a2 x -> Source m a3 x -- | getList returns the list of all values generated by the source. getList :: (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m [x] -- | 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. putList :: (Monad m, AncestorFunctor a d) => [x] -> Sink m a x -> Coroutine d m [x] -- | Like putList, except it puts the contents of the given -- Seq into the sink. putQueue :: (Monad m, AncestorFunctor a d) => Seq x -> Sink m a x -> Coroutine d m [x] -- | Consumes values from the source as long as the ticker -- accepts them. getTicked :: (Monad m, AncestorFunctor a d) => Ticker x -> Source m a x -> Coroutine d m [x] -- | Consumes values from the source as long as each satisfies the -- predicate, then returns their list. getWhile :: (Monad m, AncestorFunctor a d) => (x -> Bool) -> Source m a x -> Coroutine d m [x] -- | 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. getUntil :: (Monad m, AncestorFunctor a d) => (x -> Bool) -> Source m a x -> Coroutine d m ([x], Maybe x) -- | Like pour, copies data from the source to the -- sink, but only as long as it satisfies the predicate. pourTicked :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => Ticker x -> Source m a1 x -> Sink m a2 x -> Coroutine d m () -- | Like pour, copies data from the source to the -- sink, but only as long as it satisfies the predicate. pourWhile :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m () -- | 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. pourUntil :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m (Maybe x) -- | An equivalent of map that works on a Sink instead of a -- list. The argument function is applied to every value vefore it's -- written to the sink argument. mapSink :: Monad m => (x -> y) -> Sink m a y -> Sink m a x -- | mapStream is like pour that applies the function -- f to each argument before passing it into the sink. mapStream :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m () -- | mapMaybeStream is to mapStream like mapMaybe is -- to map. mapMaybeStream :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Maybe y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m () -- | concatMapStream is to mapStream like concatMap is -- to map. concatMapStream :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> [y]) -> Source m a1 x -> Sink m a2 y -> Coroutine d m () -- | Like mapStream except it runs the argument function on whole -- chunks read from the input. mapStreamChunks :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => ([x] -> [y]) -> Source m a1 x -> Sink m a2 y -> Coroutine d m () -- | Similar to foldl, but reads the values from a Source -- instead of a list. foldStream :: (Monad m, AncestorFunctor a d) => (acc -> x -> acc) -> acc -> Source m a x -> Coroutine d m acc -- | 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. mapAccumStream :: (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 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. concatMapAccumStream :: (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 -- | Equivalent to partition. Takes a Source instead of a -- list argument and partitions its contents into the two Sink -- arguments. partitionStream :: (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 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 :: (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_ 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. mapMStream_ :: (Monad m, AncestorFunctor a d) => (x -> Coroutine d m ()) -> Source m a x -> Coroutine d m () -- | Like mapMStream_ except it runs the argument function on whole -- chunks read from the input. mapMStreamChunks_ :: (Monad m, AncestorFunctor a d) => ([x] -> Coroutine d m ()) -> Source m a x -> Coroutine d m () -- | An equivalent of filterM. Draws the values from a Source -- instead of a list, writes the filtered values to a Sink, and -- returns a Coroutine. filterMStream :: (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 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 :: (Monad m, AncestorFunctor a d) => (acc -> x -> Coroutine d m acc) -> acc -> Source m a x -> Coroutine d m acc -- | A variant of foldMStream that discards the final result value. foldMStream_ :: (Monad m, AncestorFunctor a d) => (acc -> x -> Coroutine d m acc) -> acc -> Source m a x -> Coroutine d m () -- | unfoldMStream is a version of unfoldr that writes the -- generated values into a Sink instead of returning a list. unfoldMStream :: (Monad m, AncestorFunctor a d) => (acc -> Coroutine d m (Maybe (x, acc))) -> acc -> Sink m a x -> Coroutine d m acc -- | unmapMStream_ is opposite of mapMStream_; it takes a -- Sink instead of a Source argument and writes the -- generated values into it. unmapMStream_ :: (Monad m, AncestorFunctor a d) => Coroutine d m (Maybe x) -> Sink m a x -> Coroutine d m () -- | Like unmapMStream_ but writing whole chunks of generated data -- into the argument sink. unmapMStreamChunks_ :: (Monad m, AncestorFunctor a d) => Coroutine d m [x] -> Sink m a x -> Coroutine d m () -- | 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. zipWithMStream :: (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 is equivalent to zipWithMStream, but -- it consumes the two sources in parallel. parZipWithMStream :: (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 () -- | A coroutine that has no inputs nor outputs - and therefore may not -- suspend at all, which means it's not really a coroutine. newtype Performer m r Performer :: m r -> Performer m r perform :: Performer m r -> m r type OpenConsumer m a d x r = AncestorFunctor a d => Source m a x -> Coroutine d m r -- | A coroutine that consumes values from a Source. newtype Consumer m x r Consumer :: (forall a d. OpenConsumer m a d x r) -> Consumer m x r consume :: Consumer m x r -> 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 -- | A coroutine that produces values and puts them into a Sink. newtype Producer m x r Producer :: (forall a d. OpenProducer m a d x r) -> Producer m x r produce :: Producer m x r -> 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 -- | 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. newtype Transducer m x y Transducer :: (forall a1 a2 d. OpenTransducer m a1 a2 d x y ()) -> Transducer m x y transduce :: Transducer m x y -> 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 -- | 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. newtype Splitter m x b Splitter :: (forall a1 a2 a3 a4 d. OpenSplitter m a1 a2 a3 a4 d x b ()) -> Splitter m x b split :: Splitter m x b -> forall a1 a2 a3 a4 d. OpenSplitter m a1 a2 a3 a4 d x b () -- | A Boundary value is produced to mark either a Start and -- End of a region of data, or an arbitrary Point in data. -- A Point is semantically equivalent to a Start -- immediately followed by End. data Boundary y Start :: y -> Boundary y End :: y -> Boundary y Point :: y -> Boundary y -- | Type of values in a markup-up stream. The Content constructor -- wraps the actual data. data Markup y x Content :: x -> Markup y x Markup :: (Boundary y) -> Markup y x -- | A parser is a transducer that marks up its input. type Parser m x b = Transducer m x (Markup b x) -- | Branching is a type class representing all types that can act -- as consumers, namely Consumer, Transducer, and -- Splitter. class Branching c m :: (* -> *) x r | c -> m x combineBranches :: Branching c m x r => (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 -- | Creates a proper Consumer from a function that is, but can't be -- proven to be, an OpenConsumer. isolateConsumer :: Monad m => (forall d. Functor d => Source m d x -> Coroutine d m r) -> Consumer m x r -- | Creates a proper Producer from a function that is, but can't be -- proven to be, an OpenProducer. isolateProducer :: Monad m => (forall d. Functor d => Sink m d x -> Coroutine d m r) -> Producer m x r -- | Creates a proper Transducer from a function that is, but can't -- be proven to be, an OpenTransducer. isolateTransducer :: Monad m => (forall d. Functor d => Source m d x -> Sink m d y -> Coroutine d m ()) -> Transducer m x y -- | Creates a proper Splitter from a function that is, but can't be -- proven to be, an OpenSplitter. isolateSplitter :: 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 -- | Function oneToOneTransducer takes a function that maps one -- input value to one output value each, and lifts it into a -- Transducer. oneToOneTransducer :: Monad m => (x -> y) -> Transducer m x y -- | Function statelessTransducer takes a function that maps one -- input value into a list of output values, and lifts it into a -- Transducer. statelessTransducer :: Monad m => (x -> [y]) -> Transducer m x y -- | 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. statefulTransducer :: Monad m => (state -> x -> (state, [y])) -> state -> Transducer m x y -- | Function statelessSplitter takes a function that assigns a -- Boolean value to each input item and lifts it into a Splitter. statelessSplitter :: Monad m => (x -> Bool) -> Splitter m x b -- | Function statefulSplitter takes a state-converting function -- that also 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 () -- | Two streams of Coercible types can be unambigously converted -- one to another. class Coercible x y coerce :: (Coercible x y, Monad m) => Transducer m x y adaptConsumer :: (Coercible x y, Monad m) => Consumer m y r -> Consumer m x r adaptProducer :: (Coercible x y, Monad m) => Producer m x r -> Producer m y r -- | Adjusts the argument splitter to split the stream of a data type -- Isomorphic to the type it was meant to split. adaptSplitter :: (Monad m, Coercible x y, Coercible y x) => Splitter m x b -> Splitter m y b -- | Reads the named file and feeds the given sink from its contents. fromFile :: String -> Producer IO Char () -- | Feeds the given sink from the open text file handle. fromHandle :: Handle -> Producer IO Char () -- | Producer fromStdIn feeds the given sink from the standard -- input. fromStdIn :: Producer IO Char () -- | Feeds the given sink from the open binary file handle. The -- argument chunkSize determines the size of the chunks read from -- the handle. fromBinaryHandle :: Handle -> Int -> Producer IO ByteString () -- | Appends the given source to the named text file. appendFile :: String -> Consumer IO Char () -- | Creates the named text file and writes the entire given source to it. toFile :: String -> Consumer IO Char () -- | Copies the given source into the open text file handle. toHandle :: Handle -> Consumer IO Char () -- | Consumer toStdOut copies the given source into the standard -- output. toStdOut :: Consumer IO Char () -- | Copies the given source into the open binary file handle. toBinaryHandle :: Handle -> Consumer IO ByteString () -- | Produces the contents of the given list argument. fromList :: Monad m => [x] -> Producer m x () -- | The suppress consumer suppresses all input it receives. It is -- equivalent to substitute [] suppress :: Monad m => Consumer m x () -- | The erroneous consumer reports an error if any input reaches -- it. erroneous :: Monad m => String -> Consumer m x () -- | Collects the entire input source into a list. toList :: Monad m => Consumer m x [x] -- | Transducer parse prepares input content for subsequent parsing. parse :: Monad m => Transducer m x (Markup y x) -- | Transducer unparse removes all markup from its input and passes -- the content through. unparse :: Monad m => Transducer m (Markup b x) x -- | Performs the same task as the substring splitter, but instead -- of splitting it outputs the input as Markup x -- OccurenceTag in order to distinguish overlapping strings. parseSubstring :: (Monad m, Eq x) => [x] -> Parser m x OccurenceTag -- | Used by parseSubstring to distinguish between overlapping -- substrings. data OccurenceTag -- | The count transducer counts all its input values and outputs -- the final tally. count :: Monad m => Transducer m x Integer -- | Converts each input value x to show x. toString :: (Monad m, Show x) => Transducer m x String -- | Transducer group collects all its input values into a single -- list. group :: Monad m => Transducer m x [x] -- | Transducer concatenate flattens the input stream of lists of -- values into the output stream of values. concatenate :: Monad m => Transducer m [x] x -- | Same as concatenate except it inserts the given separator list -- between every two input lists. concatSeparate :: Monad m => [x] -> Transducer m [x] x -- | Splitter everything feeds its entire input into its true -- sink. everything :: Monad m => Splitter m x () -- | Splitter nothing feeds its entire input into its false -- sink. nothing :: Monad m => Splitter m x () -- | Splitter marked passes all marked-up input sections to its -- true sink, and all unmarked input to its false sink. marked :: (Monad m, Eq y) => Splitter m (Markup y x) () -- | 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. markedContent :: (Monad m, Eq y) => Splitter m (Markup y x) () -- | 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. markedWith :: (Monad m, Eq y) => (y -> Bool) -> Splitter m (Markup y x) () -- | 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. contentMarkedWith :: (Monad m, Eq y) => (y -> Bool) -> Splitter m (Markup y x) () -- | Splitter one feeds all input values to its true sink, -- treating every value as a separate section. one :: Monad m => Splitter m x () -- | 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. substring :: (Monad m, Eq x) => [x] -> Splitter m x () -- | The lowercase transforms all uppercase letters in the input to -- lowercase, leaving the rest unchanged. lowercase :: Monad m => Transducer m Char Char -- | The uppercase transforms all lowercase letters in the input to -- uppercase, leaving the rest unchanged. uppercase :: Monad m => Transducer m Char Char -- | Splitter whitespace feeds all white-space characters into its -- true sink, all others into false. whitespace :: Monad m => Splitter m Char () -- | Splitter letters feeds all alphabetical characters into its -- true sink, all other characters into | false. letters :: Monad m => Splitter m Char () -- | Splitter digits feeds all digits into its true sink, all -- other characters into false. digits :: Monad m => Splitter m Char () -- | 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". line :: Monad m => Splitter m Char () -- | Splitter nonEmptyLine feeds line-ends into its false -- sink, and all other characters into true. nonEmptyLine :: Monad m => Splitter m Char () -- | Converts a Consumer into a Transducer with no output. consumeBy :: Monad m => Consumer m x r -> Transducer m x y -- | 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 prepend :: Monad m => Producer m x r -> Transducer m x x -- | 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) append :: Monad m => Producer m x r -> Transducer m x x -- | The substitute combinator converts its argument producer to a -- Transducer that produces the same output, while consuming its -- entire input and ignoring it. substitute :: Monad m => Producer m y r -> Transducer m x y -- | Class PipeableComponentPair applies to any two components that -- can be combined into a third component with the following properties: -- -- class PipeableComponentPair m :: (* -> *) w c1 c2 c3 | c1 c2 -> c3, c1 c3 -> c2, c2 c3 -> c2, c1 -> m w, c2 -> m w, c3 -> m -- | Class PipeableComponentPair applies to any two components -- that can be combined into a third component with the following -- properties: -- -- (>->) :: (MonadParallel m, PipeableComponentPair m w c1 c2 c3) => c1 -> c2 -> c3 -- | Class JoinableComponentPair applies to any two components that -- can be combined into a third component with the following properties: -- -- 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 sequence :: JoinableComponentPair t1 t2 t3 m x y c1 c2 c3 => c1 -> c2 -> c3 -- | The join combinator may apply the components in any order. join :: (MonadParallel m, JoinableComponentPair t1 t2 t3 m x y c1 c2 c3) => c1 -> c2 -> c3 -- | 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. sNot :: Monad m => Splitter m x b -> Splitter m x b -- | 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. (>&) :: MonadParallel m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (b1, b2) -- | A >| combinator's input value can reach its false -- sink only by going through both argument splitters' false -- sinks. (>|) :: MonadParallel m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (Either b1 b2) -- | Combinator && is a pairwise logical conjunction of two -- splitters run in parallel on the same input. (&&) :: MonadParallel m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (b1, b2) -- | Combinator || is a pairwise logical disjunction of two -- splitters run in parallel on the same input. (||) :: MonadParallel m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (Either b1 b2) ifs :: (MonadParallel m, Branching c m x ()) => Splitter m x b -> c -> c -> c wherever :: MonadParallel m => Transducer m x x -> Splitter m x b -> Transducer m x x unless :: MonadParallel m => Transducer m x x -> Splitter m x b -> Transducer m x x select :: Monad m => Splitter m x b -> Transducer m x x -- | 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. while :: MonadParallel m => Transducer m x x -> Splitter m x b -> Transducer m x x -- | 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. nestedIn :: MonadParallel m => Splitter m x b -> Splitter m x b -> Splitter m x b -- | 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. foreach :: (MonadParallel m, Branching c m x ()) => Splitter m x b -> c -> c -> c -- | 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. having :: (MonadParallel m, Coercible x y) => Splitter m x b1 -> Splitter m y b2 -> Splitter m x b1 -- | 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. havingOnly :: (MonadParallel m, Coercible x y) => Splitter m x b1 -> Splitter m y b2 -> Splitter m x b1 -- | 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. followedBy :: MonadParallel m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (b1, b2) -- | The even combinator takes every input section that its argument -- splitter deems true, and feeds even ones into its -- true sink. The odd sections and parts of input that are -- false according to its argument splitter are fed to even -- splitter's false sink. even :: Monad m => Splitter m x b -> Splitter m x b -- | 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. first :: Monad m => Splitter m x b -> Splitter m x b -- | 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. uptoFirst :: Monad m => Splitter m x b -> Splitter m x b -- | 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. prefix :: Monad m => Splitter m x b -> Splitter m x b -- | 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. last :: Monad m => Splitter m x b -> Splitter m x b -- | 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. lastAndAfter :: Monad m => Splitter m x b -> Splitter m x b -- | 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. suffix :: Monad m => Splitter m x b -> Splitter m x b -- | 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. startOf :: Monad m => Splitter m x b -> Splitter m x (Maybe b) -- | 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. endOf :: Monad m => Splitter m x b -> Splitter m x (Maybe b) -- | 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. (...) :: MonadParallel m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x b1 splitterToMarker :: Monad m => Splitter m x b -> Transducer m x (Either (x, Bool) b) -- | Converts a splitter into a parser. parseRegions :: Monad m => Splitter m x b -> Parser m x b -- | Converts a boundary-marking splitter into a parser. parseNestedRegions :: Monad m => Splitter m x (Boundary b) -> Parser m x b -- | Converts a boundary-marking splitter into a parser. parseEachNestedRegion :: MonadParallel m => Splitter m x (Boundary b) -> Transducer m x y -> Transducer m x (Markup b y) -- | This splitter splits XML markup from data content. It is used by -- parseXMLTokens. xmlTokens :: Monad m => Splitter m Char (Boundary XMLToken) -- | The XML token parser. This parser converts plain text to parsed text, -- which is a precondition for using the remaining XML components. parseXMLTokens :: MonadParallel m => Transducer m Char (Markup XMLToken Text) -- | Converts an XML entity name into the text value it represents: -- expandXMLEntity "lt" = "<". expandXMLEntity :: String -> String data XMLToken StartTag :: XMLToken EndTag :: XMLToken EmptyTag :: XMLToken ElementName :: XMLToken AttributeName :: XMLToken AttributeValue :: XMLToken EntityReferenceToken :: XMLToken EntityName :: XMLToken ProcessingInstruction :: XMLToken ProcessingInstructionText :: XMLToken Comment :: XMLToken CommentText :: XMLToken StartMarkedSectionCDATA :: XMLToken EndMarkedSection :: XMLToken ErrorToken :: String -> XMLToken -- | Splits all top-level elements with all their content to true, -- all other input to false. xmlElement :: Monad m => Splitter m (Markup XMLToken Text) () -- | Splits the content of all top-level elements to true, their -- tags and intervening input to false. xmlElementContent :: Monad m => Splitter m (Markup XMLToken Text) () -- | Splits every element name, including the names of nested elements and -- names in end tags, to true, all the rest of input to -- false. xmlElementName :: Monad m => Splitter m (Markup XMLToken Text) () -- | Splits every attribute specification to true, everything else -- to false. xmlAttribute :: Monad m => Splitter m (Markup XMLToken Text) () -- | Splits every attribute name to true, all the rest of input to -- false. xmlAttributeName :: Monad m => Splitter m (Markup XMLToken Text) () -- | Splits every attribute value, excluding the quote delimiters, to -- true, all the rest of input to false. xmlAttributeValue :: Monad m => Splitter m (Markup XMLToken Text) () -- | Similiar to (Control.Concurrent.SCC.Combinators.having -- element), except it runs the argument splitter only on -- each element's start tag, not on the entire element with its content. xmlElementHavingTagWith :: MonadParallel m => Splitter m (Markup XMLToken Text) b -> Splitter m (Markup XMLToken Text) b -- | This module exports all of the SCC libraries. The exported combinators -- run their components by sequentially interleaving them. module Control.Concurrent.SCC.Sequential -- | A Sink can be used to yield values from any nested -- Coroutine computation whose functor provably descends from the -- functor a. It's the write-only end of a communication channel -- created by pipe. data Sink m :: (* -> *) a x -- | A Source can be used to read values into any nested -- Coroutine computation whose functor provably descends from the -- functor a. It's the read-only end of a communication channel -- created by pipe. 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 of functors that can be lifted. class (Functor a, Functor d) => AncestorFunctor a :: (* -> *) d :: (* -> *) -- | 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. pipe :: (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) -- | The pipeP function is equivalent to pipe, except it runs -- the producer and the consumer in parallel. pipeP :: (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) -- | A generic version of pipe. The first argument is used to -- combine two computation steps. pipeG :: (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) -- | A disconnected sink that ignores all values put into it. nullSink :: Monad m => Sink m a x -- | An empty source whose get always returns Nothing. nullSource :: Monad m => Source m a x -- | Function get tries to get a value from the given Source -- argument. The intervening Coroutine computations suspend all -- the way to the pipe function invocation that created the -- source. The function returns Nothing if the argument source is -- empty. get :: (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m (Maybe x) -- | Invokes its first argument with the value it gets from the source, if -- there is any to get. getWith :: (Monad m, AncestorFunctor a d) => (x -> Coroutine d m ()) -> Source m a x -> Coroutine d m () -- | Function peek acts the same way as get, but doesn't -- actually consume the value from the source; sequential calls to -- peek will always return the same value. peek :: (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m (Maybe x) -- | This function puts a value into the given Sink. The intervening -- Coroutine computations suspend up to the pipe invocation -- that has created the argument sink. put :: (Monad m, AncestorFunctor a d) => Sink m a x -> x -> Coroutine d m () -- | Like put, but returns a Bool that determines if the sink is -- still active. tryPut :: (Monad m, AncestorFunctor a d) => Sink m a x -> x -> Coroutine d m Bool -- | Converts a Sink on the ancestor functor a into a sink on -- the descendant functor d. liftSink :: (Monad m, AncestorFunctor a d) => Sink m a x -> Sink m d x -- | Converts a Source on the ancestor functor a into a -- source on the descendant functor d. liftSource :: (Monad m, AncestorFunctor a d) => Source m a x -> Source m d x -- | Copies all data from the source argument into the sink -- argument. pour :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => Source m a1 x -> Sink m a2 x -> Coroutine d m () -- | tee is similar to pour except it distributes every input -- value from its source argument into its both sink arguments. tee :: (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 () -- | Every value put into a teeSink result sink goes into its -- both argument sinks: put (teeSink s1 s2) x is equivalent to -- put s1 x >> put s2 x. The putChunk method -- returns the list of values that couldn't fit into the second sink. teeSink :: (Monad m, AncestorFunctor a1 a3, AncestorFunctor a2 a3) => Sink m a1 x -> Sink m a2 x -> Sink m a3 x -- | The Source returned by teeSource writes every value read -- from its argument source into the argument sink before providing it -- back. teeSource :: (Monad m, AncestorFunctor a1 a3, AncestorFunctor a2 a3) => Sink m a1 x -> Source m a2 x -> Source m a3 x -- | getList returns the list of all values generated by the source. getList :: (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m [x] -- | 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. putList :: (Monad m, AncestorFunctor a d) => [x] -> Sink m a x -> Coroutine d m [x] -- | Like putList, except it puts the contents of the given -- Seq into the sink. putQueue :: (Monad m, AncestorFunctor a d) => Seq x -> Sink m a x -> Coroutine d m [x] -- | Consumes values from the source as long as the ticker -- accepts them. getTicked :: (Monad m, AncestorFunctor a d) => Ticker x -> Source m a x -> Coroutine d m [x] -- | Consumes values from the source as long as each satisfies the -- predicate, then returns their list. getWhile :: (Monad m, AncestorFunctor a d) => (x -> Bool) -> Source m a x -> Coroutine d m [x] -- | 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. getUntil :: (Monad m, AncestorFunctor a d) => (x -> Bool) -> Source m a x -> Coroutine d m ([x], Maybe x) -- | Like pour, copies data from the source to the -- sink, but only as long as it satisfies the predicate. pourTicked :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => Ticker x -> Source m a1 x -> Sink m a2 x -> Coroutine d m () -- | Like pour, copies data from the source to the -- sink, but only as long as it satisfies the predicate. pourWhile :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m () -- | 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. pourUntil :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m (Maybe x) -- | An equivalent of map that works on a Sink instead of a -- list. The argument function is applied to every value vefore it's -- written to the sink argument. mapSink :: Monad m => (x -> y) -> Sink m a y -> Sink m a x -- | mapStream is like pour that applies the function -- f to each argument before passing it into the sink. mapStream :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m () -- | mapMaybeStream is to mapStream like mapMaybe is -- to map. mapMaybeStream :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Maybe y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m () -- | concatMapStream is to mapStream like concatMap is -- to map. concatMapStream :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> [y]) -> Source m a1 x -> Sink m a2 y -> Coroutine d m () -- | Like mapStream except it runs the argument function on whole -- chunks read from the input. mapStreamChunks :: (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => ([x] -> [y]) -> Source m a1 x -> Sink m a2 y -> Coroutine d m () -- | Similar to foldl, but reads the values from a Source -- instead of a list. foldStream :: (Monad m, AncestorFunctor a d) => (acc -> x -> acc) -> acc -> Source m a x -> Coroutine d m acc -- | 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. mapAccumStream :: (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 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. concatMapAccumStream :: (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 -- | Equivalent to partition. Takes a Source instead of a -- list argument and partitions its contents into the two Sink -- arguments. partitionStream :: (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 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 :: (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_ 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. mapMStream_ :: (Monad m, AncestorFunctor a d) => (x -> Coroutine d m ()) -> Source m a x -> Coroutine d m () -- | Like mapMStream_ except it runs the argument function on whole -- chunks read from the input. mapMStreamChunks_ :: (Monad m, AncestorFunctor a d) => ([x] -> Coroutine d m ()) -> Source m a x -> Coroutine d m () -- | An equivalent of filterM. Draws the values from a Source -- instead of a list, writes the filtered values to a Sink, and -- returns a Coroutine. filterMStream :: (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 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 :: (Monad m, AncestorFunctor a d) => (acc -> x -> Coroutine d m acc) -> acc -> Source m a x -> Coroutine d m acc -- | A variant of foldMStream that discards the final result value. foldMStream_ :: (Monad m, AncestorFunctor a d) => (acc -> x -> Coroutine d m acc) -> acc -> Source m a x -> Coroutine d m () -- | unfoldMStream is a version of unfoldr that writes the -- generated values into a Sink instead of returning a list. unfoldMStream :: (Monad m, AncestorFunctor a d) => (acc -> Coroutine d m (Maybe (x, acc))) -> acc -> Sink m a x -> Coroutine d m acc -- | unmapMStream_ is opposite of mapMStream_; it takes a -- Sink instead of a Source argument and writes the -- generated values into it. unmapMStream_ :: (Monad m, AncestorFunctor a d) => Coroutine d m (Maybe x) -> Sink m a x -> Coroutine d m () -- | Like unmapMStream_ but writing whole chunks of generated data -- into the argument sink. unmapMStreamChunks_ :: (Monad m, AncestorFunctor a d) => Coroutine d m [x] -> Sink m a x -> Coroutine d m () -- | 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. zipWithMStream :: (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 is equivalent to zipWithMStream, but -- it consumes the two sources in parallel. parZipWithMStream :: (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 () -- | A coroutine that has no inputs nor outputs - and therefore may not -- suspend at all, which means it's not really a coroutine. newtype Performer m r Performer :: m r -> Performer m r perform :: Performer m r -> m r type OpenConsumer m a d x r = AncestorFunctor a d => Source m a x -> Coroutine d m r -- | A coroutine that consumes values from a Source. newtype Consumer m x r Consumer :: (forall a d. OpenConsumer m a d x r) -> Consumer m x r consume :: Consumer m x r -> 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 -- | A coroutine that produces values and puts them into a Sink. newtype Producer m x r Producer :: (forall a d. OpenProducer m a d x r) -> Producer m x r produce :: Producer m x r -> 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 -- | 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. newtype Transducer m x y Transducer :: (forall a1 a2 d. OpenTransducer m a1 a2 d x y ()) -> Transducer m x y transduce :: Transducer m x y -> 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 -- | 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. newtype Splitter m x b Splitter :: (forall a1 a2 a3 a4 d. OpenSplitter m a1 a2 a3 a4 d x b ()) -> Splitter m x b split :: Splitter m x b -> forall a1 a2 a3 a4 d. OpenSplitter m a1 a2 a3 a4 d x b () -- | A Boundary value is produced to mark either a Start and -- End of a region of data, or an arbitrary Point in data. -- A Point is semantically equivalent to a Start -- immediately followed by End. data Boundary y Start :: y -> Boundary y End :: y -> Boundary y Point :: y -> Boundary y -- | Type of values in a markup-up stream. The Content constructor -- wraps the actual data. data Markup y x Content :: x -> Markup y x Markup :: (Boundary y) -> Markup y x -- | A parser is a transducer that marks up its input. type Parser m x b = Transducer m x (Markup b x) -- | Branching is a type class representing all types that can act -- as consumers, namely Consumer, Transducer, and -- Splitter. class Branching c m :: (* -> *) x r | c -> m x combineBranches :: Branching c m x r => (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 -- | Creates a proper Consumer from a function that is, but can't be -- proven to be, an OpenConsumer. isolateConsumer :: Monad m => (forall d. Functor d => Source m d x -> Coroutine d m r) -> Consumer m x r -- | Creates a proper Producer from a function that is, but can't be -- proven to be, an OpenProducer. isolateProducer :: Monad m => (forall d. Functor d => Sink m d x -> Coroutine d m r) -> Producer m x r -- | Creates a proper Transducer from a function that is, but can't -- be proven to be, an OpenTransducer. isolateTransducer :: Monad m => (forall d. Functor d => Source m d x -> Sink m d y -> Coroutine d m ()) -> Transducer m x y -- | Creates a proper Splitter from a function that is, but can't be -- proven to be, an OpenSplitter. isolateSplitter :: 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 -- | Function oneToOneTransducer takes a function that maps one -- input value to one output value each, and lifts it into a -- Transducer. oneToOneTransducer :: Monad m => (x -> y) -> Transducer m x y -- | Function statelessTransducer takes a function that maps one -- input value into a list of output values, and lifts it into a -- Transducer. statelessTransducer :: Monad m => (x -> [y]) -> Transducer m x y -- | 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. statefulTransducer :: Monad m => (state -> x -> (state, [y])) -> state -> Transducer m x y -- | Function statelessSplitter takes a function that assigns a -- Boolean value to each input item and lifts it into a Splitter. statelessSplitter :: Monad m => (x -> Bool) -> Splitter m x b -- | Function statefulSplitter takes a state-converting function -- that also 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 () -- | Two streams of Coercible types can be unambigously converted -- one to another. class Coercible x y coerce :: (Coercible x y, Monad m) => Transducer m x y adaptConsumer :: (Coercible x y, Monad m) => Consumer m y r -> Consumer m x r adaptProducer :: (Coercible x y, Monad m) => Producer m x r -> Producer m y r -- | Adjusts the argument splitter to split the stream of a data type -- Isomorphic to the type it was meant to split. adaptSplitter :: (Monad m, Coercible x y, Coercible y x) => Splitter m x b -> Splitter m y b -- | Reads the named file and feeds the given sink from its contents. fromFile :: String -> Producer IO Char () -- | Feeds the given sink from the open text file handle. fromHandle :: Handle -> Producer IO Char () -- | Producer fromStdIn feeds the given sink from the standard -- input. fromStdIn :: Producer IO Char () -- | Feeds the given sink from the open binary file handle. The -- argument chunkSize determines the size of the chunks read from -- the handle. fromBinaryHandle :: Handle -> Int -> Producer IO ByteString () -- | Appends the given source to the named text file. appendFile :: String -> Consumer IO Char () -- | Creates the named text file and writes the entire given source to it. toFile :: String -> Consumer IO Char () -- | Copies the given source into the open text file handle. toHandle :: Handle -> Consumer IO Char () -- | Consumer toStdOut copies the given source into the standard -- output. toStdOut :: Consumer IO Char () -- | Copies the given source into the open binary file handle. toBinaryHandle :: Handle -> Consumer IO ByteString () -- | Produces the contents of the given list argument. fromList :: Monad m => [x] -> Producer m x () -- | The suppress consumer suppresses all input it receives. It is -- equivalent to substitute [] suppress :: Monad m => Consumer m x () -- | The erroneous consumer reports an error if any input reaches -- it. erroneous :: Monad m => String -> Consumer m x () -- | Collects the entire input source into a list. toList :: Monad m => Consumer m x [x] -- | Transducer parse prepares input content for subsequent parsing. parse :: Monad m => Transducer m x (Markup y x) -- | Transducer unparse removes all markup from its input and passes -- the content through. unparse :: Monad m => Transducer m (Markup b x) x -- | Performs the same task as the substring splitter, but instead -- of splitting it outputs the input as Markup x -- OccurenceTag in order to distinguish overlapping strings. parseSubstring :: (Monad m, Eq x) => [x] -> Parser m x OccurenceTag -- | Used by parseSubstring to distinguish between overlapping -- substrings. data OccurenceTag -- | The count transducer counts all its input values and outputs -- the final tally. count :: Monad m => Transducer m x Integer -- | Converts each input value x to show x. toString :: (Monad m, Show x) => Transducer m x String -- | Transducer group collects all its input values into a single -- list. group :: Monad m => Transducer m x [x] -- | Transducer concatenate flattens the input stream of lists of -- values into the output stream of values. concatenate :: Monad m => Transducer m [x] x -- | Same as concatenate except it inserts the given separator list -- between every two input lists. concatSeparate :: Monad m => [x] -> Transducer m [x] x -- | Splitter everything feeds its entire input into its true -- sink. everything :: Monad m => Splitter m x () -- | Splitter nothing feeds its entire input into its false -- sink. nothing :: Monad m => Splitter m x () -- | Splitter marked passes all marked-up input sections to its -- true sink, and all unmarked input to its false sink. marked :: (Monad m, Eq y) => Splitter m (Markup y x) () -- | 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. markedContent :: (Monad m, Eq y) => Splitter m (Markup y x) () -- | 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. markedWith :: (Monad m, Eq y) => (y -> Bool) -> Splitter m (Markup y x) () -- | 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. contentMarkedWith :: (Monad m, Eq y) => (y -> Bool) -> Splitter m (Markup y x) () -- | Splitter one feeds all input values to its true sink, -- treating every value as a separate section. one :: Monad m => Splitter m x () -- | 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. substring :: (Monad m, Eq x) => [x] -> Splitter m x () -- | The lowercase transforms all uppercase letters in the input to -- lowercase, leaving the rest unchanged. lowercase :: Monad m => Transducer m Char Char -- | The uppercase transforms all lowercase letters in the input to -- uppercase, leaving the rest unchanged. uppercase :: Monad m => Transducer m Char Char -- | Splitter whitespace feeds all white-space characters into its -- true sink, all others into false. whitespace :: Monad m => Splitter m Char () -- | Splitter letters feeds all alphabetical characters into its -- true sink, all other characters into | false. letters :: Monad m => Splitter m Char () -- | Splitter digits feeds all digits into its true sink, all -- other characters into false. digits :: Monad m => Splitter m Char () -- | 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". line :: Monad m => Splitter m Char () -- | Splitter nonEmptyLine feeds line-ends into its false -- sink, and all other characters into true. nonEmptyLine :: Monad m => Splitter m Char () -- | Converts a Consumer into a Transducer with no output. consumeBy :: Monad m => Consumer m x r -> Transducer m x y -- | 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 prepend :: Monad m => Producer m x r -> Transducer m x x -- | 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) append :: Monad m => Producer m x r -> Transducer m x x -- | The substitute combinator converts its argument producer to a -- Transducer that produces the same output, while consuming its -- entire input and ignoring it. substitute :: Monad m => Producer m y r -> Transducer m x y -- | Class PipeableComponentPair applies to any two components that -- can be combined into a third component with the following properties: -- -- class PipeableComponentPair m :: (* -> *) w c1 c2 c3 | c1 c2 -> c3, c1 c3 -> c2, c2 c3 -> c2, c1 -> m w, c2 -> m w, c3 -> m -- | Class PipeableComponentPair applies to any two components -- that can be combined into a third component with the following -- properties: -- -- (>->) :: (Monad m, PipeableComponentPair m w c1 c2 c3) => c1 -> c2 -> c3 -- | Class JoinableComponentPair applies to any two components that -- can be combined into a third component with the following properties: -- -- 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 sequence :: JoinableComponentPair t1 t2 t3 m x y c1 c2 c3 => c1 -> c2 -> c3 -- | The join combinator may apply the components in any order. join :: (Monad m, JoinableComponentPair t1 t2 t3 m x y c1 c2 c3) => c1 -> c2 -> c3 -- | 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. sNot :: Monad m => Splitter m x b -> Splitter m x b -- | 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 (b1, b2) -- | A >| combinator's input value can reach its false -- sink only by going through both argument splitters' false -- sinks. (>|) :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (Either b1 b2) -- | 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 (b1, b2) -- | Combinator || is a pairwise logical disjunction 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) 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 :: Monad m => Splitter m x b -> Transducer m x x -- | 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. while :: Monad m => Transducer m x x -> Splitter m x b -> Transducer m x x -- | 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. nestedIn :: Monad m => Splitter m x b -> Splitter m x b -> Splitter m x b -- | 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. foreach :: (Monad m, Branching c m x ()) => Splitter m x b -> c -> c -> c -- | 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. having :: (Monad m, Coercible x y) => Splitter m x b1 -> Splitter m y b2 -> Splitter m x b1 -- | 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. havingOnly :: (Monad m, Coercible x y) => Splitter m x b1 -> Splitter m y b2 -> Splitter m x b1 -- | 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. followedBy :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x (b1, b2) -- | The even combinator takes every input section that its argument -- splitter deems true, and feeds even ones into its -- true sink. The odd sections and parts of input that are -- false according to its argument splitter are fed to even -- splitter's false sink. even :: Monad m => Splitter m x b -> Splitter m x b -- | 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. first :: Monad m => Splitter m x b -> Splitter m x b -- | 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. uptoFirst :: Monad m => Splitter m x b -> Splitter m x b -- | 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. prefix :: Monad m => Splitter m x b -> Splitter m x b -- | 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. last :: Monad m => Splitter m x b -> Splitter m x b -- | 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. lastAndAfter :: Monad m => Splitter m x b -> Splitter m x b -- | 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. suffix :: Monad m => Splitter m x b -> Splitter m x b -- | 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. startOf :: Monad m => Splitter m x b -> Splitter m x (Maybe b) -- | 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. endOf :: Monad m => Splitter m x b -> Splitter m x (Maybe b) -- | 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. (...) :: Monad m => Splitter m x b1 -> Splitter m x b2 -> Splitter m x b1 splitterToMarker :: Monad m => Splitter m x b -> Transducer m x (Either (x, Bool) b) -- | Converts a splitter into a parser. parseRegions :: Monad m => Splitter m x b -> Parser m x b -- | Converts a boundary-marking splitter into a parser. parseNestedRegions :: Monad m => Splitter m x (Boundary b) -> Parser m x b -- | 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) -- | This splitter splits XML markup from data content. It is used by -- parseXMLTokens. xmlTokens :: Monad m => Splitter m Char (Boundary XMLToken) -- | The XML token parser. This parser converts plain text to parsed text, -- which is a precondition for using the remaining XML components. parseXMLTokens :: MonadParallel m => Transducer m Char (Markup XMLToken Text) -- | Converts an XML entity name into the text value it represents: -- expandXMLEntity "lt" = "<". expandXMLEntity :: String -> String data XMLToken StartTag :: XMLToken EndTag :: XMLToken EmptyTag :: XMLToken ElementName :: XMLToken AttributeName :: XMLToken AttributeValue :: XMLToken EntityReferenceToken :: XMLToken EntityName :: XMLToken ProcessingInstruction :: XMLToken ProcessingInstructionText :: XMLToken Comment :: XMLToken CommentText :: XMLToken StartMarkedSectionCDATA :: XMLToken EndMarkedSection :: XMLToken ErrorToken :: String -> XMLToken -- | Splits all top-level elements with all their content to true, -- all other input to false. xmlElement :: Monad m => Splitter m (Markup XMLToken Text) () -- | Splits the content of all top-level elements to true, their -- tags and intervening input to false. xmlElementContent :: Monad m => Splitter m (Markup XMLToken Text) () -- | Splits every element name, including the names of nested elements and -- names in end tags, to true, all the rest of input to -- false. xmlElementName :: Monad m => Splitter m (Markup XMLToken Text) () -- | Splits every attribute specification to true, everything else -- to false. xmlAttribute :: Monad m => Splitter m (Markup XMLToken Text) () -- | Splits every attribute name to true, all the rest of input to -- false. xmlAttributeName :: Monad m => Splitter m (Markup XMLToken Text) () -- | Splits every attribute value, excluding the quote delimiters, to -- true, all the rest of input to false. xmlAttributeValue :: Monad m => Splitter m (Markup XMLToken Text) () -- | Similiar to (Control.Concurrent.SCC.Combinators.having -- element), except it runs the argument splitter only on -- each element's start tag, not on the entire element with its content. xmlElementHavingTagWith :: MonadParallel m => Splitter m (Markup XMLToken Text) b -> Splitter m (Markup XMLToken Text) b