| Copyright | (c) 2020 Composewell Technologies | 
|---|---|
| License | BSD-3-Clause | 
| Maintainer | streamly@composewell.com | 
| Stability | experimental | 
| Portability | GHC | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Streamly.Internal.Data.Array.Prim.Pinned.Mut.Type
Description
Synopsis
- data Array a = Array (MutableByteArray# RealWorld)
- newArray :: forall m a. (MonadIO m, Prim a) => Int -> m (Array a)
- newAlignedArray :: forall m a. (MonadIO m, Prim a) => Int -> Int -> m (Array a)
- unsafeWriteIndex :: (MonadIO m, Prim a) => Array a -> Int -> a -> m ()
- spliceTwo :: (MonadIO m, Prim a) => Array a -> Array a -> m (Array a)
- unsafeCopy :: forall m a. (MonadIO m, Prim a) => Array a -> Int -> Array a -> Int -> Int -> m ()
- fromListM :: (MonadIO m, Prim a) => [a] -> m (Array a)
- fromListNM :: (MonadIO m, Prim a) => Int -> [a] -> m (Array a)
- fromStreamDN :: (MonadIO m, Prim a) => Int -> Stream m a -> m (Array a)
- fromStreamD :: (MonadIO m, Prim a) => Stream m a -> m (Array a)
- fromStreamDArraysOf :: (MonadIO m, Prim a) => Int -> Stream m a -> Stream m (Array a)
- packArraysChunksOf :: (MonadIO m, Prim a) => Int -> Stream m (Array a) -> Stream m (Array a)
- lpackArraysChunksOf :: (MonadIO m, Prim a) => Int -> Fold m (Array a) () -> Fold m (Array a) ()
- unsafeReadIndex :: (MonadIO m, Prim a) => Array a -> Int -> m a
- length :: forall m a. (MonadIO m, Prim a) => Array a -> m Int
- byteLength :: MonadIO m => Array a -> m Int
- writeN :: (MonadIO m, Prim a) => Int -> Fold m a (Array a)
- data ArrayUnsafe a = ArrayUnsafe !(Array a) !Int
- writeNUnsafe :: (MonadIO m, Prim a) => Int -> Fold m a (Array a)
- writeNAligned :: (MonadIO m, Prim a) => Int -> Int -> Fold m a (Array a)
- write :: (MonadIO m, Prim a) => Fold m a (Array a)
- resizeArray :: (MonadIO m, Prim a) => Array a -> Int -> m (Array a)
- shrinkArray :: forall m a. (MonadIO m, Prim a) => Array a -> Int -> m ()
- touchArray :: Array a -> IO ()
- withArrayAsPtr :: Array a -> (Ptr a -> IO b) -> IO b
Documentation
Construction
newArray :: forall m a. (MonadIO m, Prim a) => Int -> m (Array a) Source #
Allocate an array that is pinned and can hold count items.  The memory of
 the array is uninitialized.
Note that this is internal routine, the reference to this array cannot be given out until the array has been written to and frozen.
newAlignedArray :: forall m a. (MonadIO m, Prim a) => Int -> Int -> m (Array a) Source #
Allocate a new array aligned to the specified alignment and using pinned memory.
Arguments
| :: forall m a. (MonadIO m, Prim a) | |
| => Array a | destination array | 
| -> Int | offset into destination array | 
| -> Array a | source array | 
| -> Int | offset into source array | 
| -> Int | number of elements to copy | 
| -> m () | 
Copy a range of the first array to the specified region in the second array. Both arrays must fully contain the specified ranges, but this is not checked. The regions are allowed to overlap, although this is only possible when the same array is provided as both the source and the destination.
Streams of arrays
fromStreamDArraysOf :: (MonadIO m, Prim a) => Int -> Stream m a -> Stream m (Array a) Source #
fromStreamArraysOf n stream groups the input stream into a stream of
 arrays of size n.
packArraysChunksOf :: (MonadIO m, Prim a) => Int -> Stream m (Array a) -> Stream m (Array a) Source #
Coalesce adjacent arrays in incoming stream to form bigger arrays of a maximum specified size in bytes. 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.
Pre-release
lpackArraysChunksOf :: (MonadIO m, Prim a) => Int -> Fold m (Array a) () -> Fold m (Array a) () Source #
Elimination
writeN :: (MonadIO m, Prim a) => Int -> Fold m a (Array a) Source #
writeN n folds a maximum of n elements from the input stream to an
 Array.
Pre-release
data ArrayUnsafe a Source #
Constructors
| ArrayUnsafe !(Array a) !Int | 
writeNUnsafe :: (MonadIO m, Prim a) => Int -> Fold m a (Array a) Source #
Like writeN but does not check the array bounds when writing. The fold
 driver must not call the step function more than n times otherwise it will
 corrupt the memory and crash. This function exists mainly because any
 conditional in the step function blocks fusion causing 10x performance
 slowdown.
Pre-release
write :: (MonadIO m, Prim a) => Fold m a (Array a) Source #
Fold the whole input to a single array.
Caution! Do not use this on infinite streams.
Pre-release
Utilities
Resize (pinned) mutable byte array to new specified size (in elem count). The returned array is either the original array resized in-place or, if not possible, a newly allocated (pinned) array (with the original content copied over).
touchArray :: Array a -> IO () Source #