Copyright | (c) Alexey Kuleshevich 2020 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <alexey@kuleshevi.ch> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class PtrAccess s p where
- toForeignPtr :: MonadPrim s m => p -> m (ForeignPtr a)
- withPtrAccess :: MonadPrim s m => p -> (Ptr a -> m b) -> m b
- withNoHaltPtrAccess :: MonadUnliftPrim s m => p -> (Ptr a -> m b) -> m b
- data ForeignPtr a = ForeignPtr Addr# ForeignPtrContents
- castForeignPtr :: ForeignPtr a -> ForeignPtr b
- unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a
- data ForeignPtrContents
- = PlainForeignPtr !(IORef Finalizers)
- | MallocPtr (MutableByteArray# RealWorld) !(IORef Finalizers)
- | PlainPtr (MutableByteArray# RealWorld)
- plusOffForeignPtr :: Prim e => ForeignPtr e -> Off e -> ForeignPtr e
- plusByteOffForeignPtr :: ForeignPtr e -> Off Word8 -> ForeignPtr e
- minusOffForeignPtr :: Prim e => ForeignPtr e -> ForeignPtr e -> Off e
- minusOffRemForeignPtr :: Prim e => ForeignPtr e -> ForeignPtr e -> (Off e, Off Word8)
- minusByteOffForeignPtr :: ForeignPtr e -> ForeignPtr e -> Off Word8
- withForeignPtr :: MonadPrim s m => ForeignPtr e -> (Ptr e -> m b) -> m b
- withNoHaltForeignPtr :: MonadUnliftPrim s m => ForeignPtr e -> (Ptr e -> m b) -> m b
- mallocPlainForeignPtr :: forall e m s. (MonadPrim s m, Prim e) => m (ForeignPtr e)
- mallocCountPlainForeignPtr :: (MonadPrim s m, Prim e) => Count e -> m (ForeignPtr e)
- mallocCountPlainForeignPtrAligned :: forall e m s. (MonadPrim s m, Prim e) => Count e -> m (ForeignPtr e)
- mallocByteCountPlainForeignPtr :: MonadPrim s m => Count Word8 -> m (ForeignPtr e)
- mallocByteCountPlainForeignPtrAligned :: MonadPrim s m => Count Word8 -> Int -> m (ForeignPtr e)
- finalizeForeignPtr :: MonadPrim RW m => ForeignPtr e -> m ()
- type FinalizerPtr a = FunPtr (Ptr a -> IO ())
- newForeignPtr :: MonadPrim RW m => FinalizerPtr e -> Ptr e -> m (ForeignPtr e)
- newForeignPtr_ :: MonadPrim RW m => Ptr e -> m (ForeignPtr e)
- touchForeignPtr :: MonadPrim s m => ForeignPtr e -> m ()
- mallocForeignPtr :: forall e m. (MonadPrim RW m, Prim e) => m (ForeignPtr e)
- mallocCountForeignPtr :: (MonadPrim RW m, Prim e) => Count e -> m (ForeignPtr e)
- mallocCountForeignPtrAligned :: (MonadPrim RW m, Prim e) => Count e -> m (ForeignPtr e)
- mallocByteCountForeignPtr :: MonadPrim RW m => Count Word8 -> m (ForeignPtr e)
- mallocByteCountForeignPtrAligned :: MonadPrim RW m => Count Word8 -> Int -> m (ForeignPtr e)
- addForeignPtrFinalizer :: MonadPrim RW m => FinalizerPtr e -> ForeignPtr e -> m ()
- type FinalizerEnvPtr env a = FunPtr (Ptr env -> Ptr a -> IO ())
- newForeignPtrEnv :: MonadPrim RW m => FinalizerEnvPtr env e -> Ptr env -> Ptr e -> m (ForeignPtr e)
- addForeignPtrFinalizerEnv :: MonadPrim RW m => FinalizerEnvPtr env e -> Ptr env -> ForeignPtr e -> m ()
- newConcForeignPtr :: MonadUnliftPrim RW m => Ptr e -> m () -> m (ForeignPtr e)
- addForeignPtrConcFinalizer :: MonadUnliftPrim RW m => ForeignPtr a -> m () -> m ()
- toForeignPtrBytes :: Bytes Pin -> ForeignPtr e
- toForeignPtrMBytes :: MBytes Pin s -> ForeignPtr e
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.
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 #18061 and related to get more insight why this is needed.
Instances
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 ForeignPtr
s 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
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.
data ForeignPtrContents #
PlainForeignPtr !(IORef Finalizers) | |
MallocPtr (MutableByteArray# RealWorld) !(IORef Finalizers) | |
PlainPtr (MutableByteArray# RealWorld) |
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 #
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
mallocByteCountPlainForeignPtr :: MonadPrim s m => Count Word8 -> m (ForeignPtr e) Source #
Lifted version of mallocForeignPtrBytes
.
mallocByteCountPlainForeignPtrAligned Source #
:: MonadPrim s m | |
=> Count Word8 | Number of bytes to allocate |
-> Int | Alignment in bytes |
-> m (ForeignPtr e) |
Lifted version of mallocForeignPtrAlignedBytes
.
With Finalizers
finalizeForeignPtr :: MonadPrim RW m => ForeignPtr e -> m () Source #
Lifted version of finalizeForeignPtr
.
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
mallocByteCountForeignPtr :: MonadPrim RW m => Count Word8 -> m (ForeignPtr e) Source #
Lifted version of mallocForeignPtrBytes
.
mallocByteCountForeignPtrAligned Source #
:: MonadPrim RW m | |
=> Count Word8 | Number of bytes to allocate |
-> Int | Alignment in bytes |
-> m (ForeignPtr e) |
Lifted version of mallocForeignPtrAlignedBytes
.
addForeignPtrFinalizer :: MonadPrim RW m => FinalizerPtr e -> ForeignPtr e -> m () Source #
Lifted version of addForeignPtrFinalizer
With environment
newForeignPtrEnv :: MonadPrim RW m => FinalizerEnvPtr env e -> Ptr env -> Ptr e -> m (ForeignPtr e) Source #
Lifted version of newForeignPtrEnv
.
addForeignPtrFinalizerEnv :: MonadPrim RW m => FinalizerEnvPtr env e -> Ptr env -> ForeignPtr e -> m () Source #
Lifted version of addForeignPtrFinalizerEnv
Haskell finalizer
newConcForeignPtr :: MonadUnliftPrim RW m => Ptr e -> m () -> m (ForeignPtr e) Source #
Unlifted version of newConcForeignPtr
addForeignPtrConcFinalizer :: MonadUnliftPrim RW m => ForeignPtr a -> m () -> m () Source #
Unlifted version of addForeignPtrConcFinalizer
Conversion
Bytes
toForeignPtrBytes :: Bytes Pin -> ForeignPtr e Source #
toForeignPtrMBytes :: MBytes Pin s -> ForeignPtr e Source #