pipes-text-0.0.2.4: properly streaming text

Safe HaskellSafe
LanguageHaskell2010

Pipes.Text

Contents

Description

The module Pipes.Text closely follows Pipes.ByteString from the pipes-bytestring package. A draft tutorial can be found in Pipes.Text.Tutorial.

Synopsis

Producers

fromLazy :: Monad m => Text -> Producer' Text m () Source

Convert a lazy Text into a Producer of strict Texts. Producers in IO can be found in IO or in pipes-bytestring, employed with the decoding lenses in Encoding

Pipes

map :: Monad m => (Char -> Char) -> Pipe Text Text m r Source

Apply a transformation to each Char in the stream

concatMap :: Monad m => (Char -> Text) -> Pipe Text Text m r Source

Map a function over the characters of a text stream and concatenate the results

take :: (Monad m, Integral a) => a -> Pipe Text Text m () Source

(take n) only allows n individual characters to pass; contrast Pipes.Prelude.take which would let n chunks pass.

takeWhile :: Monad m => (Char -> Bool) -> Pipe Text Text m () Source

Take characters until they fail the predicate

filter :: Monad m => (Char -> Bool) -> Pipe Text Text m r Source

Only allows Chars to pass if they satisfy the predicate

toCaseFold :: Monad m => Pipe Text Text m r Source

toCaseFold, toLower, toUpper and stripStart are standard Text utilities, here acting as Text pipes, rather as they would on a lazy text

toLower :: Monad m => Pipe Text Text m r Source

lowercase incoming Text

toUpper :: Monad m => Pipe Text Text m r Source

uppercase incoming Text

stripStart :: Monad m => Pipe Text Text m r Source

Remove leading white space from an incoming succession of Texts

scan :: Monad m => (Char -> Char -> Char) -> Char -> Pipe Text Text m r Source

Strict left scan over the characters >>> let margaret = ["Margaret, are you grievingnOver Golde","ngrove unleaving?":: Text] >>> let title_caser a x = case a of ' ' -> Data.Char.toUpper x; _ -> x >>> toLazy $ each margaret >-> scan title_caser ' ' " Margaret, Are You GrievingnOver Goldengrove Unleaving?"

Folds

toLazy :: Producer Text Identity () -> Text Source

Fold a pure Producer of strict Texts into a lazy Text

toLazyM :: Monad m => Producer Text m () -> m Text Source

Fold an effectful Producer of strict Texts into a lazy Text

Note: toLazyM is not an idiomatic use of pipes, but I provide it for simple testing purposes. Idiomatic pipes style consumes the chunks immediately as they are generated instead of loading them all into memory.

foldChars :: Monad m => (x -> Char -> x) -> x -> (x -> r) -> Producer Text m () -> m r Source

Reduce the text stream using a strict left fold over characters

head :: Monad m => Producer Text m () -> m (Maybe Char) Source

Retrieve the first Char

last :: Monad m => Producer Text m () -> m (Maybe Char) Source

Retrieve the last Char

null :: Monad m => Producer Text m () -> m Bool Source

Determine if the stream is empty

length :: (Monad m, Num n) => Producer Text m () -> m n Source

Count the number of characters in the stream

any :: Monad m => (Char -> Bool) -> Producer Text m () -> m Bool Source

Fold that returns whether Any received Chars satisfy the predicate

all :: Monad m => (Char -> Bool) -> Producer Text m () -> m Bool Source

Fold that returns whether All received Chars satisfy the predicate

maximum :: Monad m => Producer Text m () -> m (Maybe Char) Source

Return the maximum Char within a text stream

minimum :: Monad m => Producer Text m () -> m (Maybe Char) Source

Return the minimum Char within a text stream (surely very useful!)

find :: Monad m => (Char -> Bool) -> Producer Text m () -> m (Maybe Char) Source

Find the first element in the stream that matches the predicate

index :: (Monad m, Integral a) => a -> Producer Text m () -> m (Maybe Char) Source

Index into a text stream

Primitive Character Parsers

nextChar :: Monad m => Producer Text m r -> m (Either r (Char, Producer Text m r)) Source

Consume the first character from a stream of Text

next either fails with a Left if the Producer has no more characters or succeeds with a Right providing the next character and the remainder of the Producer.

drawChar :: Monad m => Parser Text m (Maybe Char) Source

Draw one Char from a stream of Text, returning Left if the Producer is empty

unDrawChar :: Monad m => Char -> Parser Text m () Source

Push back a Char onto the underlying Producer

