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

Streamly.Internal.Data.Array.Prim.Pinned.Mut.Type

Description

 
Synopsis

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.

unsafeWriteIndex Source #

Arguments

:: (MonadIO m, Prim a) 
=> Array a

array

-> Int

index

-> a

element

-> m () 

spliceTwo :: (MonadIO m, Prim a) => Array a -> Array a -> m (Array a) Source #

unsafeCopy Source #

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.

fromListM :: (MonadIO m, Prim a) => [a] -> m (Array a) Source #

fromListNM :: (MonadIO m, Prim a) => Int -> [a] -> m (Array a) Source #

fromStreamDN :: (MonadIO m, Prim a) => Int -> Stream m a -> m (Array a) Source #

fromStreamD :: (MonadIO m, Prim a) => Stream m a -> m (Array a) Source #

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

unsafeReadIndex :: (MonadIO m, Prim a) => Array a -> Int -> m a Source #

length :: forall m a. (MonadIO m, Prim a) => Array a -> m Int Source #

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

writeNAligned :: (MonadIO m, Prim a) => Int -> Int -> Fold m a (Array a) Source #

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

resizeArray Source #

Arguments

:: (MonadIO m, Prim a) 
=> Array a 
-> Int

new size

-> m (Array a) 

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).

shrinkArray Source #

Arguments

:: forall m a. (MonadIO m, Prim a) 
=> Array a 
-> Int

new size

-> m () 

withArrayAsPtr :: Array a -> (Ptr a -> IO b) -> IO b Source #