primal-memory-0.3.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.ForeignPtr

Description

 
Synopsis

Documentation

class PtrAccess s p where Source #

For memory allocated as pinned it is possible to operate on it with a Ptr. Any data type that is backed by such memory can have a PtrAccess instance. The simplest way is to convert it to a ForeignPtr and other functions will come for free.

Minimal complete definition

toForeignPtr

Methods

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

Convert to ForeignPtr.

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

Apply an action to the raw memory Ptr to which the data type point to. Type of data stored in memory is left ambiguous intentionaly, so that the user can choose how to treat the memory content.

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

See this GHC issue #17746 and related to it in order to get more insight why this is needed.

Instances

Instances details
PtrAccess s ByteString Source #

Read-only access, but immutability is not enforced.

Instance details

Defined in Data.Prim.Memory.ForeignPtr

Methods

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

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

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

PtrAccess RealWorld (ForeignPtr a) Source # 
Instance details

Defined in Data.Prim.Memory.ForeignPtr

PtrAccess s (Bytes 'Pin) Source #

Read-only access, but immutability 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 #

PtrAccess s (MByteString s) Source # 
Instance details

Defined in Data.Prim.Memory.ForeignPtr

Methods

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

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

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

PtrAccess s (Addr e) Source #

Read-only access, but it is not enforced.

Instance details

Defined in Data.Prim.Memory.Addr

Methods

toForeignPtr :: MonadPrim s m => Addr e -> m (ForeignPtr a) Source #

withPtrAccess :: MonadPrim s m => Addr e -> (Ptr a -> m b) -> m b Source #

withNoHaltPtrAccess :: MonadUnliftPrim s m => Addr e -> (Ptr a -> m b) -> m b Source #

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 #

PtrAccess s (PArray 'Pin e) Source #

Read-only access, but it is not enforced.

Instance details

Defined in Data.Prim.Memory.PArray

Methods

toForeignPtr :: MonadPrim s m => PArray 'Pin e -> m (ForeignPtr a) Source #

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

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

PtrAccess s (MAddr e s) Source # 
Instance details

Defined in Data.Prim.Memory.Addr

Methods

toForeignPtr :: MonadPrim s m => MAddr e s -> m (ForeignPtr a) Source #

withPtrAccess :: MonadPrim s m => MAddr e s -> (Ptr a -> m b) -> m b Source #

withNoHaltPtrAccess :: MonadUnliftPrim s m => MAddr e s -> (Ptr a -> m b) -> m b Source #

PtrAccess s (PMArray 'Pin e s) Source # 
Instance details

Defined in Data.Prim.Memory.PArray

Methods

toForeignPtr :: MonadPrim s m => PMArray 'Pin e s -> m (ForeignPtr a) Source #

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

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

ForeignPtr

data ForeignPtr a #

The type ForeignPtr represents references to objects that are maintained in a foreign language, i.e., that are not part of the data structures usually managed by the Haskell storage manager. The essential difference between ForeignPtrs and vanilla memory references of type Ptr a is that the former may be associated with finalizers. A finalizer is a routine that is invoked when the Haskell storage manager detects that - within the Haskell heap and stack - there are no more references left that are pointing to the ForeignPtr. Typically, the finalizer will, then, invoke routines in the foreign language that free the resources bound by the foreign object.

The ForeignPtr is parameterised in the same way as Ptr. The type argument of ForeignPtr should normally be an instance of class Storable.

Instances

Instances details
PtrAccess RealWorld (ForeignPtr a) Source # 
Instance details

Defined in Data.Prim.Memory.ForeignPtr

Eq (ForeignPtr a)

Since: base-2.1

Instance details

Defined in GHC.ForeignPtr

Methods

(==) :: ForeignPtr a -> ForeignPtr a -> Bool #

(/=) :: ForeignPtr a -> ForeignPtr a -> Bool #

Ord (ForeignPtr a)

Since: base-2.1

Instance details

Defined in GHC.ForeignPtr

Show (ForeignPtr a)

Since: base-2.1

Instance details

Defined in GHC.ForeignPtr

MemWrite (MemState (ForeignPtr a)) Source # 
Instance details

Defined in Data.Prim.Memory.Internal

Methods

isSameMutMem :: MemState (ForeignPtr a) s -> MemState (ForeignPtr a) s -> Bool

readOffMutMem :: (MonadPrim s m, Prim e) => MemState (ForeignPtr a) s -> Off e -> m e Source #

readByteOffMutMem :: (MonadPrim s m, Prim e) => MemState (ForeignPtr a) s -> Off Word8 -> m e Source #

writeOffMutMem :: (MonadPrim s m, Prim e) => MemState (ForeignPtr a) s -> Off e -> e -> m () Source #

writeByteOffMutMem :: (MonadPrim s m, Prim e) => MemState (ForeignPtr a) s -> Off Word8 -> e -> m () Source #

moveByteOffToMBytesMutMem :: forall s m e (p :: Pinned). (MonadPrim s m, Prim e) => MemState (ForeignPtr a) s -> Off Word8 -> MBytes p s -> Off Word8 -> Count e -> m () Source #

moveByteOffToPtrMutMem :: (MonadPrim s m, Prim e) => MemState (ForeignPtr a) s -> Off Word8 -> Ptr e -> Off Word8 -> Count e -> m () Source #

copyByteOffMem :: (MonadPrim s m, MemRead mr, Prim e) => mr -> Off Word8 -> MemState (ForeignPtr a) s -> Off Word8 -> Count e -> m () Source #

moveByteOffMutMem :: (MonadPrim s m, MemWrite mw', Prim e) => mw' s -> Off Word8 -> MemState (ForeignPtr a) s -> Off Word8 -> Count e -> m () Source #

setMutMem :: (MonadPrim s m, Prim e) => MemState (ForeignPtr a) s -> Off e -> Count e -> e -> m () Source #

castForeignPtr :: ForeignPtr a -> ForeignPtr b #

This function casts a ForeignPtr parameterised by one type into another type.

unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a #

This function extracts the pointer component of a foreign pointer. This is a potentially dangerous operations, as if the argument to unsafeForeignPtrToPtr is the last usage occurrence of the given foreign pointer, then its finalizer(s) will be run, which potentially invalidates the plain pointer just obtained. Hence, touchForeignPtr must be used wherever it has to be guaranteed that the pointer lives on - i.e., has another usage occurrence.

To avoid subtle coding errors, hand written marshalling code should preferably use withForeignPtr rather than combinations of unsafeForeignPtrToPtr and touchForeignPtr. However, the latter routines are occasionally preferred in tool generated marshalling code.

Pointer arithmetic

plusOffForeignPtr :: Prim e => ForeignPtr e -> Off e -> ForeignPtr e Source #

Advances the given address by the given offset in number of elemeents. This operation does not affect associated finalizers in any way.

Since: 0.1.0

plusByteOffForeignPtr :: ForeignPtr e -> Off Word8 -> ForeignPtr e Source #

Advances the given address by the given offset in bytes. This operation does not affect associated finalizers in any way.

Since: 0.1.0

minusOffForeignPtr :: Prim e => ForeignPtr e -> ForeignPtr e -> Off e Source #

Find the offset in number of elements that is between the two pointers by subtracting one address from another and dividing the result by the size of an element.

Since: 0.1.0

minusOffRemForeignPtr :: Prim e => ForeignPtr e -> ForeignPtr e -> (Off e, Off Word8) Source #

Same as minusOffForeignPtr, but will also return the remainder in bytes that is left over.

Since: 0.1.0

minusByteOffForeignPtr :: ForeignPtr e -> ForeignPtr e -> Off Word8 Source #

Find the offset in bytes that is between the two pointers by subtracting one address from another.

Since: 0.1.0

withForeignPtr :: MonadPrim s m => ForeignPtr e -> (Ptr e -> m b) -> m b Source #

Apply an action to the raw pointer. It is unsafe to return the actual pointer back from the action because memory itself might get garbage collected or cleaned up by finalizers.

It is also important not to run non-terminating actions, because GHC can optimize away the logic that runs after the action and GC will happen before the action get's a chance to finish resulting in corrupt memory. Whenever you have an action that runs an infinite loop or ends in an exception throwing, make sure to use withNoHaltForeignPtr instead.

withNoHaltForeignPtr :: MonadUnliftPrim s m => ForeignPtr e -> (Ptr e -> m b) -> m b Source #

Same thing as withForeignPtr except it should be used for never ending actions. See withNoHaltPtrAccess for more information on how this differes from withForeignPtr.

Since: 0.1.0

PlainPtr

mallocPlainForeignPtr :: forall e m s. (MonadPrim s m, Prim e) => m (ForeignPtr e) Source #

Similar to mallocPlainForeignPtr, except instead of Storable we use Prim and we are not restricted to IO, since finalizers are not possible with PlaintPtr

mallocCountPlainForeignPtr :: (MonadPrim s m, Prim e) => Count e -> m (ForeignPtr e) Source #

Similar to mallocPlainForeignPtrArray, except instead of Storable we use Prim.

mallocCountPlainForeignPtrAligned :: forall e m s. (MonadPrim s m, Prim e) => Count e -> m (ForeignPtr e) Source #

Just like mallocCountForeignPtr, but memory is also aligned according to Prim instance

mallocByteCountPlainForeignPtrAligned Source #

Arguments

:: MonadPrim s m 
=> Count Word8

Number of bytes to allocate

-> Int

Alignment in bytes

-> m (ForeignPtr e) 

Lifted version of mallocForeignPtrAlignedBytes.

With Finalizers

Foreign finalizer

type FinalizerPtr a = FunPtr (Ptr a -> IO ()) #

A finalizer is represented as a pointer to a foreign function that, at finalisation time, gets as an argument a plain pointer variant of the foreign pointer that the finalizer is associated with.

Note that the foreign function must use the ccall calling convention.

newForeignPtr :: MonadPrim RW m => FinalizerPtr e -> Ptr e -> m (ForeignPtr e) Source #

Lifted version of newForeignPtr.

newForeignPtr_ :: MonadPrim RW m => Ptr e -> m (ForeignPtr e) Source #

Lifted version of newForeignPtr_.

touchForeignPtr :: MonadPrim s m => ForeignPtr e -> m () Source #

Lifted version of touchForeignPtr.

mallocForeignPtr :: forall e m. (MonadPrim RW m, Prim e) => m (ForeignPtr e) Source #

Simila to mallocForeignPtr, except it operates on Prim, instead of Storable.

mallocCountForeignPtr :: (MonadPrim RW m, Prim e) => Count e -> m (ForeignPtr e) Source #

Similar to mallocForeignPtrArray, except instead of Storable we use Prim.

mallocCountForeignPtrAligned :: (MonadPrim RW m, Prim e) => Count e -> m (ForeignPtr e) Source #

Just like mallocCountForeignPtr, but memory is also aligned according to Prim instance

mallocByteCountForeignPtrAligned Source #

Arguments

:: MonadPrim RW m 
=> Count Word8

Number of bytes to allocate

-> Int

Alignment in bytes

-> m (ForeignPtr e) 

Lifted version of mallocForeignPtrAlignedBytes.

With environment

type FinalizerEnvPtr env a = FunPtr (Ptr env -> Ptr a -> IO ()) #

newForeignPtrEnv :: MonadPrim RW m => FinalizerEnvPtr env e -> Ptr env -> Ptr e -> m (ForeignPtr e) Source #

Lifted version of newForeignPtrEnv.

Haskell finalizer

newConcForeignPtr :: MonadUnliftPrim RW m => Ptr e -> m () -> m (ForeignPtr e) Source #

Unlifted version of newConcForeignPtr

Conversion

Bytes