| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Control.Concurrent.SCC.Configurable
Contents
Description
This module exports the entire SCC library except for low-level modules Control.Concurrent.SCC.Streams and Control.Concurrent.SCC.Types. The exported combinators can be configured to run their components sequentially or in parallel depending on the available resources.
- type PerformerComponent m r = Component (Performer m r)
- type ConsumerComponent m x r = Component (Consumer m x r)
- type ProducerComponent m x r = Component (Producer m x r)
- type TransducerComponent m x y = Component (Transducer m x y)
- type SplitterComponent m x = Component (Splitter m x)
- ioCost :: Int
- coerce :: (Monad m, Coercible x y) => TransducerComponent m x y
- adaptConsumer :: (Monad m, Monoid x, Monoid y, Coercible x y) => ConsumerComponent m y r -> ConsumerComponent m x r
- adaptProducer :: (Monad m, Monoid x, Monoid y, Coercible x y) => ProducerComponent m x r -> ProducerComponent m y r
- adaptSplitter :: (Monad m, Monoid x, Monoid y, Coercible x y, Coercible y x) => SplitterComponent m x -> SplitterComponent m y
- fromStdIn :: ProducerComponent IO Text ()
- fromFile :: String -> ProducerComponent IO Text ()
- fromHandle :: Handle -> ProducerComponent IO Text ()
- toStdOut :: ConsumerComponent IO Text ()
- toFile :: String -> ConsumerComponent IO Text ()
- appendFile :: String -> ConsumerComponent IO Text ()
- toHandle :: Handle -> ConsumerComponent IO Text ()
- produceFrom :: (Monad m, MonoidNull x) => x -> ProducerComponent m x ()
- consumeInto :: (Monad m, Monoid x) => ConsumerComponent m x x
- suppress :: Monad m => ConsumerComponent m x ()
- erroneous :: (Monad m, MonoidNull x) => String -> ConsumerComponent m x ()
- id :: (Monad m, Monoid x) => TransducerComponent m x x
- unparse :: (Monad m, Monoid x) => TransducerComponent m [Markup b x] x
- parse :: (Monad m, Monoid x) => ParserComponent m x y
- lowercase :: Monad m => TransducerComponent m String String
- uppercase :: Monad m => TransducerComponent m String String
- count :: (Monad m, FactorialMonoid x) => TransducerComponent m x [Integer]
- toString :: (Monad m, Show x) => TransducerComponent m [x] [String]
- parseSubstring :: (Monad m, Eq x, LeftCancellativeMonoid x, FactorialMonoid x) => x -> ParserComponent m x OccurenceTag
- group :: (Monad m, Monoid x) => TransducerComponent m x [x]
- concatenate :: (Monad m, Monoid x) => TransducerComponent m [x] x
- concatSeparate :: (Monad m, MonoidNull x) => x -> TransducerComponent m [x] x
- everything :: Monad m => SplitterComponent m x
- nothing :: (Monad m, Monoid x) => SplitterComponent m x
- marked :: (Monad m, Eq y) => SplitterComponent m [Markup y x]
- markedContent :: (Monad m, Eq y) => SplitterComponent m [Markup y x]
- markedWith :: (Monad m, Eq y) => (y -> Bool) -> SplitterComponent m [Markup y x]
- contentMarkedWith :: (Monad m, Eq y) => (y -> Bool) -> SplitterComponent m [Markup y x]
- one :: (Monad m, FactorialMonoid x) => SplitterComponent m x
- substring :: (Monad m, Eq x, LeftCancellativeMonoid x, FactorialMonoid x) => x -> SplitterComponent m x
- whitespace :: Monad m => SplitterComponent m String
- letters :: Monad m => SplitterComponent m String
- digits :: Monad m => SplitterComponent m String
- nonEmptyLine :: Monad m => SplitterComponent m String
- line :: Monad m => SplitterComponent m String
- consumeBy :: Monad m => ConsumerComponent m x r -> TransducerComponent m x y
- (>->) :: (MonadParallel m, PipeableComponentPair m w c1 c2 c3) => Component c1 -> Component c2 -> Component c3
- join :: (MonadParallel m, JoinableComponentPair t1 t2 t3 m x y c1 c2 c3) => Component c1 -> Component c2 -> Component c3
- sequence :: JoinableComponentPair t1 t2 t3 m x y c1 c2 c3 => Component c1 -> Component c2 -> Component c3
- prepend :: Monad m => ProducerComponent m x r -> TransducerComponent m x x
- append :: Monad m => ProducerComponent m x r -> TransducerComponent m x x
- substitute :: (Monad m, Monoid x) => ProducerComponent m y r -> TransducerComponent m x y
- snot :: (Monad m, Monoid x) => SplitterComponent m x -> SplitterComponent m x
- (>&) :: (MonadParallel m, Monoid x) => SplitterComponent m x -> SplitterComponent m x -> SplitterComponent m x
- (>|) :: (MonadParallel m, Monoid x) => SplitterComponent m x -> SplitterComponent m x -> SplitterComponent m x
- (&&) :: (MonadParallel m, FactorialMonoid x) => SplitterComponent m x -> SplitterComponent m x -> SplitterComponent m x
- (||) :: (MonadParallel m, FactorialMonoid x) => SplitterComponent m x -> SplitterComponent m x -> SplitterComponent m x
- while :: (MonadParallel m, MonoidNull x) => TransducerComponent m x x -> SplitterComponent m x -> TransducerComponent m x x
- nestedIn :: (MonadParallel m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x -> SplitterComponent m x
- foreach :: (MonadParallel m, MonoidNull x, Branching c m x ()) => SplitterComponent m x -> Component c -> Component c -> Component c
- having :: (MonadParallel m, MonoidNull x, MonoidNull y, Coercible x y) => SplitterComponent m x -> SplitterComponent m y -> SplitterComponent m x
- havingOnly :: (MonadParallel m, MonoidNull x, MonoidNull y, Coercible x y) => SplitterComponent m x -> SplitterComponent m y -> SplitterComponent m x
- followedBy :: (MonadParallel m, FactorialMonoid x) => SplitterComponent m x -> SplitterComponent m x -> SplitterComponent m x
- even :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x
- first :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x
- uptoFirst :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x
- prefix :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x
- last :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x
- lastAndAfter :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x
- suffix :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x
- startOf :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x
- endOf :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x
- (...) :: (MonadParallel m, FactorialMonoid x) => SplitterComponent m x -> SplitterComponent m x -> SplitterComponent m x
- parseRegions :: (Monad m, MonoidNull x) => SplitterComponent m x -> ParserComponent m x ()
- xmlTokens :: Monad m => SplitterComponent m Text
- xmlParseTokens :: MonadParallel m => TransducerComponent m Text [Markup XMLToken Text]
- xmlElement :: Monad m => SplitterComponent m [Markup XMLToken Text]
- xmlElementContent :: Monad m => SplitterComponent m [Markup XMLToken Text]
- xmlElementHavingTagWith :: MonadParallel m => SplitterComponent m [Markup XMLToken Text] -> SplitterComponent m [Markup XMLToken Text]
- xmlAttribute :: Monad m => SplitterComponent m [Markup XMLToken Text]
- xmlElementName :: Monad m => SplitterComponent m [Markup XMLToken Text]
- xmlAttributeName :: Monad m => SplitterComponent m [Markup XMLToken Text]
- xmlAttributeValue :: Monad m => SplitterComponent m [Markup XMLToken Text]
- data Component c = Component {- name :: String
- subComponents :: [AnyComponent]
- maxUsableThreads :: Int
- usingThreads :: Int -> Component c
- usedThreads :: Int
- cost :: Int
- with :: c
 
- showComponentTree :: forall c. Component c -> String
- atomic :: String -> Int -> c -> Component c
- lift :: Int -> String -> (c1 -> c2) -> Component c1 -> Component c2
- liftParallelPair :: String -> (Bool -> c1 -> c2 -> c3) -> Component c1 -> Component c2 -> Component c3
- liftSequentialPair :: String -> (c1 -> c2 -> c3) -> Component c1 -> Component c2 -> Component c3
- parallelRouterAndBranches :: String -> (Bool -> c1 -> c2 -> c3 -> c4) -> Component c1 -> Component c2 -> Component c3 -> Component c4
- recursiveComponentTree :: forall c1 c2. String -> (Bool -> c1 -> c2 -> c2) -> Component c1 -> Component c2
- expandXMLEntity :: String -> String
Configurable component types
type PerformerComponent m r = Component (Performer m r) Source
A component that performs a computation with no inputs nor outputs is a PerformerComponent.
type ConsumerComponent m x r = Component (Consumer m x r) Source
A component that consumes values from a Source is called ConsumerComponent.
type ProducerComponent m x r = Component (Producer m x r) Source
A component that produces values and puts them into a Sink is called ProducerComponent.
type TransducerComponent m x y = Component (Transducer m x y) Source
The TransducerComponent type represents computations that transform a data stream.
type SplitterComponent m x = Component (Splitter m x) Source
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.
Coercible class
coerce :: (Monad m, Coercible x y) => TransducerComponent m x y Source
A TransducerComponent that converts a stream of one type to another.
adaptConsumer :: (Monad m, Monoid x, Monoid y, Coercible x y) => ConsumerComponent m y r -> ConsumerComponent m x r Source
Adjusts the argument consumer to consume the stream of a data type coercible to the type it was meant to consume.
adaptProducer :: (Monad m, Monoid x, Monoid y, Coercible x y) => ProducerComponent m x r -> ProducerComponent m y r Source
Adjusts the argument producer to produce the stream of a data type coercible from the type it was meant to produce.
Splitter isomorphism
adaptSplitter :: (Monad m, Monoid x, Monoid y, Coercible x y, Coercible y x) => SplitterComponent m x -> SplitterComponent m y Source
Adjusts the argument splitter to split the stream of a data type isomorphic to the type it was meant to split.
I/O components
I/O producers
fromStdIn :: ProducerComponent IO Text () Source
ProducerComponent fromStdIn feeds the given sink from the standard input.
fromFile :: String -> ProducerComponent IO Text () Source
ProducerComponent fromFile opens the named file and feeds the given sink from its contents.
fromHandle :: Handle -> ProducerComponent IO Text () Source
ProducerComponent fromHandle feeds the given sink from the open file handle.
I/O consumers
toStdOut :: ConsumerComponent IO Text () Source
ConsumerComponent toStdOut copies the given source into the standard output.
toFile :: String -> ConsumerComponent IO Text () Source
ConsumerComponent toFile opens the named file and copies the given source into it.
appendFile :: String -> ConsumerComponent IO Text () Source
ConsumerComponent appendFile opens the name file and appends the given source to it.
toHandle :: Handle -> ConsumerComponent IO Text () Source
ConsumerComponent toHandle copies the given source into the open file handle.
Generic components
produceFrom :: (Monad m, MonoidNull x) => x -> ProducerComponent m x () Source
produceFrom produces the contents of the given argument.
Generic consumers
consumeInto :: (Monad m, Monoid x) => ConsumerComponent m x x Source
ConsumerComponent consumeInto collects the given source into the return value.
suppress :: Monad m => ConsumerComponent m x () Source
The suppress consumer suppresses all input it receives. It is equivalent to substitute []
erroneous :: (Monad m, MonoidNull x) => String -> ConsumerComponent m x () Source
The erroneous consumer reports an error if any input reaches it.
Generic transducers
id :: (Monad m, Monoid x) => TransducerComponent m x x Source
TransducerComponent id passes its input through unmodified.
unparse :: (Monad m, Monoid x) => TransducerComponent m [Markup b x] x Source
TransducerComponent unparse removes all markup from its input and passes the content through.
parse :: (Monad m, Monoid x) => ParserComponent m x y Source
TransducerComponent parse prepares input content for subsequent parsing.
lowercase :: Monad m => TransducerComponent m String String Source
The lowercase transforms all uppercase letters in the input to lowercase, leaving the rest unchanged.
uppercase :: Monad m => TransducerComponent m String String Source
The uppercase transforms all lowercase letters in the input to uppercase, leaving the rest unchanged.
count :: (Monad m, FactorialMonoid x) => TransducerComponent m x [Integer] Source
The count transducer counts all its input values and outputs the final tally.
toString :: (Monad m, Show x) => TransducerComponent m [x] [String] Source
Converts each input value x to show x.
parseSubstring :: (Monad m, Eq x, LeftCancellativeMonoid x, FactorialMonoid x) => x -> ParserComponent m x OccurenceTag Source
Performs the same task as the substring splitter, but instead of splitting it outputs the input as Markup x
 OccurenceTag
List stream transducers
group :: (Monad m, Monoid x) => TransducerComponent m x [x] Source
TransducerComponent group collects all its input into a single list item.
concatenate :: (Monad m, Monoid x) => TransducerComponent m [x] x Source
TransducerComponent concatenate flattens the input stream of lists of values into the output stream of values.
concatSeparate :: (Monad m, MonoidNull x) => x -> TransducerComponent m [x] x Source
Same as concatenate except it inserts the given separator list between every two input lists.
Generic splitters
everything :: Monad m => SplitterComponent m x Source
SplitterComponent everything feeds its entire input into its true sink.
nothing :: (Monad m, Monoid x) => SplitterComponent m x Source
SplitterComponent nothing feeds its entire input into its false sink.
marked :: (Monad m, Eq y) => SplitterComponent m [Markup y x] Source
SplitterComponent marked passes all marked-up input sections to its true sink, and all unmarked input to its
 false sink.
markedContent :: (Monad m, Eq y) => SplitterComponent m [Markup y x] Source
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.
markedWith :: (Monad m, Eq y) => (y -> Bool) -> SplitterComponent m [Markup y x] Source
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.
contentMarkedWith :: (Monad m, Eq y) => (y -> Bool) -> SplitterComponent m [Markup y x] Source
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.
one :: (Monad m, FactorialMonoid x) => SplitterComponent m x Source
SplitterComponent one feeds all input values to its true sink, treating every value as a separate section.
substring :: (Monad m, Eq x, LeftCancellativeMonoid x, FactorialMonoid x) => x -> SplitterComponent m x Source
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 empty chunk on false.
Character stream components
whitespace :: Monad m => SplitterComponent m String Source
SplitterComponent whitespace feeds all white-space characters into its true sink, all others into false.
letters :: Monad m => SplitterComponent m String Source
SplitterComponent letters feeds all alphabetical characters into its true sink, all other characters into
 | false.
digits :: Monad m => SplitterComponent m String Source
SplitterComponent digits feeds all digits into its true sink, all other characters into false.
nonEmptyLine :: Monad m => SplitterComponent m String Source
SplitterComponent nonEmptyLine feeds line-ends into its false sink, and all other characters into true.
line :: Monad m => SplitterComponent m String Source
The sectioning splitter line feeds line-ends into its false sink, and line contents into true. A single
 line-end can be formed by any of the character sequences "\n", "\r", "\r\n", or "\n\r".
Consumer, producer, and transducer combinators
consumeBy :: Monad m => ConsumerComponent m x r -> TransducerComponent m x y Source
Converts a ConsumerComponent into a TransducerComponent with no output.
(>->) :: (MonadParallel m, PipeableComponentPair m w c1 c2 c3) => Component c1 -> Component c2 -> Component c3 Source
Class PipeableComponentPair applies to any two components that can be combined into a third component with the
 following properties:
- The input of the result, if any, becomes the input of the first component. - The output produced by the first child component is consumed by the second child component.
- The result output, if any, is the output of the second component.
 
join :: (MonadParallel m, JoinableComponentPair t1 t2 t3 m x y c1 c2 c3) => Component c1 -> Component c2 -> Component c3 Source
Class JoinableComponentPair applies to any two components that can be combined into a third component with the
 following properties:
- if both argument components consume input, the input of the combined component gets distributed to both components in parallel, - if both argument components produce output, the output of the combined component is a concatenation of the complete output from the first component followed by the complete output of the second component, and
 
The join combinator may apply the components in any order.
sequence :: JoinableComponentPair t1 t2 t3 m x y c1 c2 c3 => Component c1 -> Component c2 -> Component c3 Source
The sequence combinator makes sure its first argument has completed before using the second one.
prepend :: Monad m => ProducerComponent m x r -> TransducerComponent m x x Source
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
append :: Monad m => ProducerComponent m x r -> TransducerComponent m x x Source
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)
substitute :: (Monad m, Monoid x) => ProducerComponent m y r -> TransducerComponent m x y Source
The substitute combinator converts its argument producer to a transducer that produces the same output, while
 | consuming its entire input and ignoring it.
Splitter combinators
snot :: (Monad m, Monoid x) => SplitterComponent m x -> SplitterComponent m x Source
The snot (streaming not) combinator simply reverses the outputs of the argument splitter. In other words, data
 that the argument splitter sends to its true sink goes to the false sink of the result, and vice versa.
Pseudo-logic flow combinators
(>&) :: (MonadParallel m, Monoid x) => SplitterComponent m x -> SplitterComponent m x -> SplitterComponent m x Source
The >& combinator sends the true sink output of its left operand to the input of its right operand for further
 splitting. Both operands' false sinks are connected to the false sink of the combined splitter, but any input
 value to reach the true sink of the combined component data must be deemed true by both splitters.
(>|) :: (MonadParallel m, Monoid x) => SplitterComponent m x -> SplitterComponent m x -> SplitterComponent m x Source
A >| combinator's input value can reach its false sink only by going through both argument splitters' false
 sinks.
Zipping logic combinators
(&&) :: (MonadParallel m, FactorialMonoid x) => SplitterComponent m x -> SplitterComponent m x -> SplitterComponent m x Source
Combinator && is a pairwise logical conjunction of two splitters run in parallel on the same input.
(||) :: (MonadParallel m, FactorialMonoid x) => SplitterComponent m x -> SplitterComponent m x -> SplitterComponent m x Source
Combinator || is a pairwise logical disjunction of two splitters run in parallel on the same input.
Flow-control combinators
Recursive
while :: (MonadParallel m, MonoidNull x) => TransducerComponent m x x -> SplitterComponent m x -> TransducerComponent m x x Source
The recursive combinator while feeds the true sink of the argument splitter back to itself, modified by the
 argument transducer. Data fed to the splitter's false sink is passed on unmodified.
nestedIn :: (MonadParallel m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x -> SplitterComponent m x Source
The recursive combinator nestedIn combines two splitters into a mutually recursive loop acting as a single
 splitter.  The true sink of one of the argument splitters and false sink of the other become the true and false sinks
 of the loop.  The other two sinks are bound to the other splitter's source.  The use of nestedIn makes sense only
 on hierarchically structured streams. If we gave it some input containing a flat sequence of values, and assuming
 both component splitters are deterministic and stateless, an input value would either not loop at all or it would
 loop forever.
Section-based combinators
foreach :: (MonadParallel m, MonoidNull x, Branching c m x ()) => SplitterComponent m x -> Component c -> Component c -> Component c Source
The foreach combinator is similar to the combinator ifs in that it combines a splitter and two transducers into
 another transducer. However, in this case the transducers are re-instantiated for each consecutive portion of the
 input as the splitter chunks it up. Each contiguous portion of the input that the splitter sends to one of its two
 sinks gets transducered through the appropriate argument transducer as that transducer's whole input. As soon as the
 contiguous portion is finished, the transducer gets terminated.
having :: (MonadParallel m, MonoidNull x, MonoidNull y, Coercible x y) => SplitterComponent m x -> SplitterComponent m y -> SplitterComponent m x Source
The having combinator combines two pure splitters into a pure splitter. One splitter is used to chunk the input
 into contiguous portions. Its false sink is routed directly to the false sink of the combined splitter. The
 second splitter is instantiated and run on each portion of the input that goes to first splitter's true sink. If
 the second splitter sends any output at all to its true sink, the whole input portion is passed on to the true
 sink of the combined splitter, otherwise it goes to its false sink.
havingOnly :: (MonadParallel m, MonoidNull x, MonoidNull y, Coercible x y) => SplitterComponent m x -> SplitterComponent m y -> SplitterComponent m x Source
The havingOnly combinator is analogous to the having combinator, but it succeeds and passes each chunk of the
 input to its true sink only if the second splitter sends no part of it to its false sink.
followedBy :: (MonadParallel m, FactorialMonoid x) => SplitterComponent m x -> SplitterComponent m x -> SplitterComponent m x Source
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.
even :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x Source
first and its variants
first :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x Source
The result of combinator first behaves the same as the argument splitter up to and including the first portion of
 the input which goes into the argument's true sink. All input following the first true portion goes into the
 false sink.
uptoFirst :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x Source
The result of combinator uptoFirst takes all input up to and including the first portion of the input which goes
 into the argument's true sink and feeds it to the result splitter's true sink. All the rest of the input goes
 into the false sink. The only difference between first and uptoFirst combinators is in where they direct the
 false portion of the input preceding the first true part.
prefix :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x Source
The prefix combinator feeds its true sink only the prefix of the input that its argument feeds to its true
 sink.  All the rest of the input is dumped into the false sink of the result.
last and its variants
last :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x Source
The result of the combinator last is a splitter which directs all input to its false sink, up to the last
 portion of the input which goes to its argument's true sink. That portion of the input is the only one that goes to
 the resulting component's true sink.  The splitter returned by the combinator last has to buffer the previous two
 portions of its input, because it cannot know if a true portion of the input is the last one until it sees the end of
 the input or another portion succeeding the previous one.
lastAndAfter :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x Source
The result of the combinator lastAndAfter is a splitter which directs all input to its false sink, up to the
 last portion of the input which goes to its argument's true sink. That portion and the remainder of the input is
 fed to the resulting component's true sink. The difference between last and lastAndAfter combinators is where
 they feed the false portion of the input, if any, remaining after the last true part.
suffix :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x Source
The suffix combinator feeds its true sink only the suffix of the input that its argument feeds to its true
 sink.  All the rest of the input is dumped into the false sink of the result.
positional splitters
startOf :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x Source
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.
endOf :: (Monad m, MonoidNull x) => SplitterComponent m x -> SplitterComponent m x Source
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.
(...) :: (MonadParallel m, FactorialMonoid x) => SplitterComponent m x -> SplitterComponent m x -> SplitterComponent m x Source
Combinator ... tracks the running balance of difference between the number of preceding starts of sections
 considered true according to its first argument and the ones according to its second argument. The combinator
 passes to true all input values for which the difference balance is positive. This combinator is typically used
 with startOf and endOf in order to count entire input sections and ignore their lengths.
Parser support
parseRegions :: (Monad m, MonoidNull x) => SplitterComponent m x -> ParserComponent m x () Source
Converts a splitter into a parser.
Parsing XML
xmlTokens :: Monad m => SplitterComponent m Text Source
This splitter splits XML markup from data content. It is used by parseXMLTokens.
xmlParseTokens :: MonadParallel m => TransducerComponent m Text [Markup XMLToken Text] Source
The XML token parser. This parser converts plain text to parsed text, which is a precondition for using the remaining XML components.
XML splitters
xmlElement :: Monad m => SplitterComponent m [Markup XMLToken Text] Source
Splits all top-level elements with all their content to true, all other input to false.
xmlElementContent :: Monad m => SplitterComponent m [Markup XMLToken Text] Source
Splits the content of all top-level elements to true, their tags and intervening input to false.
xmlElementHavingTagWith :: MonadParallel m => SplitterComponent m [Markup XMLToken Text] -> SplitterComponent m [Markup XMLToken Text] Source
Similiar to (, except it runs the argument splitter
 only on each element's start tag, not on the entire element with its content.having element)
xmlAttribute :: Monad m => SplitterComponent m [Markup XMLToken Text] Source
Splits every attribute specification to true, everything else to false.
xmlElementName :: Monad m => SplitterComponent m [Markup XMLToken Text] Source
Splits every element name, including the names of nested elements and names in end tags, to true, all the rest of input to false.
xmlAttributeName :: Monad m => SplitterComponent m [Markup XMLToken Text] Source
Splits every attribute name to true, all the rest of input to false.
xmlAttributeValue :: Monad m => SplitterComponent m [Markup XMLToken Text] Source
Splits every attribute value, excluding the quote delimiters, to true, all the rest of input to false.
The Component type
A Component carries a value and metadata about the value. It can be configured to use a specific number of
 threads.
Constructors
| Component | |
| Fields 
 | |
Utility functions
showComponentTree :: forall c. Component c -> String Source
Show details of the given component's configuration.
Constructors
atomic :: String -> Int -> c -> Component c Source
Function atomic takes the component name and its cost creates a single-threaded component with no subcomponents.
Arguments
| :: Int | combinator cost | 
| -> String | name | 
| -> (c1 -> c2) | combinator | 
| -> Component c1 | |
| -> Component c2 | 
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.
liftParallelPair :: String -> (Bool -> c1 -> c2 -> c3) -> Component c1 -> Component c2 -> Component c3 Source
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.
liftSequentialPair :: String -> (c1 -> c2 -> c3) -> Component c1 -> Component c2 -> Component c3 Source
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.
parallelRouterAndBranches :: String -> (Bool -> c1 -> c2 -> c3 -> c4) -> Component c1 -> Component c2 -> Component c3 -> Component c4 Source
Combines three components into one. The first component runs in parallel with the latter two, which are considered alternative to each other.
recursiveComponentTree :: forall c1 c2. String -> (Bool -> c1 -> c2 -> c2) -> Component c1 -> Component c2 Source
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.
expandXMLEntity :: String -> String Source
Converts an XML entity name into the text value it represents: expandXMLEntity "lt" = "<".