The following sections also give some hints and tips on the use of the foreign function interface in GHC.
When 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
-stubdir
option; see Section 4.7.4, “Redirecting the compilation output(s)”.
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).
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 int main(int argc, char *argv[]) { int i; hs_init(&argc, &argv); 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
).
After 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()
[14].
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
-no-hs-main
, otherwise GHC will try to link
to the Main
Haskell module.
To use +RTS
flags
with hs_init()
, we have to modify the
example slightly. By default, GHC's RTS will only accept
"safe"
+RTS
flags (see
Section 4.12.6, “Options affecting linking”), and
the -rtsopts
link-time flag overrides this.
However, -rtsopts
has no effect
when -no-hs-main
is in use (and the same
goes for -with-rtsopts
). To set these
options we have to call a GHC-specific API instead
of hs_init()
:
#include <stdio.h> #include "HsFFI.h" #ifdef __GLASGOW_HASKELL__ #include "foo_stub.h" #include "Rts.h" #endif int main(int argc, char *argv[]) { int i; #if __GLASGOW_HASKELL__ >= 703 { RtsConfig conf = defaultRtsConfig; conf.rts_opts_enabled = RtsOptsAll; hs_init_ghc(&argc, &argv, conf); } #else hs_init(&argc, &argv); #endif for (i = 0; i < 5; i++) { printf("%d\n", foo(2500)); } hs_exit(); return 0; }
Note two changes: we included Rts.h
,
which defines the GHC-specific external RTS interface, and we
called hs_init_ghc()
instead
of hs_init()
, passing an argument of
type RtsConfig
.
RtsConfig
is a struct with various fields
that affect the behaviour of the runtime system. Its
definition is:
typedef struct { RtsOptsEnabledEnum rts_opts_enabled; const char *rts_opts; } RtsConfig; extern const RtsConfig defaultRtsConfig; typedef enum { RtsOptsNone, // +RTS causes an error RtsOptsSafeOnly, // safe RTS options allowed; others cause an error RtsOptsAll // all RTS options allowed } RtsOptsEnabledEnum;
There is a default
value defaultRtsConfig
that should be used
to initialise variables of type RtsConfig
.
More fields will undoubtedly be added
to RtsConfig
in the future, so in order to
keep your code forwards-compatible it is best to initialise
with defaultRtsConfig
and then modify the
required fields, as in the code sample above.
The scenario here is much like in Section 8.2.1.1, “Using your own main()
”, 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:
#include <stdlib.h> #include "HsFFI.h" HsBool mylib_init(void){ int argc = 2; char *argv[] = { "+RTS", "-A32m", NULL }; char **pargv = argv; // Initialize Haskell runtime hs_init(&argc, &pargv); // 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()
as
normal to initialise the Haskell runtime, and the corresponding
deinitialisation function mylib_end()
calls
hs_exit()
to shut down the runtime.
C functions are normally declared using prototypes in a C
header file. Earlier versions of GHC (6.8.3 and
earlier) #include
d 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 generator
(-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.
The 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.
mallocForeignPtr
Useful 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/free
If 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.Pool
Pools 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.
In order to use the FFI in a multi-threaded setting, you must
use the -threaded
option
(see Section 4.12.6, “Options affecting linking”).
When you call a foreign import
ed
function that is annotated as safe
(the
default), and the program was linked
using -threaded
, then the call will run
concurrently with other running Haskell threads. If the
program was linked without -threaded
,
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 -threaded
. 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 -threaded
, 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
Section 8.2.4.2, “The relationship between Haskell threads and OS
threads”).
Note that foreign calls made by different Haskell
threads may execute in parallel, even
when the +RTS -N
flag is not being used
(Section 4.15.2, “RTS options for SMP parallelism”). 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. See Section 8.1.4, “Interruptible foreign calls” for more details.
Normally 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.
When the program is linked
with -threaded
, then you may
invoke foreign export
ed functions from
multiple OS threads concurrently. The runtime system must
be initialised as usual by
calling hs_init()
, and this call must
complete before invoking any foreign
export
ed functions.
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).
The standard C99 fenv.h
header
provides operations for inspecting and modifying the state of
the floating point unit. In particular, the rounding mode
used by floating point operations can be changed, and the
exception flags can be tested.
In Haskell, floating-point operations have pure types, and the
evaluation order is unspecified. So strictly speaking, since
the fenv.h
functions let you change the
results of, or observe the effects of floating point
operations, use of fenv.h
renders the
behaviour of floating-point operations anywhere in the program
undefined.
Having said that, we can document exactly
what GHC does with respect to the floating point state, so
that if you really need to use fenv.h
then
you can do so with full knowledge of the pitfalls:
GHC completely ignores the floating-point environment, the runtime neither modifies nor reads it.
The floating-point environment is not saved over a
normal thread context-switch. So if you modify the
floating-point state in one thread, those changes may be
visible in other threads. Furthermore, testing the
exception state is not reliable, because a context
switch may change it. If you need to modify or test the
floating point state and use threads, then you must use
bound threads
(Control.Concurrent.forkOS
), because
a bound thread has its own OS thread, and OS threads do
save and restore the floating-point state.
It is safe to modify the floating-point unit state temporarily during a foreign call, because foreign calls are never pre-empted by GHC.
[14] 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 Section 13.1.1.8, “The Foreign Function Interface”.