pvar-0.2.0.0: Mutable variable with primitive values

Copyright(c) Alexey Kuleshevich 2020
LicenseBSD3
MaintainerAlexey Kuleshevich <lehins@yandex.ru>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Primitive.PVar.Unsafe

Contents

Description

 
Synopsis

Documentation

data PVar m a Source #

Mutable variable with primitive value.

Since: 0.1.0

Constructors

PVar (MutableByteArray# (PrimState m)) 
Instances
Prim a => Storable (PVar IO a) Source #

poke+peek will result in a new copy of a PVar

Instance details

Defined in Data.Primitive.PVar.Internal

Methods

sizeOf :: PVar IO a -> Int #

alignment :: PVar IO a -> Int #

peekElemOff :: Ptr (PVar IO a) -> Int -> IO (PVar IO a) #

pokeElemOff :: Ptr (PVar IO a) -> Int -> PVar IO a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (PVar IO a) #

pokeByteOff :: Ptr b -> Int -> PVar IO a -> IO () #

peek :: Ptr (PVar IO a) -> IO (PVar IO a) #

poke :: Ptr (PVar IO a) -> PVar IO a -> IO () #

NFData (PVar m a) Source #

Values are already written into PVar in NF, this instance is trivial.

Instance details

Defined in Data.Primitive.PVar.Internal

Methods

rnf :: PVar m a -> () #

Creation

rawPVar :: forall a m. (PrimMonad m, Prim a) => m (PVar m a) Source #

Create a mutable variable in unpinned and unititialized memory

Since: 0.1.0

rawPinnedPVar :: forall a m. (PrimMonad m, Prim a) => m (PVar m a) Source #

Create a mutable variable in pinned memory with uninitialized memory.

Since: 0.1.0

rawAlignedPinnedPVar :: forall a m. (PrimMonad m, Prim a) => m (PVar m a) Source #

Create a mutable variable in pinned uninitialized memory.

Since: 0.1.0

rawStorablePVar :: forall a m. (PrimMonad m, Storable a) => m (PVar m a) 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. (PrimMonad m, Storable a) => m (PVar m a) 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, PrimMonad m) => Ptr a -> m a Source #

Use Storable reading functionality inside the PrimMonad.

Since: 0.1.0

pokePrim :: (Storable a, PrimMonad m) => Ptr a -> a -> m () Source #

Use Storable wrting functionality inside the PrimMonad.

Since: 0.1.0

Conversion

toPtrPVar :: PVar m a -> 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 m a -> 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 IO a -> ForeignPtr a Source #

Convert PVar into a ForeignPtr, very unsafe if not backed by pinned memory.

Since: 0.1.0

Reset

zeroPVar :: (PrimMonad m, Prim a) => PVar m a -> m () Source #

Reset contents of a mutable variable to zero.

Since: 0.1.0

Unpacked opartions

sizeOfPVar# :: forall m a. Prim a => PVar m a -> Int# Source #

Get the size of the mutable variable in bytes as an unpacked integer

Since: 0.1.0

alignmentPVar# :: forall m a. Prim a => PVar m a -> Int# Source #

Get the alignment of the mutable variable in bytes as an unpacked integer

Since: 0.1.0

setPVar# Source #

Arguments

:: (PrimMonad m, Prim a) 
=> PVar m a 
-> Int#

Byte value to fill the PVar with

-> m () 

Fill the contents of mutable variable with byte c

Since: 0.1.0

ByteArray

Atomic operations

atomicModifyIntArray# Source #

Arguments

:: MutableByteArray# d

Array to be mutated

-> Int#

Index in number of Int# elements into the MutableByteArray#

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

Arguments

:: MutableByteArray# d

Array to be mutated

-> Int#

Index in number of Int# elements into the MutableByteArray#

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

Arguments

:: (PrimMonad m, Prim a) 
=> ByteArray

Source array

-> Int

Offset in number of elements into the array

-> PVar m a 
-> 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 #

Arguments

:: (PrimMonad m, Prim a) 
=> MutableByteArray (PrimState m) 
-> Int

Offset in number of elements into the array

-> PVar m a 
-> 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 #

Arguments

:: (PrimMonad m, Prim a) 
=> PVar m a 
-> MutableByteArray (PrimState m) 
-> 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.

Helpers

showsType :: Typeable t => proxy t -> ShowS Source #

Show the type name

unI# :: Int -> Int# Source #

Unwrap the primitive Int

Since: 0.1.0