Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- chunkReader :: Monad m => Unfold m ByteString (Array Word8)
- reader :: Monad m => Unfold m ByteString Word8
- toChunks :: Monad m => ByteString -> Stream m (Array Word8)
- fromChunks :: Monad m => Stream m (Array Word8) -> m ByteString
- fromChunksIO :: Stream IO (Array Word8) -> IO ByteString
- read :: Monad m => Unfold m ByteString Word8
- readChunks :: Monad m => Unfold m ByteString (Array Word8)
Documentation
chunkReader :: Monad m => Unfold m ByteString (Array Word8) Source #
Unfold a lazy ByteString to a stream of Array
Words
.
reader :: Monad m => Unfold m ByteString Word8 Source #
Unfold a lazy ByteString to a stream of Word8
toChunks :: Monad m => ByteString -> Stream m (Array Word8) Source #
Convert a lazy ByteString
to a serial stream of Array
Word8
.
fromChunks :: Monad m => Stream m (Array Word8) -> m ByteString Source #
Convert a serial stream of Array
Word8
to a lazy ByteString
.
IMPORTANT NOTE: This function is lazy only for lazy monads (e.g. Identity). For strict monads (e.g. IO) it consumes the entire input before generating the output. For IO monad please use fromChunksIO instead.
For strict monads like IO you could create a newtype wrapper to make the monad bind operation lazy and lift the stream to that type using hoist, then you can use this function to generate the bytestring lazily. For example you can wrap the IO type to make the bind lazy like this:
newtype LazyIO a = LazyIO { runLazy :: IO a } deriving (Functor, Applicative) liftToLazy :: IO a -> LazyIO a liftToLazy = LazyIO instance Monad LazyIO where return = pure LazyIO a >>= f = LazyIO (unsafeInterleaveIO a >>= unsafeInterleaveIO . runLazy . f)
fromChunks can then be used as,
{-# INLINE fromChunksIO #-}
fromChunksIO :: Stream IO (Array Word8) -> IO ByteString
fromChunksIO str = runLazy (fromChunks (Stream.hoist liftToLazy str))
fromChunksIO :: Stream IO (Array Word8) -> IO ByteString Source #
Convert a serial stream of Array
Word8
to a lazy ByteString
in the
IO monad.
readChunks :: Monad m => Unfold m ByteString (Array Word8) Source #
Deprecated: Please use chunkReader instead.