{-# LANGUAGE RankNTypes, Trustworthy #-}
module Pipes.ByteString (
fromLazy
, stdin
, fromHandle
, hGetSome
, hGetNonBlocking
, hGet
, hGetRange
, hGetSomeN
, hGetN
, stdout
, toHandle
, map
, concatMap
, take
, takeWhile
, filter
, elemIndices
, findIndices
, scan
, toLazy
, toLazyM
, toLazyM'
, foldBytes
, head
, last
, null
, length
, any
, all
, maximum
, minimum
, elem
, notElem
, find
, index
, elemIndex
, findIndex
, count
, nextByte
, drawByte
, unDrawByte
, peekByte
, isEndOfBytes
, splitAt
, span
, break
, breakOn
, groupBy
, group
, word
, line
, drop
, dropWhile
, intersperse
, pack
, unpack
, chunksOf'
, chunksOf
, splitsWith
, splits
, splitOn
, groupsBy
, groups
, lines
, unlines
, words
, unwords
, module Data.ByteString
, module Data.Word
, module Pipes.Group
, module Pipes.Parse
) where
import Control.Applicative ((<*))
import Control.Exception (throwIO, try)
import Control.Monad (liftM, join)
import Control.Monad.Trans.State.Strict (modify)
import qualified Data.ByteString as BS
import Data.ByteString (ByteString)
import Data.ByteString.Internal (isSpaceWord8)
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Search
import Data.ByteString.Lazy.Internal (foldrChunks, defaultChunkSize)
import Data.ByteString.Unsafe (unsafeTake)
import Data.Char (ord)
import Data.Monoid (mempty, (<>))
import Data.Functor.Constant (Constant(Constant, getConstant))
import Data.Functor.Identity (Identity)
import qualified Data.List as List
import Data.Word (Word8)
import Foreign.C.Error (Errno(Errno), ePIPE)
import qualified GHC.IO.Exception as G
import Pipes
import Pipes.Core (respond, Server')
import qualified Pipes.Group as PG
import Pipes.Group (concats, intercalates, FreeT)
import qualified Pipes.Parse as PP
import Pipes.Parse (Parser)
import qualified Pipes.Prelude as P
import qualified System.IO as IO
import Prelude hiding (
all
, any
, break
, concatMap
, drop
, dropWhile
, elem
, filter
, head
, last
, lines
, length
, map
, maximum
, minimum
, notElem
, null
, span
, splitAt
, take
, takeWhile
, unlines
, unwords
, words
)
fromLazy :: Monad m => BL.ByteString -> Producer' ByteString m ()
fromLazy :: forall (m :: * -> *).
Monad m =>
ByteString -> Producer' ByteString m ()
fromLazy ByteString
bs = forall a. (ByteString -> a -> a) -> a -> ByteString -> a
foldrChunks (\ByteString
e Proxy x' x () ByteString m ()
a -> forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
e forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Proxy x' x () ByteString m ()
a) (forall (m :: * -> *) a. Monad m => a -> m a
return ()) ByteString
bs
{-# INLINABLE fromLazy #-}
stdin :: MonadIO m => Producer' ByteString m ()
stdin :: forall (m :: * -> *). MonadIO m => Producer' ByteString m ()
stdin = forall (m :: * -> *).
MonadIO m =>
Handle -> Producer' ByteString m ()
fromHandle Handle
IO.stdin
{-# INLINABLE stdin #-}
fromHandle :: MonadIO m => IO.Handle -> Producer' ByteString m ()
fromHandle :: forall (m :: * -> *).
MonadIO m =>
Handle -> Producer' ByteString m ()
fromHandle = forall (m :: * -> *).
MonadIO m =>
Int -> Handle -> Producer' ByteString m ()
hGetSome Int
defaultChunkSize
{-# INLINABLE fromHandle #-}
hGetSome :: MonadIO m => Int -> IO.Handle -> Producer' ByteString m ()
hGetSome :: forall (m :: * -> *).
MonadIO m =>
Int -> Handle -> Producer' ByteString m ()
hGetSome Int
size Handle
h = forall {x'} {x}. Proxy x' x () ByteString m ()
go
where
go :: Proxy x' x () ByteString m ()
go = do
ByteString
bs <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Handle -> Int -> IO ByteString
BS.hGetSome Handle
h Int
size)
if (ByteString -> Bool
BS.null ByteString
bs)
then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else do
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs
Proxy x' x () ByteString m ()
go
{-# INLINABLE hGetSome #-}
hGetNonBlocking :: MonadIO m => Int -> IO.Handle -> Producer' ByteString m ()
hGetNonBlocking :: forall (m :: * -> *).
MonadIO m =>
Int -> Handle -> Producer' ByteString m ()
hGetNonBlocking Int
size Handle
h = forall {x'} {x}. Proxy x' x () ByteString m ()
go where
go :: Proxy x' x () ByteString m ()
go = do
Bool
eof <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Handle -> IO Bool
IO.hIsEOF Handle
h)
if Bool
eof
then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else do
ByteString
bs <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Handle -> Int -> IO ByteString
BS.hGetNonBlocking Handle
h Int
size)
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs
Proxy x' x () ByteString m ()
go
{-# INLINABLE hGetNonBlocking #-}
hGet :: MonadIO m => Int -> IO.Handle -> Producer' ByteString m ()
hGet :: forall (m :: * -> *).
MonadIO m =>
Int -> Handle -> Producer' ByteString m ()
hGet Int
size Handle
h = forall {x'} {x}. Proxy x' x () ByteString m ()
go
where
go :: Proxy x' x () ByteString m ()
go = do
ByteString
bs <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Handle -> Int -> IO ByteString
BS.hGet Handle
h Int
size)
if (ByteString -> Bool
BS.null ByteString
bs)
then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else do
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs
Proxy x' x () ByteString m ()
go
{-# INLINABLE hGet #-}
hGetRange
:: MonadIO m
=> Int
-> Int
-> IO.Handle
-> Producer' ByteString m ()
hGetRange :: forall (m :: * -> *).
MonadIO m =>
Int -> Int -> Handle -> Producer' ByteString m ()
hGetRange Int
offset Int
size Handle
h = do
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ Handle -> SeekMode -> Integer -> IO ()
IO.hSeek Handle
h SeekMode
IO.AbsoluteSeek (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
offset)
forall (m :: * -> *).
MonadIO m =>
Int -> Handle -> Producer' ByteString m ()
hGet Int
size Handle
h
{-# INLINABLE hGetRange #-}
(^.) :: a -> ((b -> Constant b b) -> (a -> Constant b a)) -> b
a
a ^. :: forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. (b -> Constant b b) -> a -> Constant b a
lens = forall {k} a (b :: k). Constant a b -> a
getConstant ((b -> Constant b b) -> a -> Constant b a
lens forall {k} a (b :: k). a -> Constant a b
Constant a
a)
hGetSomeN :: MonadIO m => IO.Handle -> Int -> Server' Int ByteString m ()
hGetSomeN :: forall (m :: * -> *).
MonadIO m =>
Handle -> Int -> Server' Int ByteString m ()
hGetSomeN Handle
h Int
size = forall {m :: * -> *} {x'} {x}.
MonadIO m =>
Int -> Proxy x' x Int ByteString m ()
go Int
size
where
go :: Int -> Proxy x' x Int ByteString m ()
go Int
size = do
ByteString
bs <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Handle -> Int -> IO ByteString
BS.hGetSome Handle
h Int
size)
if (ByteString -> Bool
BS.null ByteString
bs)
then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else do
Int
size2 <- forall (m :: * -> *) a x' x a'.
Functor m =>
a -> Proxy x' x a' a m a'
respond ByteString
bs
Int -> Proxy x' x Int ByteString m ()
go Int
size2
{-# INLINABLE hGetSomeN #-}
hGetN :: MonadIO m => IO.Handle -> Int -> Server' Int ByteString m ()
hGetN :: forall (m :: * -> *).
MonadIO m =>
Handle -> Int -> Server' Int ByteString m ()
hGetN Handle
h Int
size = forall {m :: * -> *} {x'} {x}.
MonadIO m =>
Int -> Proxy x' x Int ByteString m ()
go Int
size
where
go :: Int -> Proxy x' x Int ByteString m ()
go Int
size = do
ByteString
bs <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Handle -> Int -> IO ByteString
BS.hGet Handle
h Int
size)
if (ByteString -> Bool
BS.null ByteString
bs)
then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else do
Int
size2 <- forall (m :: * -> *) a x' x a'.
Functor m =>
a -> Proxy x' x a' a m a'
respond ByteString
bs
Int -> Proxy x' x Int ByteString m ()
go Int
size2
{-# INLINABLE hGetN #-}
stdout :: MonadIO m => Consumer' ByteString m ()
stdout :: forall (m :: * -> *). MonadIO m => Consumer' ByteString m ()
stdout = forall {y'} {y}. Proxy () ByteString y' y m ()
go
where
go :: Proxy () ByteString y' y m ()
go = do
ByteString
bs <- forall (m :: * -> *) a. Functor m => Consumer' a m a
await
Either IOException ()
x <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => IO a -> IO (Either e a)
try (ByteString -> IO ()
BS.putStr ByteString
bs)
case Either IOException ()
x of
Left (G.IOError { ioe_type :: IOException -> IOErrorType
G.ioe_type = IOErrorType
G.ResourceVanished
, ioe_errno :: IOException -> Maybe CInt
G.ioe_errno = Just CInt
ioe })
| CInt -> Errno
Errno CInt
ioe forall a. Eq a => a -> a -> Bool
== Errno
ePIPE
-> forall (m :: * -> *) a. Monad m => a -> m a
return ()
Left IOException
e -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (forall e a. Exception e => e -> IO a
throwIO IOException
e)
Right () -> Proxy () ByteString y' y m ()
go
{-# INLINABLE stdout #-}
toHandle :: MonadIO m => IO.Handle -> Consumer' ByteString m r
toHandle :: forall (m :: * -> *) r.
MonadIO m =>
Handle -> Consumer' ByteString m r
toHandle Handle
h = forall (m :: * -> *) x' x b' b a' c' c.
Functor m =>
Proxy x' x b' b m a'
-> (b -> Proxy x' x c' c m b') -> Proxy x' x c' c m a'
for forall (m :: * -> *) a r. Functor m => Pipe a a m r
cat (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> ByteString -> IO ()
BS.hPut Handle
h)
{-# INLINABLE [1] toHandle #-}
{-# RULES "p >-> toHandle h" forall p h .
p >-> toHandle h = for p (\bs -> liftIO (BS.hPut h bs))
#-}
map :: Monad m => (Word8 -> Word8) -> Pipe ByteString ByteString m r
map :: forall (m :: * -> *) r.
Monad m =>
(Word8 -> Word8) -> Pipe ByteString ByteString m r
map Word8 -> Word8
f = forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map ((Word8 -> Word8) -> ByteString -> ByteString
BS.map Word8 -> Word8
f)
{-# INLINE map #-}
concatMap :: Monad m => (Word8 -> ByteString) -> Pipe ByteString ByteString m r
concatMap :: forall (m :: * -> *) r.
Monad m =>
(Word8 -> ByteString) -> Pipe ByteString ByteString m r
concatMap Word8 -> ByteString
f = forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map ((Word8 -> ByteString) -> ByteString -> ByteString
BS.concatMap Word8 -> ByteString
f)
{-# INLINABLE concatMap #-}
take :: (Monad m, Integral n) => n -> Pipe ByteString ByteString m ()
take :: forall (m :: * -> *) n.
(Monad m, Integral n) =>
n -> Pipe ByteString ByteString m ()
take n
n0 = forall {t} {m :: * -> *}.
(Functor m, Integral t) =>
t -> Proxy () ByteString () ByteString m ()
go n
n0 where
go :: t -> Proxy () ByteString () ByteString m ()
go t
n
| t
n forall a. Ord a => a -> a -> Bool
<= t
0 = forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do
ByteString
bs <- forall (m :: * -> *) a. Functor m => Consumer' a m a
await
let len :: t
len = forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
BS.length ByteString
bs)
if (t
len forall a. Ord a => a -> a -> Bool
> t
n)
then forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Int -> ByteString -> ByteString
unsafeTake (forall a b. (Integral a, Num b) => a -> b
fromIntegral t
n) ByteString
bs)
else do
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs
t -> Proxy () ByteString () ByteString m ()
go (t
n forall a. Num a => a -> a -> a
- t
len)
{-# INLINABLE take #-}
takeWhile :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString m ()
takeWhile :: forall (m :: * -> *).
Monad m =>
(Word8 -> Bool) -> Pipe ByteString ByteString m ()
takeWhile Word8 -> Bool
predicate = Proxy () ByteString () ByteString m ()
go
where
go :: Proxy () ByteString () ByteString m ()
go = do
ByteString
bs <- forall (m :: * -> *) a. Functor m => Consumer' a m a
await
let (ByteString
prefix, ByteString
suffix) = (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
BS.span Word8 -> Bool
predicate ByteString
bs
if (ByteString -> Bool
BS.null ByteString
suffix)
then do
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs
Proxy () ByteString () ByteString m ()
go
else forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
prefix
{-# INLINABLE takeWhile #-}
filter :: Monad m => (Word8 -> Bool) -> Pipe ByteString ByteString m r
filter :: forall (m :: * -> *) r.
Monad m =>
(Word8 -> Bool) -> Pipe ByteString ByteString m r
filter Word8 -> Bool
predicate = forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map ((Word8 -> Bool) -> ByteString -> ByteString
BS.filter Word8 -> Bool
predicate)
{-# INLINABLE filter #-}
elemIndices :: (Monad m, Num n) => Word8 -> Pipe ByteString n m r
elemIndices :: forall (m :: * -> *) n r.
(Monad m, Num n) =>
Word8 -> Pipe ByteString n m r
elemIndices Word8
w8 = forall (m :: * -> *) n r.
(Monad m, Num n) =>
(Word8 -> Bool) -> Pipe ByteString n m r
findIndices (Word8
w8 forall a. Eq a => a -> a -> Bool
==)
{-# INLINABLE elemIndices #-}
findIndices :: (Monad m, Num n) => (Word8 -> Bool) -> Pipe ByteString n m r
findIndices :: forall (m :: * -> *) n r.
(Monad m, Num n) =>
(Word8 -> Bool) -> Pipe ByteString n m r
findIndices Word8 -> Bool
predicate = forall {m :: * -> *} {a} {b}.
(Functor m, Num a) =>
a -> Proxy () ByteString () a m b
go n
0
where
go :: a -> Proxy () ByteString () a m b
go a
n = do
ByteString
bs <- forall (m :: * -> *) a. Functor m => Consumer' a m a
await
forall (m :: * -> *) (f :: * -> *) a x' x.
(Functor m, Foldable f) =>
f a -> Proxy x' x () a m ()
each forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
List.map (\Int
i -> a
n forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) ((Word8 -> Bool) -> ByteString -> [Int]
BS.findIndices Word8 -> Bool
predicate ByteString
bs)
a -> Proxy () ByteString () a m b
go forall a b. (a -> b) -> a -> b
$! a
n forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
BS.length ByteString
bs)
{-# INLINABLE findIndices #-}
scan
:: Monad m
=> (Word8 -> Word8 -> Word8) -> Word8 -> Pipe ByteString ByteString m r
scan :: forall (m :: * -> *) r.
Monad m =>
(Word8 -> Word8 -> Word8)
-> Word8 -> Pipe ByteString ByteString m r
scan Word8 -> Word8 -> Word8
step Word8
begin = do
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Word8 -> ByteString
BS.singleton Word8
begin)
forall {m :: * -> *} {b}.
Functor m =>
Word8 -> Proxy () ByteString () ByteString m b
go Word8
begin
where
go :: Word8 -> Proxy () ByteString () ByteString m b
go Word8
w8 = do
ByteString
bs <- forall (m :: * -> *) a. Functor m => Consumer' a m a
await
let bs' :: ByteString
bs' = (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString
BS.scanl Word8 -> Word8 -> Word8
step Word8
w8 ByteString
bs
w8' :: Word8
w8' = HasCallStack => ByteString -> Word8
BS.last ByteString
bs'
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (HasCallStack => ByteString -> ByteString
BS.tail ByteString
bs')
Word8 -> Proxy () ByteString () ByteString m b
go Word8
w8'
{-# INLINABLE scan #-}
toLazy :: Producer ByteString Identity () -> BL.ByteString
toLazy :: Producer ByteString Identity () -> ByteString
toLazy = [ByteString] -> ByteString
BL.fromChunks forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Producer a Identity () -> [a]
P.toList
{-# INLINABLE toLazy #-}
toLazyM :: Monad m => Producer ByteString m () -> m BL.ByteString
toLazyM :: forall (m :: * -> *).
Monad m =>
Producer ByteString m () -> m ByteString
toLazyM = forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM [ByteString] -> ByteString
BL.fromChunks forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => Producer a m () -> m [a]
P.toListM
{-# INLINABLE toLazyM #-}
toLazyM' :: Monad m => Producer ByteString m a -> m (BL.ByteString, a)
toLazyM' :: forall (m :: * -> *) a.
Monad m =>
Producer ByteString m a -> m (ByteString, a)
toLazyM' Producer ByteString m a
p = do ([ByteString]
chunks, a
a) <- forall (m :: * -> *) a r. Monad m => Producer a m r -> m ([a], r)
P.toListM' Producer ByteString m a
p
forall (m :: * -> *) a. Monad m => a -> m a
return ([ByteString] -> ByteString
BL.fromChunks [ByteString]
chunks, a
a)
{-# INLINABLE toLazyM' #-}
foldBytes
:: Monad m
=> (x -> Word8 -> x) -> x -> (x -> r) -> Producer ByteString m () -> m r
foldBytes :: forall (m :: * -> *) x r.
Monad m =>
(x -> Word8 -> x)
-> x -> (x -> r) -> Producer ByteString m () -> m r
foldBytes x -> Word8 -> x
step x
begin x -> r
done = forall (m :: * -> *) x a b.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b
P.fold (\x
x ByteString
bs -> forall a. (a -> Word8 -> a) -> a -> ByteString -> a
BS.foldl' x -> Word8 -> x
step x
x ByteString
bs) x
begin x -> r
done
{-# INLINABLE foldBytes #-}
head :: Monad m => Producer ByteString m () -> m (Maybe Word8)
head :: forall (m :: * -> *).
Monad m =>
Producer ByteString m () -> m (Maybe Word8)
head = forall {m :: * -> *} {r}.
Monad m =>
Producer ByteString m r -> m (Maybe Word8)
go
where
go :: Producer ByteString m r -> m (Maybe Word8)
go Producer ByteString m r
p = do
Either r (Word8, Producer ByteString m r)
x <- forall (m :: * -> *) r.
Monad m =>
Producer ByteString m r
-> m (Either r (Word8, Producer ByteString m r))
nextByte Producer ByteString m r
p
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Either r (Word8, Producer ByteString m r)
x of
Left r
_ -> forall a. Maybe a
Nothing
Right (Word8
w8, Producer ByteString m r
_) -> forall a. a -> Maybe a
Just Word8
w8
{-# INLINABLE head #-}
last :: Monad m => Producer ByteString m () -> m (Maybe Word8)
last :: forall (m :: * -> *).
Monad m =>
Producer ByteString m () -> m (Maybe Word8)
last = forall {m :: * -> *}.
Monad m =>
Maybe Word8 -> Producer ByteString m () -> m (Maybe Word8)
go forall a. Maybe a
Nothing
where
go :: Maybe Word8 -> Producer ByteString m () -> m (Maybe Word8)
go Maybe Word8
r Producer ByteString m ()
p = do
Either () (ByteString, Producer ByteString m ())
x <- forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer ByteString m ()
p
case Either () (ByteString, Producer ByteString m ())
x of
Left () -> forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Word8
r
Right (ByteString
bs, Producer ByteString m ()
p') ->
Maybe Word8 -> Producer ByteString m () -> m (Maybe Word8)
go (if ByteString -> Bool
BS.null ByteString
bs then Maybe Word8
r else (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> Word8
BS.last ByteString
bs)) Producer ByteString m ()
p'
{-# INLINABLE last #-}
null :: Monad m => Producer ByteString m () -> m Bool
null :: forall (m :: * -> *). Monad m => Producer ByteString m () -> m Bool
null = forall (m :: * -> *) a.
Monad m =>
(a -> Bool) -> Producer a m () -> m Bool
P.all ByteString -> Bool
BS.null
{-# INLINABLE null #-}
length :: (Monad m, Num n) => Producer ByteString m () -> m n
length :: forall (m :: * -> *) n.
(Monad m, Num n) =>
Producer ByteString m () -> m n
length = forall (m :: * -> *) x a b.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b
P.fold (\n
n ByteString
bs -> n
n forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
BS.length ByteString
bs)) n
0 forall a. a -> a
id
{-# INLINABLE length #-}
any :: Monad m => (Word8 -> Bool) -> Producer ByteString m () -> m Bool
any :: forall (m :: * -> *).
Monad m =>
(Word8 -> Bool) -> Producer ByteString m () -> m Bool
any Word8 -> Bool
predicate = forall (m :: * -> *) a.
Monad m =>
(a -> Bool) -> Producer a m () -> m Bool
P.any ((Word8 -> Bool) -> ByteString -> Bool
BS.any Word8 -> Bool
predicate)
{-# INLINABLE any #-}
all :: Monad m => (Word8 -> Bool) -> Producer ByteString m () -> m Bool
all :: forall (m :: * -> *).
Monad m =>
(Word8 -> Bool) -> Producer ByteString m () -> m Bool
all Word8 -> Bool
predicate = forall (m :: * -> *) a.
Monad m =>
(a -> Bool) -> Producer a m () -> m Bool
P.all ((Word8 -> Bool) -> ByteString -> Bool
BS.all Word8 -> Bool
predicate)
{-# INLINABLE all #-}
maximum :: Monad m => Producer ByteString m () -> m (Maybe Word8)
maximum :: forall (m :: * -> *).
Monad m =>
Producer ByteString m () -> m (Maybe Word8)
maximum = forall (m :: * -> *) x a b.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b
P.fold Maybe Word8 -> ByteString -> Maybe Word8
step forall a. Maybe a
Nothing forall a. a -> a
id
where
step :: Maybe Word8 -> ByteString -> Maybe Word8
step Maybe Word8
mw8 ByteString
bs =
if (ByteString -> Bool
BS.null ByteString
bs)
then Maybe Word8
mw8
else forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ case Maybe Word8
mw8 of
Maybe Word8
Nothing -> HasCallStack => ByteString -> Word8
BS.maximum ByteString
bs
Just Word8
w8 -> forall a. Ord a => a -> a -> a
max Word8
w8 (HasCallStack => ByteString -> Word8
BS.maximum ByteString
bs)
{-# INLINABLE maximum #-}
minimum :: Monad m => Producer ByteString m () -> m (Maybe Word8)
minimum :: forall (m :: * -> *).
Monad m =>
Producer ByteString m () -> m (Maybe Word8)
minimum = forall (m :: * -> *) x a b.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b
P.fold Maybe Word8 -> ByteString -> Maybe Word8
step forall a. Maybe a
Nothing forall a. a -> a
id
where
step :: Maybe Word8 -> ByteString -> Maybe Word8
step Maybe Word8
mw8 ByteString
bs =
if (ByteString -> Bool
BS.null ByteString
bs)
then Maybe Word8
mw8
else case Maybe Word8
mw8 of
Maybe Word8
Nothing -> forall a. a -> Maybe a
Just (HasCallStack => ByteString -> Word8
BS.minimum ByteString
bs)
Just Word8
w8 -> forall a. a -> Maybe a
Just (forall a. Ord a => a -> a -> a
min Word8
w8 (HasCallStack => ByteString -> Word8
BS.minimum ByteString
bs))
{-# INLINABLE minimum #-}
elem :: Monad m => Word8 -> Producer ByteString m () -> m Bool
elem :: forall (m :: * -> *).
Monad m =>
Word8 -> Producer ByteString m () -> m Bool
elem Word8
w8 = forall (m :: * -> *) a.
Monad m =>
(a -> Bool) -> Producer a m () -> m Bool
P.any (Word8 -> ByteString -> Bool
BS.elem Word8
w8)
{-# INLINABLE elem #-}
notElem :: Monad m => Word8 -> Producer ByteString m () -> m Bool
notElem :: forall (m :: * -> *).
Monad m =>
Word8 -> Producer ByteString m () -> m Bool
notElem Word8
w8 = forall (m :: * -> *) a.
Monad m =>
(a -> Bool) -> Producer a m () -> m Bool
P.all (Word8 -> ByteString -> Bool
BS.notElem Word8
w8)
{-# INLINABLE notElem #-}
find
:: Monad m
=> (Word8 -> Bool) -> Producer ByteString m () -> m (Maybe Word8)
find :: forall (m :: * -> *).
Monad m =>
(Word8 -> Bool) -> Producer ByteString m () -> m (Maybe Word8)
find Word8 -> Bool
predicate Producer ByteString m ()
p = forall (m :: * -> *).
Monad m =>
Producer ByteString m () -> m (Maybe Word8)
head (Producer ByteString m ()
p forall (m :: * -> *) a' a b r c' c.
Functor m =>
Proxy a' a () b m r -> Proxy () b c' c m r -> Proxy a' a c' c m r
>-> forall (m :: * -> *) r.
Monad m =>
(Word8 -> Bool) -> Pipe ByteString ByteString m r
filter Word8 -> Bool
predicate)
{-# INLINABLE find #-}
index
:: (Monad m, Integral n)
=> n -> Producer ByteString m () -> m (Maybe Word8)
index :: forall (m :: * -> *) n.
(Monad m, Integral n) =>
n -> Producer ByteString m () -> m (Maybe Word8)
index n
n Producer ByteString m ()
p = forall (m :: * -> *).
Monad m =>
Producer ByteString m () -> m (Maybe Word8)
head (forall (m :: * -> *) n r.
(Monad m, Integral n) =>
n -> Producer ByteString m r -> Producer ByteString m r
drop n
n Producer ByteString m ()
p)
{-# INLINABLE index #-}
elemIndex
:: (Monad m, Num n) => Word8 -> Producer ByteString m () -> m (Maybe n)
elemIndex :: forall (m :: * -> *) n.
(Monad m, Num n) =>
Word8 -> Producer ByteString m () -> m (Maybe n)
elemIndex Word8
w8 = forall (m :: * -> *) n.
(Monad m, Num n) =>
(Word8 -> Bool) -> Producer ByteString m () -> m (Maybe n)
findIndex (Word8
w8 forall a. Eq a => a -> a -> Bool
==)
{-# INLINABLE elemIndex #-}
findIndex
:: (Monad m, Num n)
=> (Word8 -> Bool) -> Producer ByteString m () -> m (Maybe n)
findIndex :: forall (m :: * -> *) n.
(Monad m, Num n) =>
(Word8 -> Bool) -> Producer ByteString m () -> m (Maybe n)
findIndex Word8 -> Bool
predicate Producer ByteString m ()
p = forall (m :: * -> *) a. Monad m => Producer a m () -> m (Maybe a)
P.head (Producer ByteString m ()
p forall (m :: * -> *) a' a b r c' c.
Functor m =>
Proxy a' a () b m r -> Proxy () b c' c m r -> Proxy a' a c' c m r
>-> forall (m :: * -> *) n r.
(Monad m, Num n) =>
(Word8 -> Bool) -> Pipe ByteString n m r
findIndices Word8 -> Bool
predicate)
{-# INLINABLE findIndex #-}
count :: (Monad m, Num n) => Word8 -> Producer ByteString m () -> m n
count :: forall (m :: * -> *) n.
(Monad m, Num n) =>
Word8 -> Producer ByteString m () -> m n
count Word8
w8 Producer ByteString m ()
p = forall (m :: * -> *) x a b.
Monad m =>
(x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b
P.fold forall a. Num a => a -> a -> a
(+) n
0 forall a. a -> a
id (Producer ByteString m ()
p forall (m :: * -> *) a' a b r c' c.
Functor m =>
Proxy a' a () b m r -> Proxy () b c' c m r -> Proxy a' a c' c m r
>-> forall (m :: * -> *) a b r. Functor m => (a -> b) -> Pipe a b m r
P.map (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> ByteString -> Int
BS.count Word8
w8))
{-# INLINABLE count #-}
nextByte
:: Monad m
=> Producer ByteString m r
-> m (Either r (Word8, Producer ByteString m r))
nextByte :: forall (m :: * -> *) r.
Monad m =>
Producer ByteString m r
-> m (Either r (Word8, Producer ByteString m r))
nextByte = forall (m :: * -> *) r.
Monad m =>
Producer ByteString m r
-> m (Either r (Word8, Producer ByteString m r))
go
where
go :: Producer ByteString m b
-> m (Either b (Word8, Producer ByteString m b))
go Producer ByteString m b
p = do
Either b (ByteString, Producer ByteString m b)
x <- forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer ByteString m b
p
case Either b (ByteString, Producer ByteString m b)
x of
Left b
r -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left b
r)
Right (ByteString
bs, Producer ByteString m b
p') -> case (ByteString -> Maybe (Word8, ByteString)
BS.uncons ByteString
bs) of
Maybe (Word8, ByteString)
Nothing -> Producer ByteString m b
-> m (Either b (Word8, Producer ByteString m b))
go Producer ByteString m b
p'
Just (Word8
w8, ByteString
bs') -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right (Word8
w8, forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer ByteString m b
p'))
{-# INLINABLE nextByte #-}
drawByte :: Monad m => Parser ByteString m (Maybe Word8)
drawByte :: forall (m :: * -> *). Monad m => Parser ByteString m (Maybe Word8)
drawByte = do
Maybe ByteString
x <- forall (m :: * -> *) a. Monad m => Parser a m (Maybe a)
PP.draw
case Maybe ByteString
x of
Maybe ByteString
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
Just ByteString
bs -> case (ByteString -> Maybe (Word8, ByteString)
BS.uncons ByteString
bs) of
Maybe (Word8, ByteString)
Nothing -> forall (m :: * -> *). Monad m => Parser ByteString m (Maybe Word8)
drawByte
Just (Word8
w8, ByteString
bs') -> do
forall (m :: * -> *) a. Monad m => a -> Parser a m ()
PP.unDraw ByteString
bs'
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just Word8
w8)
{-# INLINABLE drawByte #-}
unDrawByte :: Monad m => Word8 -> Parser ByteString m ()
unDrawByte :: forall (m :: * -> *). Monad m => Word8 -> Parser ByteString m ()
unDrawByte Word8
w8 = forall (m :: * -> *) s. Monad m => (s -> s) -> StateT s m ()
modify (forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Word8 -> ByteString
BS.singleton Word8
w8) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>)
{-# INLINABLE unDrawByte #-}
peekByte :: Monad m => Parser ByteString m (Maybe Word8)
peekByte :: forall (m :: * -> *). Monad m => Parser ByteString m (Maybe Word8)
peekByte = do
Maybe Word8
x <- forall (m :: * -> *). Monad m => Parser ByteString m (Maybe Word8)
drawByte
case Maybe Word8
x of
Maybe Word8
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just Word8
w8 -> forall (m :: * -> *). Monad m => Word8 -> Parser ByteString m ()
unDrawByte Word8
w8
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Word8
x
{-# INLINABLE peekByte #-}
isEndOfBytes :: Monad m => Parser ByteString m Bool
isEndOfBytes :: forall (m :: * -> *). Monad m => Parser ByteString m Bool
isEndOfBytes = do
Maybe Word8
x <- forall (m :: * -> *). Monad m => Parser ByteString m (Maybe Word8)
peekByte
forall (m :: * -> *) a. Monad m => a -> m a
return (case Maybe Word8
x of
Maybe Word8
Nothing -> Bool
True
Just Word8
_ -> Bool
False )
{-# INLINABLE isEndOfBytes #-}
type Lens' a b = forall f . Functor f => (b -> f b) -> (a -> f a)
splitAt
:: (Monad m, Integral n)
=> n
-> Lens' (Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
splitAt :: forall (m :: * -> *) n x.
(Monad m, Integral n) =>
n
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
splitAt n
n0 Producer ByteString m (Producer ByteString m x)
-> f (Producer ByteString m (Producer ByteString m x))
k Producer ByteString m x
p0 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Producer ByteString m (Producer ByteString m x)
-> f (Producer ByteString m (Producer ByteString m x))
k (forall {t} {m :: * -> *} {r} {x'} {x}.
(Monad m, Integral t) =>
t
-> Producer ByteString m r
-> Proxy x' x () ByteString m (Producer ByteString m r)
go n
n0 Producer ByteString m x
p0))
where
go :: t
-> Producer ByteString m r
-> Proxy x' x () ByteString m (Producer ByteString m r)
go t
n Producer ByteString m r
p =
if (t
n forall a. Ord a => a -> a -> Bool
<= t
0)
then forall (m :: * -> *) a. Monad m => a -> m a
return Producer ByteString m r
p
else do
Either r (ByteString, Producer ByteString m r)
x <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer ByteString m r
p)
case Either r (ByteString, Producer ByteString m r)
x of
Left r
r -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall (m :: * -> *) a. Monad m => a -> m a
return r
r)
Right (ByteString
bs, Producer ByteString m r
p') -> do
let len :: t
len = forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
BS.length ByteString
bs)
if (t
len forall a. Ord a => a -> a -> Bool
<= t
n)
then do
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs
t
-> Producer ByteString m r
-> Proxy x' x () ByteString m (Producer ByteString m r)
go (t
n forall a. Num a => a -> a -> a
- t
len) Producer ByteString m r
p'
else do
let (ByteString
prefix, ByteString
suffix) =
Int -> ByteString -> (ByteString, ByteString)
BS.splitAt (forall a b. (Integral a, Num b) => a -> b
fromIntegral t
n) ByteString
bs
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
prefix
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
suffix forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer ByteString m r
p')
{-# INLINABLE splitAt #-}
span
:: Monad m
=> (Word8 -> Bool)
-> Lens' (Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
span :: forall (m :: * -> *) x.
Monad m =>
(Word8 -> Bool)
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
span Word8 -> Bool
predicate Producer ByteString m (Producer ByteString m x)
-> f (Producer ByteString m (Producer ByteString m x))
k Producer ByteString m x
p0 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Producer ByteString m (Producer ByteString m x)
-> f (Producer ByteString m (Producer ByteString m x))
k (forall {m :: * -> *} {a} {x'} {x}.
Monad m =>
Producer ByteString m a
-> Proxy x' x () ByteString m (Producer ByteString m a)
go Producer ByteString m x
p0))
where
go :: Producer ByteString m a
-> Proxy x' x () ByteString m (Producer ByteString m a)
go Producer ByteString m a
p = do
Either a (ByteString, Producer ByteString m a)
x <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer ByteString m a
p)
case Either a (ByteString, Producer ByteString m a)
x of
Left a
r -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall (m :: * -> *) a. Monad m => a -> m a
return a
r)
Right (ByteString
bs, Producer ByteString m a
p') -> do
let (ByteString
prefix, ByteString
suffix) = (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
BS.span Word8 -> Bool
predicate ByteString
bs
if (ByteString -> Bool
BS.null ByteString
suffix)
then do
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs
Producer ByteString m a
-> Proxy x' x () ByteString m (Producer ByteString m a)
go Producer ByteString m a
p'
else do
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
prefix
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
suffix forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer ByteString m a
p')
{-# INLINABLE span #-}
break
:: Monad m
=> (Word8 -> Bool)
-> Lens' (Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
break :: forall (m :: * -> *) x.
Monad m =>
(Word8 -> Bool)
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
break Word8 -> Bool
predicate = forall (m :: * -> *) x.
Monad m =>
(Word8 -> Bool)
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
span (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
predicate)
{-# INLINABLE break #-}
breakOn
:: Monad m
=> ByteString
-> Lens' (Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
breakOn :: forall (m :: * -> *) x.
Monad m =>
ByteString
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
breakOn ByteString
needle Producer ByteString m (Producer ByteString m x)
-> f (Producer ByteString m (Producer ByteString m x))
k Producer ByteString m x
p0 =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Producer ByteString m (Producer ByteString m x)
-> f (Producer ByteString m (Producer ByteString m x))
k (forall {m :: * -> *} {a} {x'} {x}.
Monad m =>
ByteString
-> Producer ByteString m a
-> Proxy x' x () ByteString m (Producer ByteString m a)
go forall a. Monoid a => a
mempty Producer ByteString m x
p0))
where
len0 :: Int
len0 = ByteString -> Int
BS.length ByteString
needle
go :: ByteString
-> Producer ByteString m a
-> Proxy x' x () ByteString m (Producer ByteString m a)
go ByteString
leftovers Producer ByteString m a
p =
if ByteString -> Int
BS.length ByteString
leftovers forall a. Ord a => a -> a -> Bool
< Int
len0
then do
Either a (ByteString, Producer ByteString m a)
x <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer ByteString m a
p)
case Either a (ByteString, Producer ByteString m a)
x of
Left a
r -> do
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
leftovers
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (m :: * -> *) a. Monad m => a -> m a
return a
r)
Right (ByteString
bytes, Producer ByteString m a
p') -> do
ByteString
-> Producer ByteString m a
-> Proxy x' x () ByteString m (Producer ByteString m a)
go (ByteString
leftovers forall a. Semigroup a => a -> a -> a
<> ByteString
bytes) Producer ByteString m a
p'
else do
let (ByteString
prefix, ByteString
suffix) = ByteString -> ByteString -> (ByteString, ByteString)
Data.ByteString.Search.breakOn ByteString
needle ByteString
leftovers
if ByteString -> Bool
BS.null ByteString
suffix
then do
let len :: Int
len = ByteString -> Int
BS.length ByteString
leftovers
let (ByteString
output, ByteString
leftovers') =
Int -> ByteString -> (ByteString, ByteString)
BS.splitAt (Int
len forall a. Num a => a -> a -> a
+ Int
1 forall a. Num a => a -> a -> a
- Int
len0) ByteString
leftovers
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
output
ByteString
-> Producer ByteString m a
-> Proxy x' x () ByteString m (Producer ByteString m a)
go ByteString
leftovers' Producer ByteString m a
p
else do
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
prefix
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
suffix forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer ByteString m a
p)
{-# INLINABLE breakOn #-}
groupBy
:: Monad m
=> (Word8 -> Word8 -> Bool)
-> Lens' (Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
groupBy :: forall (m :: * -> *) x.
Monad m =>
(Word8 -> Word8 -> Bool)
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
groupBy Word8 -> Word8 -> Bool
equals Producer ByteString m (Producer ByteString m x)
-> f (Producer ByteString m (Producer ByteString m x))
k Producer ByteString m x
p0 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Producer ByteString m (Producer ByteString m x)
-> f (Producer ByteString m (Producer ByteString m x))
k (forall {m :: * -> *} {b}.
Monad m =>
Producer ByteString m b
-> Proxy X () () ByteString m (Producer ByteString m b)
_groupBy Producer ByteString m x
p0))
where
_groupBy :: Producer ByteString m b
-> Proxy X () () ByteString m (Producer ByteString m b)
_groupBy Producer ByteString m b
p = do
Either b (ByteString, Producer ByteString m b)
x <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer ByteString m b
p)
case Either b (ByteString, Producer ByteString m b)
x of
Left b
r -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall (m :: * -> *) a. Monad m => a -> m a
return b
r)
Right (ByteString
bs, Producer ByteString m b
p') -> case (ByteString -> Maybe (Word8, ByteString)
BS.uncons ByteString
bs) of
Maybe (Word8, ByteString)
Nothing -> Producer ByteString m b
-> Proxy X () () ByteString m (Producer ByteString m b)
_groupBy Producer ByteString m b
p'
Just (Word8
w8, ByteString
_) -> (forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer ByteString m b
p')forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^.forall (m :: * -> *) x.
Monad m =>
(Word8 -> Bool)
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
span (Word8 -> Word8 -> Bool
equals Word8
w8)
{-# INLINABLE groupBy #-}
group
:: Monad m
=> Lens' (Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
group :: forall (m :: * -> *) x.
Monad m =>
Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
group = forall (m :: * -> *) x.
Monad m =>
(Word8 -> Word8 -> Bool)
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
groupBy forall a. Eq a => a -> a -> Bool
(==)
{-# INLINABLE group #-}
word
:: Monad m
=> Lens' (Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
word :: forall (m :: * -> *) x.
Monad m =>
Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
word Producer ByteString m (Producer ByteString m x)
-> f (Producer ByteString m (Producer ByteString m x))
k Producer ByteString m x
p0 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Producer ByteString m (Producer ByteString m x)
-> f (Producer ByteString m (Producer ByteString m x))
k (forall {m :: * -> *} {b}.
Monad m =>
Producer ByteString m b
-> Proxy X () () ByteString m (Producer ByteString m b)
to Producer ByteString m x
p0))
where
to :: Producer ByteString m x
-> Proxy X () () ByteString m (Producer ByteString m x)
to Producer ByteString m x
p = do
Producer ByteString m x
p' <- Producer ByteString m x
pforall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^.forall (m :: * -> *) x.
Monad m =>
(Word8 -> Bool)
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
span Word8 -> Bool
isSpaceWord8
Producer ByteString m x
p'forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^.forall (m :: * -> *) x.
Monad m =>
(Word8 -> Bool)
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
break Word8 -> Bool
isSpaceWord8
{-# INLINABLE word #-}
nl :: Word8
nl :: Word8
nl = forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
'\n')
line
:: Monad m
=> Lens' (Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
line :: forall (m :: * -> *) x.
Monad m =>
Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
line = forall (m :: * -> *) x.
Monad m =>
(Word8 -> Bool)
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
break (forall a. Eq a => a -> a -> Bool
== Word8
nl)
{-# INLINABLE line #-}
drop
:: (Monad m, Integral n)
=> n -> Producer ByteString m r -> Producer ByteString m r
drop :: forall (m :: * -> *) n r.
(Monad m, Integral n) =>
n -> Producer ByteString m r -> Producer ByteString m r
drop n
n Producer ByteString m r
p = do
Producer ByteString m r
p' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) r. Monad m => Effect m r -> m r
runEffect (forall (m :: * -> *) x' x b' b a' c' c.
Functor m =>
Proxy x' x b' b m a'
-> (b -> Proxy x' x c' c m b') -> Proxy x' x c' c m a'
for (Producer ByteString m r
p forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. forall (m :: * -> *) n x.
(Monad m, Integral n) =>
n
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
splitAt n
n) forall (m :: * -> *) a. Monad m => a -> m ()
discard)
Producer ByteString m r
p'
{-# INLINABLE drop #-}
dropWhile
:: Monad m
=> (Word8 -> Bool) -> Producer ByteString m r -> Producer ByteString m r
dropWhile :: forall (m :: * -> *) r.
Monad m =>
(Word8 -> Bool)
-> Producer ByteString m r -> Producer ByteString m r
dropWhile Word8 -> Bool
predicate Producer ByteString m r
p = do
Producer ByteString m r
p' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) r. Monad m => Effect m r -> m r
runEffect (forall (m :: * -> *) x' x b' b a' c' c.
Functor m =>
Proxy x' x b' b m a'
-> (b -> Proxy x' x c' c m b') -> Proxy x' x c' c m a'
for (Producer ByteString m r
p forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. forall (m :: * -> *) x.
Monad m =>
(Word8 -> Bool)
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
span Word8 -> Bool
predicate) forall (m :: * -> *) a. Monad m => a -> m ()
discard)
Producer ByteString m r
p'
{-# INLINABLE dropWhile #-}
intersperse
:: Monad m => Word8 -> Producer ByteString m r -> Producer ByteString m r
intersperse :: forall (m :: * -> *) r.
Monad m =>
Word8 -> Producer ByteString m r -> Producer ByteString m r
intersperse Word8
w8 = forall {m :: * -> *} {b} {x'} {x}.
Monad m =>
Producer ByteString m b -> Proxy x' x () ByteString m b
go0
where
go0 :: Producer ByteString m b -> Proxy x' x () ByteString m b
go0 Producer ByteString m b
p = do
Either b (ByteString, Producer ByteString m b)
x <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer ByteString m b
p)
case Either b (ByteString, Producer ByteString m b)
x of
Left b
r -> forall (m :: * -> *) a. Monad m => a -> m a
return b
r
Right (ByteString
bs, Producer ByteString m b
p') -> do
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Word8 -> ByteString -> ByteString
BS.intersperse Word8
w8 ByteString
bs)
forall {m :: * -> *} {b} {x'} {x}.
Monad m =>
Producer ByteString m b -> Proxy x' x () ByteString m b
go1 Producer ByteString m b
p'
go1 :: Producer ByteString m b -> Proxy x' x () ByteString m b
go1 Producer ByteString m b
p = do
Either b (ByteString, Producer ByteString m b)
x <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer ByteString m b
p)
case Either b (ByteString, Producer ByteString m b)
x of
Left b
r -> forall (m :: * -> *) a. Monad m => a -> m a
return b
r
Right (ByteString
bs, Producer ByteString m b
p') -> do
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Word8 -> ByteString
BS.singleton Word8
w8)
forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Word8 -> ByteString -> ByteString
BS.intersperse Word8
w8 ByteString
bs)
Producer ByteString m b -> Proxy x' x () ByteString m b
go1 Producer ByteString m b
p'
{-# INLINABLE intersperse #-}
pack :: Monad m => Lens' (Producer Word8 m x) (Producer ByteString m x)
pack :: forall (m :: * -> *) x.
Monad m =>
Lens' (Producer Word8 m x) (Producer ByteString m x)
pack Producer ByteString m x -> f (Producer ByteString m x)
k Producer Word8 m x
p = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (m :: * -> *) x.
Monad m =>
Producer ByteString m x -> Producer Word8 m x
_unpack (Producer ByteString m x -> f (Producer ByteString m x)
k (forall (m :: * -> *) x.
Monad m =>
Producer Word8 m x -> Producer ByteString m x
_pack Producer Word8 m x
p))
{-# INLINABLE pack #-}
unpack :: Monad m => Lens' (Producer ByteString m x) (Producer Word8 m x)
unpack :: forall (m :: * -> *) x.
Monad m =>
Lens' (Producer ByteString m x) (Producer Word8 m x)
unpack Producer Word8 m x -> f (Producer Word8 m x)
k Producer ByteString m x
p = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (m :: * -> *) x.
Monad m =>
Producer Word8 m x -> Producer ByteString m x
_pack (Producer Word8 m x -> f (Producer Word8 m x)
k (forall (m :: * -> *) x.
Monad m =>
Producer ByteString m x -> Producer Word8 m x
_unpack Producer ByteString m x
p))
{-# INLINABLE unpack #-}
_pack :: Monad m => Producer Word8 m x -> Producer ByteString m x
_pack :: forall (m :: * -> *) x.
Monad m =>
Producer Word8 m x -> Producer ByteString m x
_pack Producer Word8 m x
p = forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x)
-> x -> (x -> b) -> FreeT (Producer a m) m r -> Producer b m r
PG.folds forall {a} {c}. ([a] -> c) -> a -> [a] -> c
step forall a. a -> a
id forall {a}. ([a] -> [Word8]) -> ByteString
done (Producer Word8 m x
pforall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^.forall (m :: * -> *) a' x a.
Monad m =>
Int
-> Lens
(Producer a' m x)
(Producer a m x)
(FreeT (Producer a' m) m x)
(FreeT (Producer a m) m x)
PG.chunksOf Int
defaultChunkSize)
where
step :: ([a] -> c) -> a -> [a] -> c
step [a] -> c
diffAs a
w8 = [a] -> c
diffAs forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a
w8forall a. a -> [a] -> [a]
:)
done :: ([a] -> [Word8]) -> ByteString
done [a] -> [Word8]
diffAs = [Word8] -> ByteString
BS.pack ([a] -> [Word8]
diffAs [])
{-# INLINABLE _pack #-}
_unpack :: Monad m => Producer ByteString m x -> Producer Word8 m x
_unpack :: forall (m :: * -> *) x.
Monad m =>
Producer ByteString m x -> Producer Word8 m x
_unpack Producer ByteString m x
p = forall (m :: * -> *) x' x b' b a' c' c.
Functor m =>
Proxy x' x b' b m a'
-> (b -> Proxy x' x c' c m b') -> Proxy x' x c' c m a'
for Producer ByteString m x
p (forall (m :: * -> *) (f :: * -> *) a x' x.
(Functor m, Foldable f) =>
f a -> Proxy x' x () a m ()
each forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
BS.unpack)
{-# INLINABLE _unpack #-}
chunksOf'
:: (Monad m, Integral n)
=> n -> Producer ByteString m r -> Producer ByteString m r
chunksOf' :: forall (m :: * -> *) n r.
(Monad m, Integral n) =>
n -> Producer ByteString m r -> Producer ByteString m r
chunksOf' n
n Producer ByteString m r
p =
forall (m :: * -> *) x a b r.
Monad m =>
(x -> a -> x)
-> x -> (x -> b) -> FreeT (Producer a m) m r -> Producer b m r
PG.folds
(\[ByteString] -> [ByteString]
diffBs ByteString
bs -> [ByteString] -> [ByteString]
diffBs forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString
bsforall a. a -> [a] -> [a]
:))
forall a. a -> a
id
(\[ByteString] -> [ByteString]
diffBs -> [ByteString] -> ByteString
BS.concat ([ByteString] -> [ByteString]
diffBs []))
(Producer ByteString m r
p forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^. forall (m :: * -> *) n x.
(Monad m, Integral n) =>
n
-> Lens'
(Producer ByteString m x) (FreeT (Producer ByteString m) m x)
chunksOf n
n)
{-# INLINABLE chunksOf' #-}
chunksOf
:: (Monad m, Integral n)
=> n -> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x)
chunksOf :: forall (m :: * -> *) n x.
(Monad m, Integral n) =>
n
-> Lens'
(Producer ByteString m x) (FreeT (Producer ByteString m) m x)
chunksOf n
n FreeT (Producer ByteString m) m x
-> f (FreeT (Producer ByteString m) m x)
k Producer ByteString m x
p0 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (m :: * -> *) a x.
Monad m =>
FreeT (Producer a m) m x -> Producer a m x
concats (FreeT (Producer ByteString m) m x
-> f (FreeT (Producer ByteString m) m x)
k (forall {m :: * -> *} {b}.
Monad m =>
Producer ByteString m b -> FreeT (Proxy X () () ByteString m) m b
go Producer ByteString m x
p0))
where
go :: Producer ByteString m b -> FreeT (Proxy X () () ByteString m) m b
go Producer ByteString m b
p = forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
PG.FreeT forall a b. (a -> b) -> a -> b
$ do
Either b (ByteString, Producer ByteString m b)
x <- forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer ByteString m b
p
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Either b (ByteString, Producer ByteString m b)
x of
Left b
r -> forall (f :: * -> *) a b. a -> FreeF f a b
PG.Pure b
r
Right (ByteString
bs, Producer ByteString m b
p') -> forall (f :: * -> *) a b. f b -> FreeF f a b
PG.Free forall a b. (a -> b) -> a -> b
$ do
Producer ByteString m b
p'' <- (forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer ByteString m b
p')forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^.forall (m :: * -> *) n x.
(Monad m, Integral n) =>
n
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
splitAt n
n
forall (m :: * -> *) a. Monad m => a -> m a
return (Producer ByteString m b -> FreeT (Proxy X () () ByteString m) m b
go Producer ByteString m b
p'')
{-# INLINABLE chunksOf #-}
splitsWith
:: Monad m
=> (Word8 -> Bool)
-> Producer ByteString m x -> FreeT (Producer ByteString m) m x
splitsWith :: forall (m :: * -> *) x.
Monad m =>
(Word8 -> Bool)
-> Producer ByteString m x -> FreeT (Producer ByteString m) m x
splitsWith Word8 -> Bool
predicate Producer ByteString m x
p0 = forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
PG.FreeT (forall {m :: * -> *} {a}.
Monad m =>
Producer ByteString m a
-> m (FreeF
(Proxy X () () ByteString m)
a
(FreeT (Proxy X () () ByteString m) m a))
go0 Producer ByteString m x
p0)
where
go0 :: Producer ByteString m a
-> m (FreeF
(Proxy X () () ByteString m)
a
(FreeT (Proxy X () () ByteString m) m a))
go0 Producer ByteString m a
p = do
Either a (ByteString, Producer ByteString m a)
x <- forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer ByteString m a
p
case Either a (ByteString, Producer ByteString m a)
x of
Left a
r -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *) a b. a -> FreeF f a b
PG.Pure a
r)
Right (ByteString
bs, Producer ByteString m a
p') ->
if (ByteString -> Bool
BS.null ByteString
bs)
then Producer ByteString m a
-> m (FreeF
(Proxy X () () ByteString m)
a
(FreeT (Proxy X () () ByteString m) m a))
go0 Producer ByteString m a
p'
else forall {m :: * -> *} {a}.
Monad m =>
Producer ByteString m a
-> m (FreeF
(Proxy X () () ByteString m)
a
(FreeT (Proxy X () () ByteString m) m a))
go1 (forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer ByteString m a
p')
go1 :: Producer ByteString m a
-> m (FreeF
(Proxy X () () ByteString m)
a
(FreeT (Proxy X () () ByteString m) m a))
go1 Producer ByteString m a
p = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. f b -> FreeF f a b
PG.Free forall a b. (a -> b) -> a -> b
$ do
Producer ByteString m a
p' <- Producer ByteString m a
pforall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^.forall (m :: * -> *) x.
Monad m =>
(Word8 -> Bool)
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
break Word8 -> Bool
predicate
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
PG.FreeT forall a b. (a -> b) -> a -> b
$ do
Either a (Word8, Producer ByteString m a)
x <- forall (m :: * -> *) r.
Monad m =>
Producer ByteString m r
-> m (Either r (Word8, Producer ByteString m r))
nextByte Producer ByteString m a
p'
case Either a (Word8, Producer ByteString m a)
x of
Left a
r -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *) a b. a -> FreeF f a b
PG.Pure a
r)
Right (Word8
_, Producer ByteString m a
p'') -> Producer ByteString m a
-> m (FreeF
(Proxy X () () ByteString m)
a
(FreeT (Proxy X () () ByteString m) m a))
go1 Producer ByteString m a
p''
{-# INLINABLE splitsWith #-}
splits
:: Monad m
=> Word8
-> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x)
splits :: forall (m :: * -> *) x.
Monad m =>
Word8
-> Lens'
(Producer ByteString m x) (FreeT (Producer ByteString m) m x)
splits Word8
w8 FreeT (Producer ByteString m) m x
-> f (FreeT (Producer ByteString m) m x)
k Producer ByteString m x
p =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (m :: * -> *) a x.
Monad m =>
Producer a m () -> FreeT (Producer a m) m x -> Producer a m x
PG.intercalates (forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Word8 -> ByteString
BS.singleton Word8
w8))) (FreeT (Producer ByteString m) m x
-> f (FreeT (Producer ByteString m) m x)
k (forall (m :: * -> *) x.
Monad m =>
(Word8 -> Bool)
-> Producer ByteString m x -> FreeT (Producer ByteString m) m x
splitsWith (Word8
w8 forall a. Eq a => a -> a -> Bool
==) Producer ByteString m x
p))
{-# INLINABLE splits #-}
splitOn
:: Monad m
=> ByteString
-> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x)
splitOn :: forall (m :: * -> *) x.
Monad m =>
ByteString
-> Lens'
(Producer ByteString m x) (FreeT (Producer ByteString m) m x)
splitOn ByteString
needle FreeT (Producer ByteString m) m x
-> f (FreeT (Producer ByteString m) m x)
k Producer ByteString m x
p0 =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
(forall (m :: * -> *) a x.
Monad m =>
Producer a m () -> FreeT (Producer a m) m x -> Producer a m x
PG.intercalates (forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
needle))
(FreeT (Producer ByteString m) m x
-> f (FreeT (Producer ByteString m) m x)
k (forall {m :: * -> *} {b}.
Monad m =>
Producer ByteString m b -> FreeT (Proxy X () () ByteString m) m b
go Producer ByteString m x
p0))
where
len0 :: Int
len0 = ByteString -> Int
BS.length ByteString
needle
go :: Producer ByteString m r -> FreeT (Proxy X () () ByteString m) m r
go Producer ByteString m r
p = forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
PG.FreeT forall a b. (a -> b) -> a -> b
$ do
Either r (ByteString, Producer ByteString m r)
x <- forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer ByteString m r
p
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Either r (ByteString, Producer ByteString m r)
x of
Left r
r -> forall (f :: * -> *) a b. a -> FreeF f a b
PG.Pure r
r
Right (ByteString
bs, Producer ByteString m r
p') -> forall (f :: * -> *) a b. f b -> FreeF f a b
PG.Free forall a b. (a -> b) -> a -> b
$ do
Producer ByteString m r
p'' <- (forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer ByteString m r
p')forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^.(forall (m :: * -> *) x.
Monad m =>
ByteString
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
breakOn ByteString
needle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Producer ByteString m r -> FreeT (Proxy X () () ByteString m) m r
go (forall (m :: * -> *) n r.
(Monad m, Integral n) =>
n -> Producer ByteString m r -> Producer ByteString m r
drop Int
len0 Producer ByteString m r
p''))
{-# INLINABLE splitOn #-}
groupsBy
:: Monad m
=> (Word8 -> Word8 -> Bool)
-> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x)
groupsBy :: forall (m :: * -> *) x.
Monad m =>
(Word8 -> Word8 -> Bool)
-> Lens'
(Producer ByteString m x) (FreeT (Producer ByteString m) m x)
groupsBy Word8 -> Word8 -> Bool
equals FreeT (Producer ByteString m) m x
-> f (FreeT (Producer ByteString m) m x)
k Producer ByteString m x
p0 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (m :: * -> *) a x.
Monad m =>
FreeT (Producer a m) m x -> Producer a m x
concats (FreeT (Producer ByteString m) m x
-> f (FreeT (Producer ByteString m) m x)
k (forall {m :: * -> *} {b}.
Monad m =>
Producer ByteString m b -> FreeT (Proxy X () () ByteString m) m b
_groupsBy Producer ByteString m x
p0))
where
_groupsBy :: Producer ByteString m a -> FreeT (Proxy X () () ByteString m) m a
_groupsBy Producer ByteString m a
p0' = forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
PG.FreeT (forall {m :: * -> *} {a}.
Monad m =>
Producer ByteString m a
-> m (FreeF
(Proxy X () () ByteString m)
a
(FreeT (Proxy X () () ByteString m) m a))
go Producer ByteString m a
p0')
where
go :: Producer ByteString m a
-> m (FreeF
(Proxy X () () ByteString m)
a
(FreeT (Proxy X () () ByteString m) m a))
go Producer ByteString m a
p = do
Either a (ByteString, Producer ByteString m a)
x <- forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer ByteString m a
p
case Either a (ByteString, Producer ByteString m a)
x of
Left a
r -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *) a b. a -> FreeF f a b
PG.Pure a
r)
Right (ByteString
bs, Producer ByteString m a
p') -> case (ByteString -> Maybe (Word8, ByteString)
BS.uncons ByteString
bs) of
Maybe (Word8, ByteString)
Nothing -> Producer ByteString m a
-> m (FreeF
(Proxy X () () ByteString m)
a
(FreeT (Proxy X () () ByteString m) m a))
go Producer ByteString m a
p'
Just (Word8
w8, ByteString
_) -> do
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. f b -> FreeF f a b
PG.Free forall a b. (a -> b) -> a -> b
$ do
Producer ByteString m a
p'' <- (forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer ByteString m a
p')forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^.forall (m :: * -> *) x.
Monad m =>
(Word8 -> Bool)
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
span (Word8 -> Word8 -> Bool
equals Word8
w8)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
PG.FreeT (Producer ByteString m a
-> m (FreeF
(Proxy X () () ByteString m)
a
(FreeT (Proxy X () () ByteString m) m a))
go Producer ByteString m a
p'')
{-# INLINABLE groupsBy #-}
groups
:: Monad m
=> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x)
groups :: forall (m :: * -> *) x.
Monad m =>
Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x)
groups = forall (m :: * -> *) x.
Monad m =>
(Word8 -> Word8 -> Bool)
-> Lens'
(Producer ByteString m x) (FreeT (Producer ByteString m) m x)
groupsBy forall a. Eq a => a -> a -> Bool
(==)
{-# INLINABLE groups #-}
lines
:: Monad m
=> Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x)
lines :: forall (m :: * -> *) x.
Monad m =>
Lens' (Producer ByteString m x) (FreeT (Producer ByteString m) m x)
lines FreeT (Producer ByteString m) m x
-> f (FreeT (Producer ByteString m) m x)
k Producer ByteString m x
p = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (m :: * -> *) x.
Monad m =>
FreeT (Producer ByteString m) m x -> Producer ByteString m x
_unlines (FreeT (Producer ByteString m) m x
-> f (FreeT (Producer ByteString m) m x)
k (forall {m :: * -> *} {b}.
Monad m =>
Producer ByteString m b -> FreeT (Proxy X () () ByteString m) m b
_lines Producer ByteString m x
p))
{-# INLINABLE lines #-}
unlines
:: Monad m
=> Lens' (FreeT (Producer ByteString m) m x) (Producer ByteString m x)
unlines :: forall (m :: * -> *) x.
Monad m =>
Lens' (FreeT (Producer ByteString m) m x) (Producer ByteString m x)
unlines Producer ByteString m x -> f (Producer ByteString m x)
k FreeT (Producer ByteString m) m x
p = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall {m :: * -> *} {b}.
Monad m =>
Producer ByteString m b -> FreeT (Proxy X () () ByteString m) m b
_lines (Producer ByteString m x -> f (Producer ByteString m x)
k (forall (m :: * -> *) x.
Monad m =>
FreeT (Producer ByteString m) m x -> Producer ByteString m x
_unlines FreeT (Producer ByteString m) m x
p))
{-# INLINABLE unlines #-}
_lines
:: Monad m => Producer ByteString m x -> FreeT (Producer ByteString m) m x
_lines :: forall {m :: * -> *} {b}.
Monad m =>
Producer ByteString m b -> FreeT (Proxy X () () ByteString m) m b
_lines Producer ByteString m x
p0 = forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
PG.FreeT (forall {m :: * -> *} {a}.
Monad m =>
Producer ByteString m a
-> m (FreeF
(Proxy X () () ByteString m)
a
(FreeT (Proxy X () () ByteString m) m a))
go0 Producer ByteString m x
p0)
where
go0 :: Producer ByteString m a
-> m (FreeF
(Proxy X () () ByteString m)
a
(FreeT (Proxy X () () ByteString m) m a))
go0 Producer ByteString m a
p = do
Either a (ByteString, Producer ByteString m a)
x <- forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next Producer ByteString m a
p
case Either a (ByteString, Producer ByteString m a)
x of
Left a
r -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *) a b. a -> FreeF f a b
PG.Pure a
r)
Right (ByteString
bs, Producer ByteString m a
p') ->
if (ByteString -> Bool
BS.null ByteString
bs)
then Producer ByteString m a
-> m (FreeF
(Proxy X () () ByteString m)
a
(FreeT (Proxy X () () ByteString m) m a))
go0 Producer ByteString m a
p'
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. f b -> FreeF f a b
PG.Free forall a b. (a -> b) -> a -> b
$ Producer ByteString m a
-> Proxy
X () () ByteString m (FreeT (Proxy X () () ByteString m) m a)
go1 (forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer ByteString m a
p')
go1 :: Producer ByteString m a
-> Proxy
X () () ByteString m (FreeT (Proxy X () () ByteString m) m a)
go1 Producer ByteString m a
p = do
Producer ByteString m a
p' <- Producer ByteString m a
pforall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^.forall (m :: * -> *) x.
Monad m =>
Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
line
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
PG.FreeT forall a b. (a -> b) -> a -> b
$ do
Either a (Word8, Producer ByteString m a)
x <- forall (m :: * -> *) r.
Monad m =>
Producer ByteString m r
-> m (Either r (Word8, Producer ByteString m r))
nextByte Producer ByteString m a
p'
case Either a (Word8, Producer ByteString m a)
x of
Left a
r -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *) a b. a -> FreeF f a b
PG.Pure a
r)
Right (Word8
_, Producer ByteString m a
p'') -> Producer ByteString m a
-> m (FreeF
(Proxy X () () ByteString m)
a
(FreeT (Proxy X () () ByteString m) m a))
go0 Producer ByteString m a
p''
{-# INLINABLE _lines #-}
_unlines
:: Monad m => FreeT (Producer ByteString m) m x -> Producer ByteString m x
_unlines :: forall (m :: * -> *) x.
Monad m =>
FreeT (Producer ByteString m) m x -> Producer ByteString m x
_unlines = forall (m :: * -> *) a x.
Monad m =>
FreeT (Producer a m) m x -> Producer a m x
concats forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) (g :: * -> *) (f :: * -> *) x.
(Monad m, Functor g) =>
(forall r. f r -> g r) -> FreeT f m x -> FreeT g m x
PG.maps forall {m :: * -> *} {x'} {x} {a}.
Functor m =>
Proxy x' x () ByteString m a -> Proxy x' x () ByteString m a
addNewline
where
addNewline :: Proxy x' x () ByteString m a -> Proxy x' x () ByteString m a
addNewline Proxy x' x () ByteString m a
p = Proxy x' x () ByteString m a
p forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield (Word8 -> ByteString
BS.singleton Word8
nl)
{-# INLINABLE _unlines #-}
words :: Monad m => Producer ByteString m x -> FreeT (Producer ByteString m) m x
words :: forall {m :: * -> *} {b}.
Monad m =>
Producer ByteString m b -> FreeT (Proxy X () () ByteString m) m b
words Producer ByteString m x
p = forall (f :: * -> *) (m :: * -> *) a.
m (FreeF f a (FreeT f m a)) -> FreeT f m a
PG.FreeT forall a b. (a -> b) -> a -> b
$ do
Either x (ByteString, Producer ByteString m x)
x <- forall (m :: * -> *) a r.
Monad m =>
Producer a m r -> m (Either r (a, Producer a m r))
next (forall (m :: * -> *) r.
Monad m =>
(Word8 -> Bool)
-> Producer ByteString m r -> Producer ByteString m r
dropWhile Word8 -> Bool
isSpaceWord8 Producer ByteString m x
p)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Either x (ByteString, Producer ByteString m x)
x of
Left x
r -> forall (f :: * -> *) a b. a -> FreeF f a b
PG.Pure x
r
Right (ByteString
bs, Producer ByteString m x
p') -> forall (f :: * -> *) a b. f b -> FreeF f a b
PG.Free forall a b. (a -> b) -> a -> b
$ do
Producer ByteString m x
p'' <- (forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield ByteString
bs forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Producer ByteString m x
p')forall a b. a -> ((b -> Constant b b) -> a -> Constant b a) -> b
^.forall (m :: * -> *) x.
Monad m =>
(Word8 -> Bool)
-> Lens'
(Producer ByteString m x)
(Producer ByteString m (Producer ByteString m x))
break Word8 -> Bool
isSpaceWord8
forall (m :: * -> *) a. Monad m => a -> m a
return (forall {m :: * -> *} {b}.
Monad m =>
Producer ByteString m b -> FreeT (Proxy X () () ByteString m) m b
words Producer ByteString m x
p'')
{-# INLINABLE words #-}
unwords
:: Monad m => FreeT (Producer ByteString m) m x -> Producer ByteString m x
unwords :: forall (m :: * -> *) x.
Monad m =>
FreeT (Producer ByteString m) m x -> Producer ByteString m x
unwords = forall (m :: * -> *) a x.
Monad m =>
Producer a m () -> FreeT (Producer a m) m x -> Producer a m x
PG.intercalates (forall (m :: * -> *) a x' x. Functor m => a -> Proxy x' x () a m ()
yield forall a b. (a -> b) -> a -> b
$ Word8 -> ByteString
BS.singleton forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Char -> Int
ord Char
' ')
{-# INLINABLE unwords #-}