| Copyright | (c) The University of Glasgow 1992-2003 | 
|---|---|
| License | see libraries/base/LICENSE | 
| Maintainer | ghc-devs@haskell.org | 
| Stability | internal | 
| Portability | non-portable (GHC extensions) | 
| Safe Haskell | Unsafe | 
| Language | Haskell2010 | 
GHC.Internal.ForeignPtr
Description
GHC's implementation of the ForeignPtr data type.
Synopsis
- data ForeignPtr a = ForeignPtr Addr# ForeignPtrContents
- data ForeignPtrContents
- data Finalizers- = NoFinalizers
- | CFinalizers (Weak# ())
- | HaskellFinalizers [IO ()]
 
- type FinalizerPtr a = FunPtr (Ptr a -> IO ())
- type FinalizerEnvPtr env a = FunPtr (Ptr env -> Ptr a -> IO ())
- newForeignPtr_ :: Ptr a -> IO (ForeignPtr a)
- mallocForeignPtr :: Storable a => IO (ForeignPtr a)
- mallocPlainForeignPtr :: Storable a => IO (ForeignPtr a)
- mallocForeignPtrBytes :: Int -> IO (ForeignPtr a)
- mallocPlainForeignPtrBytes :: Int -> IO (ForeignPtr a)
- mallocForeignPtrAlignedBytes :: Int -> Int -> IO (ForeignPtr a)
- mallocPlainForeignPtrAlignedBytes :: Int -> Int -> IO (ForeignPtr a)
- newConcForeignPtr :: Ptr a -> IO () -> IO (ForeignPtr a)
- addForeignPtrFinalizer :: FinalizerPtr a -> ForeignPtr a -> IO ()
- addForeignPtrFinalizerEnv :: FinalizerEnvPtr env a -> Ptr env -> ForeignPtr a -> IO ()
- addForeignPtrConcFinalizer :: ForeignPtr a -> IO () -> IO ()
- unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a
- castForeignPtr :: ForeignPtr a -> ForeignPtr b
- plusForeignPtr :: ForeignPtr a -> Int -> ForeignPtr b
- withForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
- unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
- touchForeignPtr :: ForeignPtr a -> IO ()
- finalizeForeignPtr :: ForeignPtr a -> IO ()
Types
data ForeignPtr a Source #
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.
Constructors
| ForeignPtr Addr# ForeignPtrContents | 
Instances
| Data a => Data (ForeignPtr a) Source # | Since: base-4.8.0.0 | 
| Defined in GHC.Internal.Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignPtr a -> c (ForeignPtr a) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignPtr a) Source # toConstr :: ForeignPtr a -> Constr Source # dataTypeOf :: ForeignPtr a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignPtr a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignPtr a)) Source # gmapT :: (forall b. Data b => b -> b) -> ForeignPtr a -> ForeignPtr a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignPtr a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignPtr a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ForeignPtr a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignPtr a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignPtr a -> m (ForeignPtr a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignPtr a -> m (ForeignPtr a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignPtr a -> m (ForeignPtr a) Source # | |
| Show (ForeignPtr a) Source # | Since: base-2.1 | 
| Defined in GHC.Internal.ForeignPtr | |
| Eq (ForeignPtr a) Source # | Since: base-2.1 | 
| Defined in GHC.Internal.ForeignPtr Methods (==) :: ForeignPtr a -> ForeignPtr a -> Bool Source # (/=) :: ForeignPtr a -> ForeignPtr a -> Bool Source # | |
| Ord (ForeignPtr a) Source # | Since: base-2.1 | 
| Defined in GHC.Internal.ForeignPtr Methods compare :: ForeignPtr a -> ForeignPtr a -> Ordering Source # (<) :: ForeignPtr a -> ForeignPtr a -> Bool Source # (<=) :: ForeignPtr a -> ForeignPtr a -> Bool Source # (>) :: ForeignPtr a -> ForeignPtr a -> Bool Source # (>=) :: ForeignPtr a -> ForeignPtr a -> Bool Source # max :: ForeignPtr a -> ForeignPtr a -> ForeignPtr a Source # min :: ForeignPtr a -> ForeignPtr a -> ForeignPtr a Source # | |
data ForeignPtrContents Source #
Controls finalization of a ForeignPtr, that is, what should happen
 if the ForeignPtr becomes unreachable. Visually, these data constructors
 are appropriate in these scenarios:
                          Memory backing pointer is
                           GC-Managed   Unmanaged
Finalizer functions are: +------------+-----------------+
                Allowed  | MallocPtr  | PlainForeignPtr |
                         +------------+-----------------+
             Prohibited  | PlainPtr   | FinalPtr        |
                         +------------+-----------------+Constructors
