| Copyright | (c) 2018 Composewell Technologies | 
|---|---|
| License | BSD3 | 
| Maintainer | streamly@composewell.com | 
| Stability | experimental | 
| Portability | GHC | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Streamly.Internal.FileSystem.Handle
Description
The fundamental singleton IO APIs are getChunk and putChunk and the
 fundamental stream IO APIs built on top of those are
 readChunksWith and writeChunks. Rest of this module is just
 combinatorial programming using these.
We can achieve line buffering by folding lines in the input stream into a
 stream of arrays using Stream.splitOn or Fold.takeEndBy_ and similar
 operations. One can wrap the input stream in Maybe type and then use
 writeMaybesWith to achieve user controlled buffering.
Synopsis
- getChunk :: MonadIO m => Int -> Handle -> m (Array Word8)
- getChunkOf :: Int -> Handle -> IO (Array Word8)
- putChunk :: MonadIO m => Handle -> Array a -> m ()
- read :: forall (m :: Type -> Type). MonadIO m => Handle -> Stream m Word8
- readWith :: forall (m :: Type -> Type). MonadIO m => Int -> Handle -> Stream m Word8
- readChunksWith :: forall (m :: Type -> Type). MonadIO m => Int -> Handle -> Stream m (Array Word8)
- readChunks :: forall (m :: Type -> Type). MonadIO m => Handle -> Stream m (Array Word8)
- reader :: forall (m :: Type -> Type). MonadIO m => Unfold m Handle Word8
- readerWith :: forall (m :: Type -> Type). MonadIO m => Unfold m (Int, Handle) Word8
- chunkReader :: forall (m :: Type -> Type). MonadIO m => Unfold m Handle (Array Word8)
- chunkReaderWith :: forall (m :: Type -> Type). MonadIO m => Unfold m (Int, Handle) (Array Word8)
- write :: forall (m :: Type -> Type). MonadIO m => Handle -> Fold m Word8 ()
- writeWith :: forall (m :: Type -> Type). MonadIO m => Int -> Handle -> Fold m Word8 ()
- writeChunks :: forall (m :: Type -> Type) a. MonadIO m => Handle -> Fold m (Array a) ()
- writeChunksWith :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Handle -> Fold m (Array a) ()
- writeMaybesWith :: forall (m :: Type -> Type). MonadIO m => Int -> Handle -> Fold m (Maybe Word8) ()
- writer :: forall (m :: Type -> Type). MonadIO m => Refold m Handle Word8 ()
- writerWith :: forall (m :: Type -> Type). MonadIO m => Int -> Refold m Handle Word8 ()
- chunkWriter :: forall (m :: Type -> Type) a. MonadIO m => Refold m Handle (Array a) ()
- putBytes :: MonadIO m => Handle -> Stream m Word8 -> m ()
- putBytesWith :: MonadIO m => Int -> Handle -> Stream m Word8 -> m ()
- putChunksWith :: (MonadIO m, Unbox a) => Int -> Handle -> Stream m (Array a) -> m ()
- putChunks :: MonadIO m => Handle -> Stream m (Array a) -> m ()
- chunkReaderFromToWith :: forall (m :: Type -> Type). MonadIO m => Unfold m (Int, Int, Int, Handle) (Array Word8)
- readChunksWithBufferOf :: forall (m :: Type -> Type). MonadIO m => Unfold m (Int, Handle) (Array Word8)
- readWithBufferOf :: forall (m :: Type -> Type). MonadIO m => Unfold m (Int, Handle) Word8
- writeChunksWithBufferOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Handle -> Fold m (Array a) ()
- writeWithBufferOf :: forall (m :: Type -> Type). 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 APIs
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.
getChunkOf :: Int -> Handle -> IO (Array Word8) Source #
Read a ByteArray consisting of exactly the specified number of bytes
 from a file handle.
Unimplemented
Streams
read :: forall (m :: Type -> Type). MonadIO m => Handle -> Stream m Word8 Source #
Generate a byte stream from a file Handle.
>>>read h = Stream.unfoldEach Array.reader $ Handle.readChunks h
Pre-release
readWith :: forall (m :: Type -> Type). 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.unfoldEach Array.reader $ Handle.readChunksWith size h
Pre-release
readChunksWith :: forall (m :: Type -> Type). 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)
readChunks :: forall (m :: Type -> Type). 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
Unfolds
reader :: forall (m :: Type -> Type). 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.unfoldEach Array.reader Handle.chunkReader
readerWith :: forall (m :: Type -> Type). 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.unfoldEach Array.reader Handle.chunkReaderWith
chunkReader :: forall (m :: Type -> Type). 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 :: forall (m :: Type -> Type). 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
write :: forall (m :: Type -> Type). 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 :: forall (m :: Type -> Type). 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 :: forall (m :: Type -> Type) a. 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)
writeChunksWith :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Handle -> Fold m (Array a) () Source #
writeChunksWith 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.
writeMaybesWith :: forall (m :: Type -> Type). MonadIO m => Int -> Handle -> Fold m (Maybe Word8) () Source #
Refolds
chunkWriter :: forall (m :: Type -> Type) a. MonadIO m => Refold m Handle (Array a) () Source #
Like writeChunks but uses the experimental Refold API.
Internal
Stream writes
putBytes :: MonadIO m => Handle -> Stream 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.
>>>putBytes = Handle.putBytesWith IO.defaultChunkSize
putBytesWith :: MonadIO m => Int -> Handle -> Stream m Word8 -> m () Source #
putBytesWith 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.
putChunksWith :: (MonadIO m, Unbox a) => Int -> Handle -> Stream m (Array a) -> m () Source #
putChunksWith 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.
putChunks :: MonadIO m => Handle -> Stream m (Array a) -> m () Source #
Write a stream of arrays to a handle.
>>>putChunks h = Stream.fold (Fold.drainBy (Handle.putChunk h))
Random Access (Seek)
Unlike the streaming APIs listed above, these APIs apply to devices or files that have random access or seek capability. This type of devices include disks, files, memory devices and exclude terminals, pipes, sockets and fifos.
chunkReaderFromToWith :: forall (m :: Type -> Type). MonadIO m => Unfold m (Int, Int, Int, Handle) (Array Word8) Source #
The input to the unfold is (from, to, bufferSize, handle). It starts
 reading from the offset from in the file and reads up to the offset to.
Deprecated
readChunksWithBufferOf :: forall (m :: Type -> Type). MonadIO m => Unfold m (Int, Handle) (Array Word8) Source #
Deprecated: Please use chunkReaderWith instead.
Same as chunkReaderWith
readWithBufferOf :: forall (m :: Type -> Type). MonadIO m => Unfold m (Int, Handle) Word8 Source #
Deprecated: Please use readerWith instead.
Same as readerWith