License | BSD-style |
---|---|
Maintainer | Haskell Foundation |
Safe Haskell | None |
Language | Haskell2010 |
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
- data Block ty = Block ByteArray#
- data MutableBlock ty st = MutableBlock (MutableByteArray# st)
- mutableLengthSize :: forall ty st. PrimType ty => MutableBlock ty st -> CountOf ty
- mutableLengthBytes :: MutableBlock ty st -> CountOf Word8
- mutableGetAddr :: PrimMonad prim => MutableBlock ty (PrimState prim) -> prim (Ptr ty)
- mutableWithAddr :: PrimMonad prim => MutableBlock ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a
- mutableTouch :: PrimMonad prim => MutableBlock ty (PrimState prim) -> prim ()
- new :: forall prim ty. (PrimMonad prim, PrimType ty) => CountOf ty -> prim (MutableBlock ty (PrimState prim))
- newPinned :: forall prim ty. (PrimMonad prim, PrimType ty) => CountOf ty -> prim (MutableBlock ty (PrimState prim))
- mutableEmpty :: PrimMonad prim => prim (MutableBlock ty (PrimState prim))
- iterSet :: (PrimType ty, PrimMonad prim) => (Offset ty -> ty) -> MutableBlock ty (PrimState prim) -> prim ()
- read :: (PrimMonad prim, PrimType ty) => MutableBlock ty (PrimState prim) -> Offset ty -> prim ty
- write :: (PrimMonad prim, PrimType ty) => MutableBlock ty (PrimState prim) -> Offset ty -> ty -> prim ()
- unsafeNew :: PrimMonad prim => PinnedStatus -> CountOf Word8 -> prim (MutableBlock ty (PrimState prim))
- unsafeWrite :: (PrimMonad prim, PrimType ty) => MutableBlock ty (PrimState prim) -> Offset ty -> ty -> prim ()
- unsafeRead :: (PrimMonad prim, PrimType ty) => MutableBlock ty (PrimState prim) -> Offset ty -> prim ty
- unsafeFreeze :: PrimMonad prim => MutableBlock ty (PrimState prim) -> prim (Block ty)
- unsafeThaw :: (PrimType ty, PrimMonad prim) => Block ty -> prim (MutableBlock ty (PrimState prim))
- unsafeCopyElements :: forall prim ty. (PrimMonad prim, PrimType ty) => MutableBlock ty (PrimState prim) -> Offset ty -> MutableBlock ty (PrimState prim) -> Offset ty -> CountOf ty -> prim ()
- unsafeCopyElementsRO :: forall prim ty. (PrimMonad prim, PrimType ty) => MutableBlock ty (PrimState prim) -> Offset ty -> Block ty -> Offset ty -> CountOf ty -> prim ()
- unsafeCopyBytes :: forall prim ty. PrimMonad prim => MutableBlock ty (PrimState prim) -> Offset Word8 -> MutableBlock ty (PrimState prim) -> Offset Word8 -> CountOf Word8 -> prim ()
- unsafeCopyBytesRO :: forall prim ty. PrimMonad prim => MutableBlock ty (PrimState prim) -> Offset Word8 -> Block ty -> Offset Word8 -> CountOf Word8 -> prim ()
Documentation
A block of memory containing unpacked bytes representing values of type ty
PrimType ty => IsList (Block ty) Source # | |
(PrimType ty, Eq ty) => Eq (Block ty) Source # | |
Data ty => Data (Block ty) Source # | |
(PrimType ty, Ord ty) => Ord (Block ty) Source # | |
(PrimType ty, Show ty) => Show (Block ty) Source # | |
PrimType ty => Monoid (Block ty) Source # | |
NormalForm (Block ty) Source # | |
PrimType ty => From (Block ty) (UArray ty) Source # | |
PrimType ty => From (UArray ty) (Block ty) Source # | |
PrimType ty => From (Array ty) (Block ty) Source # | |
(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => TryFrom (Block ty) (BlockN n ty) Source # | |
From (BlockN n ty) (Block ty) Source # | |
type Item (Block ty) Source # | |
data MutableBlock ty st Source #
A Mutable block of memory containing unpacked bytes representing values of type ty
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
mutableLengthBytes :: MutableBlock ty st -> CountOf Word8 Source #
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
:: (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
:: 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
:: 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