| PlainForeignPtr !(IORef Finalizers) | The pointer refers to unmanaged memory that was allocated by
 a foreign function (typically using  | 
| FinalPtr | The pointer refers to unmanaged memory that should not be freed when
 the  Since: base-4.15 | 
| MallocPtr (MutableByteArray# RealWorld) !(IORef Finalizers) | The pointer refers to a byte array.
 The  
 incrGood :: ForeignPtr Word8 -> ForeignPtr Word8 incrGood (ForeignPtr p (MallocPtr m f)) = ForeignPtr (plusPtr p 1) (MallocPtr m f) But this is unsound: incrBad :: ForeignPtr Word8 -> IO (ForeignPtr Word8) incrBad (ForeignPtr p (MallocPtr m _)) = do f <- newIORef NoFinalizers pure (ForeignPtr p (MallocPtr m f)) | 
| PlainPtr (MutableByteArray# RealWorld) | The pointer refers to a byte array. Finalization is not
 supported. This optimizes  | 
data Finalizers Source #
Functions called when a ForeignPtr is finalized. Note that
 C finalizers and Haskell finalizers cannot be mixed.
Constructors
| NoFinalizers | No finalizer. If there is no intent to add a finalizer at
 any point in the future, consider  | 
| CFinalizers (Weak# ()) | Finalizers are all C functions. | 
| HaskellFinalizers [IO ()] | Finalizers are all Haskell functions. | 
type FinalizerPtr a = FunPtr (Ptr a -> IO ()) Source #
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 either use the ccall or the capi calling convention.
Create
newForeignPtr_ :: Ptr a -> IO (ForeignPtr a) Source #
Turns a plain memory reference into a foreign pointer that may be
 associated with finalizers by using addForeignPtrFinalizer.
mallocForeignPtr :: Storable a => IO (ForeignPtr a) Source #
Allocate some memory and return a ForeignPtr to it.  The memory
 will be released automatically when the ForeignPtr is discarded.
mallocForeignPtr is equivalent to
   do { p <- malloc; newForeignPtr finalizerFree p }although it may be implemented differently internally: you may not
 assume that the memory returned by mallocForeignPtr has been
 allocated with malloc.
GHC notes: mallocForeignPtr has a heavily optimised
 implementation in GHC.  It uses pinned memory in the garbage
 collected heap, so the ForeignPtr does not require a finalizer to
 free the memory.  Use of mallocForeignPtr and associated
 functions is strongly recommended in preference to
 newForeignPtr with a finalizer.
mallocPlainForeignPtr :: Storable a => IO (ForeignPtr a) Source #
Allocate some memory and return a ForeignPtr to it.  The memory
 will be released automatically when the ForeignPtr is discarded.
GHC notes: mallocPlainForeignPtr has a heavily optimised
 implementation in GHC.  It uses pinned memory in the garbage
 collected heap, as for mallocForeignPtr. Unlike mallocForeignPtr, a
 ForeignPtr created with mallocPlainForeignPtr carries no finalizers.
 It is not possible to add a finalizer to a ForeignPtr created with
 mallocPlainForeignPtr. This is useful for ForeignPtrs that will live
 only inside Haskell (such as those created for packed strings).
 Attempts to add a finalizer to a ForeignPtr created this way, or to
 finalize such a pointer, will throw an exception.
mallocForeignPtrBytes :: Int -> IO (ForeignPtr a) Source #
This function is similar to mallocForeignPtr, except that the
 size of the memory required is given explicitly as a number of bytes.
mallocPlainForeignPtrBytes :: Int -> IO (ForeignPtr a) Source #
This function is similar to mallocForeignPtrBytes, except that
 the internally an optimised ForeignPtr representation with no
 finalizer is used. Attempts to add a finalizer will cause an
 exception to be thrown.
mallocForeignPtrAlignedBytes :: Int -> Int -> IO (ForeignPtr a) Source #
This function is similar to mallocForeignPtrBytes, except that the
 size and alignment of the memory required is given explicitly as numbers of
 bytes.
mallocPlainForeignPtrAlignedBytes :: Int -> Int -> IO (ForeignPtr a) Source #
This function is similar to mallocForeignPtrAlignedBytes, except that
 the internally an optimised ForeignPtr representation with no
 finalizer is used. Attempts to add a finalizer will cause an
 exception to be thrown.
newConcForeignPtr :: Ptr a -> IO () -> IO (ForeignPtr a) Source #
Turns a plain memory reference into a foreign object by associating a finalizer - given by the monadic operation - with the reference.
When finalization is triggered by GC, the storage manager will start the
 finalizer, in a separate thread, some time after the last reference to the
 ForeignPtr is dropped.  There is no guarantee of promptness, and
 in fact there is no guarantee that the finalizer will eventually
 run at all for GC-triggered finalization.
When finalization is triggered by explicitly calling finalizeForeignPtr,
 the finalizer will run immediately on the current Haskell thread.
Note that references from a finalizer do not necessarily prevent
 another object from being finalized.  If A's finalizer refers to B
 (perhaps using touchForeignPtr, then the only guarantee is that
 B's finalizer will never be started before A's.  If both A and B
 are unreachable, then both finalizers will start together.  See
 touchForeignPtr for more on finalizer ordering.
Add Finalizers
addForeignPtrFinalizer :: FinalizerPtr a -> ForeignPtr a -> IO () Source #
This function adds a finalizer to the given foreign object. The finalizer will run before all other finalizers for the same object which have already been registered.
addForeignPtrFinalizerEnv :: FinalizerEnvPtr env a -> Ptr env -> ForeignPtr a -> IO () Source #
Like addForeignPtrFinalizer but the finalizer is passed an additional
 environment parameter.
addForeignPtrConcFinalizer :: ForeignPtr a -> IO () -> IO () Source #
This function adds a finalizer to the given ForeignPtr.  The
 finalizer will run before all other finalizers for the same
 object which have already been registered.
This is a variant of addForeignPtrFinalizer, where the finalizer
 is an arbitrary IO action.
 When finalization is triggered by GC, the finalizer will run in a new thread.
 When finalization is triggered by explicitly calling finalizeForeignPtr,
 the finalizer will run immediately on the current Haskell thread.
NB. Be very careful with these finalizers.  One common trap is that
 if a finalizer references another finalized value, it does not
 prevent that value from being finalized.  In particular, Handles
 are finalized objects, so a finalizer should not refer to a
 Handle (including stdout, stdin, or
 stderr).
Conversion
unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a Source #
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.
castForeignPtr :: ForeignPtr a -> ForeignPtr b Source #
This function casts a ForeignPtr
 parameterised by one type into another type.
plusForeignPtr :: ForeignPtr a -> Int -> ForeignPtr b Source #
Advances the given address by the given offset in bytes.
The new ForeignPtr shares the finalizer of the original,
 equivalent from a finalization standpoint to just creating another
 reference to the original. That is, the finalizer will not be
 called before the new ForeignPtr is unreachable, nor will it be
 called an additional time due to this call, and the finalizer will
 be called with the same address that it would have had this call
 not happened, *not* the new address.
Since: base-4.10.0.0
Control over lifetype
withForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b Source #
This is a way to look at the pointer living inside a
 foreign object.  This function takes a function which is
 applied to that pointer. The resulting IO action is then
 executed. The foreign object is kept alive at least during
 the whole action, even if it is not used directly
 inside. Note that it is not safe to return the pointer from
 the action and use it after the action completes. All uses
 of the pointer should be inside the
 withForeignPtr bracket.  The reason for
 this unsafeness is the same as for
 unsafeForeignPtrToPtr below: the finalizer
 may run earlier than expected, because the compiler can only
 track usage of the ForeignPtr object, not
 a Ptr object made from it.
This function is normally used for marshalling data to
 or from the object pointed to by the
 ForeignPtr, using the operations from the
 Storable class.
unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b Source #
This is similar to withForeignPtr but comes with an important caveat:
 the user must guarantee that the continuation does not diverge (e.g. loop or
 throw an exception). In exchange for this loss of generality, this function
 offers the ability of GHC to optimise more aggressively.
Specifically, applications of the form:
 
 unsafeWithForeignPtr fptr (forever something)
 
See GHC issue #17760 for more information about the unsoundness behavior that this function can result in.
touchForeignPtr :: ForeignPtr a -> IO () Source #
This function ensures that the foreign object in
 question is alive at the given place in the sequence of IO
 actions. However, this comes with a significant caveat: the contract above
 does not hold if GHC can demonstrate that the code preceding
 touchForeignPtr diverges (e.g. by looping infinitely or throwing an
 exception). For this reason, you are strongly advised to use instead
 withForeignPtr where possible.
Also, note that this function should not be used to express dependencies
 between finalizers on ForeignPtrs.  For example, if the finalizer for a
 ForeignPtr F1 calls touchForeignPtr on a second ForeignPtr F2,
 then the only guarantee is that the finalizer for F2 is never started
 before the finalizer for F1.  They might be started together if for
 example both F1 and F2 are otherwise unreachable, and in that case the
 scheduler might end up running the finalizer for F2 first.
In general, it is not recommended to use finalizers on separate
 objects with ordering constraints between them.  To express the
 ordering robustly requires explicit synchronisation using MVars
 between the finalizers, but even then the runtime sometimes runs
 multiple finalizers sequentially in a single thread (for
 performance reasons), so synchronisation between finalizers could
 result in artificial deadlock.  Another alternative is to use
 explicit reference counting.
Finalization
finalizeForeignPtr :: ForeignPtr a -> IO () Source #
Causes the finalizers associated with a foreign pointer to be run immediately. The foreign pointer must not be used again after this function is called. If the foreign pointer does not support finalizers, this is a no-op.