{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UnliftedFFITypes #-}
module Streaming.ByteString.Internal
( ByteStream(..)
, ByteString
, consChunk
, chunkOverhead
, defaultChunkSize
, materialize
, dematerialize
, foldrChunks
, foldlChunks
, foldrChunksM
, foldlChunksM
, chunkFold
, chunkFoldM
, chunkMap
, chunkMapM
, chunkMapM_
, unfoldMChunks
, unfoldrChunks
, packChars
, packBytes
, unpackBytes
, chunk
, smallChunkSize
, mwrap
, unfoldrNE
, reread
, unsafeLast
, unsafeInit
, copy
, findIndexOrEnd
, bracketByteString
, unsafeWithForeignPtr
) where
import Control.Monad
import Control.Monad.Morph
import Control.Monad.Trans
import Prelude hiding
(all, any, appendFile, break, concat, concatMap, cycle, drop, dropWhile,
elem, filter, foldl, foldl1, foldr, foldr1, getContents, getLine, head,
init, interact, iterate, last, length, lines, map, maximum, minimum,
notElem, null, putStr, putStrLn, readFile, repeat, replicate, reverse,
scanl, scanl1, scanr, scanr1, span, splitAt, tail, take, takeWhile,
unlines, unzip, writeFile, zip, zipWith)
import qualified Prelude
#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup
#endif
import qualified Data.ByteString as B
import qualified Data.ByteString.Internal as B
import Streaming (Of(..))
import Streaming.Internal hiding (concats)
import qualified Streaming.Prelude as SP
import Data.String
import Foreign.Ptr
import Foreign.Storable
import GHC.Types (SPEC(..))
import Data.Functor.Identity
import Data.Word
import GHC.Base (realWorld#)
import GHC.IO (IO(IO))
import System.IO.Unsafe (unsafePerformIO)
import Control.Monad.Base
import Control.Monad.Catch (MonadCatch(..))
import Control.Monad.Trans.Resource
#if MIN_VERSION_base(4,15,0)
import GHC.ForeignPtr (unsafeWithForeignPtr)
#else
import Foreign.ForeignPtr (ForeignPtr, withForeignPtr)
#endif
#if !MIN_VERSION_base(4,15,0)
unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr = withForeignPtr
#endif
type ByteString = ByteStream
{-# DEPRECATED ByteString "Use ByteStream instead." #-}
data ByteStream m r =
Empty r
| Chunk {-# UNPACK #-} !B.ByteString (ByteStream m r )
| Go (m (ByteStream m r ))
instance Monad m => Functor (ByteStream m) where
fmap :: forall a b. (a -> b) -> ByteStream m a -> ByteStream m b
fmap a -> b
f ByteStream m a
x = case ByteStream m a
x of
Empty a
a -> b -> ByteStream m b
forall (m :: * -> *) r. r -> ByteStream m r
Empty (a -> b
f a
a)
Chunk ByteString
bs ByteStream m a
bss -> ByteString -> ByteStream m b -> ByteStream m b
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk ByteString
bs ((a -> b) -> ByteStream m a -> ByteStream m b
forall a b. (a -> b) -> ByteStream m a -> ByteStream m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f ByteStream m a
bss)
Go m (ByteStream m a)
mbss -> m (ByteStream m b) -> ByteStream m b
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go ((ByteStream m a -> ByteStream m b)
-> m (ByteStream m a) -> m (ByteStream m b)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> ByteStream m a -> ByteStream m b
forall a b. (a -> b) -> ByteStream m a -> ByteStream m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) m (ByteStream m a)
mbss)
instance Monad m => Applicative (ByteStream m) where
pure :: forall a. a -> ByteStream m a
pure = a -> ByteStream m a
forall (m :: * -> *) r. r -> ByteStream m r
Empty
{-# INLINE pure #-}
ByteStream m (a -> b)
bf <*> :: forall a b.
ByteStream m (a -> b) -> ByteStream m a -> ByteStream m b
<*> ByteStream m a
bx = do {a -> b
f <- ByteStream m (a -> b)
bf; a
x <- ByteStream m a
bx; b -> ByteStream m b
forall (m :: * -> *) r. r -> ByteStream m r
Empty (a -> b
f a
x)}
{-# INLINE (<*>) #-}
ByteStream m a
x0 *> :: forall a b. ByteStream m a -> ByteStream m b -> ByteStream m b
*> ByteStream m b
y = SPEC -> ByteStream m a -> ByteStream m b
loop SPEC
SPEC ByteStream m a
x0 where
loop :: SPEC -> ByteStream m a -> ByteStream m b
loop !SPEC
_ ByteStream m a
x = case ByteStream m a
x of
Empty a
_ -> ByteStream m b
y
Chunk ByteString
a ByteStream m a
b -> ByteString -> ByteStream m b -> ByteStream m b
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk ByteString
a (SPEC -> ByteStream m a -> ByteStream m b
loop SPEC
SPEC ByteStream m a
b)
Go m (ByteStream m a)
m -> m (ByteStream m b) -> ByteStream m b
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go ((ByteStream m a -> ByteStream m b)
-> m (ByteStream m a) -> m (ByteStream m b)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (SPEC -> ByteStream m a -> ByteStream m b
loop SPEC
SPEC) m (ByteStream m a)
m)
{-# INLINEABLE (*>) #-}
instance Monad m => Monad (ByteStream m) where
return :: forall a. a -> ByteStream m a
return = a -> ByteStream m a
forall a. a -> ByteStream m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
{-# INLINE return #-}
>> :: forall a b. ByteStream m a -> ByteStream m b -> ByteStream m b
(>>) = ByteStream m a -> ByteStream m b -> ByteStream m b
forall a b. ByteStream m a -> ByteStream m b -> ByteStream m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>)
{-# INLINE (>>) #-}
ByteStream m a
x >>= :: forall a b.
ByteStream m a -> (a -> ByteStream m b) -> ByteStream m b
>>= a -> ByteStream m b
f =
SPEC -> ByteStream m a -> ByteStream m b
loop SPEC
SPEC2 ByteStream m a
x where
loop :: SPEC -> ByteStream m a -> ByteStream m b
loop !SPEC
_ ByteStream m a
y = case ByteStream m a
y of
Empty a
a -> a -> ByteStream m b
f a
a
Chunk ByteString
bs ByteStream m a
bss -> ByteString -> ByteStream m b -> ByteStream m b
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk ByteString
bs (SPEC -> ByteStream m a -> ByteStream m b
loop SPEC
SPEC ByteStream m a
bss)
Go m (ByteStream m a)
mbss -> m (ByteStream m b) -> ByteStream m b
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go ((ByteStream m a -> ByteStream m b)
-> m (ByteStream m a) -> m (ByteStream m b)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (SPEC -> ByteStream m a -> ByteStream m b
loop SPEC
SPEC) m (ByteStream m a)
mbss)
{-# INLINEABLE (>>=) #-}
instance MonadIO m => MonadIO (ByteStream m) where
liftIO :: forall a. IO a -> ByteStream m a
liftIO IO a
io = m (ByteStream m a) -> ByteStream m a
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go ((a -> ByteStream m a) -> m a -> m (ByteStream m a)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> ByteStream m a
forall (m :: * -> *) r. r -> ByteStream m r
Empty (IO a -> m a
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO a
io))
{-# INLINE liftIO #-}
instance MonadTrans ByteStream where
lift :: forall (m :: * -> *) a. Monad m => m a -> ByteStream m a
lift m a
ma = m (ByteStream m a) -> ByteStream m a
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go (m (ByteStream m a) -> ByteStream m a)
-> m (ByteStream m a) -> ByteStream m a
forall a b. (a -> b) -> a -> b
$ (a -> ByteStream m a) -> m a -> m (ByteStream m a)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> ByteStream m a
forall (m :: * -> *) r. r -> ByteStream m r
Empty m a
ma
{-# INLINE lift #-}
instance MFunctor ByteStream where
hoist :: forall (m :: * -> *) (n :: * -> *) b.
Monad m =>
(forall a. m a -> n a) -> ByteStream m b -> ByteStream n b
hoist forall a. m a -> n a
phi ByteStream m b
bs = case ByteStream m b
bs of
Empty b
r -> b -> ByteStream n b
forall (m :: * -> *) r. r -> ByteStream m r
Empty b
r
Chunk ByteString
bs' ByteStream m b
rest -> ByteString -> ByteStream n b -> ByteStream n b
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk ByteString
bs' ((forall a. m a -> n a) -> ByteStream m b -> ByteStream n b
forall {k} (t :: (* -> *) -> k -> *) (m :: * -> *) (n :: * -> *)
(b :: k).
(MFunctor t, Monad m) =>
(forall a. m a -> n a) -> t m b -> t n b
forall (m :: * -> *) (n :: * -> *) b.
Monad m =>
(forall a. m a -> n a) -> ByteStream m b -> ByteStream n b
hoist m a -> n a
forall a. m a -> n a
phi ByteStream m b
rest)
Go m (ByteStream m b)
m -> n (ByteStream n b) -> ByteStream n b
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go (m (ByteStream n b) -> n (ByteStream n b)
forall a. m a -> n a
phi ((ByteStream m b -> ByteStream n b)
-> m (ByteStream m b) -> m (ByteStream n b)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((forall a. m a -> n a) -> ByteStream m b -> ByteStream n b
forall {k} (t :: (* -> *) -> k -> *) (m :: * -> *) (n :: * -> *)
(b :: k).
(MFunctor t, Monad m) =>
(forall a. m a -> n a) -> t m b -> t n b
forall (m :: * -> *) (n :: * -> *) b.
Monad m =>
(forall a. m a -> n a) -> ByteStream m b -> ByteStream n b
hoist m a -> n a
forall a. m a -> n a
phi) m (ByteStream m b)
m))
{-# INLINABLE hoist #-}
instance (r ~ ()) => IsString (ByteStream m r) where
fromString :: String -> ByteStream m r
fromString = ByteString -> ByteStream m r
ByteString -> ByteStream m ()
forall (m :: * -> *). ByteString -> ByteStream m ()
chunk (ByteString -> ByteStream m r)
-> (String -> ByteString) -> String -> ByteStream m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> ByteString
B.pack ([Word8] -> ByteString)
-> (String -> [Word8]) -> String -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Word8) -> String -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
Prelude.map Char -> Word8
B.c2w
{-# INLINE fromString #-}
instance (m ~ Identity, Show r) => Show (ByteStream m r) where
show :: ByteStream m r -> String
show ByteStream m r
bs0 = case ByteStream m r
bs0 of
Empty r
r -> String
"Empty (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ r -> String
forall a. Show a => a -> String
show r
r String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
Go (Identity ByteStream m r
bs') -> String
"Go (Identity (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteStream m r -> String
forall a. Show a => a -> String
show ByteStream m r
bs' String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"))"
Chunk ByteString
bs'' ByteStream m r
bs -> String
"Chunk " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a. Show a => a -> String
show ByteString
bs'' String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" (" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteStream m r -> String
forall a. Show a => a -> String
show ByteStream m r
bs String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
")"
instance (Semigroup r, Monad m) => Semigroup (ByteStream m r) where
<> :: ByteStream m r -> ByteStream m r -> ByteStream m r
(<>) = (r -> r -> r) -> ByteStream m r -> ByteStream m r -> ByteStream m r
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 r -> r -> r
forall a. Semigroup a => a -> a -> a
(<>)
{-# INLINE (<>) #-}
instance (Monoid r, Monad m) => Monoid (ByteStream m r) where
mempty :: ByteStream m r
mempty = r -> ByteStream m r
forall (m :: * -> *) r. r -> ByteStream m r
Empty r
forall a. Monoid a => a
mempty
{-# INLINE mempty #-}
#if MIN_VERSION_base(4,11,0)
mappend :: ByteStream m r -> ByteStream m r -> ByteStream m r
mappend = ByteStream m r -> ByteStream m r -> ByteStream m r
forall a. Semigroup a => a -> a -> a
(<>)
#else
mappend = liftM2 mappend
#endif
{-# INLINE mappend #-}
instance (MonadBase b m) => MonadBase b (ByteStream m) where
liftBase :: forall α. b α -> ByteStream m α
liftBase = m (ByteStream m α) -> ByteStream m α
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
mwrap (m (ByteStream m α) -> ByteStream m α)
-> (b α -> m (ByteStream m α)) -> b α -> ByteStream m α
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (α -> ByteStream m α) -> m α -> m (ByteStream m α)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap α -> ByteStream m α
forall a. a -> ByteStream m a
forall (m :: * -> *) a. Monad m => a -> m a
return (m α -> m (ByteStream m α))
-> (b α -> m α) -> b α -> m (ByteStream m α)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b α -> m α
forall α. b α -> m α
forall (b :: * -> *) (m :: * -> *) α. MonadBase b m => b α -> m α
liftBase
{-# INLINE liftBase #-}
instance (MonadThrow m) => MonadThrow (ByteStream m) where
throwM :: forall e a. (HasCallStack, Exception e) => e -> ByteStream m a
throwM = m a -> ByteStream m a
forall (m :: * -> *) a. Monad m => m a -> ByteStream m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ByteStream m a) -> (e -> m a) -> e -> ByteStream m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> m a
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM
{-# INLINE throwM #-}
instance (MonadCatch m) => MonadCatch (ByteStream m) where
catch :: forall e a.
(HasCallStack, Exception e) =>
ByteStream m a -> (e -> ByteStream m a) -> ByteStream m a
catch ByteStream m a
str e -> ByteStream m a
f = ByteStream m a -> ByteStream m a
go ByteStream m a
str
where
go :: ByteStream m a -> ByteStream m a
go ByteStream m a
p = case ByteStream m a
p of
Chunk ByteString
bs ByteStream m a
rest -> ByteString -> ByteStream m a -> ByteStream m a
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk ByteString
bs (ByteStream m a -> ByteStream m a
go ByteStream m a
rest)
Empty a
r -> a -> ByteStream m a
forall (m :: * -> *) r. r -> ByteStream m r
Empty a
r
Go m (ByteStream m a)
m -> m (ByteStream m a) -> ByteStream m a
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go (m (ByteStream m a)
-> (e -> m (ByteStream m a)) -> m (ByteStream m a)
forall e a. (HasCallStack, Exception e) => m a -> (e -> m a) -> m a
forall (m :: * -> *) e a.
(MonadCatch m, HasCallStack, Exception e) =>
m a -> (e -> m a) -> m a
catch (do
ByteStream m a
p' <- m (ByteStream m a)
m
ByteStream m a -> m (ByteStream m a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteStream m a -> ByteStream m a
go ByteStream m a
p'))
(ByteStream m a -> m (ByteStream m a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteStream m a -> m (ByteStream m a))
-> (e -> ByteStream m a) -> e -> m (ByteStream m a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> ByteStream m a
f))
{-# INLINABLE catch #-}
instance (MonadResource m) => MonadResource (ByteStream m) where
liftResourceT :: forall a. ResourceT IO a -> ByteStream m a
liftResourceT = m a -> ByteStream m a
forall (m :: * -> *) a. Monad m => m a -> ByteStream m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ByteStream m a)
-> (ResourceT IO a -> m a) -> ResourceT IO a -> ByteStream m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ResourceT IO a -> m a
forall a. ResourceT IO a -> m a
forall (m :: * -> *) a. MonadResource m => ResourceT IO a -> m a
liftResourceT
{-# INLINE liftResourceT #-}
bracketByteString :: MonadResource m => IO a -> (a -> IO ()) -> (a -> ByteStream m b) -> ByteStream m b
bracketByteString :: forall (m :: * -> *) a b.
MonadResource m =>
IO a -> (a -> IO ()) -> (a -> ByteStream m b) -> ByteStream m b
bracketByteString IO a
alloc a -> IO ()
free a -> ByteStream m b
inside = do
(ReleaseKey
key, a
seed) <- m (ReleaseKey, a) -> ByteStream m (ReleaseKey, a)
forall (m :: * -> *) a. Monad m => m a -> ByteStream m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO a -> (a -> IO ()) -> m (ReleaseKey, a)
forall (m :: * -> *) a.
MonadResource m =>
IO a -> (a -> IO ()) -> m (ReleaseKey, a)
allocate IO a
alloc a -> IO ()
free)
ReleaseKey -> ByteStream m b -> ByteStream m b
forall {m :: * -> *} {r}.
MonadIO m =>
ReleaseKey -> ByteStream m r -> ByteStream m r
clean ReleaseKey
key (a -> ByteStream m b
inside a
seed)
where
clean :: ReleaseKey -> ByteStream m r -> ByteStream m r
clean ReleaseKey
key = ByteStream m r -> ByteStream m r
loop where
loop :: ByteStream m r -> ByteStream m r
loop ByteStream m r
str = case ByteStream m r
str of
Empty r
r -> m (ByteStream m r) -> ByteStream m r
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go (ReleaseKey -> m ()
forall (m :: * -> *). MonadIO m => ReleaseKey -> m ()
release ReleaseKey
key m () -> m (ByteStream m r) -> m (ByteStream m r)
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ByteStream m r -> m (ByteStream m r)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (r -> ByteStream m r
forall (m :: * -> *) r. r -> ByteStream m r
Empty r
r))
Go m (ByteStream m r)
m -> m (ByteStream m r) -> ByteStream m r
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go ((ByteStream m r -> ByteStream m r)
-> m (ByteStream m r) -> m (ByteStream m r)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteStream m r -> ByteStream m r
loop m (ByteStream m r)
m)
Chunk ByteString
bs ByteStream m r
rest -> ByteString -> ByteStream m r -> ByteStream m r
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk ByteString
bs (ByteStream m r -> ByteStream m r
loop ByteStream m r
rest)
{-# INLINABLE bracketByteString #-}
consChunk :: B.ByteString -> ByteStream m r -> ByteStream m r
consChunk :: forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
consChunk c :: ByteString
c@(B.PS ForeignPtr Word8
_ Int
_ Int
len) ByteStream m r
cs
| Int
len Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = ByteStream m r
cs
| Bool
otherwise = ByteString -> ByteStream m r -> ByteStream m r
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk ByteString
c ByteStream m r
cs
{-# INLINE consChunk #-}
chunk :: B.ByteString -> ByteStream m ()
chunk :: forall (m :: * -> *). ByteString -> ByteStream m ()
chunk ByteString
bs = ByteString -> ByteStream m () -> ByteStream m ()
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
consChunk ByteString
bs (() -> ByteStream m ()
forall (m :: * -> *) r. r -> ByteStream m r
Empty ())
{-# INLINE chunk #-}
mwrap :: m (ByteStream m r) -> ByteStream m r
mwrap :: forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
mwrap = m (ByteStream m r) -> ByteStream m r
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go
{-# INLINE mwrap #-}
materialize :: (forall x . (r -> x) -> (B.ByteString -> x -> x) -> (m x -> x) -> x) -> ByteStream m r
materialize :: forall r (m :: * -> *).
(forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x)
-> ByteStream m r
materialize forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
phi = (r -> ByteStream m r)
-> (ByteString -> ByteStream m r -> ByteStream m r)
-> (m (ByteStream m r) -> ByteStream m r)
-> ByteStream m r
forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
phi r -> ByteStream m r
forall (m :: * -> *) r. r -> ByteStream m r
Empty ByteString -> ByteStream m r -> ByteStream m r
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk m (ByteStream m r) -> ByteStream m r
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go
{-# INLINE[0] materialize #-}
dematerialize :: Monad m
=> ByteStream m r
-> (forall x . (r -> x) -> (B.ByteString -> x -> x) -> (m x -> x) -> x)
dematerialize :: forall (m :: * -> *) r.
Monad m =>
ByteStream m r
-> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
dematerialize ByteStream m r
x0 r -> x
nil ByteString -> x -> x
cons m x -> x
mwrap' = SPEC -> ByteStream m r -> x
loop SPEC
SPEC ByteStream m r
x0
where
loop :: SPEC -> ByteStream m r -> x
loop !SPEC
_ ByteStream m r
x = case ByteStream m r
x of
Empty r
r -> r -> x
nil r
r
Chunk ByteString
b ByteStream m r
bs -> ByteString -> x -> x
cons ByteString
b (SPEC -> ByteStream m r -> x
loop SPEC
SPEC ByteStream m r
bs )
Go m (ByteStream m r)
ms -> m x -> x
mwrap' ((ByteStream m r -> x) -> m (ByteStream m r) -> m x
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (SPEC -> ByteStream m r -> x
loop SPEC
SPEC) m (ByteStream m r)
ms)
{-# INLINE [1] dematerialize #-}
{-# RULES
"dematerialize/materialize" forall (phi :: forall b . (r -> b) -> (B.ByteString -> b -> b) -> (m b -> b) -> b). dematerialize (materialize phi) = phi ;
#-}
defaultChunkSize :: Int
defaultChunkSize :: Int
defaultChunkSize = Int
32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
k Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
chunkOverhead
where k :: Int
k = Int
1024
{-# INLINE defaultChunkSize #-}
smallChunkSize :: Int
smallChunkSize :: Int
smallChunkSize = Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
k Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
chunkOverhead
where k :: Int
k = Int
1024
{-# INLINE smallChunkSize #-}
chunkOverhead :: Int
chunkOverhead :: Int
chunkOverhead = Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int)
{-# INLINE chunkOverhead #-}
packBytes :: Monad m => Stream (Of Word8) m r -> ByteStream m r
packBytes :: forall (m :: * -> *) r.
Monad m =>
Stream (Of Word8) m r -> ByteStream m r
packBytes Stream (Of Word8) m r
cs0 = do
([Word8]
bytes :> Stream (Of Word8) m r
rest) <- m (Of [Word8] (Stream (Of Word8) m r))
-> ByteStream m (Of [Word8] (Stream (Of Word8) m r))
forall (m :: * -> *) a. Monad m => m a -> ByteStream m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Of [Word8] (Stream (Of Word8) m r))
-> ByteStream m (Of [Word8] (Stream (Of Word8) m r)))
-> m (Of [Word8] (Stream (Of Word8) m r))
-> ByteStream m (Of [Word8] (Stream (Of Word8) m r))
forall a b. (a -> b) -> a -> b
$ Stream (Of Word8) m (Stream (Of Word8) m r)
-> m (Of [Word8] (Stream (Of Word8) m r))
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Of [a] r)
SP.toList (Stream (Of Word8) m (Stream (Of Word8) m r)
-> m (Of [Word8] (Stream (Of Word8) m r)))
-> Stream (Of Word8) m (Stream (Of Word8) m r)
-> m (Of [Word8] (Stream (Of Word8) m r))
forall a b. (a -> b) -> a -> b
$ Int
-> Stream (Of Word8) m r
-> Stream (Of Word8) m (Stream (Of Word8) m r)
forall (m :: * -> *) (f :: * -> *) r.
(Monad m, Functor f) =>
Int -> Stream f m r -> Stream f m (Stream f m r)
SP.splitAt Int
32 Stream (Of Word8) m r
cs0
case [Word8]
bytes of
[] -> case Stream (Of Word8) m r
rest of
Return r
r -> r -> ByteStream m r
forall (m :: * -> *) r. r -> ByteStream m r
Empty r
r
Step Of Word8 (Stream (Of Word8) m r)
as -> Stream (Of Word8) m r -> ByteStream m r
forall (m :: * -> *) r.
Monad m =>
Stream (Of Word8) m r -> ByteStream m r
packBytes (Of Word8 (Stream (Of Word8) m r) -> Stream (Of Word8) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step Of Word8 (Stream (Of Word8) m r)
as)
Effect m (Stream (Of Word8) m r)
m -> m (ByteStream m r) -> ByteStream m r
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go (m (ByteStream m r) -> ByteStream m r)
-> m (ByteStream m r) -> ByteStream m r
forall a b. (a -> b) -> a -> b
$ (Stream (Of Word8) m r -> ByteStream m r)
-> m (Stream (Of Word8) m r) -> m (ByteStream m r)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of Word8) m r -> ByteStream m r
forall (m :: * -> *) r.
Monad m =>
Stream (Of Word8) m r -> ByteStream m r
packBytes m (Stream (Of Word8) m r)
m
[Word8]
_ -> ByteString -> ByteStream m r -> ByteStream m r
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk ([Word8] -> ByteString
B.packBytes [Word8]
bytes) (Stream (Of Word8) m r -> ByteStream m r
forall (m :: * -> *) r.
Monad m =>
Stream (Of Word8) m r -> ByteStream m r
packBytes Stream (Of Word8) m r
rest)
{-# INLINABLE packBytes #-}
packChars :: Monad m => Stream (Of Char) m r -> ByteStream m r
packChars :: forall (m :: * -> *) r.
Monad m =>
Stream (Of Char) m r -> ByteStream m r
packChars Stream (Of Char) m r
str = do
(String
chars :> Stream (Of Char) m r
rest) <- m (Of String (Stream (Of Char) m r))
-> ByteStream m (Of String (Stream (Of Char) m r))
forall (m :: * -> *) a. Monad m => m a -> ByteStream m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Of String (Stream (Of Char) m r))
-> ByteStream m (Of String (Stream (Of Char) m r)))
-> m (Of String (Stream (Of Char) m r))
-> ByteStream m (Of String (Stream (Of Char) m r))
forall a b. (a -> b) -> a -> b
$ Stream (Of Char) m (Stream (Of Char) m r)
-> m (Of String (Stream (Of Char) m r))
forall (m :: * -> *) a r.
Monad m =>
Stream (Of a) m r -> m (Of [a] r)
SP.toList (Stream (Of Char) m (Stream (Of Char) m r)
-> m (Of String (Stream (Of Char) m r)))
-> Stream (Of Char) m (Stream (Of Char) m r)
-> m (Of String (Stream (Of Char) m r))
forall a b. (a -> b) -> a -> b
$ Int
-> Stream (Of Char) m r
-> Stream (Of Char) m (Stream (Of Char) m r)
forall (m :: * -> *) (f :: * -> *) r.
(Monad m, Functor f) =>
Int -> Stream f m r -> Stream f m (Stream f m r)
SP.splitAt Int
32 Stream (Of Char) m r
str
case String
chars of
[] -> case Stream (Of Char) m r
rest of
Return r
r -> r -> ByteStream m r
forall (m :: * -> *) r. r -> ByteStream m r
Empty r
r
Step Of Char (Stream (Of Char) m r)
as -> Stream (Of Char) m r -> ByteStream m r
forall (m :: * -> *) r.
Monad m =>
Stream (Of Char) m r -> ByteStream m r
packChars (Of Char (Stream (Of Char) m r) -> Stream (Of Char) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step Of Char (Stream (Of Char) m r)
as)
Effect m (Stream (Of Char) m r)
m -> m (ByteStream m r) -> ByteStream m r
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go (m (ByteStream m r) -> ByteStream m r)
-> m (ByteStream m r) -> ByteStream m r
forall a b. (a -> b) -> a -> b
$ (Stream (Of Char) m r -> ByteStream m r)
-> m (Stream (Of Char) m r) -> m (ByteStream m r)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Stream (Of Char) m r -> ByteStream m r
forall (m :: * -> *) r.
Monad m =>
Stream (Of Char) m r -> ByteStream m r
packChars m (Stream (Of Char) m r)
m
String
_ -> ByteString -> ByteStream m r -> ByteStream m r
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk (String -> ByteString
B.packChars String
chars) (Stream (Of Char) m r -> ByteStream m r
forall (m :: * -> *) r.
Monad m =>
Stream (Of Char) m r -> ByteStream m r
packChars Stream (Of Char) m r
rest)
{-# INLINABLE packChars #-}
unpackBytes :: Monad m => ByteStream m r -> Stream (Of Word8) m r
unpackBytes :: forall (m :: * -> *) r.
Monad m =>
ByteStream m r -> Stream (Of Word8) m r
unpackBytes ByteStream m r
bss = ByteStream m r
-> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
forall (m :: * -> *) r.
Monad m =>
ByteStream m r
-> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
dematerialize ByteStream m r
bss r -> Stream (Of Word8) m r
forall (f :: * -> *) (m :: * -> *) r. r -> Stream f m r
Return ByteString -> Stream (Of Word8) m r -> Stream (Of Word8) m r
forall (m :: * -> *) r.
ByteString -> Stream (Of Word8) m r -> Stream (Of Word8) m r
unpackAppendBytesLazy m (Stream (Of Word8) m r) -> Stream (Of Word8) m r
forall (f :: * -> *) (m :: * -> *) r.
m (Stream f m r) -> Stream f m r
Effect
where
unpackAppendBytesLazy :: B.ByteString -> Stream (Of Word8) m r -> Stream (Of Word8) m r
unpackAppendBytesLazy :: forall (m :: * -> *) r.
ByteString -> Stream (Of Word8) m r -> Stream (Of Word8) m r
unpackAppendBytesLazy b :: ByteString
b@(B.PS ForeignPtr Word8
fp Int
off Int
len) Stream (Of Word8) m r
xs
| Int
len Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
100 = ByteString -> Stream (Of Word8) m r -> Stream (Of Word8) m r
forall (m :: * -> *) r.
ByteString -> Stream (Of Word8) m r -> Stream (Of Word8) m r
unpackAppendBytesStrict ByteString
b Stream (Of Word8) m r
xs
| Bool
otherwise = ByteString -> Stream (Of Word8) m r -> Stream (Of Word8) m r
forall (m :: * -> *) r.
ByteString -> Stream (Of Word8) m r -> Stream (Of Word8) m r
unpackAppendBytesStrict (ForeignPtr Word8 -> Int -> Int -> ByteString
B.PS ForeignPtr Word8
fp Int
off Int
100) Stream (Of Word8) m r
remainder
where
remainder :: Stream (Of Word8) m r
remainder = ByteString -> Stream (Of Word8) m r -> Stream (Of Word8) m r
forall (m :: * -> *) r.
ByteString -> Stream (Of Word8) m r -> Stream (Of Word8) m r
unpackAppendBytesLazy (ForeignPtr Word8 -> Int -> Int -> ByteString
B.PS ForeignPtr Word8
fp (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
100) (Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
100)) Stream (Of Word8) m r
xs
unpackAppendBytesStrict :: B.ByteString -> Stream (Of Word8) m r -> Stream (Of Word8) m r
unpackAppendBytesStrict :: forall (m :: * -> *) r.
ByteString -> Stream (Of Word8) m r -> Stream (Of Word8) m r
unpackAppendBytesStrict (B.PS ForeignPtr Word8
fp Int
off Int
len) Stream (Of Word8) m r
xs =
IO (Stream (Of Word8) m r) -> Stream (Of Word8) m r
forall a. IO a -> a
B.accursedUnutterablePerformIO (IO (Stream (Of Word8) m r) -> Stream (Of Word8) m r)
-> IO (Stream (Of Word8) m r) -> Stream (Of Word8) m r
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8
-> (Ptr Word8 -> IO (Stream (Of Word8) m r))
-> IO (Stream (Of Word8) m r)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp ((Ptr Word8 -> IO (Stream (Of Word8) m r))
-> IO (Stream (Of Word8) m r))
-> (Ptr Word8 -> IO (Stream (Of Word8) m r))
-> IO (Stream (Of Word8) m r)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
base ->
Ptr Word8
-> Ptr Word8 -> Stream (Of Word8) m r -> IO (Stream (Of Word8) m r)
forall {b} {m :: * -> *} {r}.
Storable b =>
Ptr b -> Ptr b -> Stream (Of b) m r -> IO (Stream (Of b) m r)
loop (Ptr Word8
base Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)) (Ptr Word8
base Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
len)) Stream (Of Word8) m r
xs
where
loop :: Ptr b -> Ptr b -> Stream (Of b) m r -> IO (Stream (Of b) m r)
loop !Ptr b
sentinel !Ptr b
p Stream (Of b) m r
acc
| Ptr b
p Ptr b -> Ptr b -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr b
sentinel = Stream (Of b) m r -> IO (Stream (Of b) m r)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Stream (Of b) m r
acc
| Bool
otherwise = do
b
x <- Ptr b -> IO b
forall a. Storable a => Ptr a -> IO a
peek Ptr b
p
Ptr b -> Ptr b -> Stream (Of b) m r -> IO (Stream (Of b) m r)
loop Ptr b
sentinel (Ptr b
p Ptr b -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (-Int
1)) (Of b (Stream (Of b) m r) -> Stream (Of b) m r
forall (f :: * -> *) (m :: * -> *) r.
f (Stream f m r) -> Stream f m r
Step (b
x b -> Stream (Of b) m r -> Of b (Stream (Of b) m r)
forall a b. a -> b -> Of a b
:> Stream (Of b) m r
acc))
{-# INLINABLE unpackBytes #-}
unsafeLast :: B.ByteString -> Word8
unsafeLast :: ByteString -> Word8
unsafeLast (B.PS ForeignPtr Word8
x Int
s Int
l) =
IO Word8 -> Word8
forall a. IO a -> a
accursedUnutterablePerformIO (IO Word8 -> Word8) -> IO Word8 -> Word8
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO Word8) -> IO Word8
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO Word8) -> IO Word8)
-> (Ptr Word8 -> IO Word8) -> IO Word8
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Ptr Word8 -> Int -> IO Word8
forall b. Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
p (Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
where
accursedUnutterablePerformIO :: IO a -> a
accursedUnutterablePerformIO (IO State# RealWorld -> (# State# RealWorld, a #)
m) = case State# RealWorld -> (# State# RealWorld, a #)
m State# RealWorld
realWorld# of (# State# RealWorld
_, a
r #) -> a
r
{-# INLINE unsafeLast #-}
unsafeInit :: B.ByteString -> B.ByteString
unsafeInit :: ByteString -> ByteString
unsafeInit (B.PS ForeignPtr Word8
ps Int
s Int
l) = ForeignPtr Word8 -> Int -> Int -> ByteString
B.PS ForeignPtr Word8
ps Int
s (Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
{-# INLINE unsafeInit #-}
foldrChunks :: Monad m => (B.ByteString -> a -> a) -> a -> ByteStream m r -> m a
foldrChunks :: forall (m :: * -> *) a r.
Monad m =>
(ByteString -> a -> a) -> a -> ByteStream m r -> m a
foldrChunks ByteString -> a -> a
step a
nil ByteStream m r
bs = ByteStream m r
-> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
forall (m :: * -> *) r.
Monad m =>
ByteStream m r
-> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
dematerialize ByteStream m r
bs
(\r
_ -> a -> m a
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
nil)
((a -> a) -> m a -> m a
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> a) -> m a -> m a)
-> (ByteString -> a -> a) -> ByteString -> m a -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> a -> a
step)
m (m a) -> m a
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join
{-# INLINE foldrChunks #-}
foldlChunks :: Monad m => (a -> B.ByteString -> a) -> a -> ByteStream m r -> m (Of a r)
foldlChunks :: forall (m :: * -> *) a r.
Monad m =>
(a -> ByteString -> a) -> a -> ByteStream m r -> m (Of a r)
foldlChunks a -> ByteString -> a
f a
z = a -> ByteStream m r -> m (Of a r)
go a
z
where go :: a -> ByteStream m r -> m (Of a r)
go a
a ByteStream m r
_ | a
a a -> Bool -> Bool
forall a b. a -> b -> b
`seq` Bool
False = m (Of a r)
forall a. HasCallStack => a
undefined
go a
a (Empty r
r) = Of a r -> m (Of a r)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a a -> r -> Of a r
forall a b. a -> b -> Of a b
:> r
r)
go a
a (Chunk ByteString
c ByteStream m r
cs) = a -> ByteStream m r -> m (Of a r)
go (a -> ByteString -> a
f a
a ByteString
c) ByteStream m r
cs
go a
a (Go m (ByteStream m r)
m) = m (ByteStream m r)
m m (ByteStream m r) -> (ByteStream m r -> m (Of a r)) -> m (Of a r)
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> ByteStream m r -> m (Of a r)
go a
a
{-# INLINABLE foldlChunks #-}
chunkMap :: Monad m => (B.ByteString -> B.ByteString) -> ByteStream m r -> ByteStream m r
chunkMap :: forall (m :: * -> *) r.
Monad m =>
(ByteString -> ByteString) -> ByteStream m r -> ByteStream m r
chunkMap ByteString -> ByteString
f ByteStream m r
bs = ByteStream m r
-> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
forall (m :: * -> *) r.
Monad m =>
ByteStream m r
-> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
dematerialize ByteStream m r
bs r -> ByteStream m r
forall a. a -> ByteStream m a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> ByteStream m r -> ByteStream m r
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk (ByteString -> ByteStream m r -> ByteStream m r)
-> (ByteString -> ByteString)
-> ByteString
-> ByteStream m r
-> ByteStream m r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
f) m (ByteStream m r) -> ByteStream m r
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go
{-# INLINE chunkMap #-}
chunkMapM :: Monad m => (B.ByteString -> m B.ByteString) -> ByteStream m r -> ByteStream m r
chunkMapM :: forall (m :: * -> *) r.
Monad m =>
(ByteString -> m ByteString) -> ByteStream m r -> ByteStream m r
chunkMapM ByteString -> m ByteString
f ByteStream m r
bs = ByteStream m r
-> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
forall (m :: * -> *) r.
Monad m =>
ByteStream m r
-> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
dematerialize ByteStream m r
bs r -> ByteStream m r
forall a. a -> ByteStream m a
forall (m :: * -> *) a. Monad m => a -> m a
return (\ByteString
bs' ByteStream m r
bss -> m (ByteStream m r) -> ByteStream m r
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go ((ByteString -> ByteStream m r)
-> m ByteString -> m (ByteStream m r)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ByteString -> ByteStream m r -> ByteStream m r
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
`Chunk` ByteStream m r
bss) (ByteString -> m ByteString
f ByteString
bs'))) m (ByteStream m r) -> ByteStream m r
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go
{-# INLINE chunkMapM #-}
chunkMapM_ :: Monad m => (B.ByteString -> m x) -> ByteStream m r -> m r
chunkMapM_ :: forall (m :: * -> *) x r.
Monad m =>
(ByteString -> m x) -> ByteStream m r -> m r
chunkMapM_ ByteString -> m x
f ByteStream m r
bs = ByteStream m r
-> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
forall (m :: * -> *) r.
Monad m =>
ByteStream m r
-> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
dematerialize ByteStream m r
bs r -> m r
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (\ByteString
bs' m r
mr -> ByteString -> m x
f ByteString
bs' m x -> m r -> m r
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> m r
mr) m (m r) -> m r
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join
{-# INLINE chunkMapM_ #-}
chunkFold :: Monad m => (x -> B.ByteString -> x) -> x -> (x -> a) -> ByteStream m r -> m (Of a r)
chunkFold :: forall (m :: * -> *) x a r.
Monad m =>
(x -> ByteString -> x)
-> x -> (x -> a) -> ByteStream m r -> m (Of a r)
chunkFold x -> ByteString -> x
step x
begin x -> a
done = x -> ByteStream m r -> m (Of a r)
go x
begin
where go :: x -> ByteStream m r -> m (Of a r)
go x
a ByteStream m r
_ | x
a x -> Bool -> Bool
forall a b. a -> b -> b
`seq` Bool
False = m (Of a r)
forall a. HasCallStack => a
undefined
go x
a (Empty r
r) = Of a r -> m (Of a r)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (x -> a
done x
a a -> r -> Of a r
forall a b. a -> b -> Of a b
:> r
r)
go x
a (Chunk ByteString
c ByteStream m r
cs) = x -> ByteStream m r -> m (Of a r)
go (x -> ByteString -> x
step x
a ByteString
c) ByteStream m r
cs
go x
a (Go m (ByteStream m r)
m) = m (ByteStream m r)
m m (ByteStream m r) -> (ByteStream m r -> m (Of a r)) -> m (Of a r)
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= x -> ByteStream m r -> m (Of a r)
go x
a
{-# INLINABLE chunkFold #-}
chunkFoldM :: Monad m => (x -> B.ByteString -> m x) -> m x -> (x -> m a) -> ByteStream m r -> m (Of a r)
chunkFoldM :: forall (m :: * -> *) x a r.
Monad m =>
(x -> ByteString -> m x)
-> m x -> (x -> m a) -> ByteStream m r -> m (Of a r)
chunkFoldM x -> ByteString -> m x
step m x
begin x -> m a
done ByteStream m r
bs = m x
begin m x -> (x -> m (Of a r)) -> m (Of a r)
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteStream m r -> x -> m (Of a r)
go ByteStream m r
bs
where
go :: ByteStream m r -> x -> m (Of a r)
go ByteStream m r
str !x
x = case ByteStream m r
str of
Empty r
r -> x -> m a
done x
x m a -> (a -> m (Of a r)) -> m (Of a r)
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
a -> Of a r -> m (Of a r)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a a -> r -> Of a r
forall a b. a -> b -> Of a b
:> r
r)
Chunk ByteString
c ByteStream m r
cs -> x -> ByteString -> m x
step x
x ByteString
c m x -> (x -> m (Of a r)) -> m (Of a r)
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteStream m r -> x -> m (Of a r)
go ByteStream m r
cs
Go m (ByteStream m r)
m -> m (ByteStream m r)
m m (ByteStream m r) -> (ByteStream m r -> m (Of a r)) -> m (Of a r)
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ByteStream m r
str' -> ByteStream m r -> x -> m (Of a r)
go ByteStream m r
str' x
x
{-# INLINABLE chunkFoldM #-}
foldlChunksM :: Monad m => (a -> B.ByteString -> m a) -> m a -> ByteStream m r -> m (Of a r)
foldlChunksM :: forall (m :: * -> *) a r.
Monad m =>
(a -> ByteString -> m a) -> m a -> ByteStream m r -> m (Of a r)
foldlChunksM a -> ByteString -> m a
f m a
z ByteStream m r
bs = m a
z m a -> (a -> m (Of a r)) -> m (Of a r)
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
a -> a -> ByteStream m r -> m (Of a r)
go a
a ByteStream m r
bs
where
go :: a -> ByteStream m r -> m (Of a r)
go !a
a ByteStream m r
str = case ByteStream m r
str of
Empty r
r -> Of a r -> m (Of a r)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a
a a -> r -> Of a r
forall a b. a -> b -> Of a b
:> r
r)
Chunk ByteString
c ByteStream m r
cs -> a -> ByteString -> m a
f a
a ByteString
c m a -> (a -> m (Of a r)) -> m (Of a r)
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
aa -> a -> ByteStream m r -> m (Of a r)
go a
aa ByteStream m r
cs
Go m (ByteStream m r)
m -> m (ByteStream m r)
m m (ByteStream m r) -> (ByteStream m r -> m (Of a r)) -> m (Of a r)
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> ByteStream m r -> m (Of a r)
go a
a
{-# INLINABLE foldlChunksM #-}
foldrChunksM :: Monad m => (B.ByteString -> m a -> m a) -> m a -> ByteStream m r -> m a
foldrChunksM :: forall (m :: * -> *) a r.
Monad m =>
(ByteString -> m a -> m a) -> m a -> ByteStream m r -> m a
foldrChunksM ByteString -> m a -> m a
step m a
nil ByteStream m r
bs = ByteStream m r
-> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
forall (m :: * -> *) r.
Monad m =>
ByteStream m r
-> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x
dematerialize ByteStream m r
bs (m a -> r -> m a
forall a b. a -> b -> a
const m a
nil) ByteString -> m a -> m a
step m (m a) -> m a
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join
{-# INLINE foldrChunksM #-}
unfoldrNE :: Int -> (a -> Either r (Word8, a)) -> a -> (B.ByteString, Either r a)
unfoldrNE :: forall a r.
Int -> (a -> Either r (Word8, a)) -> a -> (ByteString, Either r a)
unfoldrNE Int
i a -> Either r (Word8, a)
f a
x0
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = (ByteString
B.empty, a -> Either r a
forall a b. b -> Either a b
Right a
x0)
| Bool
otherwise = IO (ByteString, Either r a) -> (ByteString, Either r a)
forall a. IO a -> a
unsafePerformIO (IO (ByteString, Either r a) -> (ByteString, Either r a))
-> IO (ByteString, Either r a) -> (ByteString, Either r a)
forall a b. (a -> b) -> a -> b
$ Int
-> (Ptr Word8 -> IO (Int, Int, Either r a))
-> IO (ByteString, Either r a)
forall a.
Int -> (Ptr Word8 -> IO (Int, Int, a)) -> IO (ByteString, a)
B.createAndTrim' Int
i ((Ptr Word8 -> IO (Int, Int, Either r a))
-> IO (ByteString, Either r a))
-> (Ptr Word8 -> IO (Int, Int, Either r a))
-> IO (ByteString, Either r a)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Ptr Word8 -> a -> Int -> IO (Int, Int, Either r a)
go Ptr Word8
p a
x0 Int
0
where
go :: Ptr Word8 -> a -> Int -> IO (Int, Int, Either r a)
go !Ptr Word8
p !a
x !Int
n
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
i = (Int, Int, Either r a) -> IO (Int, Int, Either r a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
0, Int
n, a -> Either r a
forall a b. b -> Either a b
Right a
x)
| Bool
otherwise = case a -> Either r (Word8, a)
f a
x of
Left r
r -> (Int, Int, Either r a) -> IO (Int, Int, Either r a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
0, Int
n, r -> Either r a
forall a b. a -> Either a b
Left r
r)
Right (Word8
w,a
x') -> do Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
p Word8
w
Ptr Word8 -> a -> Int -> IO (Int, Int, Either r a)
go (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) a
x' (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
{-# INLINE unfoldrNE #-}
unfoldMChunks :: Monad m => (s -> m (Maybe (B.ByteString, s))) -> s -> ByteStream m ()
unfoldMChunks :: forall (m :: * -> *) s.
Monad m =>
(s -> m (Maybe (ByteString, s))) -> s -> ByteStream m ()
unfoldMChunks s -> m (Maybe (ByteString, s))
step = s -> ByteStream m ()
loop where
loop :: s -> ByteStream m ()
loop s
s = m (ByteStream m ()) -> ByteStream m ()
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go (m (ByteStream m ()) -> ByteStream m ())
-> m (ByteStream m ()) -> ByteStream m ()
forall a b. (a -> b) -> a -> b
$ do
Maybe (ByteString, s)
m <- s -> m (Maybe (ByteString, s))
step s
s
case Maybe (ByteString, s)
m of
Maybe (ByteString, s)
Nothing -> ByteStream m () -> m (ByteStream m ())
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (() -> ByteStream m ()
forall (m :: * -> *) r. r -> ByteStream m r
Empty ())
Just (ByteString
bs,s
s') -> ByteStream m () -> m (ByteStream m ())
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteStream m () -> m (ByteStream m ()))
-> ByteStream m () -> m (ByteStream m ())
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteStream m () -> ByteStream m ()
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk ByteString
bs (s -> ByteStream m ()
loop s
s')
{-# INLINABLE unfoldMChunks #-}
unfoldrChunks :: Monad m => (s -> m (Either r (B.ByteString, s))) -> s -> ByteStream m r
unfoldrChunks :: forall (m :: * -> *) s r.
Monad m =>
(s -> m (Either r (ByteString, s))) -> s -> ByteStream m r
unfoldrChunks s -> m (Either r (ByteString, s))
step = s -> ByteStream m r
loop where
loop :: s -> ByteStream m r
loop !s
s = m (ByteStream m r) -> ByteStream m r
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go (m (ByteStream m r) -> ByteStream m r)
-> m (ByteStream m r) -> ByteStream m r
forall a b. (a -> b) -> a -> b
$ do
Either r (ByteString, s)
m <- s -> m (Either r (ByteString, s))
step s
s
case Either r (ByteString, s)
m of
Left r
r -> ByteStream m r -> m (ByteStream m r)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (r -> ByteStream m r
forall (m :: * -> *) r. r -> ByteStream m r
Empty r
r)
Right (ByteString
bs,s
s') -> ByteStream m r -> m (ByteStream m r)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteStream m r -> m (ByteStream m r))
-> ByteStream m r -> m (ByteStream m r)
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteStream m r -> ByteStream m r
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk ByteString
bs (s -> ByteStream m r
loop s
s')
{-# INLINABLE unfoldrChunks #-}
reread :: Monad m => (s -> m (Maybe B.ByteString)) -> s -> ByteStream m ()
reread :: forall (m :: * -> *) s.
Monad m =>
(s -> m (Maybe ByteString)) -> s -> ByteStream m ()
reread s -> m (Maybe ByteString)
step s
s = ByteStream m ()
loop where
loop :: ByteStream m ()
loop = m (ByteStream m ()) -> ByteStream m ()
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go (m (ByteStream m ()) -> ByteStream m ())
-> m (ByteStream m ()) -> ByteStream m ()
forall a b. (a -> b) -> a -> b
$ do
Maybe ByteString
m <- s -> m (Maybe ByteString)
step s
s
case Maybe ByteString
m of
Maybe ByteString
Nothing -> ByteStream m () -> m (ByteStream m ())
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (() -> ByteStream m ()
forall (m :: * -> *) r. r -> ByteStream m r
Empty ())
Just ByteString
a -> ByteStream m () -> m (ByteStream m ())
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> ByteStream m () -> ByteStream m ()
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk ByteString
a ByteStream m ()
loop)
{-# INLINEABLE reread #-}
copy :: Monad m => ByteStream m r -> ByteStream (ByteStream m) r
copy :: forall (m :: * -> *) r.
Monad m =>
ByteStream m r -> ByteStream (ByteStream m) r
copy = ByteStream m r -> ByteStream (ByteStream m) r
forall (m :: * -> *) r.
Monad m =>
ByteStream m r -> ByteStream (ByteStream m) r
loop where
loop :: ByteStream m r -> ByteStream (ByteStream m) r
loop ByteStream m r
str = case ByteStream m r
str of
Empty r
r -> r -> ByteStream (ByteStream m) r
forall (m :: * -> *) r. r -> ByteStream m r
Empty r
r
Go m (ByteStream m r)
m -> ByteStream m (ByteStream (ByteStream m) r)
-> ByteStream (ByteStream m) r
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go ((ByteStream m r -> ByteStream (ByteStream m) r)
-> ByteStream m (ByteStream m r)
-> ByteStream m (ByteStream (ByteStream m) r)
forall a b. (a -> b) -> ByteStream m a -> ByteStream m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteStream m r -> ByteStream (ByteStream m) r
loop (m (ByteStream m r) -> ByteStream m (ByteStream m r)
forall (m :: * -> *) a. Monad m => m a -> ByteStream m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m (ByteStream m r)
m))
Chunk ByteString
bs ByteStream m r
rest -> ByteString
-> ByteStream (ByteStream m) r -> ByteStream (ByteStream m) r
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk ByteString
bs (ByteStream m (ByteStream (ByteStream m) r)
-> ByteStream (ByteStream m) r
forall (m :: * -> *) r. m (ByteStream m r) -> ByteStream m r
Go (ByteString
-> ByteStream m (ByteStream (ByteStream m) r)
-> ByteStream m (ByteStream (ByteStream m) r)
forall (m :: * -> *) r.
ByteString -> ByteStream m r -> ByteStream m r
Chunk ByteString
bs (ByteStream (ByteStream m) r
-> ByteStream m (ByteStream (ByteStream m) r)
forall (m :: * -> *) r. r -> ByteStream m r
Empty (ByteStream m r -> ByteStream (ByteStream m) r
loop ByteStream m r
rest))))
{-# INLINABLE copy #-}
findIndexOrEnd :: (Word8 -> Bool) -> B.ByteString -> Int
findIndexOrEnd :: (Word8 -> Bool) -> ByteString -> Int
findIndexOrEnd Word8 -> Bool
k (B.PS ForeignPtr Word8
x Int
s Int
l) =
IO Int -> Int
forall a. IO a -> a
B.accursedUnutterablePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$
ForeignPtr Word8 -> (Ptr Word8 -> IO Int) -> IO Int
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO Int) -> IO Int)
-> (Ptr Word8 -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
f -> Ptr Word8 -> Int -> IO Int
go (Ptr Word8
f Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) Int
0
where
go :: Ptr Word8 -> Int -> IO Int
go !Ptr Word8
ptr !Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l = Int -> IO Int
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int
l
| Bool
otherwise = do Word8
w <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
ptr
if Word8 -> Bool
k Word8
w
then Int -> IO Int
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int
n
else Ptr Word8 -> Int -> IO Int
go (Ptr Word8
ptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
{-# INLINABLE findIndexOrEnd #-}