peekChar :: Monad m => Parser Text m (Maybe Char) Source

peekChar checks the first Char in the stream, but uses unDrawChar to push the Char back

peekChar = do
    x <- drawChar
    case x of
        Left  _  -> return ()
        Right c -> unDrawChar c
    return x

isEndOfChars :: Monad m => Parser Text m Bool Source

Check if the underlying Producer has no more characters

Note that this will skip over empty Text chunks, unlike isEndOfInput from pipes-parse, which would consider an empty Text a valid bit of input.

isEndOfChars = liftM isLeft peekChar

Parsing Lenses

splitAt :: (Monad m, Integral n) => n -> Lens' (Producer Text m r) (Producer Text m (Producer Text m r)) Source

Splits a Producer after the given number of characters

span :: Monad m => (Char -> Bool) -> Lens' (Producer Text m r) (Producer Text m (Producer Text m r)) Source

Split a text stream in two, producing the longest consecutive group of characters that satisfies the predicate and returning the rest

break :: Monad m => (Char -> Bool) -> Lens' (Producer Text m r) (Producer Text m (Producer Text m r)) Source

Split a text stream in two, producing the longest consecutive group of characters that don't satisfy the predicate

groupBy :: Monad m => (Char -> Char -> Bool) -> Lens' (Producer Text m r) (Producer Text m (Producer Text m r)) Source

Improper lens that splits after the first group of equivalent Chars, as defined by the given equivalence relation

group :: Monad m => Lens' (Producer Text m r) (Producer Text m (Producer Text m r)) Source

Improper lens that splits after the first succession of identical Char s

word :: Monad m => Lens' (Producer Text m r) (Producer Text m (Producer Text m r)) Source

Improper lens that splits a Producer after the first word

Unlike words, this does not drop leading whitespace

line :: Monad m => Lens' (Producer Text m r) (Producer Text m (Producer Text m r)) Source

Transforming Text and Character Streams

drop :: (Monad m, Integral n) => n -> Producer Text m r -> Producer Text m r Source

(drop n) drops the first n characters

dropWhile :: Monad m => (Char -> Bool) -> Producer Text m r -> Producer Text m r Source

Drop characters until they fail the predicate

pack :: Monad m => Lens' (Producer Char m r) (Producer Text m r) Source

Improper lens from unpacked Word8s to packaged ByteStrings

unpack :: Monad m => Lens' (Producer Text m r) (Producer Char m r) Source

Improper lens from packed ByteStrings to unpacked Word8s

intersperse :: Monad m => Char -> Producer Text m r -> Producer Text m r Source

Intersperse a Char in between the characters of stream of Text

FreeT Transformations

chunksOf :: (Monad m, Integral n) => n -> Lens' (Producer Text m r) (FreeT (Producer Text m) m r) Source

Split a text stream into FreeT-delimited text streams of fixed size

splitsWith :: Monad m => (Char -> Bool) -> Producer Text m r -> FreeT (Producer Text m) m r Source

Split a text stream into sub-streams delimited by characters that satisfy the predicate

splits :: Monad m => Char -> Lens' (Producer Text m r) (FreeT (Producer Text m) m r) Source

Split a text stream using the given Char as the delimiter

groupsBy :: Monad m => (Char -> Char -> Bool) -> Lens' (Producer Text m x) (FreeT (Producer Text m) m x) Source

Isomorphism between a stream of Text and groups of equivalent Chars , using the given equivalence relation

groups :: Monad m => Lens' (Producer Text m x) (FreeT (Producer Text m) m x) Source

Like groupsBy, where the equality predicate is (==)

lines :: Monad m => Lens' (Producer Text m r) (FreeT (Producer Text m) m r) Source

Split a text stream into FreeT-delimited lines

unlines :: Monad m => Lens' (FreeT (Producer Text m) m r) (Producer Text m r) Source

words :: Monad m => Lens' (Producer Text m r) (FreeT (Producer Text m) m r) Source

Split a text stream into FreeT-delimited words. Note that roundtripping with e.g. over words id eliminates extra space characters as with Prelude.unwords . Prelude.words

unwords :: Monad m => Lens' (FreeT (Producer Text m) m r) (Producer Text m r) Source

intercalate :: Monad m => Producer Text m () -> FreeT (Producer Text m) m r -> Producer Text m r Source

intercalate concatenates the FreeT-delimited text streams after interspersing a text stream in between them

Re-exports

Data.Text re-exports the Text type.

Pipes.Parse re-exports input, concat, FreeT (the type) and the Parse synonym.

module Data.Text