Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
The module Pipes.Text
closely follows Pipes.ByteString
from
the pipes-bytestring
package. A draft tutorial can be found in
Pipes.Text.Tutorial
.
- 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 ()
- takeWhile :: Monad m => (Char -> Bool) -> Pipe Text Text m ()
- filter :: Monad m => (Char -> Bool) -> Pipe Text Text 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
- scan :: Monad m => (Char -> Char -> Char) -> Char -> 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)
- 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))
- drop :: (Monad m, Integral n) => n -> Producer Text m r -> Producer Text m r
- dropWhile :: Monad m => (Char -> Bool) -> Producer Text m r -> Producer Text m r
- pack :: Monad m => Lens' (Producer Char m r) (Producer Text m r)
- unpack :: Monad m => Lens' (Producer Text m r) (Producer Char m r)
- intersperse :: Monad m => Char -> Producer Text m r -> 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 => Lens' (Producer Text m r) (FreeT (Producer Text m) m r)
- unlines :: Monad m => Lens' (FreeT (Producer Text m) m r) (Producer Text m r)
- words :: Monad m => Lens' (Producer Text m r) (FreeT (Producer Text m) m r)
- unwords :: Monad m => Lens' (FreeT (Producer Text m) m r) (Producer Text m r)
- intercalate :: Monad m => Producer Text m () -> FreeT (Producer Text m) m r -> Producer Text m r
- module Data.ByteString
- module Data.Text
- module Pipes.Parse
- module Pipes.Group
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.
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 Char
s to pass if they satisfy the predicate
stripStart :: Monad m => Pipe Text Text m r Source
Remove leading white space from an incoming succession of Text
s
scan :: Monad m => (Char -> Char -> Char) -> Char -> Pipe Text Text m r Source
Strict left scan over the characters
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
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
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 Word8
s to packaged ByteString
s
unpack :: Monad m => Lens' (Producer Text m r) (Producer Char m r) Source
Improper lens from packed ByteString
s to unpacked Word8
s
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
lines :: Monad m => Lens' (Producer Text m r) (FreeT (Producer Text m) m r) Source
Split a text stream into FreeT
-delimited lines
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
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.ByteString
module Data.Text
module Pipes.Parse
module Pipes.Group