License | BSD-style |
---|---|
Maintainer | Haskell Foundation |
Safe Haskell | Safe-Inferred |
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
Synopsis
- data Block ty = Block ByteArray#
- data MutableBlock ty st = MutableBlock (MutableByteArray# st)
- mutableLengthSize :: PrimType ty => MutableBlock ty st -> CountOf ty
- mutableLength :: forall ty st. PrimType ty => MutableBlock ty st -> CountOf ty
- mutableLengthBytes :: MutableBlock ty st -> CountOf Word8
- mutableWithPtr :: PrimMonad prim => MutableBlock ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a
- withMutablePtr :: PrimMonad prim => MutableBlock ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a
- withMutablePtrHint :: forall ty prim a. PrimMonad prim => Bool -> Bool -> MutableBlock ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a
- 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 ()
- unsafeCopyBytesPtr :: forall prim ty. PrimMonad prim => MutableBlock ty (PrimState prim) -> Offset Word8 -> Ptr ty -> CountOf Word8 -> prim ()
- copyFromPtr :: forall prim ty. (PrimMonad prim, PrimType ty) => Ptr ty -> MutableBlock ty (PrimState prim) -> Offset ty -> CountOf ty -> prim ()
- copyToPtr :: forall ty prim. (PrimType ty, PrimMonad prim) => MutableBlock ty (PrimState prim) -> Offset ty -> Ptr ty -> CountOf ty -> prim ()
Documentation
A block of memory containing unpacked bytes representing values of type ty
Instances
Data ty => Data (Block ty) Source # | |
Defined in Basement.Block.Base 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 :: forall r r'. (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 => Monoid (Block ty) Source # | |
PrimType ty => Semigroup (Block ty) Source # | |
PrimType ty => IsList (Block ty) Source # | |
(PrimType ty, Show ty) => Show (Block ty) Source # | |
NormalForm (Block ty) Source # | |
Defined in Basement.Block.Base toNormalForm :: Block ty -> () Source # | |
(PrimType ty, Eq ty) => Eq (Block ty) Source # | |
(PrimType ty, Ord ty) => Ord (Block ty) Source # | |
Defined in Basement.Block.Base | |
Cast (Block a) (Block Word8) Source # | |
PrimType ty => From (Block ty) (UArray ty) Source # | |
PrimType ty => From (Array ty) (Block ty) Source # | |
PrimType ty => From (UArray 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 # | |
Defined in Basement.Block.Base |
data MutableBlock ty st Source #
A Mutable block of memory containing unpacked bytes representing values of type ty
mutableLengthSize :: PrimType ty => MutableBlock ty st -> CountOf ty Source #
Deprecated: use mutableLength
mutableLength :: 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 #
mutableWithPtr :: PrimMonad prim => MutableBlock ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a Source #
Deprecated: use withMutablePtr
Use the Ptr
to a mutable block in a safer construct
If the block is not pinned, this is a _dangerous_ operation
withMutablePtr :: PrimMonad prim => MutableBlock ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a Source #
Create a pointer on the beginning of the MutableBlock
and call a function f
.
The mutable block can be mutated by the f
function
and the change will be reflected in the mutable block
If the mutable block is unpinned, a trampoline buffer
is created and the data is only copied when f
return.
it is all-in-all highly inefficient as this cause 2 copies
:: forall ty prim a. PrimMonad prim | |
=> Bool | hint that the buffer doesn't need to have the same value as the mutable block when calling f |
-> Bool | hint that the buffer is not supposed to be modified by call of f |
-> MutableBlock ty (PrimState prim) | |
-> (Ptr ty -> prim a) | |
-> prim a |
Same as withMutablePtr
but allow to specify 2 optimisations
which is only useful when the MutableBlock is unpinned and need
a pinned trampoline to be called safely.
If skipCopy is True, then the first copy which happen before
the call to f
, is skipped. The Ptr is now effectively
pointing to uninitialized data in a new mutable Block.
If skipCopyBack is True, then the second copy which happen after
the call to f
, is skipped. Then effectively in the case of a
trampoline being used the memory changed by f
will not
be reflected in the original Mutable Block.
If using the wrong parameters, it will lead to difficult to debug issue of corrupted buffer which only present themselves with certain Mutable Block that happened to have been allocated unpinned.
If unsure use withMutablePtr
, which default to *not* skip
any copy.
new :: forall prim ty. (PrimMonad prim, PrimType ty) => CountOf ty -> prim (MutableBlock ty (PrimState prim)) Source #
Create a new unpinned mutable block of a specific N size of ty
elements
If the size exceeds a GHC-defined threshold, then the memory will be
pinned. To be certain about pinning status with small size, use newPinned
newPinned :: forall prim ty. (PrimMonad prim, PrimType ty) => CountOf ty -> prim (MutableBlock ty (PrimState prim)) Source #
Create a new pinned mutable block of a specific N size of ty
elements
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
:: forall prim ty. (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
:: forall prim ty. 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
:: forall prim ty. 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
:: forall prim ty. PrimMonad prim | |
=> MutableBlock ty (PrimState prim) | destination mutable block |
-> Offset Word8 | offset at destination |
-> Ptr ty | source block |
-> CountOf Word8 | number of bytes to copy |
-> prim () |
Copy a number of bytes from a Ptr to a MutableBlock with specific byte offsets
Foreign
:: forall prim ty. (PrimMonad prim, PrimType ty) | |
=> Ptr ty | Source Ptr of |
-> MutableBlock ty (PrimState prim) | Destination mutable block |
-> Offset ty | Start offset in the destination mutable block |
-> CountOf ty | Number of |
-> prim () |
Copy from a pointer, count
elements, into the Mutable Block at a starting offset ofs
if the source pointer is invalid (size or bad allocation), bad things will happen
:: forall ty prim. (PrimType ty, PrimMonad prim) | |
=> MutableBlock ty (PrimState prim) | The source mutable block to copy |
-> Offset ty | The source offset in the mutable block |
-> Ptr ty | The destination address where the copy is going to start |
-> CountOf ty | The number of bytes |
-> prim () |
Copy all the block content to the memory starting at the destination address
If the destination pointer is invalid (size or bad allocation), bad things will happen