module Pipes.Text (
-- * Producers
- fromLazy
- -- , stdin
- -- , fromHandle
- -- , readFile
-
- -- * Consumers
- -- , stdout
- -- , toHandle
- -- , writeFile
+ fromLazy
-- * Pipes
, map
, dropWhile
, filter
, scan
--- , encodeUtf8
, pack
, unpack
, toCaseFold
, group
, word
, line
-
- -- -- * Decoding Lenses
- -- , decodeUtf8
- -- , codec
- --
- -- -- * Codecs
- -- , utf8
- -- , utf16_le
- -- , utf16_be
- -- , utf32_le
- -- , utf32_be
- --
- -- -- * Other Decoding/Encoding Functions
- -- , decodeIso8859_1
- -- , decodeAscii
- -- , encodeIso8859_1
- -- , encodeAscii
-- * FreeT Splitters
, chunksOf
, splitsWith
, splits
--- , groupsBy
--- , groups
+ , groupsBy
+ , groups
, lines
, words
, unlines
, unwords
- -- * Re-exports
+ -- * Re-exports
-- $reexports
- -- , DecodeResult(..)
- -- , Codec
- -- , TextException(..)
, module Data.ByteString
, module Data.Text
, module Data.Profunctor
import Pipes.Parse (Parser)
import qualified Pipes.Prelude as P
import Data.Char (isSpace)
+import Data.Word (Word8)
import Prelude hiding (
all,
p >-> concatMap f = for p (\txt -> yield (T.concatMap f txt))
#-}
--- | Transform a Pipe of 'Text' into a Pipe of 'ByteString's 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@
--- encodeUtf8 :: Monad m => Pipe Text ByteString m r
--- encodeUtf8 = P.map TE.encodeUtf8
--- {-# INLINEABLE encodeUtf8 #-}
---
--- {-# RULES "p >-> encodeUtf8" forall p .
--- p >-> encodeUtf8 = for p (\txt -> yield (TE.encodeUtf8 txt))
--- #-}
-- | Transform a Pipe of 'String's into one of 'Text' chunks
pack :: Monad m => Pipe String Text m r
Just c -> Just (min c (T.minimum txt))
{-# INLINABLE minimum #-}
-
-- | Find the first element in the stream that matches the predicate
find
:: (Monad m)
{-# INLINABLE count #-}
-{-| Consume the first character from a stream of 'Text'
+-- | 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'.
- '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'.
--}
nextChar
:: (Monad m)
=> Producer Text m r
Just (c, txt') -> return (Right (c, yield txt' >> p'))
{-# INLINABLE nextChar #-}
-{-| Draw one 'Char' from a stream of 'Text', returning 'Left' if the
- 'Producer' is empty
--}
+-- | Draw one 'Char' from a stream of 'Text', returning 'Left' if the 'Producer' is empty
+
drawChar :: (Monad m) => Parser Text m (Maybe Char)
drawChar = do
x <- PP.draw
> Left _ -> return ()
> Right c -> unDrawChar c
> return x
+
-}
+
peekChar :: (Monad m) => Parser Text m (Maybe Char)
peekChar = do
x <- drawChar
{-# INLINABLE isEndOfChars #-}
-
-
-- | Splits a 'Producer' after the given number of characters
splitAt
:: (Monad m, Integral n)
{-# INLINABLE splitAt #-}
-{-| Split a text stream in two, where the first text stream is the longest
- consecutive group of text that satisfy the predicate
--}
+-- | Split a text stream in two, producing the longest
+-- consecutive group of characters that satisfies the predicate
+-- and returning the rest
+
span
:: (Monad m)
=> (Char -> Bool)
return (yield suffix >> p')
{-# INLINABLE span #-}
-{-| Split a text stream in two, where the first text stream is the longest
+{-| Split a text stream in two, producing the longest
consecutive group of characters that don't satisfy the predicate
-}
break
unwords = intercalate (yield $ T.singleton ' ')
{-# INLINABLE unwords #-}
-{- $parse
- The following parsing utilities are single-character analogs of the ones found
- @pipes-parse@.
--}
{- $reexports