Copyright | (c) 2019 Composewell Technologies |
---|---|
License | BSD3-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Combinators to efficiently manipulate streams of mutable arrays.
We can either push these in the MutArray module with a "chunks" prefix or keep this as a separate module and release it.
Synopsis
- chunksOf :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a)
- pinnedChunksOf :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a)
- writeChunks :: (MonadIO m, Unbox a) => Int -> Fold m a (StreamK n (MutArray a))
- splitOn :: (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> Stream m (MutArray a)
- packArraysChunksOf :: (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- data SpliceState s arr
- = SpliceInitial s
- | SpliceBuffering s arr
- | SpliceYielding arr (SpliceState s arr)
- | SpliceFinish
- lpackArraysChunksOf :: (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) () -> Fold m (MutArray a) ()
- compact :: (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- compactLE :: (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (Either ParseError (MutArray a))
- compactEQ :: Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- compactGE :: (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- flattenArrays :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a
- flattenArraysRev :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a
- fromArrayStreamK :: (Unbox a, MonadIO m) => StreamK m (MutArray a) -> m (MutArray a)
Generation
chunksOf :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a) Source #
chunksOf n stream
groups the elements in the input stream into arrays of
n
elements each.
Same as the following but may be more efficient:
>>>
chunksOf n = Stream.foldMany (MutArray.writeN n)
Pre-release
pinnedChunksOf :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a) Source #
Like chunksOf
but creates pinned arrays.
writeChunks :: (MonadIO m, Unbox a) => Int -> Fold m a (StreamK n (MutArray a)) Source #
Buffer a stream into a stream of arrays.
>>>
writeChunks n = Fold.many (MutArray.writeN n) Fold.toStreamK
Breaking an array into an array stream can be useful to consume a large array sequentially such that memory of the array is released incrementatlly.
See also: arrayStreamKFromStreamD
.
Unimplemented
splitOn :: (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> Stream m (MutArray a) Source #
Split the array into a stream of slices using a predicate. The element matching the predicate is dropped.
Pre-release
Compaction
packArraysChunksOf :: (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
This mutates the first array (if it has space) to append values from the second one. This would work for immutable arrays as well because an immutable array never has space so a new array is allocated instead of mutating it.
| Coalesce adjacent arrays in incoming stream to form bigger arrays of a maximum specified size. Note that if a single array is bigger than the specified size we do not split it to fit. When we coalesce multiple arrays if the size would exceed the specified size we do not coalesce therefore the actual array size may be less than the specified chunk size.
Since: 0.7.0
data SpliceState s arr Source #
SpliceInitial s | |
SpliceBuffering s arr | |
SpliceYielding arr (SpliceState s arr) | |
SpliceFinish |
lpackArraysChunksOf :: (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) () -> Fold m (MutArray a) () Source #
compact :: (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
Coalesce adjacent arrays in incoming stream to form bigger arrays of a maximum specified size in bytes.
Internal
compactLE :: (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (Either ParseError (MutArray a)) Source #
Coalesce adjacent arrays in incoming stream to form bigger arrays of a maximum specified size in bytes.
Internal
compactEQ :: Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
Like compactLE
but generates arrays of exactly equal to the size
specified except for the last array in the stream which could be shorter.
Unimplemented
compactGE :: (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
Like compactLE
but generates arrays of size greater than or equal to the
specified except for the last array in the stream which could be shorter.
Internal
Elimination
flattenArrays :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a Source #
Use the "reader" unfold instead.
flattenArrays = unfoldMany reader
We can try this if there are any fusion issues in the unfold.