pipes-text-0.0.0.6: Text pipes.

Safe HaskellTrustworthy

Pipes.Text

Contents

Description

This module provides pipes utilities for "text streams", which are streams of Text chunks. The individual chunks are uniformly strict, but a Producer can be converted to and from lazy Texts, though this is generally unwise. Where pipes IO replaces lazy IO, 'Producer Text m r' replaces lazy Text. An Handle can be associated with a Producer or Consumer according as it is read or written to.

To stream to or from Handles, one can use fromHandle or toHandle. For example, the following program copies a document from one file to another:

 import Pipes
 import qualified Data.Text.Pipes as Text
 import System.IO

 main =
     withFile "inFile.txt"  ReadMode  $ \hIn  ->
     withFile "outFile.txt" WriteMode $ \hOut ->
     runEffect $ Text.fromHandle hIn >-> Text.toHandle hOut

To stream from files, the following is perhaps more Prelude-like (note that it uses Pipes.Safe):

 import Pipes
 import qualified Data.Text.Pipes as Text
 import Pipes.Safe

 main = runSafeT $ runEffect $ Text.readFile "inFile.txt" >-> Text.writeFile "outFile.txt"

You can stream to and from stdin and stdout using the predefined stdin and stdout pipes, as with the following "echo" program:

 main = runEffect $ Text.stdin >-> Text.stdout

You can also translate pure lazy Texts to and from pipes:

 main = runEffect $ Text.fromLazy (TL.pack "Hello, world!\n") >-> Text.stdout

In addition, this module provides many functions equivalent to lazy Text functions so that you can transform or fold text streams. 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.Parse as Parse

 main = runEffect $ takeLines 3 Text.stdin >-> Text.stdout
   where
     takeLines n = Text.unlines . Parse.takeFree n . Text.lines

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

Note that functions in this library are designed to operate on streams that are insensitive to text boundaries. This means that they may freely split text into smaller texts, discard empty texts. However, apart from the special case of concatMap, they will never concatenate texts in order to provide strict upper bounds on memory usage -- with the single exception of concatMap.

Synopsis

Producers

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

Convert a lazy Text into a Producer of strict Texts

stdin :: MonadIO m => Producer Text m ()Source

Stream text from stdin

fromHandle :: MonadIO m => Handle -> Producer Text m ()Source

Convert a Handle into a text stream using a text size determined by the good sense of the text library; note that this is distinctly slower than decideUtf8 (Pipes.ByteString.fromHandle h) but uses the system encoding and has other IO features

readFile :: MonadSafe m => FilePath -> Producer Text m ()Source

Stream text from a file in the simple fashion of Data.Text.IO

>>> runSafeT $ runEffect $ Text.readFile "hello.hs" >-> Text.map toUpper >-> hoist lift Text.stdout
MAIN = PUTSTRLN "HELLO WORLD"

Consumers

stdout :: MonadIO m => Consumer' Text m ()Source

Stream text to stdout

Unlike toHandle, stdout gracefully terminates on a broken output pipe.

Note: For best performance, it might be best just to use (for source (liftIO . putStr)) instead of (source >-> stdout) .

toHandle :: MonadIO m => Handle -> Consumer' Text m rSource

Convert a text stream into a Handle

Note: again, for best performance, where possible use (for source (liftIO . hPutStr handle)) instead of (source >-> toHandle handle).

writeFile :: MonadSafe m => FilePath -> Consumer' Text m ()Source

Stream text into a file. Uses pipes-safe.

Pipes

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

Apply a transformation to each Char in the stream

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

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.

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

(drop n) drops the first n characters

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

Take characters until they fail the predicate

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

Drop characters until they fail the predicate

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

Only allows Chars to pass if they satisfy the predicate

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

Strict left scan over the characters

encodeUtf8 :: Monad m => Pipe Text ByteString m rSource

Transform a Pipe of Text into a Pipe of ByteStrings using UTF-8 encoding; encodeUtf8 = Pipes.Prelude.map TE.encodeUtf8 so more complex encoding pipes can easily be constructed with the functions in Data.Text.Encoding

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

Transform a Pipe of Strings into one of Text chunks

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

Transform a Pipes of Text chunks into one of Strings

toCaseFold :: Monad m => Pipe Text Text m ()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 ()Source

lowercase incoming Text

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

uppercase incoming Text

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

Remove leading white space from an incoming succession of Texts

Folds

toLazy :: Producer Text Identity () -> TextSource

Fold a pure Producer of strict Texts into a lazy Text

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

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 rSource

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 BoolSource

Determine if the stream is empty

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

Count the number of characters in the stream

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

Fold that returns whether Any received Chars satisfy the predicate

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

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

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

Store a tally of how many segments match the given Text

Primitive Character Parsers

The following parsing utilities are single-character analogs of the ones found pipes-parse.

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 BoolSource

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, where the first text stream is the longest consecutive group of text that satisfy the predicate

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

Split a text stream in two, where the first text stream is 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

Decoding Lenses

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

An improper lens into a stream of ByteString expected to be UTF-8 encoded; the associated stream of Text ends by returning a stream of ByteStrings beginning at the point of failure.

codec :: Monad m => Codec -> Lens' (Producer ByteString m r) (Producer Text m (Producer ByteString m r))Source

Use a Codec as a pipes-style Lens into a byte stream; the available Codec s are utf8, utf16_le, utf16_be, utf32_le, utf32_be . The Codec concept and the individual Codec definitions follow the enumerator and conduit libraries.

Utf8 is handled differently in this library -- without the use of unsafePerformIO &co to catch Text exceptions; but the same 'mypipe ^. codec utf8' interface can be used. 'mypipe ^. decodeUtf8' should be the same, but has a somewhat more direct and thus perhaps better implementation.

Codecs

Other Decoding/Encoding Functions

decodeIso8859_1 :: Monad m => Producer ByteString m r -> Producer Text m (Producer ByteString m r)Source

Reduce a byte stream to a corresponding stream of ascii chars, returning the unused ByteString upon hitting the rare un-latinizable byte.

decodeAscii :: Monad m => Producer ByteString m r -> Producer Text m (Producer ByteString m r)Source

Reduce a byte stream to a corresponding stream of ascii chars, returning the unused ByteString upon hitting an un-ascii byte.

encodeIso8859_1 :: Monad m => Producer Text m r -> Producer ByteString m (Producer Text m r)Source

Reduce as much of your stream of Text actually is iso8859 or latin1 to a byte stream, returning the rest of the Text upon hitting any non-latin Char

encodeAscii :: Monad m => Producer Text m r -> Producer ByteString m (Producer Text m r)Source

ascii and latin encodings only represent a small fragment of Text; thus we cannot use the pipes Lens style to work with them. Rather we simply define functions each way.

encodeAscii : Reduce as much of your stream of Text actually is ascii to a byte stream, returning the rest of the Text at the first non-ascii Char

FreeT Splitters

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 rSource

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

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

Split a text stream into FreeT-delimited lines

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

Split a text stream into FreeT-delimited words

Transformations

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

Intersperse a Char in between the characters of stream of Text

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

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 rSource

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 rSource

Join FreeT-delimited lines into a text stream

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

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.

data Codec Source

A specific character encoding.

Instances

module Data.Text

module Data.Word