primal-memory-0.1.0.0: Unified interface for memory managemenet.

Copyright(c) Alexey Kuleshevich 2020
LicenseBSD3
MaintainerAlexey Kuleshevich <alexey@kuleshevi.ch>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Prim.Memory.Bytes

Contents

Description

 
Synopsis

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
PtrAccess s (Bytes Pin) Source #

Read-only access, but it is not enforced.

Instance details

Defined in Data.Prim.Memory.ForeignPtr

Methods

toForeignPtr :: MonadPrim s m => Bytes Pin -> m (ForeignPtr a) Source #

withPtrAccess :: MonadPrim s m => Bytes Pin -> (Ptr a -> m b) -> m b Source #

withNoHaltPtrAccess :: MonadUnliftPrim s m => Bytes Pin -> (Ptr a -> m b) -> m b Source #

Typeable p => IsList (Bytes p) Source # 
Instance details

Defined in Data.Prim.Memory.Internal

Associated Types

type Item (Bytes p) :: Type #

Methods

fromList :: [Item (Bytes p)] -> Bytes p #

fromListN :: Int -> [Item (Bytes p)] -> Bytes p #

toList :: Bytes p -> [Item (Bytes p)] #

Eq (Bytes p) Source # 
Instance details

Defined in Data.Prim.Memory.Internal

Methods

(==) :: Bytes p -> Bytes p -> Bool #

(/=) :: Bytes p -> Bytes p -> Bool #

Ord (Bytes p) Source # 
Instance details

Defined in Data.Prim.Memory.Internal

Methods

compare :: Bytes p -> Bytes p -> Ordering #

(<) :: Bytes p -> Bytes p -> Bool #

(<=) :: Bytes p -> Bytes p -> Bool #

(>) :: Bytes p -> Bytes p -> Bool #

(>=) :: Bytes p -> Bytes p -> Bool #

max :: Bytes p -> Bytes p -> Bytes p #

min :: Bytes p -> Bytes p -> Bytes p #

Show (Bytes p) Source # 
Instance details

Defined in Data.Prim.Memory.Internal

Methods

showsPrec :: Int -> Bytes p -> ShowS #

show :: Bytes p -> String #

showList :: [Bytes p] -> ShowS #

Typeable p => Semigroup (Bytes p) Source # 
Instance details

Defined in Data.Prim.Memory.Internal

Methods

(<>) :: Bytes p -> Bytes p -> Bytes p #

sconcat :: NonEmpty (Bytes p) -> Bytes p #

stimes :: Integral b => b -> Bytes p -> Bytes p #

Typeable p => Monoid (Bytes p) Source # 
Instance details

Defined in Data.Prim.Memory.Internal

Methods

mempty :: Bytes p #

mappend :: Bytes p -> Bytes p -> Bytes p #

mconcat :: [Bytes p] -> Bytes p #

NFData (Bytes p) Source # 
Instance details

Defined in Data.Prim.Memory.Bytes.Internal

Methods

rnf :: Bytes p -> () #

MemRead (Bytes p) Source # 
Instance details

Defined in Data.Prim.Memory.Internal

Methods

byteCountMem :: Bytes p -> Count Word8 Source #

indexOffMem :: Prim e => Bytes p -> Off e -> e Source #

indexByteOffMem :: Prim e => Bytes p -> Off Word8 -> e Source #

copyByteOffToMBytesMem :: (MonadPrim s m, Prim e) => Bytes p -> Off Word8 -> MBytes p0 s -> Off Word8 -> Count e -> m () Source #

copyByteOffToPtrMem :: (MonadPrim s m, Prim e) => Bytes p -> Off Word8 -> Ptr e -> Off Word8 -> Count e -> m () Source #

compareByteOffToPtrMem :: (MonadPrim s m, Prim e) => Bytes p -> Off Word8 -> Ptr e -> Off Word8 -> Count e -> m Ordering Source #

compareByteOffToBytesMem :: (MonadPrim s m, Prim e) => Bytes p -> Off Word8 -> Bytes p0 -> Off Word8 -> Count e -> m Ordering Source #

