Copyright | (c) 2019 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Streamly.Internal.FileSystem.FileIO
Description
Synopsis
- withFile :: forall (m :: Type -> Type) a. (MonadIO m, MonadCatch m) => Path -> IOMode -> (Handle -> Stream m a) -> Stream m a
- read :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Path -> Stream m Word8
- readChunksWith :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Int -> Path -> Stream m (Array Word8)
- readChunks :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Path -> Stream m (Array Word8)
- readerWith :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Unfold m (Int, Path) Word8
- reader :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Unfold m Path Word8
- chunkReaderWith :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Unfold m (Int, Path) (Array Word8)
- chunkReaderFromToWith :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Unfold m (Int, Int, Int, Path) (Array Word8)
- chunkReader :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Unfold m Path (Array Word8)
- putChunk :: Path -> Array a -> IO ()
- write :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Path -> Fold m Word8 ()
- writeWith :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Int -> Path -> Fold m Word8 ()
- writeChunks :: forall (m :: Type -> Type) a. (MonadIO m, MonadCatch m) => Path -> Fold m (Array a) ()
- fromBytes :: (MonadIO m, MonadCatch m) => Path -> Stream m Word8 -> m ()
- fromBytesWith :: (MonadIO m, MonadCatch m) => Int -> Path -> Stream m Word8 -> m ()
- fromChunks :: (MonadIO m, MonadCatch m) => Path -> Stream m (Array a) -> m ()
- writeAppend :: (MonadIO m, MonadCatch m) => Path -> Stream m Word8 -> m ()
- writeAppendWith :: (MonadIO m, MonadCatch m) => Int -> Path -> Stream m Word8 -> m ()
- writeAppendArray :: Path -> Array a -> IO ()
- writeAppendChunks :: (MonadIO m, MonadCatch m) => Path -> Stream m (Array a) -> m ()
Streaming IO
Stream data to or from a file or device sequentially. When reading,
the stream is lazy and generated on-demand as the consumer consumes it.
Read IO requests to the IO device are performed in chunks limited to a
maximum size of 32KiB, this is referred to as defaultChunkSize
in the
documentation. One IO request may or may not read the full
chunk. If the whole stream is not consumed, it is possible that we may
read slightly more from the IO device than what the consumer needed.
Unless specified otherwise in the API, writes are collected into chunks
of defaultChunkSize
before they are written to the IO device.
File IO Using Handle
withFile :: forall (m :: Type -> Type) a. (MonadIO m, MonadCatch m) => Path -> IOMode -> (Handle -> Stream m a) -> Stream m a Source #
opens a file and passes the resulting handle to
the computation withFile
name mode actact
. The handle is closed on exit from withFile
, whether
by normal termination or by raising an exception. If closing the handle
raises an exception, then that exception is raised by withFile
rather than
any exception raised by act
.
The file is opened in binary mode as encoding, decoding, and newline translation can be handled explicitly by the streaming APIs.
The file is opened without buffering as buffering can be controlled explicitly by the streaming APIs.
Pre-release
Streams
read :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Path -> Stream m Word8 Source #
Generate a stream of bytes from a file specified by path. The stream ends when EOF is encountered. File is locked using multiple reader and single writer locking mode.
Pre-release
readChunksWith :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Int -> Path -> Stream m (Array Word8) Source #
readChunksWith size file
reads a stream of arrays from file file
.
The maximum size of a single array is specified by size
. The actual size
read may be less than or equal to size
.
Pre-release
readChunks :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Path -> Stream m (Array Word8) Source #
readChunks file
reads a stream of arrays from file file
.
The maximum size of a single array is limited to defaultChunkSize
. The
actual size read may be less than defaultChunkSize
.
readChunks = readChunksWith defaultChunkSize
Pre-release
Unfolds
readerWith :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Unfold m (Int, Path) Word8 Source #
Unfolds the tuple (bufsize, filepath)
into a byte stream, read requests
to the IO device are performed using buffers of bufsize
.
Pre-release
reader :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Unfold m Path Word8 Source #
Unfolds a file path into a byte stream. IO requests to the device are
performed in sizes of
defaultChunkSize
.
Pre-release
chunkReaderWith :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Unfold m (Int, Path) (Array Word8) Source #
Unfold the tuple (bufsize, filepath)
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
.
Pre-release
chunkReaderFromToWith :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Unfold m (Int, Int, Int, Path) (Array Word8) Source #
Unfold the tuple (from, to, bufsize, filepath)
into a stream
of Word8
arrays.
Read requests to the IO device are performed using a buffer of size
bufsize
starting from absolute offset of from
till the absolute
position of to
. The size of an array in the resulting stream is always
less than or equal to bufsize
.
Pre-release
chunkReader :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Unfold m Path (Array Word8) Source #
Unfolds a Path
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
.
Pre-release
Write To File
putChunk :: Path -> Array a -> IO () Source #
Write an array to a file. Overwrites the file if it exists.
Pre-release
Folds
write :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Path -> Fold m Word8 () Source #
Write a byte stream to a file. Accumulates the input in chunks of up to
defaultChunkSize
before writing to
the IO device.
Pre-release
writeWith :: forall (m :: Type -> Type). (MonadIO m, MonadCatch m) => Int -> Path -> Fold m Word8 () Source #
writeWith chunkSize handle
writes the input stream to handle
.
Bytes in the input stream are collected into a buffer until we have a chunk
of size chunkSize
and then written to the IO device.
Pre-release
writeChunks :: forall (m :: Type -> Type) a. (MonadIO m, MonadCatch m) => Path -> Fold m (Array a) () Source #
Write a stream of chunks to a file. Each chunk in the stream is written immediately to the device as a separate IO request, without coalescing or buffering.
Writing Streams
fromBytes :: (MonadIO m, MonadCatch m) => Path -> Stream m Word8 -> m () Source #
Write a byte stream to a file. Combines the bytes in chunks of size
up to defaultChunkSize
before writing. If the file exists it is
truncated to zero size before writing. If the file does not exist it is
created. File is locked using single writer locking mode.
Pre-release
fromBytesWith :: (MonadIO m, MonadCatch m) => Int -> Path -> Stream m Word8 -> m () Source #
Like write
but provides control over the write buffer. Output will
be written to the IO device as soon as we collect the specified number of
input elements.
Pre-release
fromChunks :: (MonadIO m, MonadCatch m) => Path -> Stream m (Array a) -> m () Source #
Write a stream of arrays to a file. Overwrites the file if it exists.
Pre-release
Append To File
writeAppend :: (MonadIO m, MonadCatch m) => Path -> Stream m Word8 -> m () Source #
Append a byte stream to a file. Combines the bytes in chunks of size up to
defaultChunkSize
before writing. If the file exists then the new data
is appended to the file. If the file does not exist it is created. File is
locked using single writer locking mode.
Pre-release
writeAppendWith :: (MonadIO m, MonadCatch m) => Int -> Path -> Stream m Word8 -> m () Source #
Like append
but provides control over the write buffer. Output will
be written to the IO device as soon as we collect the specified number of
input elements.
Pre-release
writeAppendChunks :: (MonadIO m, MonadCatch m) => Path -> Stream m (Array a) -> m () Source #
Append a stream of arrays to a file.
Pre-release