| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Pipes.Text
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
- 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
- data ByteString
- data Text
- type Parser a (m :: Type -> Type) r = forall x. StateT (Producer a m x) m r
- data FreeF (f :: Type -> Type) a b
- newtype FreeT (f :: Type -> Type) (m :: Type -> Type) a = FreeT {}
- concats :: forall (m :: Type -> Type) a x. Monad m => FreeT (Producer a m) m x -> Producer a m x
- intercalates :: forall (m :: Type -> Type) a x. Monad m => Producer a m () -> FreeT (Producer a m) m x -> Producer a m x
- folds :: forall (m :: Type -> Type) x a b r. Monad m => (x -> a -> x) -> x -> (x -> b) -> FreeT (Producer a m) m r -> Producer b m r
- maps :: forall (m :: Type -> Type) g f x. (Monad m, Functor g) => (forall r. f r -> g r) -> FreeT f m x -> FreeT g m x
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 Chars 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 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
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 xisEndOfChars :: 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 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
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.
data ByteString #
A space-efficient representation of a Word8 vector, supporting many
 efficient operations.
A ByteString contains 8-bit bytes, or by using the operations from
 Data.ByteString.Char8 it can be interpreted as containing 8-bit
 characters.
Instances
A space efficient, packed, unboxed Unicode text type.
data FreeF (f :: Type -> Type) a b #
The base functor for a free monad.
Instances
| Traversable f => Bitraversable (FreeF f) | |
| Defined in Control.Monad.Trans.Free Methods bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> FreeF f a b -> f0 (FreeF f c d) # | |
| Foldable f => Bifoldable (FreeF f) | |
| Functor f => Bifunctor (FreeF f) | |
| Eq1 f => Eq2 (FreeF f) | |
| Ord1 f => Ord2 (FreeF f) | |
| Defined in Control.Monad.Trans.Free | |
| Read1 f => Read2 (FreeF f) | |
| Defined in Control.Monad.Trans.Free Methods liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (FreeF f a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [FreeF f a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (FreeF f a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [FreeF f a b] # | |
| Show1 f => Show2 (FreeF f) | |
| Generic1 (FreeF f a :: Type -> Type) | |
| Functor f => Functor (FreeF f a) | |
| Foldable f => Foldable (FreeF f a) | |
| Defined in Control.Monad.Trans.Free Methods fold :: Monoid m => FreeF f a m -> m # foldMap :: Monoid m => (a0 -> m) -> FreeF f a a0 -> m # foldMap' :: Monoid m => (a0 -> m) -> FreeF f a a0 -> m # foldr :: (a0 -> b -> b) -> b -> FreeF f a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> FreeF f a a0 -> b # foldl :: (b -> a0 -> b) -> b -> FreeF f a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> FreeF f a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> FreeF f a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> FreeF f a a0 -> a0 # toList :: FreeF f a a0 -> [a0] # null :: FreeF f a a0 -> Bool # length :: FreeF f a a0 -> Int # elem :: Eq a0 => a0 -> FreeF f a a0 -> Bool # maximum :: Ord a0 => FreeF f a a0 -> a0 # minimum :: Ord a0 => FreeF f a a0 -> a0 # | |
| Traversable f => Traversable (FreeF f a) | |
| Defined in Control.Monad.Trans.Free | |
| (Eq1 f, Eq a) => Eq1 (FreeF f a) | |
| (Ord1 f, Ord a) => Ord1 (FreeF f a) | |
| Defined in Control.Monad.Trans.Free | |
| (Read1 f, Read a) => Read1 (FreeF f a) | |
| Defined in Control.Monad.Trans.Free Methods liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (FreeF f a a0) # liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [FreeF f a a0] # liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (FreeF f a a0) # liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [FreeF f a a0] # | |
| (Show1 f, Show a) => Show1 (FreeF f a) | |
| (Eq a, Eq (f b)) => Eq (FreeF f a b) | |
| (Ord a, Ord (f b)) => Ord (FreeF f a b) | |
| Defined in Control.Monad.Trans.Free | |
| (Read a, Read (f b)) => Read (FreeF f a b) | |
| (Show a, Show (f b)) => Show (FreeF f a b) | |
| Generic (FreeF f a b) | |
| type Rep1 (FreeF f a :: Type -> Type) | |
| Defined in Control.Monad.Trans.Free type Rep1 (FreeF f a :: Type -> Type) = D1 ('MetaData "FreeF" "Control.Monad.Trans.Free" "free-5.1.8-EpEmxvZJwsJIRaqIphgMon" 'False) (C1 ('MetaCons "Pure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Free" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f))) | |
| type Rep (FreeF f a b) | |
| Defined in Control.Monad.Trans.Free type Rep (FreeF f a b) = D1 ('MetaData "FreeF" "Control.Monad.Trans.Free" "free-5.1.8-EpEmxvZJwsJIRaqIphgMon" 'False) (C1 ('MetaCons "Pure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Free" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f b)))) | |
newtype FreeT (f :: Type -> Type) (m :: Type -> Type) a #
The "free monad transformer" for a functor f
Instances
intercalates :: forall (m :: Type -> Type) a x. Monad m => Producer a m () -> FreeT (Producer a m) m x -> Producer a m x #
maps :: forall (m :: Type -> Type) g f x. (Monad m, Functor g) => (forall r. f r -> g r) -> FreeT f m x -> FreeT g m x #
Transform each individual functor layer of a FreeT
You can think of this as:
maps
    :: (forall r . Producer a m r -> Producer b m r)
    -> FreeT (Producer a m) m x -> FreeT (Producer b m) m xThis is just a synonym for transFreeT