| Copyright | (c) 2018 Composewell Technologies | 
|---|---|
| License | BSD3 | 
| Maintainer | streamly@composewell.com | 
| Stability | released | 
| Portability | GHC | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Streamly.FileSystem.Handle
Description
>>>import qualified Streamly.FileSystem.Handle as Handle
Read and write byte streams and array streams to and from file handles
 (Handle).
The TextEncoding, NewLineMode, and Buffering options of the underlying
 GHC Handle are ignored by these APIs. Please use Streamly.Unicode.Stream
 module for encoding and decoding a byte stream, use stream splitting
 operations in Streamly.Data.Stream to create a stream of lines or to split
 the input stream on any other type of boundaries.
To set the read or write start position use hSeek on the Handle, the
 before combinator may be used to do that on a
 streaming combinator.  To restrict the length of read or write use the stream
 trimming operations like take.
Note that a Handle is inherently stateful, therefore, we cannot use these
 APIs from multiple threads without serialization; reading or writing in one
 thread would affect the file position for other threads.
For additional, experimental APIs take a look at Streamly.Internal.FileSystem.Handle module.
Synopsis
- getChunk :: MonadIO m => Int -> Handle -> m (Array Word8)
- putChunk :: MonadIO m => Handle -> Array a -> m ()
- read :: MonadIO m => Handle -> Stream m Word8
- readWith :: MonadIO m => Int -> Handle -> Stream m Word8
- readChunks :: MonadIO m => Handle -> Stream m (Array Word8)
- readChunksWith :: MonadIO m => Int -> Handle -> Stream m (Array Word8)
- reader :: MonadIO m => Unfold m Handle Word8
- readerWith :: MonadIO m => Unfold m (Int, Handle) Word8
- chunkReader :: MonadIO m => Unfold m Handle (Array Word8)
- chunkReaderWith :: MonadIO m => Unfold m (Int, Handle) (Array Word8)
- write :: MonadIO m => Handle -> Fold m Word8 ()
- writeWith :: MonadIO m => Int -> Handle -> Fold m Word8 ()
- writeChunks :: MonadIO m => Handle -> Fold m (Array a) ()
- readWithBufferOf :: MonadIO m => Unfold m (Int, Handle) Word8
- readChunksWithBufferOf :: MonadIO m => Unfold m (Int, Handle) (Array Word8)
- writeChunksWithBufferOf :: (MonadIO m, Unbox a) => Int -> Handle -> Fold m (Array a) ()
- writeWithBufferOf :: MonadIO m => Int -> Handle -> Fold m Word8 ()
Setup
To execute the code examples provided in this module in ghci, please run the following commands first.
>>>:m>>>import qualified Streamly.Data.Array as Array>>>import qualified Streamly.FileSystem.Handle as Handle hiding (readChunks)>>>import qualified Streamly.Data.Fold as Fold>>>import qualified Streamly.Data.Stream as Stream>>>import qualified Streamly.Data.Unfold as Unfold
For APIs that have not been released yet.
>>>import qualified Streamly.Internal.Data.Array as Array (unsafeCreateOf)>>>import qualified Streamly.Internal.Data.Unfold as Unfold (first)>>>import qualified Streamly.Internal.FileSystem.Handle as Handle>>>import qualified Streamly.Internal.System.IO as IO (defaultChunkSize)
Singleton IO
Read or write a single buffer.
getChunk :: MonadIO m => Int -> Handle -> m (Array Word8) Source #
Read a ByteArray consisting of one or more bytes from a file handle. If
 no data is available on the handle it blocks until at least one byte becomes
 available. If any data is available then it immediately returns that data
 without blocking. As a result of this behavior, it may read less than or
 equal to the size requested.
Streaming IO
Read or write a stream of data to or from a file or device sequentially.
Read requests to the IO device are performed in chunks limited to a
 maximum size of defaultChunkSize.  Note
 that the size of the actual chunks in the resulting stream may be less
 than the defaultChunkSize but it can never exceed it.  If the whole
 stream is not consumed, it is possible that we may have 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.
Reading
TextEncoding, NewLineMode, and Buffering options of the
 underlying handle are ignored. The read occurs from the current seek
 position of the file handle. The stream ends as soon as EOF is
 encountered.
Streams
read :: MonadIO m => Handle -> Stream m Word8 Source #
Generate a byte stream from a file Handle.
>>>read h = Stream.unfoldMany Array.reader $ Handle.readChunks h
Pre-release
readWith :: MonadIO m => Int -> Handle -> Stream m Word8 Source #
readWith bufsize handle reads a byte stream from a file
 handle, reads are performed in chunks of up to bufsize.
>>>readWith size h = Stream.unfoldMany Array.reader $ Handle.readChunksWith size h
Pre-release
readChunks :: MonadIO m => Handle -> Stream m (Array Word8) Source #
getChunks 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.
>>>readChunks = Handle.readChunksWith IO.defaultChunkSize
Pre-release
readChunksWith :: MonadIO m => Int -> Handle -> Stream m (Array Word8) Source #
readChunksWith 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.
>>>readChunksWith size h = Stream.unfold Handle.chunkReaderWith (size, h)
Unfolds
reader :: 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.
>>>reader = Unfold.many Array.reader Handle.chunkReader
readerWith :: 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.
>>>readerWith = Unfold.many Array.reader Handle.chunkReaderWith
chunkReader :: 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.
>>>chunkReader = Unfold.first IO.defaultChunkSize Handle.chunkReaderWith
chunkReaderWith :: 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.
Folds
TextEncoding, NewLineMode, and Buffering options of the
 underlying handle are ignored. The write occurs from the current seek
 position of the file handle.  The write behavior depends on the IOMode
 of the 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.
>>>write = Handle.writeWith IO.defaultChunkSize
writeWith :: MonadIO m => Int -> Handle -> Fold m Word8 () Source #
writeWith 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.
>>>writeWith n h = Fold.groupsOf n (Array.unsafeCreateOf n) (Handle.writeChunks h)
writeChunks :: MonadIO m => 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.
writeChunks h = Fold.drainBy (Handle.putChunk h)
Deprecated
readWithBufferOf :: MonadIO m => Unfold m (Int, Handle) Word8 Source #
Deprecated: Please use readerWith instead.
Same as readerWith
readChunksWithBufferOf :: MonadIO m => Unfold m (Int, Handle) (Array Word8) Source #
Deprecated: Please use chunkReaderWith instead.
Same as chunkReaderWith
writeChunksWithBufferOf :: (MonadIO m, Unbox a) => Int -> Handle -> Fold m (Array a) () Source #
Deprecated: Please use writeChunksWith instead.
Same as writeChunksWith