| Copyright | (c) 2022 Composewell Technologies | 
|---|---|
| License | BSD3 | 
| Maintainer | streamly@composewell.com | 
| Stability | released | 
| Portability | GHC | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Streamly.Data.MutArray
Description
This module provides a mutable version of Streamly.Data.Array. The contents of a mutable array can be modified in-place. For general documentation, please refer to the original module.
Please refer to Streamly.Internal.Data.Array.Mut for functions that have not yet been released.
For mutable arrays that work on boxed types, not requiring the Unbox
 constraint, please refer to Streamly.Data.MutArray.Generic.
Synopsis
- data MutArray a
- new :: (MonadIO m, Unbox a) => Int -> m (MutArray a)
- newPinned :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a)
- fromListN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a)
- fromList :: (MonadIO m, Unbox a) => [a] -> m (MutArray a)
- writeN :: 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)
- snoc :: forall m a. (MonadIO m, Unbox a) => MutArray a -> a -> m (MutArray a)
- writeAppendN :: forall m a. (MonadIO m, Unbox a) => 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)
- putIndex :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> a -> m ()
- getIndex :: forall m a. (MonadIO m, Unbox a) => Int -> MutArray a -> m a
- toList :: forall m a. (MonadIO m, Unbox a) => MutArray a -> m [a]
- reader :: forall m a. (MonadIO m, Unbox a) => Unfold m (MutArray a) a
- readerRev :: forall m a. (MonadIO m, Unbox a) => Unfold m (MutArray a) a
- cast :: forall a b. Unbox b => MutArray a -> Maybe (MutArray b)
- asBytes :: MutArray a -> MutArray Word8
- length :: forall a. Unbox a => MutArray a -> Int
- class Unbox a where- sizeOf :: Proxy a -> Int
- peekByteIndex :: Int -> MutableByteArray -> IO a
- pokeByteIndex :: Int -> MutableByteArray -> a -> IO ()
 
Setup
To execute the code examples provided in this module in ghci, please run the following commands first.
>>>:m>>>import qualified Streamly.Data.Fold as Fold>>>import qualified Streamly.Data.MutArray as MutArray>>>import qualified Streamly.Data.Stream as Stream
For APIs that have not been released yet.
>>>import Streamly.Internal.Data.Array.Mut as MutArray
Mutable Array Type
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.
Construction
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.
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.
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.
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)
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.
Appending elements
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.
Appending streams
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)
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)
Inplace mutation
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))
Random access
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.
Conversion
toList :: forall m a. (MonadIO m, Unbox a) => MutArray a -> m [a] Source #
Convert a MutArray into a list.
Unfolds
reader :: forall m a. (MonadIO m, Unbox a) => Unfold m (MutArray a) a Source #
Unfold an array into a stream.
readerRev :: forall m a. (MonadIO m, Unbox a) => Unfold m (MutArray a) a Source #
Unfold an array into a stream in reverse order.
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.
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.
Unbox Type Class
A type implementing the Unbox interface supplies operations for reading
 and writing the type from and to a mutable byte array (an unboxed
 representation of the type) in memory. The read operation peekByteIndex
 deserializes the boxed type from the mutable byte array. The write operation
 pokeByteIndex serializes the boxed type to the mutable byte array.
Instances can be derived via Generic. Note that the data type must be
 non-recursive. Here is an example, for deriving an instance of this type
 class.
>>>import GHC.Generics (Generic)>>>:{data Object = Object { _int0 :: Int , _int1 :: Int } deriving Generic :}
WARNING! Generic deriving hangs for recursive data types.
>>>import Streamly.Data.Array (Unbox(..))>>>instance Unbox Object
If you want to write the instance manually:
>>>:{instance Unbox Object where sizeOf _ = 16 peekByteIndex i arr = do x0 <- peekByteIndex i arr x1 <- peekByteIndex (i + 8) arr return $ Object x0 x1 pokeByteIndex i arr (Object x0 x1) = do pokeByteIndex i arr x0 pokeByteIndex (i + 8) arr x1 :}
Minimal complete definition
Nothing
Methods
sizeOf :: Proxy a -> Int Source #
Get the size. Size cannot be zero.
peekByteIndex :: Int -> MutableByteArray -> IO a Source #
Read an element of type "a" from a MutableByteArray given the byte index.
IMPORTANT: The implementation of this interface may not check the bounds of the array, the caller must not assume that.
default peekByteIndex :: (Generic a, PeekRep (Rep a)) => Int -> MutableByteArray -> IO a Source #
pokeByteIndex :: Int -> MutableByteArray -> a -> IO () Source #
Write an element of type "a" to a MutableByteArray given the byte index.
IMPORTANT: The implementation of this interface may not check the bounds of the array, the caller must not assume that.
default pokeByteIndex :: (Generic a, PokeRep (Rep a)) => Int -> MutableByteArray -> a -> IO () Source #