basement-0.0.3: Foundation scrap box of array & string

MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Basement.UArray.Mutable

Contents

Description

A simple array abstraction that allow to use typed array of bytes where the array is pinned in memory to allow easy use with Foreign interfaces, ByteString and always aligned to 64 bytes.

Synopsis

Documentation

data MUArray ty st Source #

A Mutable array of types built on top of GHC primitive.

Element in this array can be modified in place.

Constructors

MUArray !(Offset ty) !(CountOf ty) !(MUArrayBackend ty st) 

Property queries

mutableLength :: PrimType ty => MUArray ty st -> CountOf ty Source #

return the numbers of elements in a mutable array

mutableSame :: MUArray ty st -> MUArray ty st -> Bool Source #

onMutableBackend :: PrimMonad prim => (MutableBlock ty (PrimState prim) -> prim a) -> (FinalPtr ty -> prim a) -> MUArray ty (PrimState prim) -> prim a Source #

Allocation & Copy

new :: (PrimMonad prim, PrimType ty) => CountOf ty -> prim (MUArray ty (PrimState prim)) Source #

Create a new mutable array of size @n.

When memory for a new array is allocated, we decide if that memory region should be pinned (will not be copied around by GC) or unpinned (can be moved around by GC) depending on its size.

You can change the threshold value used by setting the environment variable HS_FOUNDATION_UARRAY_UNPINNED_MAX.

newPinned :: forall prim ty. (PrimMonad prim, PrimType ty) => CountOf ty -> prim (MUArray ty (PrimState prim)) Source #

Create a new pinned mutable array of size @n.

all the cells are uninitialized and could contains invalid values.

All mutable arrays are allocated on a 64 bits aligned addresses

newNative :: (PrimMonad prim, PrimType ty) => CountOf ty -> (MutableBlock ty (PrimState prim) -> prim a) -> prim (a, MUArray ty (PrimState prim)) Source #

mutableForeignMem Source #

Arguments

:: (PrimMonad prim, PrimType ty) 
=> FinalPtr ty

the start pointer with a finalizer

-> Int

the number of elements (in elements, not bytes)

-> prim (MUArray ty (PrimState prim)) 

copyAt Source #

Arguments

:: (PrimMonad prim, PrimType ty) 
=> MUArray ty (PrimState prim)

destination array

-> Offset ty

offset at destination

-> MUArray ty (PrimState prim)

source array

-> Offset ty

offset at source

-> CountOf ty

number of elements to copy

-> prim () 

Copy a number of elements from an array to another array with offsets

copyFromPtr :: forall prim ty. (PrimMonad prim, PrimType ty) => Ptr ty -> CountOf ty -> MUArray ty (PrimState prim) -> prim () Source #

Copy from a pointer, count elements, into the mutable array

copyToPtr Source #

Arguments

:: (PrimType ty, PrimMonad prim) 
=> MUArray ty (PrimState prim)

the source mutable array to copy

-> Ptr ty

The destination address where the copy is going to start

-> prim () 

Copy all the block content to the memory starting at the destination address

sub :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Int -> Int -> prim (MUArray ty (PrimState prim)) Source #

Reading and Writing cells

unsafeWrite :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> ty -> prim () Source #

write to a cell in a mutable array without bounds checking.

Writing with invalid bounds will corrupt memory and your program will become unreliable. use write if unsure.

unsafeRead :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> prim ty Source #

read from a cell in a mutable array without bounds checking.

Reading from invalid memory can return unpredictable and invalid values. use read if unsure.

write :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> ty -> prim () Source #

Write to a cell in a mutable array.

If the index is out of bounds, an error is raised.

read :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> prim ty Source #

read a cell in a mutable array.

If the index is out of bounds, an error is raised.

withMutablePtr :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a Source #

Create a pointer on the beginning of the mutable array and call a function f.

The mutable buffer can be mutated by the f function and the change will be reflected in the mutable array

If the mutable array is unpinned, a trampoline buffer is created and the data is only copied when f return.