streaming-bytestring-0.1.6: effectful byte steams, or: bytestring io done right.

Safe HaskellNone
LanguageHaskell2010

Data.ByteString.Streaming.Internal

Contents

Synopsis

Documentation

data ByteString m r Source #

A space-efficient representation of a succession of Word8 vectors, supporting many efficient operations.

An effectful ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Streaming.Char8 it can be interpreted as containing 8-bit characters.

Constructors

Empty r 
Chunk !ByteString (ByteString m r) 
Go (m (ByteString m r)) 

Instances

MonadTrans ByteString Source # 

Methods

lift :: Monad m => m a -> ByteString m a #

MonadBase b m => MonadBase b (ByteString m) Source # 

Methods

liftBase :: b α -> ByteString m α #

Monad m => Monad (ByteString m) Source # 

Methods

(>>=) :: ByteString m a -> (a -> ByteString m b) -> ByteString m b #

(>>) :: ByteString m a -> ByteString m b -> ByteString m b #

return :: a -> ByteString m a #

fail :: String -> ByteString m a #

Monad m => Functor (ByteString m) Source # 

Methods

fmap :: (a -> b) -> ByteString m a -> ByteString m b #

(<$) :: a -> ByteString m b -> ByteString m a #

Monad m => Applicative (ByteString m) Source # 

Methods

pure :: a -> ByteString m a #

(<*>) :: ByteString m (a -> b) -> ByteString m a -> ByteString m b #

liftA2 :: (a -> b -> c) -> ByteString m a -> ByteString m b -> ByteString m c #

(*>) :: ByteString m a -> ByteString m b -> ByteString m b #

(<*) :: ByteString m a -> ByteString m b -> ByteString m a #

MonadIO m => MonadIO (ByteString m) Source # 

Methods

liftIO :: IO a -> ByteString m a #

MonadThrow m => MonadThrow (ByteString m) Source # 

Methods

throwM :: Exception e => e -> ByteString m a #

MonadCatch m => MonadCatch (ByteString m) Source # 

Methods

catch :: Exception e => ByteString m a -> (e -> ByteString m a) -> ByteString m a #

MonadResource m => MonadResource (ByteString m) Source # 
MFunctor * ByteString Source # 

Methods

hoist :: Monad m => (forall a. m a -> n a) -> t m b -> t n b #

((~) (* -> *) m Identity, Show r) => Show (ByteString m r) Source # 

Methods

showsPrec :: Int -> ByteString m r -> ShowS #

show :: ByteString m r -> String #

showList :: [ByteString m r] -> ShowS #

(~) * r () => IsString (ByteString m r) Source # 

Methods

fromString :: String -> ByteString m r #

(Semigroup r, Monad m) => Semigroup (ByteString m r) Source # 

Methods

(<>) :: ByteString m r -> ByteString m r -> ByteString m r #

sconcat :: NonEmpty (ByteString m r) -> ByteString m r #

stimes :: Integral b => b -> ByteString m r -> ByteString m r #

(Monoid r, Monad m) => Monoid (ByteString m r) Source # 

Methods

mempty :: ByteString m r #

mappend :: ByteString m r -> ByteString m r -> ByteString m r #

mconcat :: [ByteString m r] -> ByteString m r #

consChunk :: ByteString -> ByteString m r -> ByteString m r Source #

Smart constructor for Chunk.

chunkOverhead :: Int Source #

The memory management overhead. Currently this is tuned for GHC only.

defaultChunkSize :: Int Source #

The chunk size used for I/O. Currently set to 32k, less the memory management overhead

materialize :: (forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x) -> ByteString m r Source #

Construct a succession of chunks from its Church encoding (compare GHC.Exts.build)

dematerialize :: Monad m => ByteString m r -> forall x. (r -> x) -> (ByteString -> x -> x) -> (m x -> x) -> x Source #

Resolve a succession of chunks into its Church encoding; this is not a safe operation; it is equivalent to exposing the constructors

foldrChunks :: Monad m => (ByteString -> a -> a) -> a -> ByteString m r -> m a Source #

Consume the chunks of an effectful ByteString with a natural right fold.

foldlChunks :: Monad m => (a -> ByteString -> a) -> a -> ByteString m r -> m (Of a r) Source #

foldrChunksM :: Monad m => (ByteString -> m a -> m a) -> m a -> ByteString m r -> m a Source #

Consume the chunks of an effectful ByteString with a natural right monadic fold.

foldlChunksM :: Monad m => (a -> ByteString -> m a) -> m a -> ByteString m r -> m (Of a r) Source #

chunkFold :: Monad m => (x -> ByteString -> x) -> x -> (x -> a) -> ByteString m r -> m (Of a r) Source #

chunkFold is preferable to foldlChunks since it is an appropriate argument for Control.Foldl.purely which permits many folds and sinks to be run simulaneously on one bytestream.

