Copyright | (c) 2020 Composewell Technologies |
---|---|
License | BSD3-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Pinned and unpinned mutable array for Unboxed
types. 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)
Stream and Fold APIs allow easy, efficient and convenient operations on arrays.
Mutable arrays and file system files are quite similar, they can grow and their content is mutable. Therefore, both have similar APIs as well. We strive to keep the API consistent for both. Ideally, you should be able to replace one with another with little changes to the code.
Synopsis
- data MutArray a = MutArray {
- arrContents :: !MutableByteArray
- arrStart :: !Int
- arrEnd :: !Int
- arrBound :: !Int
- data MutableByteArray
- touch :: MutableByteArray -> IO ()
- pin :: MutArray a -> IO (MutArray a)
- unpin :: MutArray a -> IO (MutArray a)
- nil :: MutArray a
- newPinned :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a)
- newPinnedBytes :: MonadIO m => Int -> m (MutArray a)
- newAlignedPinned :: (MonadIO m, Unbox a) => Int -> Int -> m (MutArray a)
- new :: (MonadIO m, Unbox a) => Int -> m (MutArray a)
- newArrayWith :: forall m a. (MonadIO m, Unbox a) => (Int -> Int -> m MutableByteArray) -> Int -> Int -> m (MutArray a)
- withNewArrayUnsafe :: (MonadIO m, Unbox a) => Int -> (Ptr a -> m ()) -> m (MutArray a)
- data ArrayUnsafe a = ArrayUnsafe !MutableByteArray !Int !Int
- writeNWithUnsafe :: forall m a. (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a)
- writeNWith :: forall m a. (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a)
- writeNUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- writeN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- writeNAligned :: forall m a. (MonadIO m, Unbox a) => Int -> Int -> Fold m a (MutArray a)
- writeWith :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- write :: forall m a. (MonadIO m, Unbox a) => Fold m a (MutArray a)
- writeRevN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- fromListN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a)
- fromList :: (MonadIO m, Unbox a) => [a] -> m (MutArray a)
- fromListRevN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a)
- fromListRev :: (MonadIO m, Unbox a) => [a] -> m (MutArray a)
- fromStreamDN :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> m (MutArray a)
- fromStreamD :: (MonadIO m, Unbox a) => Stream m a -> m (MutArray a)
- putIndex :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> a -> m ()
- putIndexUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> a -> m ()
- putIndices :: forall m a. (MonadIO m, Unbox a) => MutArray a -> Fold m (Int, a) ()
- modifyIndexUnsafe :: forall m a b. (MonadIO m, Unbox a) => Int -> MutArray a -> (a -> (a, b)) -> m b
- modifyIndex :: forall m a b. (MonadIO m, Unbox a) => Int -> MutArray a -> (a -> (a, b)) -> m b
- modifyIndices :: forall m a. (MonadIO m, Unbox a) => MutArray a -> (Int -> a -> a) -> Fold m Int ()
- modify :: forall m a. (MonadIO m, Unbox a) => MutArray a -> (a -> a) -> m ()
- swapIndices :: forall m a. (MonadIO m, Unbox a) => Int -> Int -> MutArray a -> m ()
- unsafeSwapIndices :: forall m a. (MonadIO m, Unbox a) => Int -> Int -> MutArray a -> m ()
- snocWith :: forall m a. (MonadIO m, Unbox a) => (Int -> Int) -> MutArray a -> a -> m (MutArray a)
- snoc :: forall m a. (MonadIO m, Unbox a) => MutArray a -> a -> m (MutArray a)
- snocLinear :: forall m a. (MonadIO m, Unbox a) => MutArray a -> a -> m (MutArray a)
- snocMay :: forall m a. (MonadIO m, Unbox a) => MutArray a -> a -> m (Maybe (MutArray a))
- snocUnsafe :: forall m a. (MonadIO m, Unbox a) => MutArray a -> a -> m (MutArray a)
- writeAppendNUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a)
- writeAppendN :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a)
- writeAppendWith :: forall m a. (MonadIO m, Unbox a) => (Int -> Int) -> m (MutArray a) -> Fold m a (MutArray a)
- writeAppend :: forall m a. (MonadIO m, Unbox a) => m (MutArray a) -> Fold m a (MutArray a)
- reader :: forall m a. (MonadIO m, Unbox a) => Unfold m (MutArray a) a
- readerRevWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> Unfold m (MutArray a) a
- readerRev :: forall m a. (MonadIO m, Unbox a) => Unfold m (MutArray a) a
- toStreamDWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> Stream m a
- toStreamDRevWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> Stream m a
- toStreamKWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> StreamK m a
- toStreamKRevWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> StreamK m a
- toStreamD :: forall m a. (MonadIO m, Unbox a) => MutArray a -> Stream m a
- toStreamDRev :: forall m a. (MonadIO m, Unbox a) => MutArray a -> Stream m a
- toStreamK :: forall m a. (MonadIO m, Unbox a) => MutArray a -> StreamK m a
- toStreamKRev :: forall m a. (MonadIO m, Unbox a) => MutArray a -> StreamK m a
- toList :: forall m a. (MonadIO m, Unbox a) => MutArray a -> m [a]
- producerWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> Producer m (MutArray a) a
- producer :: forall m a. (MonadIO m, Unbox a) => Producer m (MutArray a) a
- getIndex :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m a
- getIndexUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m a
- getIndices :: (MonadIO m, Unbox a) => Stream m Int -> Unfold m (MutArray a) a
- getIndicesD :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m Int -> Unfold m (MutArray a) a
- getIndexRev :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m a
- blockSize :: Int
- arrayChunkBytes :: Int
- allocBytesToElemCount :: Unbox a => a -> Int -> Int
- realloc :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a)
- resize :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a)
- resizeExp :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a)
- rightSize :: forall m a. (MonadIO m, Unbox a) => MutArray a -> m (MutArray a)
- length :: forall a. Unbox a => MutArray a -> Int
- byteLength :: MutArray a -> Int
- byteCapacity :: MutArray a -> Int
- bytesFree :: MutArray a -> Int
- strip :: forall a m. (Unbox a, MonadIO m) => (a -> Bool) -> MutArray a -> m (MutArray a)
- reverse :: forall m a. (MonadIO m, Unbox a) => MutArray a -> m ()
- permute :: MutArray a -> m Bool
- partitionBy :: forall m a. (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> m (MutArray a, MutArray a)
- shuffleBy :: (a -> a -> m Bool) -> MutArray a -> MutArray a -> m ()
- divideBy :: Int -> (MutArray a -> m (MutArray a, MutArray a)) -> MutArray a -> m ()
- mergeBy :: Int -> (MutArray a -> MutArray a -> m ()) -> MutArray a -> m ()
- bubble :: (MonadIO m, Unbox a) => (a -> a -> Ordering) -> MutArray a -> m ()
- cast :: forall a b. Unbox b => MutArray a -> Maybe (MutArray b)
- castUnsafe :: MutArray a -> MutArray b
- asBytes :: MutArray a -> MutArray Word8
- asPtrUnsafe :: MonadIO m => MutArray a -> (Ptr a -> m b) -> m b
- foldl' :: (MonadIO m, Unbox a) => (b -> a -> b) -> b -> MutArray a -> m b
- foldr :: (MonadIO m, Unbox a) => (a -> b -> b) -> b -> MutArray a -> m b
- cmp :: MonadIO m => MutArray a -> MutArray a -> m Ordering
- chunksOf :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a)
- arrayStreamKFromStreamD :: forall m a. (MonadIO m, Unbox a) => Stream m a -> m (StreamK m (MutArray a))
- writeChunks :: (MonadIO m, Unbox a) => Int -> Fold m a (StreamK n (MutArray a))
- flattenArrays :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a
- flattenArraysRev :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a
- fromArrayStreamK :: (Unbox a, MonadIO m) => StreamK m (MutArray a) -> m (MutArray a)
- getSliceUnsafe :: forall a. Unbox a => Int -> Int -> MutArray a -> MutArray a
- getSlice :: forall a. Unbox a => Int -> Int -> MutArray a -> MutArray a
- splitAt :: forall a. Unbox a => Int -> MutArray a -> (MutArray a, MutArray a)
- breakOn :: MonadIO m => Word8 -> MutArray Word8 -> m (MutArray Word8, Maybe (MutArray Word8))
- spliceCopy :: forall m a. MonadIO m => MutArray a -> MutArray a -> m (MutArray a)
- spliceWith :: forall m a. (MonadIO m, Unbox a) => (Int -> Int -> Int) -> MutArray a -> MutArray a -> m (MutArray a)
- splice :: (MonadIO m, Unbox a) => MutArray a -> MutArray a -> m (MutArray a)
- spliceExp :: (MonadIO m, Unbox a) => MutArray a -> MutArray a -> m (MutArray a)
- spliceUnsafe :: MonadIO m => MutArray a -> MutArray a -> m (MutArray a)
- putSliceUnsafe :: MonadIO m => MutArray a -> Int -> MutArray a -> Int -> Int -> m ()
- roundUpToPower2 :: Int -> Int
- memcpy :: Ptr Word8 -> Ptr Word8 -> Int -> IO ()
- memcmp :: Ptr Word8 -> Ptr Word8 -> Int -> IO Bool
- c_memchr :: Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
Type
We can use an Unboxed
constraint in the MutArray type and the constraint
can be automatically provided to a function that pattern matches on the
MutArray type. However, it has huge performance cost, so we do not use it.
Investigate a GHC improvement possiblity.
An unboxed mutable array. An array is created with a given length and capacity. Length is the number of valid elements in the array. Capacity is the maximum number of elements that the array can be expanded to without having to reallocate the memory.
The elements in the array can be mutated in-place without changing the reference (constructor). However, the length of the array cannot be mutated in-place. A new array reference is generated when the length changes. When the length is increased (upto the maximum reserved capacity of the array), the array is not reallocated and the new reference uses the same underlying memory as the old one.
Several routines in this module allow the programmer to control the capacity of the array. The programmer can control the trade-off between memory usage and performance impact due to reallocations when growing or shrinking the array.
MutArray | |
|
data MutableByteArray Source #
touch :: MutableByteArray -> IO () Source #
Constructing and Writing
Construction
Uninitialized Arrays
newPinned :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) Source #
Allocates an empty pinned array that can hold count
items. The memory of
the array is uninitialized and the allocation is aligned as per the Unboxed
instance of the type.
newPinnedBytes :: MonadIO m => Int -> m (MutArray a) Source #
Allocates a pinned empty array that can hold count
items. The memory of
the array is uninitialized and the allocation is aligned as per the
Unboxed
instance of the type.
Pre-release
newAlignedPinned :: (MonadIO m, Unbox a) => Int -> Int -> m (MutArray a) Source #
Like newArrayWith
but using an allocator is a pinned memory allocator and
the alignment is dictated by the Unboxed
instance of the type.
Internal
new :: (MonadIO m, Unbox a) => Int -> m (MutArray a) Source #
Allocates an empty unpinned array that can hold count
items. The memory
of the array is uninitialized.
newArrayWith :: forall m a. (MonadIO m, Unbox a) => (Int -> Int -> m MutableByteArray) -> Int -> Int -> m (MutArray a) Source #
newArrayWith allocator alignment count
allocates a new array of zero
length and with a capacity to hold count
elements, using allocator
size alignment
as the memory allocator function.
Alignment must be greater than or equal to machine word size and a power of 2.
Alignment is ignored if the allocator allocates unpinned memory.
Pre-release
Initialized Arrays
withNewArrayUnsafe :: (MonadIO m, Unbox a) => Int -> (Ptr a -> m ()) -> m (MutArray a) Source #
Allocate a pinned MutArray of the given size and run an IO action passing the array start pointer.
Internal
From streams
data ArrayUnsafe a Source #
writeNWithUnsafe :: forall m a. (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a) Source #
Like writeNUnsafe
but takes a new array allocator alloc size
function
as argument.
>>>
writeNWithUnsafe alloc n = MutArray.writeAppendNUnsafe (alloc n) n
Pre-release
writeNWith :: forall m a. (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a) Source #
writeNWith alloc n
folds a maximum of n
elements into an array
allocated using the alloc
function.
>>>
writeNWith alloc n = Fold.take n (MutArray.writeNWithUnsafe alloc n)
>>>
writeNWith alloc n = MutArray.writeAppendN (alloc n) n
writeNUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray 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.
>>>
writeNUnsafe = MutArray.writeNWithUnsafe MutArray.newPinned
writeN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
writeN n
folds a maximum of n
elements from the input stream to an
MutArray
.
>>>
writeN = MutArray.writeNWith MutArray.newPinned
>>>
writeN n = Fold.take n (MutArray.writeNUnsafe n)
>>>
writeN n = MutArray.writeAppendN n (MutArray.newPinned n)
writeNAligned :: forall m a. (MonadIO m, Unbox a) => Int -> Int -> Fold m a (MutArray a) Source #
writeNAligned align n
folds a maximum of n
elements from the input
stream to a MutArray
aligned to the given size.
>>>
writeNAligned align = MutArray.writeNWith (MutArray.newAlignedPinned align)
>>>
writeNAligned align n = MutArray.writeAppendN n (MutArray.newAlignedPinned align n)
Pre-release
writeWith :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
writeWith 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.
>>>
f n = MutArray.writeAppendWith (* 2) (MutArray.newPinned n)
>>>
writeWith n = Fold.rmapM MutArray.rightSize (f n)
>>>
writeWith n = Fold.rmapM MutArray.fromArrayStreamK (MutArray.writeChunks n)
Pre-release
write :: forall m a. (MonadIO m, Unbox a) => Fold m a (MutArray a) Source #
Fold the whole input to a single array.
Same as writeWith
using an initial array size of arrayChunkBytes
bytes
rounded up to the element size.
Caution! Do not use this on infinite streams.
writeRevN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Like writeN but writes the array in reverse order.
Pre-release
From containers
fromListN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a) Source #
Create a MutArray
from the first N elements of a list. The array is
allocated to size N, if the list terminates before N elements then the
array may hold less than N elements.
fromList :: (MonadIO m, Unbox a) => [a] -> m (MutArray a) Source #
Create a MutArray
from a list. The list must be of finite size.
fromListRevN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a) Source #
Like fromListN but writes the array in reverse order.
Pre-release
fromListRev :: (MonadIO m, Unbox a) => [a] -> m (MutArray a) Source #
Like fromList
but writes the contents of the list in reverse order.
fromStreamDN :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> m (MutArray a) Source #
Use the writeN
fold instead.
>>>
fromStreamDN n = Stream.fold (MutArray.writeN n)
fromStreamD :: (MonadIO m, Unbox a) => Stream m a -> m (MutArray a) Source #
We could take the approach of doubling the memory allocation on each overflow. This would result in more or less the same amount of copying as in the chunking approach. However, if we have to shrink in the end then it may result in an extra copy of the entire data.
>>>
fromStreamD = StreamD.fold MutArray.write
Random writes
putIndex :: forall m a. (MonadIO m, Unbox a) => 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, ()))
>>>
f = MutArray.putIndices
>>>
putIndex ix arr val = Stream.fold (f arr) (Stream.fromPure (ix, val))
putIndexUnsafe :: forall m a. (MonadIO m, Unbox a) => 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 :: forall m a. (MonadIO m, Unbox a) => 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 :: forall m a b. (MonadIO m, Unbox a) => Int -> MutArray a -> (a -> (a, b)) -> m b Source #
Modify a given index of an array using a modifier function.
Pre-release
modifyIndex :: forall m a b. (MonadIO m, Unbox a) => Int -> MutArray a -> (a -> (a, b)) -> m b Source #
Modify a given index of an array using a modifier function.
Pre-release
modifyIndices :: forall m a. (MonadIO m, Unbox a) => MutArray a -> (Int -> a -> a) -> Fold m Int () Source #
Modify the array indices generated by the supplied stream.
Pre-release
modify :: forall m a. (MonadIO m, Unbox a) => MutArray a -> (a -> a) -> m () Source #
Modify each element of an array using the supplied modifier function.
Pre-release
swapIndices :: forall m a. (MonadIO m, Unbox a) => Int -> Int -> MutArray a -> m () Source #
Swap the elements at two indices.
Pre-release
unsafeSwapIndices :: forall m a. (MonadIO m, Unbox a) => Int -> Int -> MutArray a -> m () Source #
Swap the elements at two indices without validating the indices.
Unsafe: This could result in memory corruption if indices are not valid.
Pre-release
Growing and Shrinking
Appending elements
snocWith :: forall m a. (MonadIO m, Unbox a) => (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 oldSizeBytes
function, where
oldSizeBytes
is the original size of the array in bytes.
If the new array size is more than largeObjectThreshold
we automatically
round it up to blockSize
.
Note that the returned array may be a mutated version of the original array.
Pre-release
snoc :: forall m a. (MonadIO m, Unbox a) => 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.
snocLinear :: forall m a. (MonadIO m, Unbox a) => 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 grow
it by arrayChunkBytes
rounded up to blockSize
when the size becomes more
than largeObjectThreshold
.
Note that the returned array may be a mutated version of the original array.
Performs O(n^2) copies to grow but is thrifty on memory.
Pre-release
snocMay :: forall m a. (MonadIO m, Unbox a) => MutArray a -> a -> m (Maybe (MutArray a)) Source #
Like snoc
but does not reallocate when pre-allocated array capacity
becomes full.
Internal
snocUnsafe :: forall m a. (MonadIO m, Unbox a) => 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 first array does not have enough space to append the element.
Internal
Appending streams
writeAppendNUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a) Source #
writeAppendNUnsafe n alloc
appends up to n
input items to the supplied
array.
Unsafe: Do not drive the fold beyond n
elements, it will lead to memory
corruption or segfault.
Any free space left in the array after appending n
elements is lost.
Internal
writeAppendN :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a) Source #
Append n
elements to an existing array. Any free space left in the array
after appending n
elements is lost.
>>>
writeAppendN n initial = Fold.take n (MutArray.writeAppendNUnsafe n initial)
writeAppendWith :: forall m a. (MonadIO m, Unbox a) => (Int -> Int) -> m (MutArray a) -> Fold m a (MutArray a) Source #
writeAppendWith realloc action
mutates the array generated by action
to
append the input stream. If there is no reserved space available in the
array it is reallocated to a size in bytes determined by realloc oldSize
,
where oldSize
is the current size of the array in bytes.
Note that the returned array may be a mutated version of original array.
>>>
writeAppendWith sizer = Fold.foldlM' (MutArray.snocWith sizer)
Pre-release
writeAppend :: forall m a. (MonadIO m, Unbox a) => m (MutArray a) -> Fold m a (MutArray a) Source #
append action
mutates the array generated by action
to append the
input stream. If there is no reserved space available in the array it is
reallocated to double the size.
Note that the returned array may be a mutated version of original array.
>>>
writeAppend = MutArray.writeAppendWith (* 2)
Eliminating and Reading
To streams
reader :: forall m a. (MonadIO m, Unbox a) => Unfold m (MutArray a) a Source #
Unfold an array into a stream.
readerRevWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> Unfold m (MutArray a) a Source #
readerRev :: forall m a. (MonadIO m, Unbox a) => Unfold m (MutArray a) a Source #
Unfold an array into a stream in reverse order.
To containers
toStreamDWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> Stream m a Source #
toStreamDRevWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> Stream m a Source #
toStreamKWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> StreamK m a Source #
toStreamKRevWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> StreamK m a Source #
toStreamD :: forall m a. (MonadIO m, Unbox a) => MutArray a -> Stream m a Source #
Use the reader
unfold instead.
toStreamD = D.unfold reader
We can try this if the unfold has any performance issues.
toStreamDRev :: forall m a. (MonadIO m, Unbox a) => MutArray a -> Stream m a Source #
Use the readerRev
unfold instead.
toStreamDRev = D.unfold readerRev
We can try this if the unfold has any perf issues.
toList :: forall m a. (MonadIO m, Unbox a) => MutArray a -> m [a] Source #
Convert a MutArray
into a list.
producerWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> Producer m (MutArray a) a Source #
producer :: forall m a. (MonadIO m, Unbox a) => Producer m (MutArray a) a Source #
Resumable unfold of an array.
Random reads
getIndex :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m a Source #
O(1) Lookup the element at the given index. Index starts from 0.
getIndexUnsafe :: forall m a. (MonadIO m, Unbox a) => 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.
getIndicesD :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m Int -> Unfold m (MutArray a) a Source #
Given an unfold that generates array indices, read the elements on those indices from the supplied MutArray. An error is thrown if an index is out of bounds.
Pre-release
getIndexRev :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m a Source #
O(1) Lookup the element at the given index from the end of the array. Index starts from 0.
Slightly faster than computing the forward index and using getIndex.
Memory Management
The page or block size used by the GHC allocator. Allocator allocates at least a block and then allocates smaller allocations from within a block.
arrayChunkBytes :: Int Source #
The default chunk size by which the array creation routines increase the size of the array when the array is grown linearly.
allocBytesToElemCount :: Unbox a => a -> Int -> Int Source #
Given an Unboxed
type (unused first arg) and real allocation size
(including overhead), return how many elements of that type will completely
fit in it, returns at least 1.
realloc :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
realloc newCapacity array
reallocates the array to the specified
capacity in bytes.
If the new size is less than the original array the array gets truncated.
If the new size is not a multiple of array element size then it is rounded
down to multiples of array size. If the new size is more than
largeObjectThreshold
then it is rounded up to the block size (4K).
resize :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
resize newCapacity array
changes the total capacity of the array so that
it is enough to hold the specified number of elements. Nothing is done if
the specified capacity is less than the length of the array.
If the capacity is more than largeObjectThreshold
then it is rounded up to
the block size (4K).
Pre-release
resizeExp :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
Like resize
but if the byte capacity is more than largeObjectThreshold
then it is rounded up to the closest power of 2.
Pre-release
rightSize :: forall m a. (MonadIO m, Unbox a) => MutArray a -> m (MutArray a) Source #
Resize the allocated memory to drop any reserved free space at the end of the array and reallocate it to reduce wastage.
Up to 25% wastage is allowed to avoid reallocations. If the capacity is
more than largeObjectThreshold
then free space up to the blockSize
is
retained.
Pre-release
Size
length :: forall a. Unbox a => MutArray a -> Int Source #
O(1) Get the length of the array i.e. the number of elements in the array.
Note that byteLength
is less expensive than this operation, as length
involves a costly division operation.
byteLength :: MutArray a -> Int Source #
O(1) Get the byte length of the array.
byteCapacity :: MutArray a -> Int Source #
Get the total capacity of an array. An array may have space reserved beyond the current used length of the array.
Pre-release
bytesFree :: MutArray a -> Int Source #
The remaining capacity in the array for appending more elements without reallocation.
Pre-release
In-place Mutation Algorithms
strip :: forall a m. (Unbox a, MonadIO m) => (a -> Bool) -> MutArray a -> m (MutArray a) Source #
Strip elements which match with predicate from both ends.
Pre-release
reverse :: forall m a. (MonadIO m, Unbox a) => MutArray a -> m () Source #
You may not need to reverse an array because you can consume it in reverse
using readerRev
. To reverse large arrays you can read in reverse and write
to another array. However, in-place reverse can be useful to take adavantage
of cache locality and when you do not want to allocate additional memory.
permute :: MutArray a -> m Bool Source #
Generate the next permutation of the sequence, returns False if this is the last permutation.
Unimplemented
partitionBy :: forall m a. (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> m (MutArray a, MutArray a) Source #
shuffleBy :: (a -> a -> m Bool) -> MutArray a -> MutArray a -> m () Source #
Shuffle corresponding elements from two arrays using a shuffle function.
If the shuffle function returns False
then do nothing otherwise swap the
elements. This can be used in a bottom up fold to shuffle or reorder the
elements.
Unimplemented
divideBy :: Int -> (MutArray a -> m (MutArray a, MutArray a)) -> MutArray a -> m () Source #
divideBy level partition array
performs a top down hierarchical
recursive partitioning fold of items in the container using the given
function as the partition function. Level indicates the level in the tree
where the fold would stop.
This performs a quick sort if the partition function is 'partitionBy (< pivot)'.
Unimplemented
mergeBy :: Int -> (MutArray a -> MutArray a -> m ()) -> MutArray a -> m () Source #
mergeBy level merge array
performs a pairwise bottom up fold recursively
merging the pairs using the supplied merge function. Level indicates the
level in the tree where the fold would stop.
This performs a random shuffle if the merge function is random. If we stop at level 0 and repeatedly apply the function then we can do a bubble sort.
Unimplemented
bubble :: (MonadIO m, Unbox a) => (a -> a -> Ordering) -> MutArray a -> m () Source #
Given an array sorted in ascending order except the last element being out of order, use bubble sort to place the last element at the right place such that the array remains sorted in ascending order.
Pre-release
Casting
cast :: forall a b. Unbox b => MutArray a -> Maybe (MutArray b) Source #
Cast an array having elements of type a
into an array having elements of
type b
. The length of the array should be a multiple of the size of the
target element otherwise Nothing
is returned.
castUnsafe :: MutArray a -> MutArray b Source #
Cast an array having elements of type a
into an array having elements of
type b
. The array size must be a multiple of the size of type b
otherwise accessing the last element of the array may result into a crash or
a random value.
Pre-release
asPtrUnsafe :: MonadIO m => MutArray a -> (Ptr a -> m b) -> m b Source #
Use an MutArray a
as Ptr a
. This is useful when we want to pass an array
as a pointer to some operating system call or to a "safe" FFI call.
If the array is not pinned it is copied to pinned memory before passing it to the monadic action.
Performance Notes: Forces a copy if the array is not pinned. It is advised that the programmer keeps this in mind and creates a pinned array opportunistically before this operation occurs, to avoid the cost of a copy if possible.
Unsafe
Pre-release
Folding
foldl' :: (MonadIO m, Unbox a) => (b -> a -> b) -> b -> MutArray a -> m b Source #
Strict left fold of an array.
foldr :: (MonadIO m, Unbox a) => (a -> b -> b) -> b -> MutArray a -> m b Source #
Right fold of an array.
cmp :: MonadIO m => 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, Unbox a) => 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 = StreamD.foldMany (MutArray.writeN n)
Pre-release
arrayStreamKFromStreamD :: forall m a. (MonadIO m, Unbox a) => Stream m a -> m (StreamK m (MutArray a)) Source #
Buffer the stream into arrays in memory.
writeChunks :: (MonadIO m, Unbox a) => Int -> Fold m a (StreamK n (MutArray a)) Source #
Buffer a stream into a stream of arrays.
>>>
writeChunks n = Fold.many (MutArray.writeN n) Fold.toStreamK
Breaking an array into an array stream can be useful to consume a large array sequentially such that memory of the array is released incrementatlly.
See also: arrayStreamKFromStreamD
.
Unimplemented
Eliminate to streams
flattenArrays :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a Source #
Use the "reader" unfold instead.
flattenArrays = unfoldMany reader
We can try this if there are any fusion issues in the unfold.
flattenArraysRev :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a Source #
Use the "readerRev" unfold instead.
flattenArrays = unfoldMany readerRev
We can try this if there are any fusion issues in the unfold.
fromArrayStreamK :: (Unbox a, MonadIO m) => StreamK m (MutArray a) -> m (MutArray a) Source #
Convert an array stream to an array. Note that this requires peak memory that is double the size of the array stream.
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
splitAt :: forall a. Unbox a => Int -> MutArray a -> (MutArray a, MutArray a) Source #
Create two slices of an array without copying the original array. The
specified index i
is the first index of the second slice.
breakOn :: MonadIO m => Word8 -> MutArray Word8 -> m (MutArray Word8, Maybe (MutArray Word8)) Source #
Drops the separator byte
Appending arrays
spliceCopy :: forall m a. MonadIO m => MutArray a -> MutArray a -> m (MutArray a) Source #
Copy two arrays into a newly allocated array.
spliceWith :: forall m a. (MonadIO m, Unbox a) => (Int -> Int -> Int) -> MutArray a -> MutArray a -> m (MutArray a) Source #
spliceWith sizer dst src
mutates dst
to append src
. If there is no
reserved space available in dst
it is reallocated to a size determined by
the sizer dstBytes srcBytes
function, where dstBytes
is the size of the
first array and srcBytes
is the size of the second array, in bytes.
Note that the returned array may be a mutated version of first array.
Pre-release
splice :: (MonadIO m, Unbox a) => MutArray a -> MutArray a -> m (MutArray a) Source #
The first array is mutated to append the second array. If there is no reserved space available in the first array a new allocation of exact required size is done.
Note that the returned array may be a mutated version of first array.
>>>
splice = MutArray.spliceWith (+)
Pre-release
spliceExp :: (MonadIO m, Unbox a) => MutArray a -> MutArray a -> m (MutArray a) Source #
Like append
but the growth of the array is exponential. Whenever a new
allocation is required the previous array size is at least doubled.
This is useful to reduce allocations when folding many arrays together.
Note that the returned array may be a mutated version of first array.
>>>
spliceExp = MutArray.spliceWith (\l1 l2 -> max (l1 * 2) (l1 + l2))
Pre-release
spliceUnsafe :: MonadIO m => MutArray a -> MutArray a -> m (MutArray a) Source #
Really really unsafe, appends the second array into the first array. If the first array does not have enough space it may cause silent data corruption or if you are lucky a segfault.
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.
Utilities
roundUpToPower2 :: Int -> Int Source #