streamly-0.8.3: Dataflow programming and declarative concurrency
Copyright(c) 2020 Composewell Technologies
LicenseBSD3-3-Clause
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Internal.Data.Array.Mut.Type

Description

 
Synopsis

Type

data Array a Source #

Constructors

Array 

Fields

  • arrContents# :: MutableArray# RealWorld a

    The internal contents of the array representing the entire array.

  • arrStart :: !Int

    The starting index of this slice.

  • arrLen :: !Int

    The length of this slice.

  • arrTrueLen :: !Int

    This is the true length of the array. Coincidentally, this also represents the first index beyond the maximum acceptable index of the array. This is specific to the array contents itself and not dependent on the slice. This value should not change and is shared across all the slices.

Constructing and Writing

Construction

Uninitialized Arrays

newArray :: forall m a. MonadIO m => Int -> m (Array a) Source #

newArray count allocates an empty array that can hold count items.

Pre-release

From streams

writeNUnsafe :: MonadIO m => 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

writeN :: MonadIO m => Int -> Fold m a (Array a) Source #

writeN n folds a maximum of n elements from the input stream to an Array.

>>> writeN n = Fold.take n (Array.writeNUnsafe n)

Pre-release

From containers

Random writes

putIndex :: MonadIO m => Array a -> Int -> a -> m () Source #

O(1) Write the given element at the given index in the array. Performs in-place mutation of the array.

>>> putIndex arr ix val = Array.modifyIndex arr ix (const (val, ()))

Pre-release

putIndexUnsafe :: forall m a. MonadIO m => Array a -> Int -> a -> m () Source #

Write the given element to the given index of the array. Does not check if the index is out of bounds of the array.

Pre-release

modifyIndexUnsafe :: MonadIO m => Array a -> Int -> (a -> (a, b)) -> m b Source #

Modify a given index of an array using a modifier function without checking the bounds.

Unsafe because it does not check the bounds of the array.

Pre-release

modifyIndex :: MonadIO m => Array a -> Int -> (a -> (a, b)) -> m b Source #

Modify a given index of an array using a modifier function.

Pre-release

Growing and Shrinking

Appending elements

snocWith :: MonadIO m => (Int -> Int) -> Array a -> a -> m (Array a) Source #

snocWith sizer arr elem mutates arr to append elem. The length of the array increases by 1.

If there is no reserved space available in arr it is reallocated to a size in bytes determined by the sizer oldSize function, where oldSize is the original size of the array.

Note that the returned array may be a mutated version of the original array.

Pre-release

snoc :: MonadIO m => Array a -> a -> m (Array a) Source #

The array is mutated to append an additional element to it. If there is no reserved space available in the array then it is reallocated to double the original size.

This is useful to reduce allocations when appending unknown number of elements.

Note that the returned array may be a mutated version of the original array.

>>> snoc = Array.snocWith (* 2)

Performs O(n * log n) copies to grow, but is liberal with memory allocation.

Pre-release

snocUnsafe :: MonadIO m => Array a -> a -> m (Array a) Source #

Really really unsafe, appends the element into the first array, may cause silent data corruption or if you are lucky a segfault if the index is out of bounds.

Internal

Appending streams

Truncation

Eliminating and Reading

To streams

read :: MonadIO m => Unfold m (Array a) a Source #

Unfold an array into a stream.

To containers

toStreamD :: MonadIO m => Array a -> Stream m a Source #

Use the read unfold instead.

toStreamD = D.unfold read

We can try this if the unfold has any performance issues.

toList :: MonadIO m => Array a -> m [a] Source #

Convert an Array into a list.

Pre-release

producer :: MonadIO m => Producer m (Array a) a Source #

Resumable unfold of an array.

Random reads

getIndex :: MonadIO m => Array a -> Int -> m a Source #

O(1) Lookup the element at the given index. Index starts from 0.

getIndexUnsafe :: MonadIO m => Array a -> Int -> m a Source #

Return the element at the specified index without checking the bounds.

Unsafe because it does not check the bounds of the array.

In-place Mutation Algorithms

Folding

Arrays of arrays

Operations dealing with multiple arrays, streams of arrays or multidimensional array representations.

Construct from streams

Eliminate to streams

Construct from arrays

getSliceUnsafe Source #

Arguments

:: Int

from index

-> Int

length of the slice

-> Array a 
-> Array a 

O(1) Slice an array in constant time.

Unsafe: The bounds of the slice are not checked.

Unsafe

Pre-release

getSlice Source #

Arguments

:: Int

from index

-> Int

length of the slice

-> Array a 
-> Array a 

O(1) Slice an array in constant time. Throws an error if the slice extends out of the array bounds.

Pre-release

Appending arrays