scc-0.3: Streaming component combinators

Control.Concurrent.SCC.Components

Contents

Description

Module Components defines primitive components of Producer, Consumer, Transducer and Splitter types, defined in the Foundation and ComponentTypes modules.

Synopsis

Tag types

data OccurenceTag Source

Used by parseSubstring to distinguish between overlapping substrings.

List producers and consumers

fromList :: forall m x. (Monad m, Typeable x) => [x] -> Producer m x [x]Source

fromList produces the contents of the given list argument.

toList :: forall m x. (Monad m, Typeable x) => Consumer m x [x]Source

Consumer toList copies the given source into a list.

I/O producers and consumers

fromFile :: String -> Producer IO Char ()Source

Producer fromFile opens the named file and feeds the given sink from its contents.

fromHandle :: Handle -> Bool -> Producer IO Char ()Source

Producer fromHandle feeds the given sink from the open file handle. The argument doClose determines if | handle should be closed when the handle is consumed or the sink closed.

fromStdIn :: Producer IO Char ()Source

Producer fromStdIn feeds the given sink from the standard input.

appendFile :: String -> Consumer IO Char ()Source

Consumer appendFile opens the name file and appends the given source to it.

toFile :: String -> Consumer IO Char ()Source

Consumer toFile opens the named file and copies the given source into it.

toHandle :: Handle -> Bool -> Consumer IO Char ()Source

Consumer toHandle copies the given source into the open file handle. The argument doClose determines if | handle should be closed once the entire source is consumed and copied.

toStdOut :: Consumer IO Char ()Source

Consumer toStdOut copies the given source into the standard output.

Generic consumers

suppress :: forall m x y. (Monad m, Typeable x) => Consumer m x ()Source

The suppress consumer suppresses all input it receives. It is equivalent to substitute []

erroneous :: forall m x. (Monad m, Typeable x) => String -> Consumer m x ()Source

The erroneous consumer reports an error if any input reaches it.

Generic transducers

asis :: forall m x. (Monad m, Typeable x) => Transducer m x xSource

Transducer asis passes its input through unmodified.

parse :: forall m x y. (Monad m, Typeable x, Typeable y) => Transducer m x (Markup x y)Source

Transducer parse prepares input content for subsequent parsing.

unparse :: forall m x y. (Monad m, Typeable x, Typeable y) => Transducer m (Markup x y) xSource

Transducer unparse removes all markup from its input and passes the content through.

parseSubstring :: forall m x y. (ParallelizableMonad m, Eq x, Typeable x) => [x] -> Parser m x OccurenceTagSource

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.

Generic splitters

everything :: forall m x. (ParallelizableMonad m, Typeable x) => Splitter m x ()Source

Splitter everything feeds its entire input into its true sink.

nothing :: forall m x. (ParallelizableMonad m, Typeable x) => Splitter m x ()Source

Splitter nothing feeds its entire input into its false sink.

marked :: forall m x y. (ParallelizableMonad m, Typeable x, Typeable y, Eq y) => Splitter m (Markup x y) ()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. (ParallelizableMonad m, Typeable x, Typeable y, Eq y) => Splitter m (Markup x y) ()Source

Splitter markedContent passes the content of all marked-up input sections to its true sink, while the outermost tags and all unmarked input go to its false sink.

markedWith :: forall m x y. (ParallelizableMonad m, Typeable x, Typeable y, Eq y) => (y -> Bool) -> Splitter m (Markup x y) ()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. (ParallelizableMonad m, Typeable x, Typeable y, Eq y) => (y -> Bool) -> Splitter m (Markup x y) ()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. (ParallelizableMonad m, Typeable 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. (ParallelizableMonad m, Eq x, Typeable x) => [x] -> Splitter m x ()Source

Splitter substring feeds to its true sink all input parts that match the contents of the given list argument. If two overlapping parts of the input both match the argument, both are sent to true and each is preceded by an edge.

List transducers

The following laws hold:

group :: forall m x. (Monad m, Typeable x) => Transducer m x [x]Source

Transducer group collects all its input values into a single list.

concatenate :: forall m x. (Monad m, Typeable x) => Transducer m [x] xSource

Transducer concatenate flattens the input stream of lists of values into the output stream of values.

concatSeparate :: forall m x. (Monad m, Typeable x) => [x] -> Transducer m [x] xSource

Same as concatenate except it inserts the given separator list between every two input lists.

Character stream components

lowercase :: forall m. Monad m => Transducer m Char CharSource

The lowercase transforms all uppercase letters in the input to lowercase, leaving the rest unchanged.

uppercase :: forall m. Monad m => Transducer m Char CharSource

The uppercase transforms all lowercase letters in the input to uppercase, leaving the rest unchanged.

whitespace :: forall m. ParallelizableMonad m => Splitter m Char ()Source

Splitter whitespace feeds all white-space characters into its true sink, all others into false.

letters :: forall m. ParallelizableMonad m => Splitter m Char ()Source

Splitter letters feeds all alphabetical characters into its true sink, all other characters into false.

digits :: forall m. ParallelizableMonad m => Splitter m Char ()Source

Splitter digits feeds all digits into its true sink, all other characters into false.

line :: forall m. ParallelizableMonad m => Splitter m Char ()Source

The sectioning splitter line feeds line-ends into its false sink, and line contents into true. A single line-end can be formed by any of the character sequences "\n", "\r", "\r\n", or "\n\r".

nonEmptyLine :: forall m. ParallelizableMonad m => Splitter m Char ()Source

Splitter nonEmptyLine feeds line-ends into its false sink, and all other characters into true.

Oddballs

count :: forall m x. (Monad m, Typeable x) => Transducer m x IntegerSource

The count transducer counts all its input values and outputs the final tally.

toString :: forall m x. (Monad m, Show x, Typeable x) => Transducer m x StringSource

Converts each input value x to show x.

ioCost :: IntSource

The constant cost of each I/O-performing component.