module Pipes.Text (
fromLazy
, stdin
, fromHandle
, readFile
, stdout
, toHandle
, writeFile
, map
, concatMap
, take
, drop
, takeWhile
, dropWhile
, filter
, scan
, encodeUtf8
, pack
, unpack
, toCaseFold
, toLower
, toUpper
, stripStart
, toLazy
, toLazyM
, foldChars
, head
, last
, null
, length
, any
, all
, maximum
, minimum
, find
, index
, count
, nextChar
, drawChar
, unDrawChar
, peekChar
, isEndOfChars
, splitAt
, span
, break
, groupBy
, group
, word
, line
, decodeUtf8
, codec
, utf8
, utf16_le
, utf16_be
, utf32_le
, utf32_be
, decodeIso8859_1
, decodeAscii
, encodeIso8859_1
, encodeAscii
, chunksOf
, splitsWith
, splits
, lines
, words
, intersperse
, packChars
, intercalate
, unlines
, unwords
, Decoding(..)
, streamDecodeUtf8
, decodeSomeUtf8
, Codec(..)
, TextException(..)
, module Data.ByteString
, module Data.Text
, module Data.Profunctor
, module Data.Word
, module Pipes.Parse
, module Pipes.Group
) where
import Control.Exception (throwIO, try)
import Control.Applicative ((<*))
import Control.Monad (liftM, unless, join)
import Control.Monad.Trans.State.Strict (StateT(..), modify)
import Data.Monoid ((<>))
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Data.Text.Encoding as TE
import qualified Data.Text.Encoding.Error as TE
import Data.Text (Text)
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.IO as TL
import Data.Text.Lazy.Internal (foldrChunks, defaultChunkSize)
import Data.ByteString.Unsafe (unsafeTake, unsafeDrop)
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import Data.Char (ord, isSpace)
import Data.Functor.Constant (Constant(Constant, getConstant))
import Data.Functor.Identity (Identity)
import Data.Profunctor (Profunctor)
import qualified Data.Profunctor
import qualified Data.List as List
import Foreign.C.Error (Errno(Errno), ePIPE)
import qualified GHC.IO.Exception as G
import Pipes
import qualified Pipes.ByteString as PB
import qualified Pipes.Text.Internal as PI
import Pipes.Text.Internal
import Pipes.Core (respond, Server')
import Pipes.Group (concats, intercalates, FreeT(..), FreeF(..))
import qualified Pipes.Group as PG
import qualified Pipes.Parse as PP
import Pipes.Parse (Parser)
import qualified Pipes.Safe.Prelude as Safe
import qualified Pipes.Safe as Safe
import Pipes.Safe (MonadSafe(..), Base(..))
import qualified Pipes.Prelude as P
import qualified System.IO as IO
import Data.Char (isSpace)
import Data.Word (Word8)
import Prelude hiding (
all,
any,
break,
concat,
concatMap,
drop,
dropWhile,
elem,
filter,
head,
last,
lines,
length,
map,
maximum,
minimum,
notElem,
null,
readFile,
span,
splitAt,
take,
takeWhile,
unlines,
unwords,
words,
writeFile )
fromLazy :: (Monad m) => TL.Text -> Producer' Text m ()
fromLazy = foldrChunks (\e a -> yield e >> a) (return ())
stdin :: MonadIO m => Producer Text m ()
stdin = fromHandle IO.stdin
fromHandle :: MonadIO m => IO.Handle -> Producer Text m ()
fromHandle h = go where
go = do txt <- liftIO (T.hGetChunk h)
unless (T.null txt) ( do yield txt
go )
readFile :: MonadSafe m => FilePath -> Producer Text m ()
readFile file = Safe.withFile file IO.ReadMode fromHandle
stdout :: MonadIO m => Consumer' Text m ()
stdout = go
where
go = do
txt <- await
x <- liftIO $ try (T.putStr txt)
case x of
Left (G.IOError { G.ioe_type = G.ResourceVanished
, G.ioe_errno = Just ioe })
| Errno ioe == ePIPE
-> return ()
Left e -> liftIO (throwIO e)
Right () -> go
toHandle :: MonadIO m => IO.Handle -> Consumer' Text m r
toHandle h = for cat (liftIO . T.hPutStr h)
writeFile :: (MonadSafe m) => FilePath -> Consumer' Text m ()
writeFile file = Safe.withFile file IO.WriteMode toHandle
type Lens' a b = forall f . Functor f => (b -> f b) -> (a -> f a)
type Iso' a b = forall f p . (Functor f, Profunctor p) => p b (f b) -> p a (f a)
(^.) :: a -> ((b -> Constant b b) -> (a -> Constant b a)) -> b
a ^. lens = getConstant (lens Constant a)
map :: (Monad m) => (Char -> Char) -> Pipe Text Text m r
map f = P.map (T.map f)
concatMap
:: (Monad m) => (Char -> Text) -> Pipe Text Text m r
concatMap f = P.map (T.concatMap f)
encodeUtf8 :: Monad m => Pipe Text ByteString m r
encodeUtf8 = P.map TE.encodeUtf8
pack :: Monad m => Pipe String Text m r
pack = P.map T.pack
unpack :: Monad m => Pipe Text String m r
unpack = for cat (\t -> yield (T.unpack t))
toCaseFold :: Monad m => Pipe Text Text m ()
toCaseFold = P.map T.toCaseFold
toLower :: Monad m => Pipe Text Text m ()
toLower = P.map T.toLower
toUpper :: Monad m => Pipe Text Text m ()
toUpper = P.map T.toUpper
stripStart :: Monad m => Pipe Text Text m r
stripStart = do
chunk <- await
let text = T.stripStart chunk
if T.null text
then stripStart
else do yield text
cat
take :: (Monad m, Integral a) => a -> Pipe Text Text m ()
take n0 = go n0 where
go n
| n <= 0 = return ()
| otherwise = do
txt <- await
let len = fromIntegral (T.length txt)
if (len > n)
then yield (T.take (fromIntegral n) txt)
else do
yield txt
go (n len)
drop :: (Monad m, Integral a) => a -> Pipe Text Text m r
drop n0 = go n0 where
go n
| n <= 0 = cat
| otherwise = do
txt <- await
let len = fromIntegral (T.length txt)
if (len >= n)
then do
yield (T.drop (fromIntegral n) txt)
cat
else go (n len)
takeWhile :: (Monad m) => (Char -> Bool) -> Pipe Text Text m ()
takeWhile predicate = go
where
go = do
txt <- await
let (prefix, suffix) = T.span predicate txt
if (T.null suffix)
then do
yield txt
go
else yield prefix
dropWhile :: (Monad m) => (Char -> Bool) -> Pipe Text Text m r
dropWhile predicate = go where
go = do
txt <- await
case T.findIndex (not . predicate) txt of
Nothing -> go
Just i -> do
yield (T.drop i txt)
cat
filter :: (Monad m) => (Char -> Bool) -> Pipe Text Text m r
filter predicate = P.map (T.filter predicate)
scan
:: (Monad m)
=> (Char -> Char -> Char) -> Char -> Pipe Text Text m r
scan step begin = go begin
where
go c = do
txt <- await
let txt' = T.scanl step c txt
c' = T.last txt'
yield txt'
go c'
toLazy :: Producer Text Identity () -> TL.Text
toLazy = TL.fromChunks . P.toList
toLazyM :: (Monad m) => Producer Text m () -> m TL.Text
toLazyM = liftM TL.fromChunks . P.toListM
foldChars
:: Monad m
=> (x -> Char -> x) -> x -> (x -> r) -> Producer Text m () -> m r
foldChars step begin done = P.fold (T.foldl' step) begin done
head :: (Monad m) => Producer Text m () -> m (Maybe Char)
head = go
where
go p = do
x <- nextChar p
case x of
Left _ -> return Nothing
Right (c, _) -> return (Just c)
last :: (Monad m) => Producer Text m () -> m (Maybe Char)
last = go Nothing
where
go r p = do
x <- next p
case x of
Left () -> return r
Right (txt, p') ->
if (T.null txt)
then go r p'
else go (Just $ T.last txt) p'
null :: (Monad m) => Producer Text m () -> m Bool
null = P.all T.null
length :: (Monad m, Num n) => Producer Text m () -> m n
length = P.fold (\n txt -> n + fromIntegral (T.length txt)) 0 id
any :: (Monad m) => (Char -> Bool) -> Producer Text m () -> m Bool
any predicate = P.any (T.any predicate)
all :: (Monad m) => (Char -> Bool) -> Producer Text m () -> m Bool
all predicate = P.all (T.all predicate)
maximum :: (Monad m) => Producer Text m () -> m (Maybe Char)
maximum = P.fold step Nothing id
where
step mc txt =
if (T.null txt)
then mc
else Just $ case mc of
Nothing -> T.maximum txt
Just c -> max c (T.maximum txt)
minimum :: (Monad m) => Producer Text m () -> m (Maybe Char)
minimum = P.fold step Nothing id
where
step mc txt =
if (T.null txt)
then mc
else case mc of
Nothing -> Just (T.minimum txt)
Just c -> Just (min c (T.minimum txt))
find
:: (Monad m)
=> (Char -> Bool) -> Producer Text m () -> m (Maybe Char)
find predicate p = head (p >-> filter predicate)
index
:: (Monad m, Integral a)
=> a-> Producer Text m () -> m (Maybe Char)
index n p = head (p >-> drop n)
count :: (Monad m, Num n) => Text -> Producer Text m () -> m n
count c p = P.fold (+) 0 id (p >-> P.map (fromIntegral . T.count c))
nextChar
:: (Monad m)
=> Producer Text m r
-> m (Either r (Char, Producer Text m r))
nextChar = go
where
go p = do
x <- next p
case x of
Left r -> return (Left r)
Right (txt, p') -> case (T.uncons txt) of
Nothing -> go p'
Just (c, txt') -> return (Right (c, yield txt' >> p'))
drawChar :: (Monad m) => Parser Text m (Maybe Char)
drawChar = do
x <- PP.draw
case x of
Nothing -> return Nothing
Just txt -> case (T.uncons txt) of
Nothing -> drawChar
Just (c, txt') -> do
PP.unDraw txt'
return (Just c)
unDrawChar :: (Monad m) => Char -> Parser Text m ()
unDrawChar c = modify (yield (T.singleton c) >>)
peekChar :: (Monad m) => Parser Text m (Maybe Char)
peekChar = do
x <- drawChar
case x of
Nothing -> return ()
Just c -> unDrawChar c
return x
isEndOfChars :: (Monad m) => Parser Text m Bool
isEndOfChars = do
x <- peekChar
return (case x of
Nothing -> True
Just _-> False )
decodeUtf8 :: Monad m => Lens' (Producer ByteString m r)
(Producer Text m (Producer ByteString m r))
decodeUtf8 k p0 = fmap (\p -> join (for p (yield . TE.encodeUtf8)))
(k (go B.empty PI.streamDecodeUtf8 p0)) where
go !carry dec0 p = do
x <- lift (next p)
case x of Left r -> return (if B.null carry
then return r
else (do yield carry
return r))
Right (chunk, p') -> case dec0 chunk of
PI.Some text carry2 dec -> do yield text
go carry2 dec p'
PI.Other text bs -> do yield text
return (do yield bs
p')
splitAt
:: (Monad m, Integral n)
=> n
-> Lens' (Producer Text m r)
(Producer Text m (Producer Text m r))
splitAt n0 k p0 = fmap join (k (go n0 p0))
where
go 0 p = return p
go n p = do
x <- lift (next p)
case x of
Left r -> return (return r)
Right (txt, p') -> do
let len = fromIntegral (T.length txt)
if (len <= n)
then do
yield txt
go (n len) p'
else do
let (prefix, suffix) = T.splitAt (fromIntegral n) txt
yield prefix
return (yield suffix >> p')
span
:: (Monad m)
=> (Char -> Bool)
-> Lens' (Producer Text m r)
(Producer Text m (Producer Text m r))
span predicate k p0 = fmap join (k (go p0))
where
go p = do
x <- lift (next p)
case x of
Left r -> return (return r)
Right (txt, p') -> do
let (prefix, suffix) = T.span predicate txt
if (T.null suffix)
then do
yield txt
go p'
else do
yield prefix
return (yield suffix >> p')
break
:: (Monad m)
=> (Char -> Bool)
-> Lens' (Producer Text m r)
(Producer Text m (Producer Text m r))
break predicate = span (not . predicate)
groupBy
:: (Monad m)
=> (Char -> Char -> Bool)
-> Lens' (Producer Text m r)
(Producer Text m (Producer Text m r))
groupBy equals k p0 = fmap join (k ((go p0))) where
go p = do
x <- lift (next p)
case x of
Left r -> return (return r)
Right (txt, p') -> case T.uncons txt of
Nothing -> go p'
Just (c, _) -> (yield txt >> p') ^. span (equals c)
group :: Monad m
=> Lens' (Producer Text m r)
(Producer Text m (Producer Text m r))
group = groupBy (==)
word :: (Monad m)
=> Lens' (Producer Text m r)
(Producer Text m (Producer Text m r))
word k p0 = fmap join (k (to p0))
where
to p = do
p' <- p^.span isSpace
p'^.break isSpace
line :: (Monad m)
=> Lens' (Producer Text m r)
(Producer Text m (Producer Text m r))
line = break (== '\n')
intersperse
:: (Monad m) => Char -> Producer Text m r -> Producer Text m r
intersperse c = go0
where
go0 p = do
x <- lift (next p)
case x of
Left r -> return r
Right (txt, p') -> do
yield (T.intersperse c txt)
go1 p'
go1 p = do
x <- lift (next p)
case x of
Left r -> return r
Right (txt, p') -> do
yield (T.singleton c)
yield (T.intersperse c txt)
go1 p'
packChars :: Monad m => Iso' (Producer Char m x) (Producer Text m x)
packChars = Data.Profunctor.dimap to (fmap from)
where
to p = PG.folds step id done (p^.PG.chunksOf defaultChunkSize)
step diffAs c = diffAs . (c:)
done diffAs = T.pack (diffAs [])
from p = for p (each . T.unpack)
chunksOf
:: (Monad m, Integral n)
=> n -> Lens' (Producer Text m r)
(FreeT (Producer Text m) m r)
chunksOf n k p0 = fmap concats (k (FreeT (go p0)))
where
go p = do
x <- next p
return $ case x of
Left r -> Pure r
Right (txt, p') -> Free $ do
p'' <- (yield txt >> p') ^. splitAt n
return $ FreeT (go p'')
splitsWith
:: (Monad m)
=> (Char -> Bool)
-> Producer Text m r
-> FreeT (Producer Text m) m r
splitsWith predicate p0 = FreeT (go0 p0)
where
go0 p = do
x <- next p
case x of
Left r -> return (Pure r)
Right (txt, p') ->
if (T.null txt)
then go0 p'
else return $ Free $ do
p'' <- (yield txt >> p') ^. span (not . predicate)
return $ FreeT (go1 p'')
go1 p = do
x <- nextChar p
return $ case x of
Left r -> Pure r
Right (_, p') -> Free $ do
p'' <- p' ^. span (not . predicate)
return $ FreeT (go1 p'')
splits :: (Monad m)
=> Char
-> Lens' (Producer Text m r)
(FreeT (Producer Text m) m r)
splits c k p =
fmap (PG.intercalates (yield (T.singleton c))) (k (splitsWith (c ==) p))
groupsBy
:: Monad m
=> (Char -> Char -> Bool)
-> Lens' (Producer Text m x) (FreeT (Producer Text m) m x)
groupsBy equals k p0 = fmap concats (k (FreeT (go p0))) where
go p = do x <- next p
case x of Left r -> return (Pure r)
Right (bs, p') -> case T.uncons bs of
Nothing -> go p'
Just (c, _) -> do return $ Free $ do
p'' <- (yield bs >> p')^.span (equals c)
return $ FreeT (go p'')
groups
:: Monad m
=> Lens' (Producer Text m x) (FreeT (Producer Text m) m x)
groups = groupsBy (==)
lines
:: (Monad m) => Iso' (Producer Text m r) (FreeT (Producer Text m) m r)
lines = Data.Profunctor.dimap _lines (fmap _unlines)
where
_lines p0 = FreeT (go0 p0)
where
go0 p = do
x <- next p
case x of
Left r -> return (Pure r)
Right (txt, p') ->
if (T.null txt)
then go0 p'
else return $ Free $ go1 (yield txt >> p')
go1 p = do
p' <- p ^. break ('\n' ==)
return $ FreeT $ do
x <- nextChar p'
case x of
Left r -> return $ Pure r
Right (_, p'') -> go0 p''
_unlines = concats . PG.maps (<* yield (T.singleton '\n'))
words
:: (Monad m) => Iso' (Producer Text m r) (FreeT (Producer Text m) m r)
words = Data.Profunctor.dimap go (fmap _unwords)
where
go p = FreeT $ do
x <- next (p >-> dropWhile isSpace)
return $ case x of
Left r -> Pure r
Right (bs, p') -> Free $ do
p'' <- (yield bs >> p') ^. break isSpace
return (go p'')
_unwords = PG.intercalates (yield $ T.singleton ' ')
intercalate
:: (Monad m)
=> Producer Text m ()
-> FreeT (Producer Text m) m r
-> Producer Text m r
intercalate p0 = go0
where
go0 f = do
x <- lift (runFreeT f)
case x of
Pure r -> return r
Free p -> do
f' <- p
go1 f'
go1 f = do
x <- lift (runFreeT f)
case x of
Pure r -> return r
Free p -> do
p0
f' <- p
go1 f'
unlines
:: (Monad m) => FreeT (Producer Text m) m r -> Producer Text m r
unlines = go
where
go f = do
x <- lift (runFreeT f)
case x of
Pure r -> return r
Free p -> do
f' <- p
yield $ T.singleton '\n'
go f'
unwords
:: (Monad m) => FreeT (Producer Text m) m r -> Producer Text m r
unwords = intercalate (yield $ T.singleton ' ')
codec :: Monad m => Codec -> Lens' (Producer ByteString m r) (Producer Text m (Producer ByteString m r))
codec (Codec _ enc dec) k p0 = fmap (\p -> join (for p (yield . fst . enc)))
(k (decoder (dec B.empty) p0) ) where
decoder :: Monad m => PI.Decoding -> Producer ByteString m r -> Producer Text m (Producer ByteString m r)
decoder !d p0 = case d of
PI.Other txt bad -> do yield txt
return (do yield bad
p0)
PI.Some txt extra dec -> do yield txt
x <- lift (next p0)
case x of Left r -> return (do yield extra
return r)
Right (chunk,p1) -> decoder (dec chunk) p1
encodeAscii :: Monad m => Producer Text m r -> Producer ByteString m (Producer Text m r)
encodeAscii = go where
go p = do echunk <- lift (next p)
case echunk of
Left r -> return (return r)
Right (chunk, p') ->
if T.null chunk
then go p'
else let (safe, unsafe) = T.span (\c -> ord c <= 0x7F) chunk
in do yield (B8.pack (T.unpack safe))
if T.null unsafe
then go p'
else return $ do yield unsafe
p'
encodeIso8859_1 :: Monad m => Producer Text m r -> Producer ByteString m (Producer Text m r)
encodeIso8859_1 = go where
go p = do etxt <- lift (next p)
case etxt of
Left r -> return (return r)
Right (txt, p') ->
if T.null txt
then go p'
else let (safe, unsafe) = T.span (\c -> ord c <= 0xFF) txt
in do yield (B8.pack (T.unpack safe))
if T.null unsafe
then go p'
else return $ do yield unsafe
p'
decodeAscii :: Monad m => Producer ByteString m r -> Producer Text m (Producer ByteString m r)
decodeAscii = go where
go p = do echunk <- lift (next p)
case echunk of
Left r -> return (return r)
Right (chunk, p') ->
if B.null chunk
then go p'
else let (safe, unsafe) = B.span (<= 0x7F) chunk
in do yield (T.pack (B8.unpack safe))
if B.null unsafe
then go p'
else return $ do yield unsafe
p'
decodeIso8859_1 :: Monad m => Producer ByteString m r -> Producer Text m (Producer ByteString m r)
decodeIso8859_1 = go where
go p = do echunk <- lift (next p)
case echunk of
Left r -> return (return r)
Right (chunk, p') ->
if B.null chunk
then go p'
else let (safe, unsafe) = B.span (<= 0xFF) chunk
in do yield (T.pack (B8.unpack safe))
if B.null unsafe
then go p'
else return $ do yield unsafe
p'