Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
- fromLazy :: Monad m => Text -> Producer' Text m ()
- map :: Monad m => (Char -> Char) -> Pipe Text Text m r
- concatMap :: Monad m => (Char -> Text) -> Pipe Text Text m r
- take :: (Monad m, Integral a) => a -> Pipe Text Text m ()
- drop :: (Monad m, Integral a) => a -> Pipe Text Text m r
- takeWhile :: Monad m => (Char -> Bool) -> Pipe Text Text m ()
- dropWhile :: Monad m => (Char -> Bool) -> Pipe Text Text m r
- filter :: Monad m => (Char -> Bool) -> Pipe Text Text m r
- scan :: Monad m => (Char -> Char -> Char) -> Char -> Pipe Text Text m r
- pack :: Monad m => Pipe String Text m r
- unpack :: Monad m => Pipe Text String m r
- toCaseFold :: Monad m => Pipe Text Text m r
- toLower :: Monad m => Pipe Text Text m r
- toUpper :: Monad m => Pipe Text Text m r
- stripStart :: Monad m => Pipe Text Text m r
- toLazy :: Producer Text Identity () -> Text
- toLazyM :: Monad m => Producer Text m () -> m Text
- foldChars :: Monad m => (x -> Char -> x) -> x -> (x -> r) -> Producer Text m () -> m r
- head :: Monad m => Producer Text m () -> m (Maybe Char)
- last :: Monad m => Producer Text m () -> m (Maybe Char)
- null :: Monad m => Producer Text m () -> m Bool
- length :: (Monad m, Num n) => Producer Text m () -> m n
- any :: Monad m => (Char -> Bool) -> Producer Text m () -> m Bool
- all :: Monad m => (Char -> Bool) -> Producer Text m () -> m Bool
- maximum :: Monad m => Producer Text m () -> m (Maybe Char)
- minimum :: Monad m => Producer Text m () -> m (Maybe Char)
- find :: Monad m => (Char -> Bool) -> Producer Text m () -> m (Maybe Char)
- index :: (Monad m, Integral a) => a -> Producer Text m () -> m (Maybe Char)
- count :: (Monad m, Num n) => Text -> Producer Text m () -> m n
- nextChar :: Monad m => Producer Text m r -> m (Either r (Char, Producer Text m r))
- drawChar :: Monad m => Parser Text m (Maybe Char)
- unDrawChar :: Monad m => Char -> Parser Text m ()
- peekChar :: Monad m => Parser Text m (Maybe Char)
- isEndOfChars :: Monad m => Parser Text m Bool
- splitAt :: (Monad m, Integral n) => n -> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
- span :: Monad m => (Char -> Bool) -> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
- break :: Monad m => (Char -> Bool) -> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
- groupBy :: Monad m => (Char -> Char -> Bool) -> Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
- group :: Monad m => Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
- word :: Monad m => Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
- line :: Monad m => Lens' (Producer Text m r) (Producer Text m (Producer Text m r))
- chunksOf :: (Monad m, Integral n) => n -> Lens' (Producer Text m r) (FreeT (Producer Text m) m r)
- splitsWith :: Monad m => (Char -> Bool) -> Producer Text m r -> FreeT (Producer Text m) m r
- splits :: Monad m => Char -> Lens' (Producer Text m r) (FreeT (Producer Text m) m r)
- groupsBy :: Monad m => (Char -> Char -> Bool) -> Lens' (Producer Text m x) (FreeT (Producer Text m) m x)
- groups :: Monad m => Lens' (Producer Text m x) (FreeT (Producer Text m) m x)
- lines :: Monad m => Iso' (Producer Text m r) (FreeT (Producer Text m) m r)
- words :: Monad m => Iso' (Producer Text m r) (FreeT (Producer Text m) m r)
- intersperse :: Monad m => Char -> Producer Text m r -> Producer Text m r
- packChars :: Monad m => Iso' (Producer Char m x) (Producer Text m x)
- intercalate :: Monad m => Producer Text m () -> FreeT (Producer Text m) m r -> Producer Text m r
- unlines :: Monad m => FreeT (Producer Text m) m r -> Producer Text m r
- unwords :: Monad m => FreeT (Producer Text m) m r -> Producer Text m r
- module Data.ByteString
- module Data.Text
- module Data.Profunctor
- module Pipes.Parse
- module Pipes.Group
Introduction
Effectful Text
This package provides
pipes
utilities for text streams, understood as streams ofText
chunks. The individual chunks are uniformly strict, and thus you will generally wantData.Text
in scope. But the typeProducer Text m r
as we are using it is a sort of pipes equivalent of the lazyText
type.This particular 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 inPipes.Text.IO
-- as lazy IOText
operations are inData.Text.Lazy.IO
. Inter-operation withByteString
is provided inPipes.Text.Encoding
, which parallelsData.Text.Lazy.Encoding
.The Text type exported by
Data.Text.Lazy
is basically that of a lazy list of strict Text: the implementation is arranged so that the individual strictText
chunks are kept to a reasonable size; the user is not aware of the divisions between the connectedText
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. The objective, though, 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
tostdout
you might write:
import Pipes import qualified Pipes.Text as Text import qualified Pipes.Text.IO as Text import Pipes.Group (takes') import Lens.Family main = runEffect $ takeLines 3 Text.stdin >-> Text.stdout where takeLines n = Text.unlines . takes' n . view 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.
Lenses
As this example shows, one superficial difference from
Data.Text.Lazy
is that many of the operations, likelines
, are 'lensified'; this has a number of advantages (where it is possible), in particular it facilitates their use withParser
s of Text (in the general pipes-parse sense.) Each such lens, e.g.lines
,chunksOf
orsplitAt
, reduces to the intuitively corresponding function when used withview
or(^.)
.Note similarly that many equivalents of 'Text -> Text' functions are exported here as
Pipe
s. They reduce to the intuitively corresponding functions when used with '(>->)'. Thus something like
stripLines = Text.unlines . Group.maps (>-> Text.stripStart) . view Text.lines
would drop the leading white space from each line.
The lens combinators
you will find indispensible are view
/ (^.)
), zoom
and probably over
. These
are supplied by both lens and
lens-family The use of zoom
is explained
in Pipes.Parse.Tutorial
and to some extent in the Pipes.Text.Encoding
module here. The use of
over
is simple, illustrated by the fact that we can rewrite stripLines
above as
stripLines = over Text.lines $ maps (>-> stripStart)
- Special types:
Producer Text m (Producer Text m r)
andFreeT (Producer Text m) m r
These simple lines
examples reveal a more important difference from Data.Text.Lazy
.
This is in the types that are most closely associated with our central text type,
Producer Text m r
. In Data.Text
and Data.Text.Lazy
we find functions like
splitAt :: Int -> Text -> (Text, Text) lines :: Text -> [Text] chunksOf :: Int -> Text -> [Text]
which relate a Text with a pair of Texts or a 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 m (Producer 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
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
In the type Producer Text m (Producer Text m r)
the second
element of the 'pair' of effectful Texts cannot simply be retrieved
with something like snd
. This is an 'effectful' pair, and one must work
through the effects of the first element to arrive at the second Text stream, even
if you are proposing to throw the Text in the first element away.
Note that we use Control.Monad.join to fuse the pair back together, since it specializes to
join :: Monad m => Producer Text m (Producer m r) -> Producer m r
The return type of lines
, words
, chunksOf
and the other "splitter" functions,
FreeT (Producer m Text) m r
-- our Texts m r
-- is the type of (effectful)
lists of (effectful) texts. The type ([Text],r)
might be seen to gather
together things of the forms:
r (Text,r) (Text, (Text, r)) (Text, (Text, (Text, r))) (Text, (Text, (Text, (Text, r)))) ...
We might also have identified the sum of those types with Free ((,) Text) r
-- or, more absurdly, FreeT ((,) Text) Identity r
. Similarly, FreeT (Producer Text m) m r
encompasses all the members of the sequence:
m r Producer Text m r Producer Text m (Producer Text m r) Producer Text m (Producer Text m (Producer Text m r)) ...
One might think that
lines :: Monad m => Lens' (Producer Text m r) (FreeT (Producer Text m) m r) view . lines :: Monad m => Producer Text m r -> FreeT (Producer Text m) m r
should really have the type
lines :: Monad m => Pipe Text Text m r
as e.g. toUpper
does. But this would spoil the control we are
attempting to maintain over the size of chunks. It is in fact just
as unreasonable to want such a pipe as to want
Data.Text.Lazy.lines :: Text -> Text
to rechunk
the strict Text chunks inside the lazy Text to respect
line boundaries. In fact we have
Data.Text.Lazy.lines :: Text -> [Text] Prelude.lines :: String -> [String]
where the elements of the list are themselves lazy Texts or Strings; the use
of FreeT (Producer Text m) m r
is simply the effectful
version of this.
The Pipes.Group
module, which can generally be imported without qualification,
provides many functions for working with things of type FreeT (Producer a m) m r
Producers
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.
drop :: (Monad m, Integral a) => a -> Pipe Text Text m r Source
(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 r Source
Drop characters until they fail the predicate
filter :: Monad m => (Char -> Bool) -> Pipe Text Text m r Source
Only allows Char
s to pass if they satisfy the predicate
scan :: Monad m => (Char -> Char -> Char) -> Char -> Pipe Text Text m r Source
Strict left scan over the characters
stripStart :: Monad m => Pipe Text Text m r Source
Remove leading white space from an incoming succession of Text
s
Folds
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
length :: (Monad m, Num n) => Producer Text m () -> m n Source
Count the number of characters in the stream
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 n Source
Store a tally of how many segments match the given Text
Primitive Character Parsers
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
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 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
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
packChars :: Monad m => Iso' (Producer Char m x) (Producer Text m x) Source
Improper isomorphism between a Producer
of ByteString
s and Word8
s
Joiners
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
unlines :: Monad m => FreeT (Producer Text m) m r -> Producer Text m r Source
Join FreeT
-delimited lines into a text stream
unwords :: Monad m => FreeT (Producer Text m) m r -> Producer Text m r Source
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.ByteString
module Data.Text
module Data.Profunctor
module Pipes.Parse
module Pipes.Group