| 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.MutArray
Description
Synopsis
- data MutArray a = MutArray {- arrContents :: !MutByteArray
- arrStart :: !Int
- arrEnd :: !Int
- arrBound :: !Int
 
- pin :: MutArray a -> IO (MutArray a)
- unpin :: MutArray a -> IO (MutArray a)
- isPinned :: MutArray a -> Bool
- cast :: forall a b. Unbox b => MutArray a -> Maybe (MutArray b)
- castUnsafe :: MutArray a -> MutArray b
- asBytes :: MutArray a -> MutArray Word8
- unsafePinnedAsPtr :: MonadIO m => MutArray a -> (Ptr a -> m b) -> m b
- unsafeAsPtr :: MonadIO m => MutArray a -> (Ptr a -> m b) -> m b
- empty :: MutArray a
- emptyOf :: (MonadIO m, Unbox a) => Int -> m (MutArray a)
- newArrayWith :: forall m a. (MonadIO m, Unbox a) => (Int -> Int -> m MutByteArray) -> Int -> Int -> m (MutArray a)
- pinnedEmptyOf :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a)
- pinnedNewAligned :: (MonadIO m, Unbox a) => Int -> Int -> m (MutArray a)
- clone :: MonadIO m => MutArray a -> m (MutArray a)
- pinnedClone :: MonadIO 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))
- data ArrayUnsafe a = ArrayUnsafe !MutByteArray !Int !Int
- unsafeCreateOfWith :: forall m a. (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a)
- unsafeCreateOf :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- unsafePinnedCreateOf :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- pinnedCreateOf :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- createOfWith :: forall m a. (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a)
- createOf :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- revCreateOf :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- pinnedCreate :: forall m a. (MonadIO m, Unbox a) => Fold m a (MutArray a)
- createWith :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- create :: forall m a. (MonadIO m, Unbox a) => Fold m a (MutArray a)
- fromListN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a)
- pinnedFromListN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a)
- fromList :: (MonadIO m, Unbox a) => [a] -> m (MutArray a)
- pinnedFromList :: (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)
- fromStreamN :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> m (MutArray a)
- fromStream :: (MonadIO m, Unbox a) => Stream m a -> m (MutArray a)
- fromPureStreamN :: (MonadIO m, Unbox a) => Int -> Stream Identity a -> m (MutArray a)
- fromPureStream :: (MonadIO m, Unbox a) => Stream Identity a -> m (MutArray a)
- fromByteStr# :: MonadIO m => Addr# -> m (MutArray Word8)
- fromPtrN :: MonadIO m => Int -> Ptr Word8 -> m (MutArray Word8)
- fromChunksK :: (Unbox a, MonadIO m) => StreamK m (MutArray a) -> m (MutArray a)
- fromChunksRealloced :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray 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 ()
- getIndex :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (Maybe a)
- getIndexUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m a
- getIndexRev :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m a
- indexReader :: (MonadIO m, Unbox a) => Stream m Int -> Unfold m (MutArray a) a
- indexReaderWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m Int -> Unfold m (MutArray a) a
- read :: forall m a. (MonadIO m, Unbox a) => MutArray a -> Stream m a
- readRev :: forall m a. (MonadIO m, Unbox a) => MutArray a -> Stream m a
- toStreamWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> Stream m a
- toStreamRevWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> Stream m a
- toStreamK :: forall m a. (MonadIO m, Unbox a) => MutArray a -> StreamK m a
- toStreamKWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> StreamK m a
- toStreamKRev :: forall m a. (MonadIO m, Unbox a) => MutArray a -> StreamK m a
- toStreamKRevWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> 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
- 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
- length :: forall a. Unbox a => MutArray a -> Int
- byteLength :: MutArray a -> Int
- byteCapacity :: MutArray a -> Int
- bytesFree :: MutArray a -> Int
- blockSize :: Int
- arrayChunkBytes :: Int
- allocBytesToElemCount :: Unbox a => a -> Int -> Int
- realloc :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a)
- grow :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a)
- growExp :: 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)
- 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
- byteCmp :: MonadIO m => MutArray a -> MutArray a -> m Ordering
- byteEq :: MonadIO m => MutArray a -> MutArray a -> m Bool
- 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 ()
- 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)
- unsafeAppendN :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a)
- appendN :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a)
- appendWith :: forall m a. (MonadIO m, Unbox a) => (Int -> Int) -> m (MutArray a) -> Fold m a (MutArray a)
- append :: forall m a. (MonadIO m, Unbox a) => m (MutArray a) -> Fold m a (MutArray a)
- 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)
- pokeAppend :: forall m a. (MonadIO m, Unbox a) => MutArray Word8 -> a -> m (MutArray Word8)
- pokeAppendMay :: forall m a. (MonadIO m, Unbox a) => MutArray Word8 -> a -> m (Maybe (MutArray Word8))
- pokeSkipUnsafe :: Int -> MutArray Word8 -> MutArray Word8
- peekUncons :: forall m a. (MonadIO m, Unbox a) => MutArray Word8 -> m (Maybe a, MutArray Word8)
- peekUnconsUnsafe :: forall m a. (MonadIO m, Unbox a) => MutArray Word8 -> m (a, MutArray Word8)
- peekSkipUnsafe :: Int -> MutArray Word8 -> MutArray Word8
- chunksOf :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a)
- pinnedChunksOf :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a)
- buildChunks :: (MonadIO m, Unbox a) => Int -> Fold m a (StreamK n (MutArray a))
- splitOn :: (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> Stream m (MutArray a)
- concatWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m (MutArray a) -> Stream m a
- concatRevWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m (MutArray a) -> Stream m a
- concat :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a
- concatRev :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a
- data SpliceState s arr- = SpliceInitial s
- | SpliceBuffering s arr
- | SpliceYielding arr (SpliceState s arr)
- | SpliceFinish
 
- pCompactLE :: forall m a. (MonadIO m, Unbox a) => Int -> Parser (MutArray a) m (MutArray a)
- pPinnedCompactLE :: forall m a. (MonadIO m, Unbox a) => Int -> Parser (MutArray a) m (MutArray a)
- compactLeAs :: forall m a. (MonadIO m, Unbox a) => PinnedState -> Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- fCompactGE :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) (MutArray a)
- fPinnedCompactGE :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) (MutArray a)
- lCompactGE :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) () -> Fold m (MutArray a) ()
- lPinnedCompactGE :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) () -> Fold m (MutArray a) ()
- compactGE :: (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- compactEQ :: Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- 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)
- asPtrUnsafe :: MonadIO m => MutArray a -> (Ptr a -> m b) -> m b
- 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)
- 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)
- cmp :: MonadIO m => MutArray a -> MutArray a -> m Ordering
- getIndices :: (MonadIO m, Unbox a) => Stream m Int -> Unfold m (MutArray a) a
- getIndicesWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m Int -> Unfold m (MutArray a) 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)
- nil :: MutArray a
- new :: (MonadIO m, Unbox a) => Int -> m (MutArray a)
- pinnedNew :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a)
- pinnedNewBytes :: MonadIO m => Int -> 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)
- 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)
- pinnedWriteNUnsafe :: 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)
- pinnedWriteN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- pinnedWriteNAligned :: 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)
- pinnedWrite :: 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)
- sliceIndexerFromLen :: forall m a. (Monad m, Unbox a) => Int -> Int -> Unfold m (MutArray a) (Int, Int)
- slicerFromLen :: forall m a. (Monad m, Unbox a) => Int -> Int -> Unfold m (MutArray a) (MutArray a)
- compactLE :: (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- pinnedCompactLE :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- compactOnByte :: MonadIO m => Word8 -> Stream m (MutArray Word8) -> Stream m (MutArray Word8)
- compactOnByteSuffix :: MonadIO m => Word8 -> Stream m (MutArray Word8) -> Stream m (MutArray Word8)
- data IORef a
- newIORef :: forall a. Unbox a => a -> IO (IORef a)
- writeIORef :: Unbox a => IORef a -> a -> IO ()
- modifyIORef' :: Unbox a => IORef a -> (a -> a) -> IO ()
- readIORef :: Unbox a => IORef a -> IO a
- pollIntIORef :: (MonadIO m, Unbox a) => IORef a -> Stream m a
- genSlicesFromLen :: forall m a. (Monad m, Unbox a) => Int -> Int -> Unfold m (MutArray a) (Int, Int)
- getSlicesFromLen :: forall m a. (Monad m, Unbox a) => Int -> Int -> Unfold m (MutArray a) (MutArray a)
MutArray.Type module
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.
Constructors
| MutArray | |
| Fields 
 | |
Conversion
Pinned and Unpinned
pin :: MutArray a -> IO (MutArray a) Source #
Return a copy of the array in pinned memory if unpinned, else return the original array.
unpin :: MutArray a -> IO (MutArray a) Source #
Return a copy of the array in unpinned memory if pinned, else return the original array.
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
unsafePinnedAsPtr :: MonadIO m => MutArray a -> (Ptr a -> m b) -> m b Source #
Use a 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 because of direct pointer operations. The user must ensure that they are writing within the legal bounds of the array.
Pre-release
Construction
New
New arrays are always empty arrays with some reserve capacity to extend the length without reallocating.
emptyOf :: (MonadIO m, Unbox a) => Int -> m (MutArray a) Source #
Allocates an unpinned array of zero length but growable to the specified capacity without reallocation.
newArrayWith :: forall m a. (MonadIO m, Unbox a) => (Int -> Int -> m MutByteArray) -> 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
pinnedEmptyOf :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) Source #
Allocates a pinned array of zero length but growable to the specified capacity without reallocation.
pinnedNewAligned :: (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
Cloning
Slicing
Get a subarray without copying
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
Stream Folds
data ArrayUnsafe a Source #
Constructors
| ArrayUnsafe !MutByteArray !Int !Int | 
unsafeCreateOfWith :: forall m a. (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a) Source #
Like unsafeCreateOf but takes a new array allocator alloc size
 function as argument.
>>>unsafeCreateOfWith alloc n = MutArray.unsafeAppendN (alloc n) n
Pre-release
unsafeCreateOf :: forall m a. (MonadIO m, Unbox a) => 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.
>>>unsafeCreateOf = MutArray.unsafeCreateOfWith MutArray.emptyOf
unsafePinnedCreateOf :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Like unsafeCreateOf but creates a pinned array.
pinnedCreateOf :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Like createOf but creates a pinned array.
createOfWith :: forall m a. (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a) Source #
createOfWith alloc n folds a maximum of n elements into an array
 allocated using the alloc function.
>>>createOfWith alloc n = Fold.take n (MutArray.unsafeCreateOfWith alloc n)>>>createOfWith alloc n = MutArray.appendN (alloc n) n
createOf :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
createOf n folds a maximum of n elements from the input stream to an
 MutArray.
>>>createOf = MutArray.createOfWith MutArray.new>>>createOf n = Fold.take n (MutArray.unsafeCreateOf n)>>>createOf n = MutArray.appendN n (MutArray.emptyOf n)
revCreateOf :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Like createOf but writes the array in reverse order.
Pre-release
pinnedCreate :: forall m a. (MonadIO m, Unbox a) => Fold m a (MutArray a) Source #
Like create but creates a pinned array.
createWith :: forall m a. (MonadIO m, Unbox a) => 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.
>>>f n = MutArray.appendWith (* 2) (MutArray.emptyOf n)>>>createWith n = Fold.rmapM MutArray.rightSize (f n)>>>createWith n = Fold.rmapM MutArray.fromChunksK (MutArray.buildChunks n)
Pre-release
create :: forall m a. (MonadIO m, Unbox a) => Fold m a (MutArray a) Source #
Fold the whole input to a single array.
Same as createWith using an initial array size of arrayChunkBytes bytes
 rounded up to the element size.
Caution! Do not use this on infinite streams.
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.
pinnedFromListN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a) Source #
Like fromListN but creates a pinned array.
fromList :: (MonadIO m, Unbox a) => [a] -> m (MutArray a) Source #
Create a MutArray from a list. The list must be of finite size.
pinnedFromList :: (MonadIO m, Unbox a) => [a] -> m (MutArray a) Source #
Like fromList but creates a pinned array.
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.
fromStreamN :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> m (MutArray a) Source #
Use the createOf fold instead.
>>>fromStreamN n = Stream.fold (MutArray.createOf n)
fromStream :: (MonadIO m, Unbox a) => Stream m a -> m (MutArray a) Source #
Create an Array from a stream. This is useful when we want to create a
 single array from a stream of unknown size. createOf is at least twice
 as efficient when the size is already known.