compareByteOffMem :: (MemRead r', Prim e) => r' -> Off Word8 -> Bytes p -> Off Word8 -> Count e -> Ordering Source #

type Item (Bytes p) Source # 
Instance details

Defined in Data.Prim.Memory.Internal

type Item (Bytes p) = Word8

fromByteArray# :: ByteArray# -> Bytes Inc Source #

Unwrap Bytes to get the underlying ByteArray#.

eqBytes :: Bytes p1 -> Bytes p2 -> Bool Source #

singletonBytes :: forall e p. (Prim e, Typeable p) => e -> Bytes p 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

data Pinned Source #

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 Pinned or Inconclusive.

It is possible to use one of toPinnedBytes or toPinnedMBytes to get a conclusive type.

Since: 0.1.0

Constructors

Pin 
Inc 

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
PtrAccess s (MBytes Pin s) Source # 
Instance details

Defined in Data.Prim.Memory.ForeignPtr

Methods

toForeignPtr :: MonadPrim s m => MBytes Pin s -> m (ForeignPtr a) Source #

withPtrAccess :: MonadPrim s m => MBytes Pin s -> (Ptr a -> m b) -> m b Source #

withNoHaltPtrAccess :: MonadUnliftPrim s m => MBytes Pin s -> (Ptr a -> m b) -> m b Source #

MemWrite (MBytes p) Source # 
Instance details

Defined in Data.Prim.Memory.Internal

Methods

readOffMem :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> m e Source #

readByteOffMem :: (MonadPrim s m, Prim e) => MBytes p s -> Off Word8 -> m e Source #

writeOffMem :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> e -> m () Source #

writeByteOffMem :: (MonadPrim s m, Prim e) => MBytes p s -> Off Word8 -> e -> m () Source #

moveByteOffToMBytesMem :: (MonadPrim s m, Prim e) => MBytes p s -> Off Word8 -> MBytes p0 s -> Off Word8 -> Count e -> m () Source #

moveByteOffToPtrMem :: (MonadPrim s m, Prim e) => MBytes p s -> Off Word8 -> Ptr e -> Off Word8 -> Count e -> m () Source #

copyByteOffMem :: (MonadPrim s m, MemRead r, Prim e) => r -> Off Word8 -> MBytes p s -> Off Word8 -> Count e -> m () Source #

moveByteOffMem :: (MonadPrim s m, MemWrite w', Prim e) => w' s -> Off Word8 -> MBytes p s -> Off Word8 -> Count e -> m () Source #

setMem :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> Count e -> e -> m () Source #

Typeable p => MemAlloc (MBytes p) Source # 
Instance details

Defined in Data.Prim.Memory.Internal

Associated Types

type FrozenMem (MBytes p) = (fa :: Type) Source #

Methods

getByteCountMem :: MonadPrim s m => MBytes p s -> m (Count Word8) Source #

allocByteCountMem :: MonadPrim s m => Count Word8 -> m (MBytes p s) Source #

thawMem :: MonadPrim s m => FrozenMem (MBytes p) -> m (MBytes p s) Source #

freezeMem :: MonadPrim s m => MBytes p s -> m (FrozenMem (MBytes p)) Source #

resizeMem :: (MonadPrim s m, Prim e) => MBytes p s -> Count e -> m (MBytes p s) Source #

NFData (MBytes p s) Source # 
Instance details

Defined in Data.Prim.Memory.Bytes.Internal

Methods

rnf :: MBytes p s -> () #

type FrozenMem (MBytes p) Source # 
Instance details

Defined in Data.Prim.Memory.Internal

type FrozenMem (MBytes p) = Bytes p

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

indexOffBytes :: Prim e => Bytes p -> Off e -> e Source #

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.

compareBytes :: Prim e => Bytes p1 -> Off e -> Bytes p2 -> Off e -> Count e -> Ordering Source #

Mutable

To/From immutable

thawBytes :: MonadPrim s m => Bytes p -> m (MBytes p s) Source #

freezeMBytes :: MonadPrim s m => MBytes p s -> m (Bytes p) Source #

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 #

allocAlignedMBytes Source #

Arguments

:: (MonadPrim s m, Prim e) 
=> Count e

Size in number of bytes

-> m (MBytes Pin s) 

callocMBytes :: (MonadPrim s m, Prim e, Typeable p) => Count e -> m (MBytes p s) Source #

callocAlignedMBytes Source #

Arguments

:: (MonadPrim s m, Prim e) 
=> Count e

Size in number of bytes

-> m (MBytes Pin s) 

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

cloneMBytes :: (MonadPrim s m, Typeable p) => MBytes p s -> m (MBytes p s) Source #

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 #

withCloneMBytesST_ :: Typeable p => Bytes p -> (forall s. MBytes p s -> ST s a) -> Bytes p Source #

loadListMBytes :: (MonadPrim s m, Prim e) => [e] -> MBytes p s -> m Ordering Source #

Returns EQ if the full list did fit into the supplied memory chunk exactly. Otherwise it will return either LT if the list was smaller than allocated memory or GT if the list was bigger than the available memory and did not fit into MBytes.

loadListMBytes_ :: (MonadPrim s m, Prim e) => [e] -> MBytes p s -> m () 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

readOffMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> m e Source #

readByteOffMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> Off Word8 -> m e Source #

writeOffMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> e -> m () Source #

writeByteOffMBytes :: (MonadPrim s m, Prim e) => MBytes p s -> Off Word8 -> e -> m () Source #

setMBytes Source #

Arguments

:: (MonadPrim s m, Prim e) 
=> MBytes p s

Chunk of memory to fill

-> Off e

Offset in number of elements

-> Count e

Number of cells to fill

-> e

A value to fill the cells with

-> m () 

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

withPtrMBytes :: MonadPrim s m => MBytes Pin s -> (Ptr e -> m b) -> m b Source #

withNoHaltPtrMBytes :: MonadUnliftPrim s m => MBytes Pin s -> (Ptr e -> m b) -> m b Source #

Conversion

fromListBytes :: forall e p. (Prim e, Typeable p) => [e] -> Bytes p Source #

fromListBytesN :: (Prim e, Typeable p) => Count e -> [e] -> (Ordering, Bytes p) Source #

If the list is bigger than the supplied Count a then GT 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.

fromListBytesN_ :: (Prim e, Typeable p) => Count e -> [e] -> Bytes p Source #

appendBytes Source #

Arguments

:: Typeable p 
=> Bytes p1

First memory region

-> Bytes p2

Second memory region

-> Bytes p 

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.

toListSlackBytes :: Prim e => Bytes p -> ([e], [Word8]) Source #

Atomic

casMBytes Source #

Arguments

:: (MonadPrim s m, Atomic e) 
=> MBytes p s

Array to be mutated

-> Off e

Index is in elements of a, rather than bytes.

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

casBoolMBytes Source #

Arguments

:: (MonadPrim s m, Atomic e) 
=> MBytes p s

Array to be mutated

-> Off e

Index is in elements of a, rather than bytes.

-> e

Expected old value

-> e

New value

-> m Bool 

Perform atomic modification of an element in the MBytes at the supplied index. Returns True if swap was successfull and false otherwise. 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

casBoolFetchMBytes Source #

Arguments

:: (MonadPrim s m, Atomic e) 
=> MBytes p s

Array to be mutated

-> Off e

Index is in elements of a, rather than bytes.

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

atomicReadMBytes Source #

Arguments

:: (MonadPrim s m, Atomic e) 
=> MBytes p s

Array to be mutated

-> Off e

Index is in elements of a, rather than bytes.

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

atomicWriteMBytes Source #

Arguments

:: (MonadPrim s m, Atomic e) 
=> MBytes p s

Array to be mutated

-> Off e

Index is in elements of a, rather than bytes.

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

atomicModifyMBytes Source #

Arguments

:: (MonadPrim s m, Atomic e) 
=> MBytes p s

Array to be mutated

-> Off e

Index is in elements of a, rather than bytes.

-> (e -> (e, b))

Function that is applied to the old value and returns new value and some artifact of computation b

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

atomicModifyMBytes_ Source #

Arguments

:: (MonadPrim s m, Atomic e) 
=> MBytes p s

Array to be mutated

-> Off e

Index is in elements of a, rather than bytes.

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

Arguments

:: (MonadPrim s m, Atomic e) 
=> MBytes p s

Array to be mutated

-> Off e

Index is in elements of a, rather than bytes.

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

Arguments

:: (MonadPrim s m, Atomic e) 
=> MBytes p s

Array to be mutated

-> Off e

Index is in elements of a, rather than bytes.

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

Arguments

:: (MonadPrim s m, Atomic e) 
=> MBytes p s

Array to be mutated

-> Off e

Index is in elements of a, rather than bytes.

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

Add a numeric value to 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.

Note - Bounds are not checked, therefore this function is unsafe.

Since: 0.1.0

atomicAddFetchNewMBytes :: (MonadPrim s m, AtomicCount e) => MBytes p s -> Off e -> e -> m e Source #

Add a numeric value to 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.

Note - Bounds are not checked, therefore this function is unsafe.

Since: 0.1.0

atomicSubFetchOldMBytes :: (MonadPrim s m, AtomicCount e) => MBytes p s -> Off e -> e -> m e Source #

Subtract a numeric value from 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.

Note - Bounds are not checked, therefore this function is unsafe.

Since: 0.1.0

atomicSubFetchNewMBytes :: (MonadPrim s m, AtomicCount e) => MBytes p s -> Off e -> e -> m e Source #

Subtract a numeric value from 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.

Note - Bounds are not checked, therefore this function is unsafe.

Since: 0.1.0

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 #

Binary conjunction (AND) 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.

Note - Bounds are not checked, therefore this function is unsafe.

Since: 0.1.0

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 -> complement (x .&. y) 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

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 -> complement (x .&. y) done atomically. Returns the new 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

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 #

Binary disjunction (OR) 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.

Note - Bounds are not checked, therefore this function is unsafe.

Since: 0.1.0

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

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 xor done atomically. Returns the new 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

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 (complement) 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

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 (complement) done atomically. Returns the new 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

Prefetch

prefetchBytes0 :: (MonadPrim s m, Prim e) => Bytes p -> Off e -> m () Source #

prefetchMBytes0 :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> m () Source #

prefetchBytes1 :: (MonadPrim s m, Prim e) => Bytes p -> Off e -> m () Source #

prefetchMBytes1 :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> m () Source #

prefetchBytes2 :: (MonadPrim s m, Prim e) => Bytes p -> Off e -> m () Source #

prefetchMBytes2 :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> m () Source #

prefetchBytes3 :: (MonadPrim s m, Prim e) => Bytes p -> Off e -> m () Source #

prefetchMBytes3 :: (MonadPrim s m, Prim e) => MBytes p s -> Off e -> m () Source #

module Data.Prim

Helpers