Copyright | (c) Alexey Kuleshevich 2020 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data PVar a s = PVar (MutableByteArray# s)
- rawPVar :: forall a m s. (MonadPrim s m, Prim a) => m (PVar a s)
- rawPinnedPVar :: forall a m s. (MonadPrim s m, Prim a) => m (PVar a s)
- rawAlignedPinnedPVar :: forall a m s. (MonadPrim s m, Prim a) => m (PVar a s)
- rawStorablePVar :: forall a m s. (MonadPrim s m, Storable a) => m (PVar a s)
- rawAlignedStorablePVar :: forall a m s. (MonadPrim s m, Storable a) => m (PVar a s)
- peekPrim :: (Storable a, MonadPrim s m) => Ptr a -> m a
- pokePrim :: (Storable a, MonadPrim s m) => Ptr a -> a -> m ()
- toPtrPVar :: PVar a s -> Maybe (Ptr a)
- unsafeToPtrPVar :: PVar a s -> Ptr a
- unsafeToForeignPtrPVar :: PVar a s -> ForeignPtr a
- zeroPVar :: (MonadPrim s m, Prim a) => PVar a s -> m ()
- sizeOfPVar# :: forall a s. Prim a => PVar a s -> Int#
- alignmentPVar# :: forall a s. Prim a => PVar a s -> Int#
- setPVar# :: (MonadPrim s m, Prim a) => PVar a s -> Int# -> m ()
- atomicModifyIntArray# :: MutableByteArray# d -> Int# -> (Int# -> (#Int#, b#)) -> State# d -> (#State# d, b#)
- atomicModifyIntArray_# :: MutableByteArray# d -> Int# -> (Int# -> Int#) -> State# d -> State# d
- copyFromByteArrayPVar :: (MonadPrim s m, Prim a) => ByteArray -> Int -> PVar a s -> m ()
- copyFromMutableByteArrayPVar :: (MonadPrim s m, Prim a) => MutableByteArray s -> Int -> PVar a s -> m ()
- copyPVarToMutableByteArray :: (MonadPrim s m, Prim a) => PVar a s -> MutableByteArray s -> Int -> m ()
- isByteArrayPinned :: ByteArray -> Bool
- isMutableByteArrayPinned :: MutableByteArray s -> Bool
- isByteArrayPinned# :: ByteArray# -> Int#
- isMutableByteArrayPinned# :: MutableByteArray# d -> Int#
- showsType :: Typeable t => proxy t -> ShowS
- unI# :: Int -> Int#
Documentation
Mutable variable with primitive value.
Since: 0.1.0
Instances
Prim a => Storable (PVar a RealWorld) Source # | |
Defined in Data.Primitive.PVar.Internal sizeOf :: PVar a RealWorld -> Int # alignment :: PVar a RealWorld -> Int # peekElemOff :: Ptr (PVar a RealWorld) -> Int -> IO (PVar a RealWorld) # pokeElemOff :: Ptr (PVar a RealWorld) -> Int -> PVar a RealWorld -> IO () # peekByteOff :: Ptr b -> Int -> IO (PVar a RealWorld) # pokeByteOff :: Ptr b -> Int -> PVar a RealWorld -> IO () # peek :: Ptr (PVar a RealWorld) -> IO (PVar a RealWorld) # poke :: Ptr (PVar a RealWorld) -> PVar a RealWorld -> IO () # | |
NFData (PVar a s) Source # | Values are already written into |
Defined in Data.Primitive.PVar.Internal |
Creation
rawPVar :: forall a m s. (MonadPrim s m, Prim a) => m (PVar a s) Source #
Create a mutable variable in unpinned and unititialized memory
Since: 0.1.0
rawPinnedPVar :: forall a m s. (MonadPrim s m, Prim a) => m (PVar a s) Source #
Create a mutable variable in pinned memory with uninitialized memory.
Since: 0.1.0
rawAlignedPinnedPVar :: forall a m s. (MonadPrim s m, Prim a) => m (PVar a s) Source #
Create a mutable variable in pinned uninitialized memory.
Since: 0.1.0
rawStorablePVar :: forall a m s. (MonadPrim s m, Storable a) => m (PVar a s) Source #
Create a mutable variable in pinned uninitialized memory using Storable interface for getting the number of bytes for memory allocation.
Since: 0.1.0
rawAlignedStorablePVar :: forall a m s. (MonadPrim s m, Storable a) => m (PVar a s) Source #
Create a mutable variable in pinned uninitialized memory using Storable interface for getting the number of bytes for memory allocation and alignement.
Since: 0.1.0
Access
peekPrim :: (Storable a, MonadPrim s m) => Ptr a -> m a Source #
Use Storable
reading functionality inside the PrimMonad
.
Since: 0.1.0
pokePrim :: (Storable a, MonadPrim s m) => Ptr a -> a -> m () Source #
Use Storable
wrting functionality inside the PrimMonad
.
Since: 0.1.0
Conversion
toPtrPVar :: PVar a s -> Maybe (Ptr a) Source #
Extract the address to the mutable variable, but only if it is backed by pinned
memory. It is unsafe because even for pinned memory memory can be deallocated if
associated PVar
goes out of scope. Use withPtrPVar
or
toForeignPtr
instead.
Since: 0.1.0
unsafeToPtrPVar :: PVar a s -> Ptr a Source #
Get the address to the contents. This is highly unsafe, espcially if memory is not pinned
Since: 0.1.0
unsafeToForeignPtrPVar :: PVar a s -> ForeignPtr a Source #
Convert PVar
into a ForeignPtr
, very unsafe if not backed by pinned memory.
Since: 0.1.0
Reset
zeroPVar :: (MonadPrim s m, Prim a) => PVar a s -> m () Source #
Reset contents of a mutable variable to zero.
Since: 0.1.0
Unpacked opartions
sizeOfPVar# :: forall a s. Prim a => PVar a s -> Int# Source #
Get the size of the mutable variable in bytes as an unpacked integer
Since: 0.1.0
alignmentPVar# :: forall a s. Prim a => PVar a s -> Int# Source #
Get the alignment of the mutable variable in bytes as an unpacked integer
Since: 0.1.0
Fill the contents of mutable variable with byte c
Since: 0.1.0
ByteArray
Atomic operations
atomicModifyIntArray# Source #
:: MutableByteArray# d | Array to be mutated |
-> Int# | Index in number of |
-> (Int# -> (#Int#, b#)) | Function to be applied atomically to the element |
-> State# d | Starting state |
-> (#State# d, b#) |
Using casIntArray#
perform atomic modification of an integer element in a
MutableByteArray#
. Implies a full memory barrier.
Since: 0.1.0
atomicModifyIntArray_# Source #
:: MutableByteArray# d | Array to be mutated |
-> Int# | Index in number of |
-> (Int# -> Int#) | Function to be applied atomically to the element |
-> State# d | Starting state |
-> State# d |
Uses casIntArray#
to perform atomic modification of an integer element in a
MutableByteArray#
. Implies a full memory barrier.
Since: 0.1.0
Memory copying
copyFromByteArrayPVar Source #
:: (MonadPrim s m, Prim a) | |
=> ByteArray | Source array |
-> Int | Offset in number of elements into the array |
-> PVar a s | |
-> m () |
Copy the value from a frozen ByteArray
into a mutable variable at specified
index. Index of array is not checked and can result in an unchecked exception when
incorrect
Since: 0.1.0
copyFromMutableByteArrayPVar Source #
:: (MonadPrim s m, Prim a) | |
=> MutableByteArray s | |
-> Int | Offset in number of elements into the array |
-> PVar a s | |
-> m () |
Copy the value from MutableByteArray at specified index into the mutable variable. Index of array is not checked and can result in an unchecked exception when incorrect
Since: 0.1.0
copyPVarToMutableByteArray Source #
:: (MonadPrim s m, Prim a) | |
=> PVar a s | |
-> MutableByteArray s | |
-> Int | Offset in number of elements into the array |
-> m () |
Copy the value from a mutable variable into a mutable array at the specified index. Index of array is not checked and can result in an unchecked exception when incorrect
Since: 0.1.0
Check if memory is pinned
isByteArrayPinned :: ByteArray -> Bool Source #
Check whether or not the ByteArray
is pinned.
Note - This function uses GHC built-in functions for GHC 8.2 and newer, but for older versions it fallsback onto custom implementation.
Since: 0.1.1
isMutableByteArrayPinned :: MutableByteArray s -> Bool Source #
Check whether or not the MutableByteArray
is pinned.
Note - This function uses GHC built-in functions for GHC 8.2 and newer, but for older versions it fallsback onto custom implementation.
Since: 0.1.1
Primitive versions
isByteArrayPinned# :: ByteArray# -> Int# #
Determine whether a ByteArray#
is guaranteed not to move during GC.
isMutableByteArrayPinned# :: MutableByteArray# d -> Int# #
Determine whether a MutableByteArray#
is guaranteed not to move
during GC.