Portability | portable |
---|---|
Stability | provisional |
Maintainer | ffi@haskell.org |
Safe Haskell | Unsafe |
A collection of data types, classes, and functions for interfacing with another programming language.
- module Data.Bits
- module Data.Int
- module Data.Word
- module Foreign.Ptr
- 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 ()
- 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)
- unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a
- module Foreign.StablePtr
- module Foreign.Storable
- module Foreign.Marshal
- unsafePerformIO :: IO a -> a
Documentation
module Data.Bits
module Data.Int
module Data.Word
module Foreign.Ptr
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 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
.
Typeable1 ForeignPtr | |
Eq (ForeignPtr a) | |
Typeable a => Data (ForeignPtr a) | |
Ord (ForeignPtr a) | |
Show (ForeignPtr a) |
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.
Basic operations
newForeignPtr :: FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)Source
Turns a plain memory reference into a foreign pointer, and associates a finalizer with the reference. The finalizer will be executed after the last reference to the foreign object is dropped. There is no guarantee of promptness, however the finalizer will be executed before the program exits.
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
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 withForeignPtr
does a touchForeignPtr
after it
executes the user action.
Note that this function should not be used to express dependencies
between finalizers on ForeignPtr
s. 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 MVar
s
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 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 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 malloc
.
mallocForeignPtrArray0 :: Storable a => Int -> IO (ForeignPtr a)Source
This function is similar to 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 malloc
.
Unsafe low-level operations
unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr aSource
module Foreign.StablePtr
module Foreign.Storable
module Foreign.Marshal
Unsafe Functions
unsafePerformIO
is exported here for backwards
compatibility reasons only. For doing local marshalling in
the FFI, use unsafeLocalState
. For other uses, see
unsafePerformIO
.
unsafePerformIO :: IO a -> aSource