Note that if the input stream is too large memory allocation for the array
 may fail.  When the stream size is not known, chunksOf followed by
 processing of indvidual arrays in the resulting stream should be preferred.
Pre-release
fromPureStreamN :: (MonadIO m, Unbox a) => Int -> Stream Identity a -> m (MutArray a) Source #
Convert a pure stream in Identity monad to a mutable array.
fromPureStream :: (MonadIO m, Unbox a) => Stream Identity a -> m (MutArray a) Source #
Convert a pure stream in Identity monad to a mutable array.
fromChunksK :: (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.
Also see fromChunksRealloced.
fromChunksRealloced :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> m (MutArray a) Source #
Also see fromChunksK.
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.
Unsafe because it does not check the bounds of the array.
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.
This is an in-place equivalent of an immutable map operation.
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
Reading
Indexing
getIndex :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (Maybe 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.
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.
indexReader :: (MonadIO m, Unbox a) => 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
indexReaderWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m Int -> Unfold m (MutArray a) a Source #
To Streams
read :: forall m a. (MonadIO m, Unbox a) => MutArray a -> Stream m a Source #
Convert a MutArray into a stream.
>>>read = Stream.unfold MutArray.reader
readRev :: forall m a. (MonadIO m, Unbox a) => MutArray a -> Stream m a Source #
Convert a MutArray into a stream in reverse order.
>>>readRev = Stream.unfold MutArray.readerRev
toStreamWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> Stream m a Source #
toStreamRevWith :: 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 #
To Containers
toList :: forall m a. (MonadIO m, Unbox a) => MutArray a -> m [a] Source #
Convert a MutArray into a list.
Unfolds
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.
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.
Size and Capacity
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.
Capacity
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
Capacity 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).
If the original array is pinned, the newly allocated array is also pinned.
grow :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
grow 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
growExp :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
Like grow but if the requested 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
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.
byteCmp :: MonadIO m => MutArray a -> MutArray a -> m Ordering Source #
Byte compare two arrays. 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.
Unsafe: Note that the Unbox instance of sum types with constructors of
 different sizes may leave some memory uninitialized which can make byte
 comparison unreliable.
Pre-release
byteEq :: MonadIO m => MutArray a -> MutArray a -> m Bool Source #
Byte equality of two arrays.
>>>byteEq arr1 arr2 = (==) EQ $ MArray.byteCmp arr1 arr2
Unsafe: See byteCmp.
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
Growing and Shrinking
Arrays grow only at the end, though it is possible to grow on both sides and therefore have a cons as well as snoc. But that will require both lower and upper bound in the array representation.
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
unsafeAppendN :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a) Source #
unsafeAppendN n arr 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
appendN :: 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.
>>>appendN n initial = Fold.take n (MutArray.unsafeAppendN n initial)
appendWith :: forall m a. (MonadIO m, Unbox a) => (Int -> Int) -> m (MutArray a) -> Fold m a (MutArray a) Source #
appendWith 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.
>>>appendWith sizer = Fold.foldlM' (MutArray.snocWith sizer)
Pre-release
append :: 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.
>>>append = MutArray.appendWith (* 2)
Appending arrays
spliceCopy :: forall m a. MonadIO m => MutArray a -> MutArray a -> m (MutArray a) Source #
Copy two arrays into a newly allocated array. If the first array is pinned the spliced array is also pinned.
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 (+)
If the original array is pinned the spliced array is also pinned.
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.
Serialization using Unbox
pokeAppend :: forall m a. (MonadIO m, Unbox a) => MutArray Word8 -> a -> m (MutArray Word8) Source #
Unbox a Haskell type and append the resulting bytes to a mutable byte array. The array is grown exponentially when more space is needed.
Definition:
>>>pokeAppend arr x = MutArray.castUnsafe <$> MutArray.snoc (MutArray.castUnsafe arr) x
pokeAppendMay :: forall m a. (MonadIO m, Unbox a) => MutArray Word8 -> a -> m (Maybe (MutArray Word8)) Source #
Like pokeAppend but does not grow the array when pre-allocated array
 capacity becomes full.
