streamly-core-0.2.2: Streaming, parsers, arrays, serialization and more
Copyright(c) 2022 Composewell Technologies
LicenseBSD3
Maintainerstreamly@composewell.com
Stabilityreleased
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

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.MutArray 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

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.MutArray as MutArray

Mutable Array Type

data MutArray a Source #

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

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.

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.

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.

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)

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.

Pinning & Unpinning

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.

isPinned :: MutArray a -> Bool Source #

Return True if the array is allocated in pinned memory.

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

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)

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)

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))

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

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

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

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

Random access

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.

Conversion

toList :: forall m a. (MonadIO m, Unbox a) => MutArray a -> m [a] Source #

Convert a MutArray into a list.

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

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.

asBytes :: MutArray a -> MutArray Word8 Source #

Cast an MutArray a into an MutArray Word8.

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.

Re-exports

class Unbox a where Source #

The Unbox type class provides operations for serialization (unboxing) and deserialization (boxing) of fixed-length, non-recursive Haskell data types to and from their byte stream representation.

Unbox uses fixed size encoding, therefore, size is independent of the value, it must be determined solely by the type. This restriction makes types with Unbox instances suitable for storing in arrays. Note that sum types may have multiple constructors of different sizes, the size of a sum type is computed as the maximum required by any constructor.

The peekAt operation reads as many bytes from the mutable byte array as the size of the data type and builds a Haskell data type from these bytes. pokeAt operation converts a Haskell data type to its binary representation which consists of size bytes and then stores these bytes into the mutable byte array. These operations do not check the bounds of the array, the user of the type class is expected to check the bounds before peeking or poking.

IMPORTANT: The serialized data's byte ordering remains the same as the host machine's byte order. Therefore, it can not be deserialized from host machines with a different byte ordering.

Instances can be derived via Generics, Template Haskell, or written manually. Note that the data type must be non-recursive. WARNING! Generic and Template Haskell deriving, both hang for recursive data types. Deriving via Generics is more convenient but Template Haskell should be preferred over Generics for the following reasons:

  1. Instances derived via Template Haskell provide better and more reliable performance.
  2. Generic deriving allows only 256 fields or constructor tags whereas template Haskell has no limit.

Here is an example, for deriving an instance of this type class using generics:

>>> import GHC.Generics (Generic)
>>> :{
data Object = Object
    { _int0 :: Int
    , _int1 :: Int
    } deriving Generic
:}
>>> import Streamly.Data.MutByteArray (Unbox(..))
>>> instance Unbox Object

To derive the instance via Template Haskell:

import Streamly.Data.MutByteArray (deriveUnbox)
$(deriveUnbox [d|instance Unbox Object|])

See deriveUnbox for more information on deriving using Template Haskell.

If you want to write the instance manually:

>>> :{
instance Unbox Object where
    sizeOf _ = 16
    peekAt i arr = do
       -- Check the array bounds
        x0 <- peekAt i arr
        x1 <- peekAt (i + 8) arr
        return $ Object x0 x1
    pokeAt i arr (Object x0 x1) = do
       -- Check the array bounds
        pokeAt i arr x0
        pokeAt (i + 8) arr x1
:}

Minimal complete definition

Nothing

Methods

sizeOf :: Proxy a -> Int Source #

Get the size. Size cannot be zero, should be at least 1 byte.

default sizeOf :: SizeOfRep (Rep a) => Proxy a -> Int Source #

peekAt :: Int -> MutByteArray -> IO a Source #

peekAt byte-offset array reads an element of type a from the the given the byte offset in the array.

IMPORTANT: The implementation of this interface may not check the bounds of the array, the caller must not assume that.

default peekAt :: (Generic a, PeekRep (Rep a)) => Int -> MutByteArray -> IO a Source #

peekByteIndex :: Int -> MutByteArray -> IO a Source #

Deprecated: Use peekAt.

pokeAt :: Int -> MutByteArray -> a -> IO () Source #

pokeAt byte-offset array writes an element of type a to the the given the byte offset in the array.

IMPORTANT: The implementation of this interface may not check the bounds of the array, the caller must not assume that.

default pokeAt :: (Generic a, PokeRep (Rep a)) => Int -> MutByteArray -> a -> IO () Source #

pokeByteIndex :: Int -> MutByteArray -> a -> IO () Source #

Deprecated: Use pokeAt.

Instances

Instances details
Unbox IntPtr Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox WordPtr Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Fingerprint Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Int16 Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Int32 Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Int64 Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Int8 Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox IoSubSystem Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Word16 Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Word32 Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Word64 Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Word8 Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox MicroSecond64 Source # 
Instance details

Defined in Streamly.Internal.Data.Time.Units

Unbox MilliSecond64 Source # 
Instance details

Defined in Streamly.Internal.Data.Time.Units

Unbox NanoSecond64 Source # 
Instance details

Defined in Streamly.Internal.Data.Time.Units

Unbox () Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Bool Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Char Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Double Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Float Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Int Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox Word Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox a => Unbox (Complex a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox a => Unbox (Identity a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox a => Unbox (Down a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox (FunPtr a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox (Ptr a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox a => Unbox (Ratio a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox (StablePtr a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Unbox a => Unbox (Const a b) Source # 
Instance details

Defined in Streamly.Internal.Data.Unbox

Deprecated

newPinned :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) Source #

Deprecated: Please use pinnedNew instead.

new :: (MonadIO m, Unbox a) => Int -> m (MutArray a) Source #

pinnedNew :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) Source #

writeN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #

write :: forall m a. (MonadIO m, Unbox a) => Fold m a (MutArray a) Source #

writeAppendN :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a) Source #

writeAppend :: forall m a. (MonadIO m, Unbox a) => m (MutArray a) -> Fold m a (MutArray a) Source #