base-4.1.0.0: Basic librariesSource codeContentsIndex
Foreign.ForeignPtr
Portabilityportable
Stabilityprovisional
Maintainerffi@haskell.org
Contents
Finalised data pointers
Basic operations
Low-level operations
Allocating managed memory
Description
The ForeignPtr type and operations. This module is part of the Foreign Function Interface (FFI) and will usually be imported via the Foreign module.
Synopsis
data ForeignPtr a
type FinalizerPtr a = FunPtr (Ptr a -> IO ())
type FinalizerEnvPtr env a = FunPtr (Ptr env -> Ptr a -> IO ())
newForeignPtr :: FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr_ :: Ptr a -> IO (ForeignPtr a)
addForeignPtrFinalizer :: FinalizerPtr a -> ForeignPtr a -> IO ()
newForeignPtrEnv :: FinalizerEnvPtr env a -> Ptr env -> Ptr a -> IO (ForeignPtr a)
addForeignPtrFinalizerEnv :: FinalizerEnvPtr env a -> Ptr env -> ForeignPtr a -> IO ()
withForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
finalizeForeignPtr :: ForeignPtr a -> IO ()
unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a
touchForeignPtr :: ForeignPtr a -> IO ()
castForeignPtr :: ForeignPtr a -> ForeignPtr b
mallocForeignPtr :: Storable a => IO (ForeignPtr a)
mallocForeignPtrBytes :: Int -> IO (ForeignPtr a)
mallocForeignPtrArray :: Storable a => Int -> IO (ForeignPtr a)
mallocForeignPtrArray0 :: Storable a => Int -> IO (ForeignPtr a)
Finalised data pointers
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.

show/hide Instances
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.
type FinalizerEnvPtr env a = FunPtr (Ptr env -> Ptr a -> IO ())Source
Basic operations
newForeignPtr :: FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)Source
Turns a plain memory reference into a foreign pointer, and associates a finaliser with the reference. The finaliser will be executed after the last reference to the foreign object is dropped. Note that there is no guarantee on how soon the finaliser is executed after the last reference was dropped; this depends on the details of the Haskell storage manager. Indeed, there is no guarantee that the finalizer is executed at all; a program may exit with finalizers outstanding. (This is true of GHC, other implementations may give stronger guarantees).
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.
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.
newForeignPtrEnv :: FinalizerEnvPtr env a -> Ptr env -> Ptr a -> IO (ForeignPtr a)Source
This variant of newForeignPtr adds a finalizer that expects an environment in addition to the finalized pointer. The environment that will be passed to the finalizer is fixed by the second argument to newForeignPtrEnv.
addForeignPtrFinalizerEnv :: FinalizerEnvPtr env a -> Ptr env -> ForeignPtr a -> IO ()Source
like addForeignPtrFinalizerEnv but allows the finalizer to be passed an additional environment parameter to be passed to the finalizer. The environment passed to the finalizer is fixed by the second argument to addForeignPtrFinalizerEnv
withForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO bSource

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.

finalizeForeignPtr :: ForeignPtr a -> IO ()Source
Causes the finalizers associated with a foreign pointer to be run immediately.
Low-level operations
unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr aSource

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 Foreign.ForeignPtr.withForeignPtr rather than combinations of unsafeForeignPtrToPtr and touchForeignPtr. However, the later routines are occasionally preferred in tool generated marshalling code.

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. In particular Foreign.ForeignPtr.withForeignPtr does a touchForeignPtr after it executes the user action.

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.

castForeignPtr :: ForeignPtr a -> ForeignPtr bSource
This function casts a ForeignPtr parameterised by one type into another type.
Allocating managed memory
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 Foreign.Marshal.Alloc.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.

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.
mallocForeignPtrArray :: Storable a => Int -> IO (ForeignPtr a)Source
This function is similar to Foreign.Marshal.Array.mallocArray, but yields a memory area that has a finalizer attached that releases the memory area. As with mallocForeignPtr, it is not guaranteed that the block of memory was allocated by Foreign.Marshal.Alloc.malloc.
mallocForeignPtrArray0 :: Storable a => Int -> IO (ForeignPtr a)Source
This function is similar to Foreign.Marshal.Array.mallocArray0, but yields a memory area that has a finalizer attached that releases the memory area. As with mallocForeignPtr, it is not guaranteed that the block of memory was allocated by Foreign.Marshal.Alloc.malloc.
Produced by Haddock version 2.4.2