pipes-text-0.0.0.8: Text pipes.

Safe HaskellTrustworthy

Pipes.Text

Contents

Description

This package provides pipes utilities for 'text streams', which are streams of Text chunks. The individual chunks are uniformly strict, and thus you will generally want Data.Text in scope. But the type Producer Text m r is in some ways the pipes equivalent of the lazy Text type.

This module provides many functions equivalent in one way or another to the pure functions in Data.Text.Lazy. They transform, divide, group and fold text streams. Though Producer Text m r is the type of 'effectful Text', the functions in this module are 'pure' in the sense that they are uniformly monad-independent. Simple IO operations are defined in Pipes.Text.IO -- as lazy IO Text operations are in Data.Text.Lazy.IO. Interoperation with ByteString is provided in Pipes.Text.Encoding, which parallels Data.Text.Lazy.Encoding.

The Text type exported by Data.Text.Lazy is basically '[Text]'. The implementation is arranged so that the individual strict Text chunks are kept to a reasonable size; the user is not aware of the divisions between the connected Text chunks. So also here: the functions in this module are designed to operate on streams that are insensitive to text boundaries. This means that they may freely split text into smaller texts and discard empty texts. However, the objective is that they should never concatenate texts in order to provide strict upper bounds on memory usage.

For example, to stream only the first three lines of stdin to stdout you might write:

 import Pipes
 import qualified Pipes.Text as Text
 import qualified Pipes.Text.IO as Text
 import Pipes.Group
 import Lens.Family 
 
 main = runEffect $ takeLines 3 Text.stdin >-> Text.stdout
   where 
     takeLines n = Text.unlines . takes' n . view Text.lines
  -- or equivalently: 
  -- takeLines n = over Text.lines (takes' n)

The above program will never bring more than one chunk of text (~ 32 KB) into memory, no matter how long the lines are.

As this example shows, one superficial difference from Data.Text.Lazy is that many of the operations, like lines, are 'lensified'; this has a number of advantages where it is possible, in particular it facilitates their use with Parsers of Text (in the general pipes-parse sense.) Each such expression, e.g. lines, chunksOf or splitAt, reduces to the intuitively corresponding function when used with view or (^.). The lens combinators you will find indispensible are 'view'/ '(^.)', zoom and probably over, which are supplied by both lens and lens-family

A more important difference the example reveals is in the types closely associated with the central type, Producer Text m r. In Data.Text and Data.Text.Lazy we find functions like

   splitAt :: Int -> Text -> (Text, Text)
   lines :: Int -> Text -> [Text]
   chunksOf :: Int -> Text -> [Text]

which relate a Text with a pair or list of Texts. The corresponding functions here (taking account of 'lensification') are

   view . splitAt :: (Monad m, Integral n) => n -> Producer Text m r -> Producer Text.Text m (Producer Text.Text m r)
   view lines :: Monad m => Producer Text m r -> FreeT (Producer Text m) m r
   view . chunksOf ::  (Monad m, Integral n) => n -> Producer Text m r -> FreeT (Producer Text m) m r

In the type Producer Text m (Producer Text m r) the second element of the 'pair' of of 'effectful Texts' cannot simply be retrieved with snd. This is an 'effectful' pair, and one must work through the effects of the first element to arrive at the second Text stream. Similarly in FreeT (Producer Text m) m r, which corresponds with [Text], on cannot simply drop 10 Producers and take the others; we can only get to the ones we want to take by working through their predecessors.

Some of the types may be more readable if you imagine that we have introduced our own type synonyms

   type Text m r = Producer T.Text m r
   type Texts m r = FreeT (Producer T.Text m) m r

Then we would think of the types above as

   view . splitAt :: (Monad m, Integral n) => n -> Text m r -> Text m (Text m r)
   view lines :: (Monad m) => Text m r -> Texts m r
   view . chunksOf :: (Monad m, Integral n) => n -> Text m r -> Texts m r

which brings one closer to the types of the similar functions in Data.Text.Lazy

Synopsis

Producers

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

Convert a lazy Text into a Producer of strict Texts

Pipes

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

Apply a transformation to each Char in the stream

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

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

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

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

drop :: (Monad m, Integral a) => a -> Pipe Text Text m r

(drop n) drops the first n characters

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

Take characters until they fail the predicate

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

Drop characters until they fail the predicate

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

Only allows Chars to pass if they satisfy the predicate

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

Strict left scan over the characters

pack :: Monad m => Pipe String Text m r

Transform a Pipe of Strings into one of Text chunks

unpack :: Monad m => Pipe Text String m r

Transform a Pipes of Text chunks into one of Strings

toCaseFold :: Monad m => Pipe Text Text m ()

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 ()

lowercase incoming Text

toUpper :: Monad m => Pipe Text Text m ()

uppercase incoming Text

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

Remove leading white space from an incoming succession of Texts

Folds

toLazy :: Producer Text Identity () -> Text

Fold a pure Producer of strict Texts into a lazy Text

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

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

Reduce the text stream using a strict left fold over characters

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

Retrieve the first Char

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

Retrieve the last Char

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

Determine if the stream is empty

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

Count the number of characters in the stream

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

Fold that returns whether Any received Chars satisfy the predicate

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

Fold that returns whether All received Chars satisfy the predicate

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

Return the maximum Char within a text stream

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

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

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

Find the first element in the stream that matches the predicate

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

Index into a text stream

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

Store a tally of how many segments match the given Text

Primitive Character Parsers

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

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)

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

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

Push back a Char onto the underlying Producer

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

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

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))

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))

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))

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))

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))

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))

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))

FreeT Splitters

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

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

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)

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)

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)

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

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

Split a text stream into FreeT-delimited lines

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

Split a text stream into FreeT-delimited words

Transformations

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

Intersperse a Char in between the characters of stream of Text

packChars :: Monad m => Iso' (Producer Char m x) (Producer Text m x)

Improper isomorphism between a Producer of ByteStrings and Word8s

Joiners

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

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

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

Join FreeT-delimited lines into a text stream

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

Join FreeT-delimited words into a text stream

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