chunkFoldM :: Monad m => (x -> ByteString -> m x) -> m x -> (x -> m a) -> ByteString m r -> m (Of a r) Source #

chunkFoldM is preferable to foldlChunksM since it is an appropriate argument for Control.Foldl.impurely which permits many folds and sinks to be run simulaneously on one bytestream.

chunkMapM_ :: Monad m => (ByteString -> m x) -> ByteString m r -> m r Source #

unfoldMChunks :: Monad m => (s -> m (Maybe (ByteString, s))) -> s -> ByteString m () Source #

unfoldrChunks :: Monad m => (s -> m (Either r (ByteString, s))) -> s -> ByteString m r Source #

smallChunkSize :: Int Source #

The recommended chunk size. Currently set to 4k, less the memory management overhead

packBytes :: Monad m => Stream (Of Word8) m r -> ByteString m r Source #

Packing and unpacking from lists packBytes' :: Monad m => [Word8] -> ByteString m () packBytes' cs0 = packChunks 32 cs0 where packChunks n cs = case S.packUptoLenBytes n cs of (bs, []) -> Chunk bs (Empty ()) (bs, cs') -> Chunk bs (packChunks (min (n * 2) BI.smallChunkSize) cs') -- packUptoLenBytes :: Int -> [Word8] -> (ByteString, [Word8]) packUptoLenBytes len xs0 = unsafeDupablePerformIO (createUptoN' len $ p -> go p len xs0) where go !_ !n [] = return (len-n, []) go !_ !0 xs = return (len, xs) go !p !n (x:xs) = poke p x >> go (p plusPtr 1) (n-1) xs createUptoN' :: Int -> (Ptr Word8 -> IO (Int, a)) -> IO (S.ByteString, a) createUptoN' l f = do fp <- S.mallocByteString l (l', res) withForeignPtr fp $ p - f p assert (l' <= l) $ return (S.PS fp 0 l', res) {--}

chunk :: ByteString -> ByteString m () Source #

Yield-style smart constructor for Chunk.

mwrap :: m (ByteString m r) -> ByteString m r Source #

Reconceive an effect that results in an effectful bytestring as an effectful bytestring. Compare Streaming.mwrap. The closes equivalent of

>>> Streaming.wrap :: f (Stream f m r) -> Stream f m r

is here consChunk. mwrap is the smart constructor for the internal Go constructor.

unfoldrNE :: Int -> (a -> Either r (Word8, a)) -> a -> (ByteString, Either r a) Source #

reread :: Monad m => (s -> m (Maybe ByteString)) -> s -> ByteString m () Source #

Stream chunks from something that contains IO (Maybe ByteString) until it returns Nothing. reread is of particular use rendering io-streams input streams as byte streams in the present sense

Q.reread Streams.read             :: InputStream S.ByteString -> Q.ByteString IO ()
Q.reread (liftIO . Streams.read)  :: MonadIO m => InputStream S.ByteString -> Q.ByteString m ()

The other direction here is

Streams.unfoldM Q.unconsChunk     :: Q.ByteString IO r -> IO (InputStream S.ByteString)

copy :: Monad m => ByteString m r -> ByteString (ByteString m) r Source #

Make the information in a bytestring available to more than one eliminating fold, e.g.

>>> Q.count 'l' $ Q.count 'o' $ Q.copy $ "hello\nworld"
3 :> (2 :> ())
>>> Q.length $ Q.count 'l' $ Q.count 'o' $ Q.copy $ Q.copy "hello\nworld"
11 :> (3 :> (2 :> ()))
>>> runResourceT $ Q.writeFile "hello2.txt" $ Q.writeFile "hello1.txt" $ Q.copy $ "hello\nworld\n"
>>> :! cat hello2.txt
hello
world
>>> :! cat hello1.txt
hello
world

This sort of manipulation could as well be acheived by combining folds - using Control.Foldl for example. But any sort of manipulation can be involved in the fold. Here are a couple of trivial complications involving splitting by lines:

>>> let doubleLines = Q.unlines . maps (<* Q.chunk "\n" ) . Q.lines
>>> let emphasize = Q.unlines . maps (<* Q.chunk "!" ) . Q.lines
>>> runResourceT $ Q.writeFile "hello2.txt" $ emphasize $ Q.writeFile "hello1.txt" $ doubleLines $ Q.copy $ "hello\nworld"
>>> :! cat hello2.txt
hello!
world!
>>> :! cat hello1.txt
hello

world

As with the parallel operations in Streaming.Prelude, we have

Q.effects . Q.copy       = id
hoist Q.effects . Q.copy = id

The duplication does not by itself involve the copying of bytestring chunks; it just makes two references to each chunk as it arises. This does, however double the number of constructors associated with each chunk.

ResourceT help

bracketByteString :: MonadResource m => IO a -> (a -> IO ()) -> (a -> ByteString m b) -> ByteString m b Source #