Internal
pokeSkipUnsafe :: Int -> MutArray Word8 -> MutArray Word8 Source #
Skip the specified number of bytes in the array. The data in the skipped region remains uninitialzed.
Deserialization using Unbox
peekUncons :: forall m a. (MonadIO m, Unbox a) => MutArray Word8 -> m (Maybe a, MutArray Word8) Source #
Create a Haskell value from its unboxed representation from the head of a byte array, return the value and the remaining array.
peekUnconsUnsafe :: forall m a. (MonadIO m, Unbox a) => MutArray Word8 -> m (a, MutArray Word8) Source #
Really really unsafe, create a Haskell value from an unboxed byte array, does not check if the array is big enough, may return garbage or if you are lucky may cause a segfault.
Internal
peekSkipUnsafe :: Int -> MutArray Word8 -> MutArray Word8 Source #
Discard the specified number of bytes in the array.
Streams of Arrays
Chunk
Group a stream into arrays.
chunksOf :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a) Source #
chunksOf n stream groups the elements in the input stream into arrays of
 n elements each.
Same as the following but may be more efficient:
>>>chunksOf n = Stream.foldMany (MutArray.createOf n)
Pre-release
pinnedChunksOf :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a) Source #
Like chunksOf but creates pinned arrays.
buildChunks :: (MonadIO m, Unbox a) => Int -> Fold m a (StreamK n (MutArray a)) Source #
Buffer a stream into a stream of arrays.
>>>buildChunks n = Fold.many (MutArray.createOf 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
Split
Split an array into slices.
splitOn :: (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> Stream m (MutArray a) Source #
Generate a stream of array slices using a predicate. The array element matching the predicate is dropped.
Pre-release
Concat
Append the arrays in a stream to form a stream of elements.
concatWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m (MutArray a) -> Stream m a Source #
concatRevWith :: forall m a. (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m (MutArray a) -> Stream m a Source #
concat :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a Source #
Use the "reader" unfold instead.
concat = unfoldMany reader
We can try this if there are any fusion issues in the unfold.
concatRev :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a Source #
Use the "readerRev" unfold instead.
concat = unfoldMany readerRev
We can try this if there are any fusion issues in the unfold.
Compact
Append the arrays in a stream to form a stream of larger arrays.
data SpliceState s arr Source #
Constructors
| SpliceInitial s | |
| SpliceBuffering s arr | |
| SpliceYielding arr (SpliceState s arr) | |
| SpliceFinish | 
pCompactLE :: forall m a. (MonadIO m, Unbox a) => Int -> Parser (MutArray a) m (MutArray a) Source #
Parser pCompactLE maxElems coalesces adjacent arrays in the input stream
 only if the combined size would be less than or equal to maxElems
 elements. Note that it won't split an array if the original array is already
 larger than maxElems.
maxElems must be greater than 0.
Generates unpinned arrays irrespective of the pinning status of input arrays.
Internal
pPinnedCompactLE :: forall m a. (MonadIO m, Unbox a) => Int -> Parser (MutArray a) m (MutArray a) Source #
Pinned version of pCompactLE.
compactLeAs :: forall m a. (MonadIO m, Unbox a) => PinnedState -> Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
fCompactGE :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) (MutArray a) Source #
Fold fCompactGE minElems coalesces adjacent arrays in the input stream
 until the size becomes greater than or equal to minElems.
Generates unpinned arrays irrespective of the pinning status of input arrays.
fPinnedCompactGE :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) (MutArray a) Source #
Pinned version of fCompactGE.
lCompactGE :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) () -> Fold m (MutArray a) () Source #
Like compactGE but for transforming folds instead of stream.
>>>lCompactGE n = Fold.many (MutArray.fCompactGE n)
Generates unpinned arrays irrespective of the pinning status of input arrays.
lPinnedCompactGE :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) () -> Fold m (MutArray a) () Source #
Pinned version of lCompactGE.
compactGE :: (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
compactGE n stream coalesces adjacent arrays in the stream until
 the size becomes greater than or equal to n.
>>>compactGE n = Stream.foldMany (MutArray.fCompactGE n)
compactEQ :: Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
'compactEQ n' coalesces adajacent arrays in the input stream to
 arrays of exact size n.
Unimplemented
Utilities
roundUpToPower2 :: Int -> Int Source #
Deprecated
asPtrUnsafe :: MonadIO m => MutArray a -> (Ptr a -> m b) -> m b Source #
Deprecated: Please use unsafePinnedAsPtr instead.
writeChunks :: (MonadIO m, Unbox a) => Int -> Fold m a (StreamK n (MutArray a)) Source #
Deprecated: Please use buildChunks instead.
flattenArrays :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a Source #
Deprecated: Please use "unfoldMany reader" instead.
flattenArraysRev :: forall m a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a Source #
Deprecated: Please use "unfoldMany readerRev" instead.
fromArrayStreamK :: (Unbox a, MonadIO m) => StreamK m (MutArray a) -> m (MutArray a) Source #
Deprecated: Please use fromChunksK instead.
fromStreamDN :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m a -> m (MutArray a) Source #
Deprecated: Please use fromStreamN instead.
fromStreamD :: (MonadIO m, Unbox a) => Stream m a -> m (MutArray a) Source #
Deprecated: Please use fromStream instead.
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.create
cmp :: MonadIO m => MutArray a -> MutArray a -> m Ordering Source #
Deprecated: Please use byteCmp instead.
getIndices :: (MonadIO m, Unbox a) => Stream m Int -> Unfold m (MutArray a) a Source #
Deprecated: Please use indexReader instead.
getIndicesWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m Int -> Unfold m (MutArray a) a Source #
Deprecated: Please use indexReaderWith instead.
resize :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
Deprecated: Please use grow instead.
resizeExp :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
Deprecated: Please use growExp instead.
pinnedNewBytes :: MonadIO m => Int -> m (MutArray a) Source #
Deprecated: Please use pinnedEmptyOf with appropriate calculation
Allocates a pinned empty array that with a reserved capacity of bytes.
 The memory of the array is uninitialized and the allocation is aligned as
 per the Unboxed instance of the type.
Pre-release
writeAppendNUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a) Source #
Deprecated: Please use unsafeAppendN instead.
writeAppendN :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a) Source #
writeAppendWith :: forall m a. (MonadIO m, Unbox a) => (Int -> Int) -> m (MutArray a) -> Fold m a (MutArray a) Source #
Deprecated: Please use appendWith instead.
writeNWithUnsafe :: forall m a. (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a) Source #
Deprecated: Please use unsafeCreateOfWith instead.
writeNWith :: forall m a. (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a) Source #
writeNUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use unsafeCreateOf instead.
pinnedWriteNUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use unsafePinnedCreateOf instead.
pinnedWriteN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use pinnedCreateOf instead.
pinnedWriteNAligned :: forall m a. (MonadIO m, Unbox a) => Int -> Int -> Fold m a (MutArray a) Source #
pinnedWriteNAligned align n folds a maximum of n elements from the
 input stream to a MutArray aligned to the given size.
