streamly-0.8.2: Dataflow programming and declarative concurrency
Copyright(c) 2018 Composewell Technologies
LicenseBSD3
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

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 readChunksWithBufferOf 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 writeMaybesWithBufferOf to achieve user controlled buffering.

Synopsis

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.

Since: 0.8.1

getChunkOf :: Int -> Handle -> IO (Array Word8) Source #

Read a ByteArray consisting of exactly the specified number of bytes from a file handle.

Unimplemented

putChunk :: (MonadIO m, Storable a) => Handle -> Array a -> m () Source #

Write an Array to a file handle.

Since: 0.8.1

Byte Stream Read

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.

>>> read = Unfold.many Handle.readChunks Array.read

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.

>>> readWithBufferOf = Unfold.many Handle.readChunksWithBufferOf Array.read

Since: 0.7.0

toBytes :: (IsStream t, MonadIO m) => Handle -> t m Word8 Source #

Generate a byte stream from a file Handle.

>>> toBytes h = Stream.unfoldMany Array.read $ Handle.toChunks h

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.

>>> toBytesWithBufferOf size h = Stream.unfoldMany Array.read $ Handle.toChunksWithBufferOf size h

Pre-release

Chunked Stream Read

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.

>>> readChunks = Unfold.supplyFirst IO.defaultChunkSize Handle.readChunksWithBufferOf

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.

>>> toChunksWithBufferOf size h = Stream.unfold Handle.readChunksWithBufferOf (size, h)

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 = Handle.toChunksWithBufferOf IO.defaultChunkSize

Since: 0.7.0

Byte Stream Write

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.writeWithBufferOf IO.defaultChunkSize

Since: 0.7.0

consumer :: MonadIO m => Refold m Handle Word8 () Source #

Like write but uses the experimental Refold API.

Internal

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.

>>> writeWithBufferOf n h = Fold.chunksOf n (Array.writeNUnsafe n) (Handle.writeChunks h)

Since: 0.7.0

writeMaybesWithBufferOf :: MonadIO m => Int -> Handle -> Fold m (Maybe Word8) () Source #

Write a stream of Maybe values. Keep buffering the just values in an array until a Nothing is encountered or the buffer size exceeds the specified limit, at that point flush the buffer to the handle.

Pre-release

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.

>>> putBytes = Handle.putBytesWithBufferOf IO.defaultChunkSize

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.

>>> putBytesWithBufferOf n h m = Handle.putChunks h $ Stream.arraysOf n m

Since: 0.7.0

Chunked Stream Write

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.

writeChunks h = Fold.drainBy (Handle.putChunk h)

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

putChunks :: (MonadIO m, Storable a) => Handle -> SerialT m (Array a) -> m () Source #

Write a stream of arrays to a handle.

>>> putChunks h = Stream.mapM_ (Handle.putChunk h)

Since: 0.7.0

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.

readChunksFromToWith :: 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.