Copyright | (c) 2018 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- read :: MonadIO m => Unfold m Handle Word8
- readWithBufferOf :: MonadIO m => Unfold m (Int, Handle) Word8
- toBytes :: (IsStream t, MonadIO m) => Handle -> t m Word8
- toBytesWithBufferOf :: (IsStream t, MonadIO m) => Int -> Handle -> t m Word8
- readChunks :: MonadIO m => Unfold m Handle (Array Word8)
- readChunksWithBufferOf :: MonadIO m => Unfold m (Int, Handle) (Array Word8)
- toChunksWithBufferOf :: (IsStream t, MonadIO m) => Int -> Handle -> t m (Array Word8)
- toChunks :: (IsStream t, MonadIO m) => Handle -> t m (Array Word8)
- write :: MonadIO m => Handle -> Fold m Word8 ()
- write2 :: MonadIO m => Fold2 m Handle Word8 ()
- writeWithBufferOf :: MonadIO m => Int -> Handle -> Fold m Word8 ()
- putBytes :: MonadIO m => Handle -> SerialT m Word8 -> m ()
- putBytesWithBufferOf :: MonadIO m => Int -> Handle -> SerialT m Word8 -> m ()
- writeArray :: Storable a => Handle -> Array a -> IO ()
- writeChunks :: (MonadIO m, Storable a) => Handle -> Fold m (Array a) ()
- writeChunksWithBufferOf :: (MonadIO m, Storable a) => Int -> Handle -> Fold m (Array a) ()
- putChunksWithBufferOf :: (MonadIO m, Storable a) => Int -> Handle -> SerialT m (Array a) -> m ()
- putChunks :: (MonadIO m, Storable a) => Handle -> SerialT m (Array a) -> m ()
Read from Handle
read :: MonadIO m => Unfold m Handle Word8 Source #
Unfolds a file handle into a byte stream. IO requests to the device are
performed in sizes of
defaultChunkSize
.
Since: 0.7.0
readWithBufferOf :: MonadIO m => Unfold m (Int, Handle) Word8 Source #
Unfolds the tuple (bufsize, handle)
into a byte stream, read requests
to the IO device are performed using buffers of bufsize
.
Since: 0.7.0
toBytes :: (IsStream t, MonadIO m) => Handle -> t m Word8 Source #
Generate a byte stream from a file Handle
.
Pre-release
toBytesWithBufferOf :: (IsStream t, MonadIO m) => Int -> Handle -> t m Word8 Source #
toBytesWithBufferOf bufsize handle
reads a byte stream from a file
handle, reads are performed in chunks of up to bufsize
.
Pre-release
readChunks :: MonadIO m => Unfold m Handle (Array Word8) Source #
Unfolds a handle into a stream of Word8
arrays. Requests to the IO
device are performed using a buffer of size
defaultChunkSize
. The
size of arrays in the resulting stream are therefore less than or equal to
defaultChunkSize
.
Since: 0.7.0
readChunksWithBufferOf :: MonadIO m => Unfold m (Int, Handle) (Array Word8) Source #
Unfold the tuple (bufsize, handle)
into a stream of Word8
arrays.
Read requests to the IO device are performed using a buffer of size
bufsize
. The size of an array in the resulting stream is always less than
or equal to bufsize
.
Since: 0.7.0
toChunksWithBufferOf :: (IsStream t, MonadIO m) => Int -> Handle -> t m (Array Word8) Source #
toChunksWithBufferOf size handle
reads a stream of arrays from the file
handle handle
. The maximum size of a single array is limited to size
.
The actual size read may be less than or equal to size
.
Since: 0.7.0
toChunks :: (IsStream t, MonadIO m) => Handle -> t m (Array Word8) Source #
toChunks handle
reads a stream of arrays from the specified file
handle. The maximum size of a single array is limited to
defaultChunkSize
. The actual size read may be less than or equal to
defaultChunkSize
.
toChunks = toChunksWithBufferOf defaultChunkSize
Since: 0.7.0
Write to Handle
write :: MonadIO m => Handle -> Fold m Word8 () Source #
Write a byte stream to a file handle. Accumulates the input in chunks of
up to defaultChunkSize
before writing
to the IO device.
Since: 0.7.0
writeWithBufferOf :: MonadIO m => Int -> Handle -> Fold m Word8 () Source #
writeWithBufferOf reqSize handle
writes the input stream to handle
.
Bytes in the input stream are collected into a buffer until we have a chunk
of reqSize
and then written to the IO device.
Since: 0.7.0
putBytes :: MonadIO m => Handle -> SerialT m Word8 -> m () Source #
Write a byte stream to a file handle. Accumulates the input in chunks of
up to defaultChunkSize
before writing.
NOTE: This may perform better than the write
fold, you can try this if you
need some extra perf boost.
Since: 0.7.0
putBytesWithBufferOf :: MonadIO m => Int -> Handle -> SerialT m Word8 -> m () Source #
putBytesWithBufferOf bufsize handle stream
writes stream
to handle
in chunks of bufsize
. A write is performed to the IO device as soon as we
collect the required input size.
Since: 0.7.0
writeArray :: Storable a => Handle -> Array a -> IO () Source #
Write an Array
to a file handle.
Since: 0.7.0
writeChunks :: (MonadIO m, Storable a) => Handle -> Fold m (Array a) () Source #
Write a stream of arrays to a handle. Each array in the stream is written to the device as a separate IO request.
Since: 0.7.0
writeChunksWithBufferOf :: (MonadIO m, Storable a) => Int -> Handle -> Fold m (Array a) () Source #
writeChunksWithBufferOf bufsize handle
writes a stream of arrays
to handle
after coalescing the adjacent arrays in chunks of bufsize
.
We never split an array, if a single array is bigger than the specified size
it emitted as it is. Multiple arrays are coalesed as long as the total size
remains below the specified size.
Since: 0.7.0
putChunksWithBufferOf :: (MonadIO m, Storable a) => Int -> Handle -> SerialT m (Array a) -> m () Source #
putChunksWithBufferOf bufsize handle stream
writes a stream of arrays
to handle
after coalescing the adjacent arrays in chunks of bufsize
.
The chunk size is only a maximum and the actual writes could be smaller as
we do not split the arrays to fit exactly to the specified size.
Since: 0.7.0