Copyright | (c) 2020 Composewell Technologies |
---|---|
License | BSD3-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data MutArray a = MutArray {
- arrContents# :: MutableArray# RealWorld a
- arrStart :: !Int
- arrLen :: !Int
- arrTrueLen :: !Int
- nil :: MonadIO m => m (MutArray a)
- emptyOf :: MonadIO m => Int -> m (MutArray a)
- unsafeCreateOf :: MonadIO m => Int -> Fold m a (MutArray a)
- createOf :: MonadIO m => Int -> Fold m a (MutArray a)
- createWith :: MonadIO m => Int -> Fold m a (MutArray a)
- create :: MonadIO m => Fold m a (MutArray a)
- fromStreamN :: MonadIO m => Int -> Stream m a -> m (MutArray a)
- fromStream :: MonadIO m => Stream m a -> m (MutArray a)
- fromPureStream :: MonadIO m => Stream Identity a -> m (MutArray a)
- fromListN :: MonadIO m => Int -> [a] -> m (MutArray a)
- fromList :: MonadIO m => [a] -> m (MutArray a)
- putIndex :: MonadIO m => Int -> MutArray a -> a -> m ()
- putIndexUnsafe :: forall m a. MonadIO m => Int -> MutArray a -> a -> m ()
- putIndices :: MonadIO m => MutArray a -> Fold m (Int, a) ()
- modifyIndexUnsafe :: MonadIO m => Int -> MutArray a -> (a -> (a, b)) -> m b
- modifyIndex :: MonadIO m => Int -> MutArray a -> (a -> (a, b)) -> m b
- realloc :: MonadIO m => Int -> MutArray a -> m (MutArray a)
- uninit :: MonadIO m => MutArray a -> Int -> m (MutArray a)
- snocWith :: MonadIO m => (Int -> Int) -> MutArray a -> a -> m (MutArray a)
- snoc :: MonadIO m => MutArray a -> a -> m (MutArray a)
- snocUnsafe :: MonadIO m => MutArray a -> a -> m (MutArray a)
- reader :: MonadIO m => Unfold m (MutArray a) a
- producerWith :: Monad m => (forall b. IO b -> m b) -> Producer m (MutArray a) a
- producer :: MonadIO m => Producer m (MutArray a) a
- read :: MonadIO m => MutArray a -> Stream m a
- readRev :: MonadIO m => MutArray a -> Stream m a
- toStreamK :: MonadIO m => MutArray a -> StreamK m a
- toList :: MonadIO m => MutArray a -> m [a]
- getIndex :: MonadIO m => Int -> MutArray a -> m (Maybe a)
- getIndexUnsafe :: MonadIO m => Int -> MutArray a -> m a
- getIndexUnsafeWith :: MonadIO m => MutableArray# RealWorld a -> Int -> m a
- length :: MutArray a -> Int
- strip :: MonadIO m => (a -> Bool) -> MutArray a -> m (MutArray a)
- cmp :: (MonadIO m, Ord a) => MutArray a -> MutArray a -> m Ordering
- eq :: (MonadIO m, Eq a) => MutArray a -> MutArray a -> m Bool
- chunksOf :: forall m a. MonadIO m => Int -> Stream m a -> Stream m (MutArray a)
- getSliceUnsafe :: Int -> Int -> MutArray a -> MutArray a
- getSlice :: Int -> Int -> MutArray a -> MutArray a
- putSliceUnsafe :: MonadIO m => MutArray a -> Int -> MutArray a -> Int -> Int -> m ()
- clone :: MonadIO m => MutArray a -> m (MutArray a)
- new :: MonadIO m => Int -> m (MutArray a)
- writeNUnsafe :: MonadIO m => Int -> Fold m a (MutArray a)
- writeN :: MonadIO m => Int -> Fold m a (MutArray a)
- writeWith :: MonadIO m => Int -> Fold m a (MutArray a)
- write :: MonadIO m => Fold m a (MutArray a)
Type
MutArray | |
|
Constructing and Writing
Construction
Uninitialized Arrays
emptyOf :: MonadIO m => Int -> m (MutArray a) Source #
emptyOf count
allocates a zero length array that can be extended to hold
up to count
items without reallocating.
Pre-release
From streams
unsafeCreateOf :: MonadIO m => Int -> Fold m a (MutArray a) Source #
Like createOf
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
createOf :: MonadIO m => Int -> Fold m a (MutArray a) Source #
createOf n
folds a maximum of n
elements from the input stream to an
Array
.
>>>
createOf n = Fold.take n (MutArray.unsafeCreateOf n)
Pre-release
createWith :: MonadIO m => Int -> Fold m a (MutArray a) Source #
createWith minCount
folds the whole input to a single array. The array
starts at a size big enough to hold minCount elements, the size is doubled
every time the array needs to be grown.
Caution! Do not use this on infinite streams.
Pre-release
create :: MonadIO m => Fold m a (MutArray a) Source #
Fold the whole input to a single array.
Same as createWith
using an initial array size of arrayChunkSize
bytes
rounded up to the element size.
Caution! Do not use this on infinite streams.
fromStreamN :: MonadIO m => Int -> Stream m a -> m (MutArray a) Source #
Create a MutArray
from the first n
elements of a stream. The
array is allocated to size n
, if the stream terminates before n
elements then the array may hold less than n
elements.
From containers
Random writes
putIndex :: MonadIO m => Int -> MutArray a -> a -> m () Source #
O(1) Write the given element at the given index in the array. Performs in-place mutation of the array.
>>>
putIndex ix arr val = MutArray.modifyIndex ix arr (const (val, ()))
Pre-release
putIndexUnsafe :: forall m a. MonadIO m => Int -> MutArray a -> 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
putIndices :: MonadIO m => MutArray a -> Fold m (Int, a) () Source #
Write an input stream of (index, value) pairs to an array. Throws an error if any index is out of bounds.
Pre-release
modifyIndexUnsafe :: MonadIO m => Int -> MutArray a -> (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 => Int -> MutArray a -> (a -> (a, b)) -> m b Source #
Modify a given index of an array using a modifier function.
Pre-release
Growing and Shrinking
Reallocation
realloc :: MonadIO m => Int -> MutArray a -> m (MutArray a) Source #
Reallocates the array according to the new size. This is a safe function that always creates a new array and copies the old array into the new one. If the reallocated size is less than the original array it results in a truncated version of the original array.
uninit :: MonadIO m => MutArray a -> Int -> m (MutArray a) Source #
Make the uninitialized memory in the array available for use extending it by the supplied length beyond the current length of the array. The array may be reallocated.
Appending elements
snocWith :: MonadIO m => (Int -> Int) -> MutArray a -> a -> m (MutArray 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 => MutArray a -> a -> m (MutArray 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 = MutArray.snocWith (* 2)
Performs O(n * log n) copies to grow, but is liberal with memory allocation.
Pre-release
snocUnsafe :: MonadIO m => MutArray a -> a -> m (MutArray 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
Unfolds
producerWith :: Monad m => (forall b. IO b -> m b) -> Producer m (MutArray a) a Source #
Resumable unfold of an array.
To containers
read :: MonadIO m => MutArray a -> Stream m a Source #
Generates a stream from the elements of a MutArray
.
>>>
read = Stream.unfold MutArray.reader
Random reads
getIndex :: MonadIO m => Int -> MutArray a -> m (Maybe a) Source #
O(1) Lookup the element at the given index. Index starts from 0.
getIndexUnsafe :: MonadIO m => Int -> MutArray a -> 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.
getIndexUnsafeWith :: MonadIO m => MutableArray# RealWorld a -> Int -> m a Source #
Return the element at the specified index without checking the bounds from
a MutableArray# RealWorld
.
Unsafe because it does not check the bounds of the array.
Size
In-place Mutation Algorithms
Folding
cmp :: (MonadIO m, Ord a) => MutArray a -> MutArray a -> m Ordering Source #
Compare the length of the arrays. If the length is equal, compare the lexicographical ordering of two underlying byte arrays otherwise return the result of length comparison.
Pre-release
Arrays of arrays
Operations dealing with multiple arrays, streams of arrays or multidimensional array representations.
Construct from streams
chunksOf :: forall m a. MonadIO m => Int -> Stream m a -> Stream m (MutArray a) Source #
chunksOf n stream
groups the input stream into a stream of
arrays of size n.
chunksOf n = foldMany (MutArray.writeN n)
Pre-release
Eliminate to streams
Construct from arrays
O(1) Slice an array in constant time.
Unsafe: The bounds of the slice are not checked.
Unsafe
Pre-release
O(1) Slice an array in constant time. Throws an error if the slice extends out of the array bounds.
Pre-release
Appending arrays
putSliceUnsafe :: MonadIO m => MutArray a -> Int -> MutArray a -> Int -> Int -> m () Source #
Put a sub range of a source array into a subrange of a destination array. This is not safe as it does not check the bounds.
Deprecated
writeNUnsafe :: MonadIO m => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use unsafeCreateOf instead.