Haskell Hierarchical Libraries (base package)ContentsIndex
GHC.ForeignPtr
Portability non-portable (GHC extensions)
Stability internal
Maintainer cvs-ghc@haskell.org
Description
GHC's implementation of the ForeignPtr data type.
Synopsis
data ForeignPtr a
= ForeignPtr ForeignObj# !(IORef [IO ()])
| MallocPtr (MutableByteArray# RealWorld) !(IORef [IO ()])
type FinalizerPtr a = FunPtr (Ptr a -> IO ())
newForeignPtr_ :: Ptr a -> IO (ForeignPtr a)
mallocForeignPtr :: Storable a => IO (ForeignPtr a)
mallocForeignPtrBytes :: Int -> IO (ForeignPtr a)
addForeignPtrFinalizer :: FinalizerPtr a -> ForeignPtr a -> IO ()
touchForeignPtr :: ForeignPtr a -> IO ()
unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a
castForeignPtr :: ForeignPtr a -> ForeignPtr b
newConcForeignPtr :: Ptr a -> IO () -> IO (ForeignPtr a)
addForeignPtrConcFinalizer :: ForeignPtr a -> IO () -> IO ()
Documentation
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 finalisers. A finaliser 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 finaliser 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 ForeignObj# !(IORef [IO ()])
MallocPtr (MutableByteArray# RealWorld) !(IORef [IO ()])
Instances
Eq (ForeignPtr a)
Ord (ForeignPtr a)
Show (ForeignPtr a)
Typeable a => Typeable (ForeignPtr a)
type FinalizerPtr a = FunPtr (Ptr a -> IO ())
A Finaliser 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.
newForeignPtr_ :: Ptr a -> IO (ForeignPtr a)
Turns a plain memory reference into a foreign pointer that may be associated with finalizers by using addForeignPtrFinalizer.
mallocForeignPtr :: Storable a => IO (ForeignPtr a)

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.

mallocForeignPtrBytes :: Int -> IO (ForeignPtr a)
This function is similar to mallocForeignPtr, except that the size of the memory required is given explicitly as a number of bytes.
addForeignPtrFinalizer :: FinalizerPtr a -> ForeignPtr a -> IO ()
This function adds a finaliser to the given foreign object. The finalizer will run before all other finalizers for the same object which have already been registered.
touchForeignPtr :: ForeignPtr a -> IO ()

This function ensures that the foreign object in question is alive at the given place in the sequence of IO actions. In particular withForeignPtr does a touchForeignPtr after it executes the user action.

This function can be used to express liveness dependencies between ForeignPtrs: for example, if the finalizer for one ForeignPtr touches a second ForeignPtr, then it is ensured that the second ForeignPtr will stay alive at least as long as the first. This can be useful when you want to manipulate interior pointers to a foreign structure: you can use touchForeignObj to express the requirement that the exterior pointer must not be finalized until the interior pointer is no longer referenced.

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 occurence of the given foreign pointer, then its finaliser(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 later routines are occasionally preferred in tool generated marshalling code.

castForeignPtr :: ForeignPtr a -> ForeignPtr b
This function casts a ForeignPtr parameterised by one type into another type.
newConcForeignPtr :: Ptr a -> IO () -> IO (ForeignPtr a)

Turns a plain memory reference into a foreign object by associating a finaliser - given by the monadic operation - 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. The only guarantee is that the finaliser runs before the program terminates.

The finalizer, when invoked, will run in a separate thread.

addForeignPtrConcFinalizer :: ForeignPtr a -> IO () -> IO ()

This function adds a finaliser 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 it is invoked, the finalizer will run in a new thread.

Produced by Haddock version 0.6