basement-0.0.1: Foundation scrap box of array & string

LicenseBSD-style
MaintainerHaskell Foundation
Safe HaskellNone
LanguageHaskell2010

Basement.Block.Mutable

Description

A block of memory that contains elements of a type, very similar to an unboxed array but with the key difference:

  • It doesn't have slicing capability (no cheap take or drop)
  • It consume less memory: 1 Offset, 1 CountOf, 1 Pinning status trimmed
  • It's unpackable in any constructor
  • It uses unpinned memory by default

It should be rarely needed in high level API, but in lowlevel API or some data structure containing lots of unboxed array that will benefit from optimisation.

Because it's unpinned, the blocks are compactable / movable, at the expense of making them less friendly to interop with the C layer as address.

Note that sadly the bytearray primitive type automatically create a pinned bytearray if the size is bigger than a certain threshold

GHC Documentation associated:

includesrtsstorage/Block.h * LARGE_OBJECT_THRESHOLD ((uint32_t)(BLOCK_SIZE * 8 / 10)) * BLOCK_SIZE (1<<BLOCK_SHIFT)

includesrtsConstant.h * BLOCK_SHIFT 12

Synopsis

Documentation

data Block ty Source #

A block of memory containing unpacked bytes representing values of type ty

Constructors

Block ByteArray# 

Instances

PrimType ty => IsList (Block ty) Source # 

Associated Types

type Item (Block ty) :: * #

Methods

fromList :: [Item (Block ty)] -> Block ty #

fromListN :: Int -> [Item (Block ty)] -> Block ty #

toList :: Block ty -> [Item (Block ty)] #

(PrimType ty, Eq ty) => Eq (Block ty) Source # 

Methods

(==) :: Block ty -> Block ty -> Bool #

(/=) :: Block ty -> Block ty -> Bool #

Data ty => Data (Block ty) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Block ty -> c (Block ty) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Block ty) #

toConstr :: Block ty -> Constr #

dataTypeOf :: Block ty -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Block ty)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Block ty)) #

gmapT :: (forall b. Data b => b -> b) -> Block ty -> Block ty #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block ty -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block ty -> r #

gmapQ :: (forall d. Data d => d -> u) -> Block ty -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Block ty -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Block ty -> m (Block ty) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Block ty -> m (Block ty) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Block ty -> m (Block ty) #

(PrimType ty, Ord ty) => Ord (Block ty) Source # 

Methods

compare :: Block ty -> Block ty -> Ordering #

(<) :: Block ty -> Block ty -> Bool #

(<=) :: Block ty -> Block ty -> Bool #

(>) :: Block ty -> Block ty -> Bool #

(>=) :: Block ty -> Block ty -> Bool #

max :: Block ty -> Block ty -> Block ty #

min :: Block ty -> Block ty -> Block ty #

(PrimType ty, Show ty) => Show (Block ty) Source # 

Methods

showsPrec :: Int -> Block ty -> ShowS #

show :: Block ty -> String #

showList :: [Block ty] -> ShowS #

PrimType ty => Monoid (Block ty) Source # 

Methods

mempty :: Block ty #

mappend :: Block ty -> Block ty -> Block ty #

mconcat :: [Block ty] -> Block ty #

NormalForm (Block ty) Source # 

Methods

toNormalForm :: Block ty -> () Source #

PrimType ty => From (Block ty) (UArray ty) Source # 

Methods

from :: Block ty -> UArray ty Source #

PrimType ty => From (UArray ty) (Block ty) Source # 

Methods

from :: UArray ty -> Block ty Source #

PrimType ty => From (Array ty) (Block ty) Source # 

Methods

from :: Array ty -> Block ty Source #

(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (Block ty) (BlockN n ty) Source # 

Methods

tryFrom :: Block ty -> Maybe (BlockN n ty) Source #

From (BlockN n ty) (Block ty) Source # 

Methods

from :: BlockN n ty -> Block ty Source #

type Item (Block ty) Source # 
type Item (Block ty) = ty

data MutableBlock ty st Source #

A Mutable block of memory containing unpacked bytes representing values of type ty

Constructors

MutableBlock (MutableByteArray# st) 

mutableLengthSize :: forall ty st. PrimType ty => MutableBlock ty st -> CountOf ty Source #

Return the length of a Mutable Block

note: we don't allow resizing yet, so this can remain a pure function

mutableGetAddr :: PrimMonad prim => MutableBlock ty (PrimState prim) -> prim (Ptr ty) Source #

Get the address of the context of the mutable block.

if the block is not pinned, this is a _dangerous_ operation

Note that if nothing is holding the block, the GC can garbage collect the block and thus the address is dangling on the memory. use mutableWithAddr to prevent this problem by construction

mutableWithAddr :: PrimMonad prim => MutableBlock ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a Source #

Get the address of the mutable block in a safer construct

if the block is not pinned, this is a _dangerous_ operation

mutableTouch :: PrimMonad prim => MutableBlock ty (PrimState prim) -> prim () Source #

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

Create a new mutable block of a specific N size of ty elements

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

mutableEmpty :: PrimMonad prim => prim (MutableBlock ty (PrimState prim)) Source #

iterSet :: (PrimType ty, PrimMonad prim) => (Offset ty -> ty) -> MutableBlock ty (PrimState prim) -> prim () Source #

Set all mutable block element to a value

read :: (PrimMonad prim, PrimType ty) => MutableBlock 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.

write :: (PrimMonad prim, PrimType ty) => MutableBlock 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.

unsafeNew :: PrimMonad prim => PinnedStatus -> CountOf Word8 -> prim (MutableBlock ty (PrimState prim)) Source #

Create a new mutable block of a specific size in bytes.

Note that no checks are made to see if the size in bytes is compatible with the size of the underlaying element ty in the block.

use new if unsure

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

write to a cell in a mutable block 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) => MutableBlock ty (PrimState prim) -> Offset ty -> prim ty Source #

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

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

unsafeFreeze :: PrimMonad prim => MutableBlock ty (PrimState prim) -> prim (Block ty) Source #

Freeze a mutable block into a block.

If the mutable block is still use after freeze, then the modification will be reflected in an unexpected way in the Block.

unsafeThaw :: (PrimType ty, PrimMonad prim) => Block ty -> prim (MutableBlock ty (PrimState prim)) Source #

Thaw an immutable block.

If the immutable block is modified, then the original immutable block will be modified too, but lead to unexpected results when querying

unsafeCopyElements Source #

Arguments

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

destination mutable block

-> Offset ty

offset at destination

-> MutableBlock ty (PrimState prim)

source mutable block

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

unsafeCopyElementsRO Source #

Arguments

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

destination mutable block

-> Offset ty

offset at destination

-> Block ty

source block

-> Offset ty

offset at source

-> CountOf ty

number of elements to copy

-> prim () 

unsafeCopyBytes Source #

Arguments

:: PrimMonad prim 
=> MutableBlock ty (PrimState prim)

destination mutable block

-> Offset Word8

offset at destination

-> MutableBlock ty (PrimState prim)

source mutable block

-> Offset Word8

offset at source

-> CountOf Word8

number of elements to copy

-> prim () 

Copy a number of bytes from a MutableBlock to another MutableBlock with specific byte offsets

unsafeCopyBytesRO Source #

Arguments

:: PrimMonad prim 
=> MutableBlock ty (PrimState prim)

destination mutable block

-> Offset Word8

offset at destination

-> Block ty

source block

-> Offset Word8

offset at source

-> CountOf Word8

number of elements to copy

-> prim () 

Copy a number of bytes from a Block to a MutableBlock with specific byte offsets