Foreign function interface (FFI)
GHC (mostly) conforms to the Haskell 98 Foreign Function Interface
Addendum 1.0, whose definition is available from http://www.haskell.org/.To enable FFI support in GHC, give the flag.GHC implements a number of GHC-specific extensions to the FFI
Addendum. These extensions are described in , but please note that programs using
these features are not portable. Hence, these features should be
avoided where possible.The FFI libraries are documented in the accompanying library
documentation; see for example the
Foreign module.GHC extensions to the FFI AddendumThe FFI features that are described in this section are specific to
GHC. Your code will not be portable to other compilers if you use them.Unboxed typesThe following unboxed types may be used as basic foreign types
(see FFI Addendum, Section 3.2): Int#,
Word#, Char#,
Float#, Double#,
Addr#, StablePtr# a,
MutableByteArray#, ForeignObj#,
and ByteArray#.Newtype wrapping of the IO monadThe FFI spec requires the IO monad to appear in various places,
but it can sometimes be convenient to wrap the IO monad in a
newtype, thus:
newtype MyIO a = MIO (IO a)
(A reason for doing so might be to prevent the programmer from
calling arbitrary IO procedures in some part of the program.)
The Haskell FFI already specifies that arguments and results of
foreign imports and exports will be automatically unwrapped if they are
newtypes (Section 3.2 of the FFI addendum). GHC extends the FFI by automatically unwrapping any newtypes that
wrap the IO monad itself.
More precisely, wherever the FFI specification requires an IO type, GHC will
accept any newtype-wrapping of an IO type. For example, these declarations are
OK:
foreign import foo :: Int -> MyIO Int
foreign import "dynamic" baz :: (Int -> MyIO Int) -> CInt -> MyIO Int
Primitive imports
GHC extends the FFI with an additional calling convention
prim, e.g.:
foreign import prim "foo" foo :: ByteArray# -> (# Int#, Int# #)
This is used to import functions written in Cmm code that follow an
internal GHC calling convention. This feature is not intended for
use outside of the core libraries that come with GHC. For more
details see the GHC developer wiki.
Using the FFI with GHCThe following sections also give some hints and tips on the
use of the foreign function interface in GHC.Using foreign export and foreign import ccall "wrapper" with GHCforeign export
with GHCWhen GHC compiles a module (say M.hs)
which uses foreign export or
foreign import "wrapper", it generates two
additional files, M_stub.c and
M_stub.h. GHC will automatically compile
M_stub.c to generate
M_stub.o at the same time.For a plain foreign export, the file
M_stub.h contains a C prototype for the
foreign exported function, and M_stub.c
contains its definition. For example, if we compile the
following module:
module Foo where
foreign export ccall foo :: Int -> IO Int
foo :: Int -> IO Int
foo n = return (length (f n))
f :: Int -> [Int]
f 0 = []
f n = n:(f (n-1))Then Foo_stub.h will contain
something like this:
#include "HsFFI.h"
extern HsInt foo(HsInt a0);and Foo_stub.c contains the
compiler-generated definition of foo(). To
invoke foo() from C, just #include
"Foo_stub.h" and call foo().The foo_stub.c and
foo_stub.h files can be redirected using the
option; see .When linking the program, remember to include
M_stub.o in the final link command line, or
you'll get link errors for the missing function(s) (this isn't
necessary when building your program with ghc
––make, as GHC will automatically link in the
correct bits).Using your own main()Normally, GHC's runtime system provides a
main(), which arranges to invoke
Main.main in the Haskell program. However,
you might want to link some Haskell code into a program which
has a main function written in another language, say C. In
order to do this, you have to initialize the Haskell runtime
system explicitly.Let's take the example from above, and invoke it from a
standalone C program. Here's the C code:
#include <stdio.h>
#include "HsFFI.h"
#ifdef __GLASGOW_HASKELL__
#include "foo_stub.h"
#endif
#ifdef __GLASGOW_HASKELL__
extern void __stginit_Foo ( void );
#endif
int main(int argc, char *argv[])
{
int i;
hs_init(&argc, &argv);
#ifdef __GLASGOW_HASKELL__
hs_add_root(__stginit_Foo);
#endif
for (i = 0; i < 5; i++) {
printf("%d\n", foo(2500));
}
hs_exit();
return 0;
}We've surrounded the GHC-specific bits with
#ifdef __GLASGOW_HASKELL__; the rest of the
code should be portable across Haskell implementations that
support the FFI standard.The call to hs_init()
initializes GHC's runtime system. Do NOT try to invoke any
Haskell functions before calling
hs_init(): bad things will
undoubtedly happen.We pass references to argc and
argv to hs_init()
so that it can separate out any arguments for the RTS
(i.e. those arguments between
+RTS...-RTS).Next, we call
hs_add_rooths_add_root, a GHC-specific interface which is required to
initialise the Haskell modules in the program. The argument
to hs_add_root should be the name of the
initialization function for the "root" module in your program
- in other words, the module which directly or indirectly
imports all the other Haskell modules in the program. In a
standalone Haskell program the root module is normally
Main, but when you are using Haskell code
from a library it may not be. If your program has multiple
root modules, then you can call
hs_add_root multiple times, one for each
root. The name of the initialization function for module
M is
__stginit_M, and
it may be declared as an external function symbol as in the
code above. Note that the symbol name should be transformed
according to the Z-encoding:CharacterReplacement.zd_zu`zqZZZzzzAfter we've finished invoking our Haskell functions, we
can call hs_exit(), which terminates the
RTS.There can be multiple calls to
hs_init(), but each one should be matched
by one (and only one) call to
hs_exit()The outermost
hs_exit() will actually de-initialise the
system. NOTE that currently GHC's runtime cannot reliably
re-initialise after this has happened,
see ..NOTE: when linking the final program, it is normally
easiest to do the link using GHC, although this isn't
essential. If you do use GHC, then don't forget the flag
, otherwise GHC will try to link
to the Main Haskell module.Making a Haskell library that can be called from foreign
codeThe scenario here is much like in , except that the aim is not to link a complete program, but to
make a library from Haskell code that can be deployed in the same
way that you would deploy a library of C code.The main requirement here is that the runtime needs to be
initialized before any Haskell code can be called, so your library
should provide initialisation and deinitialisation entry points,
implemented in C or C++. For example:
HsBool mylib_init(void){
int argc = ...
char *argv[] = ...
// Initialize Haskell runtime
hs_init(&argc, &argv);
// Tell Haskell about all root modules
hs_add_root(__stginit_Foo);
// do any other initialization here and
// return false if there was a problem
return HS_BOOL_TRUE;
}
void mylib_end(void){
hs_exit();
}
The initialisation routine, mylib_init, calls
hs_init() and hs_add_root() as
normal to initialise the Haskell runtime, and the corresponding
deinitialisation function mylib_end() calls
hs_exit() to shut down the runtime.Using header filesC calls, function headersC functions are normally declared using prototypes in a C
header file. Earlier versions of GHC (6.8.3 and
earlier) #included the header file in
the C source file generated from the Haskell code, and the C
compiler could therefore check that the C function being
called via the FFI was being called at the right type.GHC no longer includes external header files when
compiling via C, so this checking is not performed. The
change was made for compatibility with the native code backend
(-fasm) and to comply strictly with the FFI
specification, which requires that FFI calls are not subject
to macro expansion and other CPP conversions that may be
applied when using C header files. This approach also
simplifies the inlining of foreign calls across module and
package boundaries: there's no need for the header file to be
available when compiling an inlined version of a foreign call,
so the compiler is free to inline foreign calls in any
context.The -#include option is now
deprecated, and the include-files field
in a Cabal package specification is ignored.Memory AllocationThe FFI libraries provide several ways to allocate memory
for use with the FFI, and it isn't always clear which way is the
best. This decision may be affected by how efficient a
particular kind of allocation is on a given compiler/platform,
so this section aims to shed some light on how the different
kinds of allocation perform with GHC.alloca and friendsUseful for short-term allocation when the allocation
is intended to scope over a given IO
computation. This kind of allocation is commonly used
when marshalling data to and from FFI functions.In GHC, alloca is implemented
using MutableByteArray#, so allocation
and deallocation are fast: much faster than C's
malloc/free, but not quite as fast as
stack allocation in C. Use alloca
whenever you can.mallocForeignPtrUseful for longer-term allocation which requires
garbage collection. If you intend to store the pointer to
the memory in a foreign data structure, then
mallocForeignPtr is
not a good choice, however.In GHC, mallocForeignPtr is also
implemented using MutableByteArray#.
Although the memory is pointed to by a
ForeignPtr, there are no actual
finalizers involved (unless you add one with
addForeignPtrFinalizer), and the
deallocation is done using GC, so
mallocForeignPtr is normally very
cheap.malloc/freeIf all else fails, then you need to resort to
Foreign.malloc and
Foreign.free. These are just wrappers
around the C functions of the same name, and their
efficiency will depend ultimately on the implementations
of these functions in your platform's C library. We
usually find malloc and
free to be significantly slower than
the other forms of allocation above.Foreign.Marshal.PoolPools are currently implemented using
malloc/free, so while they might be a
more convenient way to structure your memory allocation
than using one of the other forms of allocation, they
won't be any more efficient. We do plan to provide an
improved-performance implementation of Pools in the
future, however.Multi-threading and the FFIIn order to use the FFI in a multi-threaded setting, you must
use the option
(see ).Foreign imports and multi-threadingWhen you call a foreign imported
function that is annotated as safe (the
default), and the program was linked
using , then the call will run
concurrently with other running Haskell threads. If the
program was linked without ,
then the other Haskell threads will be blocked until the
call returns.This means that if you need to make a foreign call to
a function that takes a long time or blocks indefinitely,
then you should mark it safe and
use . Some library functions
make such calls internally; their documentation should
indicate when this is the case.If you are making foreign calls from multiple Haskell
threads and using , make sure that
the foreign code you are calling is thread-safe. In
particularly, some GUI libraries are not thread-safe and
require that the caller only invokes GUI methods from a
single thread. If this is the case, you may need to
restrict your GUI operations to a single Haskell thread,
and possibly also use a bound thread (see
).Note that foreign calls made by different Haskell
threads may execute in parallel, even
when the +RTS -N flag is not being used
(). The +RTS
-N flag controls parallel execution of Haskell
threads, but there may be an arbitrary number of foreign
calls in progress at any one time, regardless of
the +RTS -N value.If a call is annotated as interruptible
and the program was multithreaded, the call may be
interrupted in the event that the Haskell thread receives an
exception. The mechanism by which the interrupt occurs
is platform dependent, but is intended to cause blocking
system calls to return immediately with an interrupted error
code. The underlying operating system thread is not to be
destroyed.The relationship between Haskell threads and OS
threadsNormally there is no fixed relationship between Haskell
threads and OS threads. This means that when you make a
foreign call, that call may take place in an unspecified OS
thread. Furthermore, there is no guarantee that multiple
calls made by one Haskell thread will be made by the same OS
thread.This usually isn't a problem, and it allows the GHC
runtime system to make efficient use of OS thread resources.
However, there are cases where it is useful to have more
control over which OS thread is used, for example when
calling foreign code that makes use of thread-local state.
For cases like this, we provide bound
threads, which are Haskell threads tied to a
particular OS thread. For information on bound threads, see
the documentation
for the Control.Concurrent
module.Foreign exports and multi-threadingWhen the program is linked
with , then you may
invoke foreign exported functions from
multiple OS threads concurrently. The runtime system must
be initialised as usual by
calling hs_init()
and hs_add_root, and these calls must
complete before invoking any foreign
exported functions.On the use of hs_exit()hs_exit() normally causes the termination of
any running Haskell threads in the system, and when
hs_exit() returns, there will be no more Haskell
threads running. The runtime will then shut down the system in an
orderly way, generating profiling
output and statistics if necessary, and freeing all the memory it
owns.It isn't always possible to terminate a Haskell thread forcibly:
for example, the thread might be currently executing a foreign call,
and we have no way to force the foreign call to complete. What's
more, the runtime must
assume that in the worst case the Haskell code and runtime are about
to be removed from memory (e.g. if this is a Windows DLL,
hs_exit() is normally called before unloading the
DLL). So hs_exit()must wait
until all outstanding foreign calls return before it can return
itself.The upshot of this is that if you have Haskell threads that are
blocked in foreign calls, then hs_exit() may hang
(or possibly busy-wait) until the calls return. Therefore it's a
good idea to make sure you don't have any such threads in the system
when calling hs_exit(). This includes any threads
doing I/O, because I/O may (or may not, depending on the
type of I/O and the platform) be implemented using blocking foreign
calls.The GHC runtime treats program exit as a special case, to avoid
the need to wait for blocked threads when a standalone
executable exits. Since the program and all its threads are about to
terminate at the same time that the code is removed from memory, it
isn't necessary to ensure that the threads have exited first.
(Unofficially, if you want to use this fast and loose version of
hs_exit(), then call
shutdownHaskellAndExit() instead).