Copyright | (c) Alexey Kuleshevich 2020 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <alexey@kuleshevi.ch> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Bytes (p :: Pinned)
- toByteArray# :: Bytes p -> ByteArray#
- fromByteArray# :: ByteArray# -> Bytes Inc
- cloneBytes :: Typeable p => Bytes p -> Bytes p
- emptyBytes :: Bytes p
- eqBytes :: Bytes p1 -> Bytes p2 -> Bool
- singletonBytes :: forall e p. (Prim e, Typeable p) => e -> Bytes p
- isEmptyBytes :: Bytes p -> Bool
- createBytes :: forall p e b s m. (Prim e, Typeable p, MonadPrim s m) => Count e -> (MBytes p s -> m b) -> m (b, Bytes p)
- createBytes_ :: forall p e b s m. (Prim e, Typeable p, MonadPrim s m) => Count e -> (MBytes p s -> m b) -> m (Bytes p)
- createBytesST :: forall p e b. (Prim e, Typeable p) => Count e -> (forall s. MBytes p s -> ST s b) -> (b, Bytes p)
- createBytesST_ :: forall p e b. (Prim e, Typeable p) => Count e -> (forall s. MBytes p s -> ST s b) -> Bytes p
- data Pinned
- isPinnedBytes :: Bytes p -> Bool
- isPinnedMBytes :: MBytes p d -> Bool
- toPinnedBytes :: Bytes p -> Maybe (Bytes Pin)
- toPinnedMBytes :: MBytes p s -> Maybe (MBytes Pin s)
- relaxPinnedBytes :: Bytes p -> Bytes Inc
- relaxPinnedMBytes :: MBytes p e -> MBytes Inc e
- ensurePinnedBytes :: Bytes p -> Bytes Pin
- ensurePinnedMBytes :: MonadPrim s m => MBytes p s -> m (MBytes Pin s)
- data MBytes (p :: Pinned) s
- toMutableByteArray# :: MBytes p s -> MutableByteArray# s
- fromMutableByteArray# :: MutableByteArray# s -> MBytes Inc s
- isSameBytes :: Bytes p1 -> Bytes p2 -> Bool
- isSamePinnedBytes :: Bytes Pin -> Bytes Pin -> Bool
- isSameMBytes :: MBytes p1 s -> MBytes p2 s -> Bool
- indexOffBytes :: Prim e => Bytes p -> Off e -> e
- indexByteOffBytes :: Prim e => Bytes p -> Off Word8 -> e
- byteCountBytes :: Bytes p -> Count Word8
- countBytes :: Prim e => Bytes p -> Count e
- countRemBytes :: forall e p. Prim e => Bytes p -> (Count e, Count Word8)
- compareBytes :: Prim e => Bytes p1 -> Off e -> Bytes p2 -> Off e -> Count e -> Ordering
- compareByteOffBytes :: Prim e => Bytes p1 -> Off Word8 -> Bytes p2 -> Off Word8 -> Count e -> Ordering
- thawBytes :: MonadPrim s m => Bytes p -> m (MBytes p s)
- freezeMBytes :: MonadPrim s m => MBytes p s -> m (Bytes p)
- allocMBytes :: forall p e s m. (Typeable p, Prim e, MonadPrim s m) => Count e -> m (MBytes p s)
- singletonMBytes :: forall e p m s. (Prim e, Typeable p, MonadPrim s m) => e -> m (MBytes p s)
- allocPinnedMBytes :: (MonadPrim s m, Prim e) => Count e -> m (MBytes Pin s)
- allocAlignedMBytes :: forall e m s. (MonadPrim s m, Prim e) => Count e -> m (MBytes Pin s)
- allocUnpinnedMBytes :: (MonadPrim s m, Prim e) => Count e -> m (MBytes Inc s)
- callocMBytes :: (MonadPrim s m, Prim e, Typeable p) => Count e -> m (MBytes p s)
- callocAlignedMBytes :: (MonadPrim s m, Prim e) => Count e -> m (MBytes Pin s)
- shrinkMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> Count e -> m ()
- resizeMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> Count e -> m (MBytes Inc s)
- reallocMBytes :: forall e p m s. (MonadPrim s m, Typeable p, Prim e) => MBytes p s -> Count e -> m (MBytes p s)
- coerceStateMBytes :: MBytes p s' -> MBytes p s
- cloneMBytes :: (MonadPrim s m, Typeable p) => MBytes p s -> m (MBytes p s)
- withCloneMBytes :: (MonadPrim s m, Typeable p) => Bytes p -> (MBytes p s -> m a) -> m (a, Bytes p)
- withCloneMBytes_ :: (MonadPrim s m, Typeable p) => Bytes p -> (MBytes p s -> m a) -> m (Bytes p)
- withCloneMBytesST :: Typeable p => Bytes p -> (forall s. MBytes p s -> ST s a) -> (a, Bytes p)
- withCloneMBytesST_ :: Typeable p => Bytes p -> (forall s. MBytes p s -> ST s a) -> Bytes p
- loadListMBytes :: (MonadPrim s m, Prim e) => [e] -> MBytes p s -> m Ordering
- loadListMBytes_ :: (MonadPrim s m, Prim e) => [e] -> MBytes p s -> m ()
- copyBytesToMBytes :: (MonadPrim s m, Prim e) => Bytes ps -> Off e -> MBytes pd s -> Off e -> Count e -> m ()
- moveMBytesToMBytes :: (MonadPrim s m, Prim e) => MBytes ps s -> Off e -> MBytes pd s -> Off e -> Count e -> m ()
- getByteCountMBytes :: MonadPrim s m => MBytes p s -> m (Count Word8)
- getCountMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> m (Count e)
- getCountRemOfMBytes :: forall e p s m. (MonadPrim s m, Prim e) => MBytes p s -> m (Count e, Count Word8)
- readOffMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> m e
- readByteOffMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> Off Word8 -> m e
- writeOffMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> e -> m ()
- writeByteOffMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> Off Word8 -> e -> m ()
- setMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> Count e -> e -> m ()
- zeroMBytes :: MonadPrim s m => MBytes p s -> m ()
- withPtrBytes :: MonadPrim s m => Bytes Pin -> (Ptr e -> m b) -> m b
- withNoHaltPtrBytes :: MonadUnliftPrim s m => Bytes Pin -> (Ptr e -> m b) -> m b
- withPtrMBytes :: MonadPrim s m => MBytes Pin s -> (Ptr e -> m b) -> m b
- withNoHaltPtrMBytes :: MonadUnliftPrim s m => MBytes Pin s -> (Ptr e -> m b) -> m b
- toPtrBytes :: Bytes Pin -> Ptr e
- toPtrMBytes :: MBytes Pin s -> Ptr e
- toForeignPtrBytes :: Bytes Pin -> ForeignPtr e
- toForeignPtrMBytes :: MBytes Pin s -> ForeignPtr e
- fromListBytes :: forall e p. (Prim e, Typeable p) => [e] -> Bytes p
- fromListBytesN :: (Prim e, Typeable p) => Count e -> [e] -> (Ordering, Bytes p)
- fromListBytesN_ :: (Prim e, Typeable p) => Count e -> [e] -> Bytes p
- appendBytes :: Typeable p => Bytes p1 -> Bytes p2 -> Bytes p
- concatBytes :: Typeable p => [Bytes p'] -> Bytes p
- toListBytes :: Prim e => Bytes p -> [e]
- toListSlackBytes :: Prim e => Bytes p -> ([e], [Word8])
- casMBytes :: (MonadPrim s m, Atomic e) => MBytes p s -> Off e -> e -> e -> m e
- casBoolMBytes :: (MonadPrim s m, Atomic e) => MBytes p s -> Off e -> e -> e -> m Bool
- casBoolFetchMBytes :: (MonadPrim s m, Atomic e) => MBytes p s -> Off e -> e -> e -> m (Bool, e)
- atomicReadMBytes :: (MonadPrim s m, Atomic e) => MBytes p s -> Off e -> m e
- atomicWriteMBytes :: (MonadPrim s m, Atomic e) => MBytes p s -> Off e -> e -> m ()
- atomicModifyMBytes :: (MonadPrim s m, Atomic e) => MBytes p s -> Off e -> (e -> (e, b)) -> m b
- atomicModifyMBytes_ :: (MonadPrim s m, Atomic e) => MBytes p s -> Off e -> (e -> e) -> m ()
- atomicBoolModifyFetchOldMBytes :: (MonadPrim s m, Atomic e) => MBytes p s -> Off e -> (e -> e) -> m e
- atomicModifyFetchOldMBytes :: (MonadPrim s m, Atomic e) => MBytes p s -> Off e -> (e -> e) -> m e
- atomicModifyFetchNewMBytes :: (MonadPrim s m, Atomic e) => MBytes p s -> Off e -> (e -> e) -> m e
- atomicAddFetchOldMBytes :: (MonadPrim s m, AtomicCount e) => MBytes p s -> Off e -> e -> m e
- atomicAddFetchNewMBytes :: (MonadPrim s m, AtomicCount e) => MBytes p s -> Off e -> e -> m e
- atomicSubFetchOldMBytes :: (MonadPrim s m, AtomicCount e) => MBytes p s -> Off e -> e -> m e
- atomicSubFetchNewMBytes :: (MonadPrim s m, AtomicCount e) => MBytes p s -> Off e -> e -> m e
- atomicAndFetchOldMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e
- atomicAndFetchNewMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e
- atomicNandFetchOldMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e
- atomicNandFetchNewMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e
- atomicOrFetchOldMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e
- atomicOrFetchNewMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e
- atomicXorFetchOldMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e
- atomicXorFetchNewMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e
- atomicNotFetchOldMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> m e
- atomicNotFetchNewMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> m e
- prefetchBytes0 :: (MonadPrim s m, Prim e) => Bytes p -> Off e -> m ()
- prefetchMBytes0 :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> m ()
- prefetchBytes1 :: (MonadPrim s m, Prim e) => Bytes p -> Off e -> m ()
- prefetchMBytes1 :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> m ()
- prefetchBytes2 :: (MonadPrim s m, Prim e) => Bytes p -> Off e -> m ()
- prefetchMBytes2 :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> m ()
- prefetchBytes3 :: (MonadPrim s m, Prim e) => Bytes p -> Off e -> m ()
- prefetchMBytes3 :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> m ()
- module Data.Prim
Mutable
data Bytes (p :: Pinned) Source #
An immutable region of memory which was allocated either as pinned or unpinned.
Constructor is not exported for safety. Violating type level Pinned
kind is very
dangerous. Type safe constructor fromByteArray#
and unwrapper
toByteArray#
should be used instead. As a backdoor, of course,
the actual constructor is available in Data.Prim.Memory.Internal module and specially
unsafe function castPinnedBytes
was crafted.
Instances
toByteArray# :: Bytes p -> ByteArray# Source #
Wrap ByteArray#
into Bytes
fromByteArray# :: ByteArray# -> Bytes Inc Source #
Unwrap Bytes
to get the underlying ByteArray#
.
emptyBytes :: Bytes p Source #
isEmptyBytes :: Bytes p -> Bool Source #
createBytes :: forall p e b s m. (Prim e, Typeable p, MonadPrim s m) => Count e -> (MBytes p s -> m b) -> m (b, Bytes p) Source #
Allocated memory is not cleared, so make sure to fill it in properly, otherwise you might find some garbage there.
createBytes_ :: forall p e b s m. (Prim e, Typeable p, MonadPrim s m) => Count e -> (MBytes p s -> m b) -> m (Bytes p) Source #
createBytesST :: forall p e b. (Prim e, Typeable p) => Count e -> (forall s. MBytes p s -> ST s b) -> (b, Bytes p) Source #
createBytesST_ :: forall p e b. (Prim e, Typeable p) => Count e -> (forall s. MBytes p s -> ST s b) -> Bytes p Source #
Pinness
In Haskell there is a distinction between pinned or unpinned memory.
Pinned memory is such, when allocated, it is guaranteed not to move throughout the lifetime of a program. In other words the address pointer that refers to allocated bytes will not change until it gets garbage collected because it is no longer referenced by anything. Unpinned memory on the other hand can be moved around during GC, which helps to reduce memory fragmentation.
Pinned/unpinnned choice during allocation is a bit of a lie, because when attempt is
made to allocate memory as unpinned, but requested size is a bit more than a certain
threashold (somewhere around 3KiB) it might still be allocated as pinned. Because of
that fact through out the "primal" universe there is a distinction between memory that
is either
or Pin
ned
.Inc
onclusive
It is possible to use one of toPinnedBytes
or
toPinnedMBytes
to get a conclusive type.
Since: 0.1.0
isPinnedBytes :: Bytes p -> Bool Source #
isPinnedMBytes :: MBytes p d -> Bool Source #
Mutable
data MBytes (p :: Pinned) s Source #
Mutable region of memory which was allocated either as pinned or unpinned.
Constructor is not exported for safety. Violating type level Pinned
kind is very
dangerous. Type safe constructor fromMutableByteArray#
and
unwrapper toMutableByteArray#
should be used instead. As a
backdoor, of course, the actual constructor is available in Data.Prim.Memory.Internal
module and specially unsafe function castPinnedMBytes
was crafted.
Instances
toMutableByteArray# :: MBytes p s -> MutableByteArray# s Source #
Wrap MutableByteArray#
into MBytes
fromMutableByteArray# :: MutableByteArray# s -> MBytes Inc s Source #
Unwrap MBytes
to get the underlying MutableByteArray#
.
isSameBytes :: Bytes p1 -> Bytes p2 -> Bool Source #
Check if two byte arrays refer to pinned memory and compare their pointers.
isSamePinnedBytes :: Bytes Pin -> Bytes Pin -> Bool Source #
Perform pointer equality on pinned Bytes
.
isSameMBytes :: MBytes p1 s -> MBytes p2 s -> Bool Source #
Check if two mutable bytes pointers refer to the same memory
countBytes :: Prim e => Bytes p -> Count e Source #
How many elements of type a
fits into bytes completely. In order to get a possible
count of leftover bytes use countRemBytes
countRemBytes :: forall e p. Prim e => Bytes p -> (Count e, Count Word8) Source #
Get the count of elements of type a
that can fit into bytes as well as the slack
number of bytes that would be leftover in case when total number of bytes available is
not exactly divisable by the size of the element that will be stored in the memory
chunk.
compareByteOffBytes :: Prim e => Bytes p1 -> Off Word8 -> Bytes p2 -> Off Word8 -> Count e -> Ordering Source #
Mutable
To/From immutable
Construction
allocMBytes :: forall p e s m. (Typeable p, Prim e, MonadPrim s m) => Count e -> m (MBytes p s) Source #
singletonMBytes :: forall e p m s. (Prim e, Typeable p, MonadPrim s m) => e -> m (MBytes p s) Source #
shrinkMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> Count e -> m () Source #
Shrink mutable bytes to new specified count of elements. The new count must be less
than or equal to the current count as reported by getCountMBytes
.
resizeMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> Count e -> m (MBytes Inc s) Source #
Attempt to resize mutable bytes in place.
- New bytes might be allocated, with the copy of an old one.
- Old references should not be kept around to allow GC to claim it
- Old references should not be used to avoid undefined behavior
reallocMBytes :: forall e p m s. (MonadPrim s m, Typeable p, Prim e) => MBytes p s -> Count e -> m (MBytes p s) Source #
coerceStateMBytes :: MBytes p s' -> MBytes p s Source #
This function allows the change of state token. Use with care, because it can allow
mutation to escape the ST
monad.
Modifying data
withCloneMBytes :: (MonadPrim s m, Typeable p) => Bytes p -> (MBytes p s -> m a) -> m (a, Bytes p) Source #
withCloneMBytes_ :: (MonadPrim s m, Typeable p) => Bytes p -> (MBytes p s -> m a) -> m (Bytes p) Source #
withCloneMBytesST :: Typeable p => Bytes p -> (forall s. MBytes p s -> ST s a) -> (a, Bytes p) Source #
copyBytesToMBytes :: (MonadPrim s m, Prim e) => Bytes ps -> Off e -> MBytes pd s -> Off e -> Count e -> m () Source #
moveMBytesToMBytes :: (MonadPrim s m, Prim e) => MBytes ps s -> Off e -> MBytes pd s -> Off e -> Count e -> m () Source #
Moving data
Size
getCountMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> m (Count e) Source #
How many elements of type a
fits into bytes completely. In order to get any number
of leftover bytes use countRemBytes
getCountRemOfMBytes :: forall e p s m. (MonadPrim s m, Prim e) => MBytes p s -> m (Count e, Count Word8) Source #
Get the number of elements of type a
that can fit into bytes as well as the slack
number of bytes that would be leftover in case when total number of bytes available is
not exactly divisable by the size of the element that will be stored in the memory
chunk.
Access
zeroMBytes :: MonadPrim s m => MBytes p s -> m () Source #
Fill the mutable array with zeros efficiently.
Ptr
withPtrBytes :: MonadPrim s m => Bytes Pin -> (Ptr e -> m b) -> m b Source #
Pointer access to immutable Bytes
should be for read only purposes, but it is
not enforced. Any mutation will break referential transparency
withNoHaltPtrBytes :: MonadUnliftPrim s m => Bytes Pin -> (Ptr e -> m b) -> m b Source #
Same as withPtrBytes
, but is suitable for actions that don't terminate
withNoHaltPtrMBytes :: MonadUnliftPrim s m => MBytes Pin s -> (Ptr e -> m b) -> m b Source #
toForeignPtrBytes :: Bytes Pin -> ForeignPtr e Source #
toForeignPtrMBytes :: MBytes Pin s -> ForeignPtr e Source #
Conversion
fromListBytesN :: (Prim e, Typeable p) => Count e -> [e] -> (Ordering, Bytes p) Source #
If the list is bigger than the supplied
then Count
aGT
ordering will be
returned, along with the Bytes
fully filled with the prefix of the list. On the other
hand if the list is smaller than the supplied Count
, LT
with partially filled
Bytes
will returned. In the latter case expect some garbage at the end of the
allocated memory, since no attempt is made to zero it out. Exact match obviously
results in an EQ
.
Allocate new memory region and append second bytes region after the first one
toListBytes :: Prim e => Bytes p -> [e] Source #
It is only guaranteed to convert the whole memory to a list whenever the size of allocated memory is exactly divisible by the size of the element, otherwise there will be some slack left unaccounted for.
Atomic
:: (MonadPrim s m, Atomic e) | |
=> MBytes p s | Array to be mutated |
-> Off e | Index is in elements of |
-> e | Expected old value |
-> e | New value |
-> m e |
Perform atomic modification of an element in the MBytes
at the supplied
index. Returns the actual value. Offset is in number of elements,
rather than bytes. Implies a full memory barrier.
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
:: (MonadPrim s m, Atomic e) | |
=> MBytes p s | Array to be mutated |
-> Off e | Index is in elements of |
-> e | Expected old value |
-> e | New value |
-> m (Bool, e) |
Just like casBoolMBytes
, but also returns the actual value, which will match the
supplied expected value if the returned flag is True
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
:: (MonadPrim s m, Atomic e) | |
=> MBytes p s | Array to be mutated |
-> Off e | Index is in elements of |
-> m e |
Perform atomic read of MBytes
at the supplied index. Offset is in number of
elements, rather than bytes. Implies a full memory barrier.
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
:: (MonadPrim s m, Atomic e) | |
=> MBytes p s | Array to be mutated |
-> Off e | Index is in elements of |
-> e | |
-> m () |
Perform a write into MBytes
at the supplied index atomically. Offset is in number
of elements, rather than bytes. Implies a full memory barrier.
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
:: (MonadPrim s m, Atomic e) | |
=> MBytes p s | Array to be mutated |
-> Off e | Index is in elements of |
-> (e -> (e, b)) | Function that is applied to the old value and returns new value
and some artifact of computation |
-> m b |
Perform atomic modification of an element in the MBytes
at the supplied
index. Returns the artifact of computation b
. Offset is in number of elements,
rather than bytes. Implies a full memory barrier.
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
:: (MonadPrim s m, Atomic e) | |
=> MBytes p s | Array to be mutated |
-> Off e | Index is in elements of |
-> (e -> e) | Function that is applied to the old value and returns new value. |
-> m () |
Perform atomic modification of an element in the MBytes
at the supplied
index. Offset is in number of elements, rather than bytes. Implies a full memory
barrier.
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
atomicBoolModifyFetchOldMBytes Source #
:: (MonadPrim s m, Atomic e) | |
=> MBytes p s | Array to be mutated |
-> Off e | Index is in elements of |
-> (e -> e) | Function that is applied to the old value and returns the new value |
-> m e |
Perform atomic modification of an element in the MBytes
at the supplied
index. Returns the previous value. Offset is in number of elements, rather than
bytes. Implies a full memory barrier.
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
atomicModifyFetchOldMBytes Source #
:: (MonadPrim s m, Atomic e) | |
=> MBytes p s | Array to be mutated |
-> Off e | Index is in elements of |
-> (e -> e) | Function that is applied to the old value and returns the new value |
-> m e |
Perform atomic modification of an element in the MBytes
at the supplied
index. Returns the previous value. Offset is in number of elements, rather than
bytes. Implies a full memory barrier.
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
atomicModifyFetchNewMBytes Source #
:: (MonadPrim s m, Atomic e) | |
=> MBytes p s | Array to be mutated |
-> Off e | Index is in elements of |
-> (e -> e) | Function that is applied to the old value and returns the new value |
-> m e |
Perform atomic modification of an element in the MBytes
at the supplied
index. Offset is in number of elements, rather than bytes. Implies a full memory
barrier.
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
Numberic
atomicAddFetchOldMBytes :: (MonadPrim s m, AtomicCount e) => MBytes p s -> Off e -> e -> m e Source #
atomicAddFetchNewMBytes :: (MonadPrim s m, AtomicCount e) => MBytes p s -> Off e -> e -> m e Source #
atomicSubFetchOldMBytes :: (MonadPrim s m, AtomicCount e) => MBytes p s -> Off e -> e -> m e Source #
atomicSubFetchNewMBytes :: (MonadPrim s m, AtomicCount e) => MBytes p s -> Off e -> e -> m e Source #
Binary
atomicAndFetchOldMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e Source #
Binary conjunction (AND) of an element of a MBytes
with the supplied value,
corresponds to (
done atomically. Returns the previous value. Offset
is in number of elements, rather than bytes. Implies a full memory barrier..&.
)
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
atomicAndFetchNewMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e Source #
atomicNandFetchOldMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e Source #
Negation of binary conjunction (NAND) of an element of a MBytes
with the
supplied value, corresponds to \x y ->
done atomically. Returns the previous value. Offset is in number of elements, rather
than bytes. Implies a full memory barrier.complement
(x .&.
y)
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
atomicNandFetchNewMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e Source #
Negation of binary conjunction (NAND) of an element of a MBytes
with the supplied
value, corresponds to \x y ->
done
atomically. Returns the new value. Offset is in number of elements, rather than
bytes. Implies a full memory barrier.complement
(x .&.
y)
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
atomicOrFetchOldMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e Source #
Binary disjunction (OR) of an element of a MBytes
with the supplied value,
corresponds to (
done atomically. Returns the previous value. Offset
is in number of elements, rather than bytes. Implies a full memory barrier..|.
)
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
atomicOrFetchNewMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e Source #
atomicXorFetchOldMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e Source #
Binary exclusive disjunction (XOR) of an element of a MBytes
with the supplied value,
corresponds to
done atomically. Returns the previous value. Offset
is in number of elements, rather than bytes. Implies a full memory barrier.xor
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
atomicXorFetchNewMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> e -> m e Source #
Binary exclusive disjunction (XOR) of an element of a MBytes
with the supplied value,
corresponds to
done atomically. Returns the new value. Offset is
in number of elements, rather than bytes. Implies a full memory barrier.xor
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
atomicNotFetchOldMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> m e Source #
Binary negation (NOT) of an element of a MBytes
, corresponds to
(
done atomically. Returns the previous value. Offset is in
number of elements, rather than bytes. Implies a full memory barrier.complement
)
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
atomicNotFetchNewMBytes :: (MonadPrim s m, AtomicBits e) => MBytes p s -> Off e -> m e Source #
Binary negation (NOT) of an element of a MBytes
, corresponds to
(
done atomically. Returns the new value. Offset is in number
of elements, rather than bytes. Implies a full memory barrier.complement
)
Note - Bounds are not checked, therefore this function is unsafe.
Since: 0.1.0
Prefetch
module Data.Prim