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.6.4, “Redirecting the compilation output(s)”.
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()
: strange things will
undoubtedly happen.
We pass 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_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_
, 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:M
Character | Replacement |
---|---|
. | zd |
_ | zu |
` | zq |
Z | ZZ |
z | zz |
After we've finished invoking our Haskell functions, we
can call hs_exit()
, which
terminates the RTS. It runs any outstanding finalizers and
generates any profiling or stats output that might have been
requested.
There can be multiple calls to
hs_init()
, but each one should be matched
by one (and only one) call to
hs_exit()
[9].
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.
When foreign import ccall "wrapper"
is used
in a Haskell module, The C stub file M_stub.c
generated by GHC contains small helper functions used by the code
generated for the imported wrapper, so it must be linked in to the
final program. 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).
When generating C (using the -fvia-C
directive), one can assist the C compiler in detecting type
errors by using the -#include
directive
(Section 4.10.5, “Options affecting the C compiler (if applicable)”) to provide
.h
files containing function
headers.
For example,
#include "HsFFI.h" void initialiseEFS (HsInt size); HsInt terminateEFS (void); HsForeignObj emptyEFS(void); HsForeignObj updateEFS (HsForeignObj a, HsInt i, HsInt x); HsInt lookupEFS (HsForeignObj a, HsInt i);
The types HsInt
,
HsForeignObj
etc. are described in the H98 FFI
Addendum.
Note that this approach is only
essential for returning
float
s (or if sizeof(int) !=
sizeof(int *)
on your architecture) but is a Good
Thing for anyone who cares about writing solid code. You're
crazy not to do it.
What if you are importing a module from another package, and
a cross-module inlining exposes a foreign call that needs a supporting
-#include
? If the imported module is from the same package as
the module being compiled, you should supply all the -#include
that you supplied when compiling the imported module. If the imported module comes
from another package, you won't necessarily know what the appropriate
-#include
options are; but they should be in the package
configuration, which GHC knows about. So if you are building a package, remember
to put all those -#include
options into the package configuration.
See the c_includes
field in Section 4.8.5, “Package management (the ghc-pkg
command)”.
It is also possible, according the FFI specification, to put the
-#include
option in the foreign import
declaration itself:
foreign import "foo.h f" f :: Int -> IO Int
When compiling this module, GHC will generate a C file that includes
the specified -#include
. However, GHC
disables cross-module inlining for such foreign
calls, because it doesn't transport the -#include
information across module boundaries. (There is no fundamental reason for this;
it was just tiresome to implement. The wrapper, which unboxes the arguments
etc, is still inlined across modules.) So if you want the foreign call itself
to be inlined across modules, use the command-line and package-configuration
-#include
mechanism.
Header files named by the -#include
option or in a foreign import
declaration
are searched for using the C compiler's usual search path.
You can add directories to this search path using the
-I
option (see Section 4.10.3, “Options affecting the C pre-processor”).
Note: header files are ignored unless compiling via C.
If you had been compiling your code using the native code
generator (the default) and suddenly switch to compiling via
C, then you can get unexpected errors about missing include
files. Compiling via C is enabled automatically when certain
options are given (eg. -O
and
-prof
both enable
-fvia-C
).
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.
[9] The outermost
hs_exit()
will actually de-initialise the
system. NOTE that currently GHC's runtime cannot reliably
re-initialise after this has happened.