>>>pinnedWriteNAligned align = MutArray.createOfWith (MutArray.pinnedNewAligned align)>>>pinnedWriteNAligned align n = MutArray.appendN n (MutArray.pinnedNewAligned align n)
Pre-release
writeWith :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use createWith instead.
pinnedWrite :: forall m a. (MonadIO m, Unbox a) => Fold m a (MutArray a) Source #
Deprecated: Please use pinnedCreate instead.
writeRevN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use revCreateOf instead.
MutArray module
Arguments
| :: forall m a. (Monad m, Unbox a) | |
| => Int | from index | 
| -> Int | length of the slice | 
| -> Unfold m (MutArray a) (Int, Int) | 
Generate a stream of array slice descriptors ((index, len)) of specified length from an array, starting from the supplied array index. The last slice may be shorter than the requested length depending on the array length.
Pre-release
Arguments
| :: forall m a. (Monad m, Unbox a) | |
| => Int | from index | 
| -> Int | length of the slice | 
| -> Unfold m (MutArray a) (MutArray a) | 
Generate a stream of slices of specified length from an array, starting from the supplied array index. The last slice may be shorter than the requested length depending on the array length.
Pre-release
compactLE :: (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
compactLE maxElems coalesces adjacent arrays in the input stream
 only if the combined size would be less than or equal to maxElems
 elements. Note that it won't split an array if the original array is already
 larger than maxElems.
maxElems must be greater than 0.
Generates unpinned arrays irrespective of the pinning status of input arrays.
pinnedCompactLE :: forall m a. (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
Pinned version of compactLE.
compactOnByte :: MonadIO m => Word8 -> Stream m (MutArray Word8) -> Stream m (MutArray Word8) Source #
Split a stream of arrays on a given separator byte, dropping the separator and coalescing all the arrays between two separators into a single array.
compactOnByteSuffix :: MonadIO m => Word8 -> Stream m (MutArray Word8) -> Stream m (MutArray Word8) Source #
Like compactOnByte considers the separator in suffix position instead of
 infix position.
Unboxed IORef
modifyIORef' :: Unbox a => IORef a -> (a -> a) -> IO () Source #
Modify the value of an IORef using a function with strict application.
Pre-release
pollIntIORef :: (MonadIO m, Unbox a) => IORef a -> Stream m a Source #
Generate a stream by continuously reading the IORef.
This operation reads the IORef without any synchronization. It can be assumed to be atomic because the IORef (MutableByteArray) is always aligned to Int boundaries, we are assuming that compiler uses single instructions to access the memory. It may read stale values though until caches are synchronised in a multiprocessor architecture.
Pre-release