Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module exports the entire SCC library except for low-level modules Control.Concurrent.SCC.Streams and Control.Concurrent.SCC.Types. The exported combinators run their components in parallel.
Synopsis
- class Coercible x y where
- coerce :: Monad m => Transducer m x y
- adaptConsumer :: (Monad m, Monoid x, Monoid y) => Consumer m y r -> Consumer m x r
- adaptProducer :: (Monad m, Monoid x, Monoid y) => Producer m x r -> Producer m y r
- adaptSplitter :: forall m x y b. (Monad m, Monoid x, Monoid y, Coercible x y, Coercible y x) => Splitter m x -> Splitter m y
- fromFile :: String -> Producer IO Text ()
- fromHandle :: Handle -> Producer IO Text ()
- fromStdIn :: Producer IO Text ()
- fromBinaryHandle :: Handle -> Int -> Producer IO ByteString ()
- appendFile :: String -> Consumer IO Text ()
- toFile :: String -> Consumer IO Text ()
- toHandle :: Handle -> Consumer IO Text ()
- toStdOut :: Consumer IO Text ()
- toBinaryHandle :: Handle -> Consumer IO ByteString ()
- produceFrom :: forall m x. (Monad m, MonoidNull x) => x -> Producer m x ()
- suppress :: forall m x. Monad m => Consumer m x ()
- erroneous :: forall m x. (Monad m, MonoidNull x) => String -> Consumer m x ()
- consumeInto :: forall m x. (Monad m, Monoid x) => Consumer m x x
- parse :: forall m x y. (Monad m, Monoid x) => Parser m x y
- unparse :: forall m x b. (Monad m, Monoid x) => Transducer m [Markup b x] x
- parseSubstring :: forall m x. (Monad m, Eq x, LeftReductiveMonoid x, FactorialMonoid x) => x -> Parser m x OccurenceTag
- data OccurenceTag
- count :: forall m x. (Monad m, FactorialMonoid x) => Transducer m x [Integer]
- toString :: forall m x. (Monad m, Show x) => Transducer m [x] [String]
- group :: forall m x. (Monad m, Monoid x) => Transducer m x [x]
- concatenate :: forall m x. (Monad m, Monoid x) => Transducer m [x] x
- concatSeparate :: forall m x. (Monad m, MonoidNull x) => x -> Transducer m [x] x
- everything :: forall m x. Monad m => Splitter m x
- nothing :: forall m x. (Monad m, Monoid x) => Splitter m x
- marked :: forall m x y. (Monad m, Eq y) => Splitter m [Markup y x]
- markedContent :: forall m x y. (Monad m, Eq y) => Splitter m [Markup y x]
- markedWith :: forall m x y. (Monad m, Eq y) => (y -> Bool) -> Splitter m [Markup y x]
- contentMarkedWith :: forall m x y. (Monad m, Eq y) => (y -> Bool) -> Splitter m [Markup y x]
- one :: forall m x. (Monad m, FactorialMonoid x) => Splitter m x
- substring :: forall m x. (Monad m, Eq x, LeftReductiveMonoid x, FactorialMonoid x) => x -> Splitter m x
- lowercase :: forall m. Monad m => Transducer m String String
- uppercase :: forall m. Monad m => Transducer m String String
- whitespace :: forall m. Monad m => Splitter m String
- letters :: forall m. Monad m => Splitter m String
- digits :: forall m. Monad m => Splitter m String
- line :: forall m. Monad m => Splitter m String
- nonEmptyLine :: forall m. Monad m => Splitter m String
- consumeBy :: forall m x y r. Monad m => Consumer m x r -> Transducer m x y
- prepend :: forall m x r. Monad m => Producer m x r -> Transducer m x x
- append :: forall m x r. Monad m => Producer m x r -> Transducer m x x
- substitute :: forall m x y r. (Monad m, Monoid x) => Producer m y r -> Transducer m x y
- class PipeableComponentPair (m :: * -> *) w c1 c2 c3 | c1 c2 -> c3, c1 c3 -> c2, c2 c3 -> c2, c1 -> m w, c2 -> m w, c3 -> m
- (>->) :: (MonadParallel m, PipeableComponentPair m w c1 c2 c3) => c1 -> c2 -> c3
- class (Monad m, CompatibleSignature c1 t1 m x y, CompatibleSignature c2 t2 m x y, CompatibleSignature c3 t3 m x y) => JoinableComponentPair t1 t2 t3 m x y c1 c2 c3 | c1 c2 -> c3, c1 -> t1 m, c2 -> t2 m, c3 -> t3 m x y, t1 m x y -> c1, t2 m x y -> c2, t3 m x y -> c3 where
- sequence :: c1 -> c2 -> c3
- join :: (MonadParallel m, JoinableComponentPair t1 t2 t3 m x y c1 c2 c3) => c1 -> c2 -> c3
- sNot :: forall m x. (Monad m, Monoid x) => Splitter m x -> Splitter m x
- (>&) :: (MonadParallel m, Monoid x) => Splitter m x -> Splitter m x -> Splitter m x
- (>|) :: (MonadParallel m, Monoid x) => Splitter m x -> Splitter m x -> Splitter m x
- (&&) :: (MonadParallel m, FactorialMonoid x) => Splitter m x -> Splitter m x -> Splitter m x
- (||) :: (MonadParallel m, FactorialMonoid x) => Splitter m x -> Splitter m x -> Splitter m x
- ifs :: (MonadParallel m, Monoid x, Branching c m x ()) => Splitter m x -> c -> c -> c
- wherever :: (MonadParallel m, Monoid x) => Transducer m x x -> Splitter m x -> Transducer m x x
- unless :: (MonadParallel m, Monoid x) => Transducer m x x -> Splitter m x -> Transducer m x x
- select :: forall m x. (Monad m, Monoid x) => Splitter m x -> Transducer m x x
- while :: (MonadParallel m, MonoidNull x) => Transducer m x x -> Splitter m x -> Transducer m x x
- nestedIn :: (MonadParallel m, MonoidNull x) => Splitter m x -> Splitter m x -> Splitter m x
- foreach :: (MonadParallel m, MonoidNull x, Branching c m x ()) => Splitter m x -> c -> c -> c
- having :: (MonadParallel m, MonoidNull x, MonoidNull y, Coercible x y) => Splitter m x -> Splitter m y -> Splitter m x
- havingOnly :: (MonadParallel m, MonoidNull x, MonoidNull y, Coercible x y) => Splitter m x -> Splitter m y -> Splitter m x
- followedBy :: (MonadParallel m, FactorialMonoid x) => Splitter m x -> Splitter m x -> Splitter m x
- even :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter m x
- first :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter m x
- uptoFirst :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter m x
- prefix :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter m x
- last :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter m x
- lastAndAfter :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter m x
- suffix :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter m x
- startOf :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter m x
- endOf :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter m x
- (...) :: (MonadParallel m, FactorialMonoid x) => Splitter m x -> Splitter m x -> Splitter m x
- splitterToMarker :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Transducer m x [(x, Bool)]
- parseRegions :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Parser m x ()
- xmlTokens :: Monad m => Splitter m Text
- parseXMLTokens :: Monad m => Transducer m Text [Markup XMLToken Text]
- expandXMLEntity :: String -> String
- data XMLToken
- xmlElement :: Monad m => Splitter m [Markup XMLToken Text]
- xmlElementContent :: Monad m => Splitter m [Markup XMLToken Text]
- xmlElementName :: Monad m => Splitter m [Markup XMLToken Text]
- xmlAttribute :: Monad m => Splitter m [Markup XMLToken Text]
- xmlAttributeName :: Monad m => Splitter m [Markup XMLToken Text]
- xmlAttributeValue :: Monad m => Splitter m [Markup XMLToken Text]
- xmlElementHavingTagWith :: forall m b. Monad m => Splitter m [Markup XMLToken Text] -> Splitter m [Markup XMLToken Text]
Coercible class
class Coercible x y where Source #
Two streams of Coercible
types can be unambigously converted one to another.
coerce :: Monad m => Transducer m x y Source #
A Transducer
that converts a stream of one type to another.
adaptConsumer :: (Monad m, Monoid x, Monoid y) => Consumer m y r -> Consumer m x r Source #
adaptProducer :: (Monad m, Monoid x, Monoid y) => Producer m x r -> Producer m y r Source #
Instances
Splitter isomorphism
adaptSplitter :: forall m x y b. (Monad m, Monoid x, Monoid y, Coercible x y, Coercible y x) => Splitter m x -> Splitter 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
fromFile :: String -> Producer IO Text () Source #
Reads the named file and feeds the given sink from its contents.
fromHandle :: Handle -> Producer IO Text () Source #
Feeds the given sink from the open text file handle.
fromStdIn :: Producer IO Text () Source #
Producer fromStdIn
feeds the given sink from the standard input.
fromBinaryHandle :: Handle -> Int -> Producer IO ByteString () Source #
Feeds the given sink from the open binary file handle. The argument chunkSize determines the size of the chunks read from the handle.
I/O consumers
appendFile :: String -> Consumer IO Text () Source #
Appends the given source to the named text file.
toFile :: String -> Consumer IO Text () Source #
Creates the named text file and writes the entire given source to it.
toHandle :: Handle -> Consumer IO Text () Source #
Copies the given source into the open text file handle.
toStdOut :: Consumer IO Text () Source #
Consumer toStdOut
copies the given source into the standard output.
toBinaryHandle :: Handle -> Consumer IO ByteString () Source #
Copies the given source into the open binary file handle.
Generic components
produceFrom :: forall m x. (Monad m, MonoidNull x) => x -> Producer m x () Source #
Produces the contents of the given argument.
Generic consumers
suppress :: forall m x. Monad m => Consumer m x () Source #
The suppress
consumer suppresses all input it receives. It is equivalent to substitute
[]
erroneous :: forall m x. (Monad m, MonoidNull x) => String -> Consumer m x () Source #
The erroneous
consumer reports an error if any input reaches it.
consumeInto :: forall m x. (Monad m, Monoid x) => Consumer m x x Source #
Collects the entire input source into the return value.
Generic transducers
parse :: forall m x y. (Monad m, Monoid x) => Parser m x y Source #
Transducer parse
prepares input content for subsequent parsing.
unparse :: forall m x b. (Monad m, Monoid x) => Transducer m [Markup b x] x Source #
Transducer unparse
removes all markup from its input and passes the content through.
parseSubstring :: forall m x. (Monad m, Eq x, LeftReductiveMonoid x, FactorialMonoid x) => x -> Parser m x OccurenceTag Source #
Performs the same task as the substring
splitter, but instead of splitting it outputs the input as
in order to distinguish overlapping strings.Markup
x
OccurenceTag
data OccurenceTag Source #
Used by parseSubstring
to distinguish between overlapping substrings.
Instances
Enum OccurenceTag Source # | |
Defined in Control.Concurrent.SCC.Primitives succ :: OccurenceTag -> OccurenceTag # pred :: OccurenceTag -> OccurenceTag # toEnum :: Int -> OccurenceTag # fromEnum :: OccurenceTag -> Int # enumFrom :: OccurenceTag -> [OccurenceTag] # enumFromThen :: OccurenceTag -> OccurenceTag -> [OccurenceTag] # enumFromTo :: OccurenceTag -> OccurenceTag -> [OccurenceTag] # enumFromThenTo :: OccurenceTag -> OccurenceTag -> OccurenceTag -> [OccurenceTag] # | |
Show OccurenceTag Source # | |
Defined in Control.Concurrent.SCC.Primitives showsPrec :: Int -> OccurenceTag -> ShowS # show :: OccurenceTag -> String # showList :: [OccurenceTag] -> ShowS # | |
Eq OccurenceTag Source # | |
Defined in Control.Concurrent.SCC.Primitives (==) :: OccurenceTag -> OccurenceTag -> Bool # (/=) :: OccurenceTag -> OccurenceTag -> Bool # |
count :: forall m x. (Monad m, FactorialMonoid x) => Transducer m x [Integer] Source #
The count
transducer counts all its input values and outputs the final tally.
toString :: forall m x. (Monad m, Show x) => Transducer m [x] [String] Source #
Converts each input value x
to show x
.
List stream transducers
The following laws hold:
group
>>>
concatenate
==id
concatenate
==concatSeparate
[]
group :: forall m x. (Monad m, Monoid x) => Transducer m x [x] Source #
Transducer group
collects all its input into a single list item.
concatenate :: forall m x. (Monad m, Monoid x) => Transducer m [x] x Source #
Transducer concatenate
flattens the input stream of lists of values into the output stream of values.
concatSeparate :: forall m x. (Monad m, MonoidNull x) => x -> Transducer m [x] x Source #
Same as concatenate
except it inserts the given separator list between every two input lists.
Generic splitters
everything :: forall m x. Monad m => Splitter m x Source #
Splitter everything
feeds its entire input into its true sink.
nothing :: forall m x. (Monad m, Monoid x) => Splitter m x Source #
Splitter nothing
feeds its entire input into its false sink.
marked :: forall m x y. (Monad m, Eq y) => Splitter m [Markup y x] Source #
Splitter marked
passes all marked-up input sections to its true sink, and all unmarked input to its
false sink.
markedContent :: forall m x y. (Monad m, Eq y) => Splitter m [Markup y x] Source #
Splitter markedContent
passes the content of all marked-up input sections to its true sink, takeWhile the
outermost tags and all unmarked input go to its false sink.
markedWith :: forall m x y. (Monad m, Eq y) => (y -> Bool) -> Splitter m [Markup y x] Source #
Splitter markedWith
passes input sections marked-up with the appropriate tag to its true sink, and the
rest of the input to its false sink. The argument select determines if the tag is appropriate.
contentMarkedWith :: forall m x y. (Monad m, Eq y) => (y -> Bool) -> Splitter m [Markup y x] Source #
Splitter contentMarkedWith
passes the content of input sections marked-up with the appropriate tag to
its true sink, and the rest of the input to its false sink. The argument select determines if the tag is
appropriate.
one :: forall m x. (Monad m, FactorialMonoid x) => Splitter m x Source #
Splitter one
feeds all input values to its true sink, treating every value as a separate section.
substring :: forall m x. (Monad m, Eq x, LeftReductiveMonoid x, FactorialMonoid x) => x -> Splitter m x Source #
Splitter substring
feeds to its true sink all input parts that match the contents of the given list
argument. If two overlapping parts of the input both match the argument, both are sent to true and each is preceded
by an empty chunk on false.
Character stream components
lowercase :: forall m. Monad m => Transducer m String String Source #
The lowercase
transforms all uppercase letters in the input to lowercase, leaving the rest unchanged.
uppercase :: forall m. Monad m => Transducer m String String Source #
The uppercase
transforms all lowercase letters in the input to uppercase, leaving the rest unchanged.
whitespace :: forall m. Monad m => Splitter m String Source #
Splitter whitespace
feeds all white-space characters into its true sink, all others into false.
letters :: forall m. Monad m => Splitter m String Source #
Splitter letters
feeds all alphabetical characters into its true sink, all other characters into
| false.
digits :: forall m. Monad m => Splitter m String Source #
Splitter digits
feeds all digits into its true sink, all other characters into false.
line :: forall m. Monad m => Splitter 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".
nonEmptyLine :: forall m. Monad m => Splitter m String Source #
Splitter nonEmptyLine
feeds line-ends into its false sink, and all other characters into true.
Consumer, producer, and transducer combinators
consumeBy :: forall m x y r. Monad m => Consumer m x r -> Transducer m x y Source #
Converts a Consumer
into a Transducer
with no output.
prepend :: forall m x r. Monad m => Producer m x r -> Transducer m x x Source #
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) id
append :: forall m x r. Monad m => Producer m x r -> Transducer m x x Source #
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
id
(substitute
suffix)
substitute :: forall m x y r. (Monad m, Monoid x) => Producer m y r -> Transducer 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.
class PipeableComponentPair (m :: * -> *) w c1 c2 c3 | c1 c2 -> c3, c1 c3 -> c2, c2 c3 -> c2, c1 -> m w, c2 -> m w, c3 -> m 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.
Instances
(>->) :: (MonadParallel m, PipeableComponentPair m w c1 c2 c3) => c1 -> c2 -> 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.
class (Monad m, CompatibleSignature c1 t1 m x y, CompatibleSignature c2 t2 m x y, CompatibleSignature c3 t3 m x y) => JoinableComponentPair t1 t2 t3 m x y c1 c2 c3 | c1 c2 -> c3, c1 -> t1 m, c2 -> t2 m, c3 -> t3 m x y, t1 m x y -> c1, t2 m x y -> c2, t3 m x y -> c3 where 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, and
- if both argument components produce output, the output of the combined component is a concatenation of the complete output from the first component followed by the complete output of the second component.
join :: (MonadParallel m, JoinableComponentPair t1 t2 t3 m x y c1 c2 c3) => c1 -> c2 -> c3 Source #
The join
combinator may apply the components in any order.
Splitter combinators
sNot :: forall m x. (Monad m, Monoid x) => Splitter m x -> Splitter 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
Combinators >&
and >|
are only pseudo-logic. While the laws of double negation and De Morgan's laws
hold, sAnd
and sOr
are in general not commutative, associative, nor idempotent. In the special case when all
argument splitters are stateless, such as those produced by statelessSplitter
,
these combinators do satisfy all laws of Boolean algebra.
(>&) :: (MonadParallel m, Monoid x) => Splitter m x -> Splitter m x -> Splitter 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) => Splitter m x -> Splitter m x -> Splitter 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
The &&
and ||
combinators run the argument splitters in parallel and combine their logical outputs using
the corresponding logical operation on each output pair, in a manner similar to zipWith
. They fully
satisfy the laws of Boolean algebra.
(&&) :: (MonadParallel m, FactorialMonoid x) => Splitter m x -> Splitter m x -> Splitter m x Source #
Combinator &&
is a pairwise logical conjunction of two splitters run in parallel on the same input.
(||) :: (MonadParallel m, FactorialMonoid x) => Splitter m x -> Splitter m x -> Splitter m x Source #
Combinator ||
is a pairwise logical disjunction of two splitters run in parallel on the same input.
Flow-control combinators
The following combinators resemble the common flow-control programming language constructs. Combinators
wherever
, unless
, and select
are just the special cases of the combinator ifs
.
wherever :: (MonadParallel m, Monoid x) => Transducer m x x -> Splitter m x -> Transducer m x x Source #
unless :: (MonadParallel m, Monoid x) => Transducer m x x -> Splitter m x -> Transducer m x x Source #
Recursive
while :: (MonadParallel m, MonoidNull x) => Transducer m x x -> Splitter m x -> Transducer 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) => Splitter m x -> Splitter m x -> Splitter 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
All combinators in this section use their Splitter
argument to determine the structure
of the input. Every contiguous portion of the input that gets passed to one or the other sink of the splitter is
treated as one section in the logical structure of the input stream. What is done with the section depends on the
combinator, but the sections, and therefore the logical structure of the input stream, are determined by the
argument splitter alone.
foreach :: (MonadParallel m, MonoidNull x, Branching c m x ()) => Splitter m x -> c -> c -> 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) => Splitter m x -> Splitter m y -> Splitter 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) => Splitter m x -> Splitter m y -> Splitter 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) => Splitter m x -> Splitter m x -> Splitter m x Source #
Combinator followedBy
treats its argument Splitter
s as patterns components and returns a Splitter
that
matches their concatenation. A section of input is considered true by the result iff its prefix is considered
true by argument s1 and the rest of the section is considered true by s2. The splitter s2 is started anew
after every section split to true sink by s1.
first and its variants
first :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter 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 :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter 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 :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter 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 :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter 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 :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter 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 :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter 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 :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter m x Source #
Splitter startOf
issues an empty true section at the beginning of every section considered true by its
argument splitter, otherwise the entire input goes into its false sink.
endOf :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Splitter m x Source #
Splitter endOf
issues an empty true section at the end of every section considered true by its argument
splitter, otherwise the entire input goes into its false sink.
(...) :: (MonadParallel m, FactorialMonoid x) => Splitter m x -> Splitter m x -> Splitter 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
splitterToMarker :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Transducer m x [(x, Bool)] Source #
parseRegions :: forall m x. (Monad m, MonoidNull x) => Splitter m x -> Parser m x () Source #
Converts a splitter into a parser.
Parsing XML
parseXMLTokens :: Monad m => Transducer 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.
expandXMLEntity :: String -> String Source #
Converts an XML entity name into the text value it represents: expandXMLEntity "lt" = "<"
.
Instances
XML splitters
xmlElement :: Monad m => Splitter m [Markup XMLToken Text] Source #
Splits all top-level elements with all their content to true, all other input to false.
xmlElementContent :: Monad m => Splitter m [Markup XMLToken Text] Source #
Splits the content of all top-level elements to true, their tags and intervening input to false.
xmlElementName :: Monad m => Splitter m [Markup XMLToken Text] Source #
Splits every element name, including the names of nested elements and names in end tags, to true, all the rest of input to false.
xmlAttribute :: Monad m => Splitter m [Markup XMLToken Text] Source #
Splits every attribute specification to true, everything else to false.
xmlAttributeName :: Monad m => Splitter m [Markup XMLToken Text] Source #
Splits every attribute name to true, all the rest of input to false.