Copyright | (c) 2020 Composewell Technologies |
---|---|
License | BSD-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Unboxed pinned mutable array type for Storable
types with an option to use
foreign (non-GHC) memory allocators. Fulfils the following goals:
- Random access (array)
- Efficient storage (unboxed)
- Performance (unboxed access)
- Performance - in-place operations (mutable)
- Performance - GC (pinned, mutable)
- interfacing with OS (pinned)
- Fragmentation control (foreign allocators)
Stream and Fold APIs allow easy, efficient and convenient operations on arrays.
Synopsis
- module Streamly.Internal.Data.Array.Foreign.Mut.Type
- splitOn :: (MonadIO m, Storable a) => (a -> Bool) -> Array a -> SerialT m (Array a)
- genSlicesFromLen :: forall m a. (Monad m, Storable a) => Int -> Int -> Unfold m (Array a) (Int, Int)
- getSlicesFromLen :: forall m a. (Monad m, Storable a) => Int -> Int -> Unfold m (Array a) (Array a)
- fromStream :: (MonadIO m, Storable a) => SerialT m a -> m (Array a)
Documentation
splitOn :: (MonadIO m, Storable a) => (a -> Bool) -> Array a -> SerialT m (Array a) Source #
Split the array into a stream of slices using a predicate. The element matching the predicate is dropped.
Pre-release
:: forall m a. (Monad m, Storable a) | |
=> Int | from index |
-> Int | length of the slice |
-> Unfold m (Array a) (Int, Int) |
Generate a stream of array slice descriptors ((index, len)) of specified length from an array, starting from the supplied array index. The last slice may be shorter than the requested length depending on the array length.
Pre-release
:: forall m a. (Monad m, Storable a) | |
=> Int | from index |
-> Int | length of the slice |
-> Unfold m (Array a) (Array a) |
Generate a stream of slices of specified length from an array, starting from the supplied array index. The last slice may be shorter than the requested length depending on the array length.
Pre-release
fromStream :: (MonadIO m, Storable a) => SerialT m a -> m (Array a) Source #
Create an Array
from a stream. This is useful when we want to create a
single array from a stream of unknown size. writeN
is at least twice
as efficient when the size is already known.
Note that if the input stream is too large memory allocation for the array
may fail. When the stream size is not known, arraysOf
followed by
processing of indvidual arrays in the resulting stream should be preferred.
Pre-release