To bind a Haskell variable name and type to an external function, we introduce a new construct: foreign import. It defines the type of a Haskell function together with the name of an external function that actually implements it. The syntax of foreign import construct is as follows:
topdecl : ... .. | 'foreign' 'import' [callconv] [ext_fun] ['unsafe'] varid '::' prim_type |
A foreign import declaration is only allowed as a toplevel declaration. It consists of two parts, one giving the Haskell type (prim_type), Haskell name (varid) and a flag indicating whether the primitive is unsafe, the other giving details of the name of the external function (ext_fun) and its calling interface (callconv.)
Giving a Haskell name and type to an external entry point is clearly an unsafe thing to do, as the external name will in most cases be untyped. The onus is on the programmer using foreign import to ensure that the Haskell type given correctly maps on to the type of the external function. Section 8.2.5 specifies the mapping from Haskell types to external types.
The external function has to be given a Haskell name. The name must be a Haskell varid, so the language rules regarding variable names must be followed, i.e., it must start with a lower case letter followed by a sequence of alphanumeric (`in the Unicode sense') characters or '. [1]
varid : small ( small | large | udigit | ' )* |
The name of the external function is a string:
ext_fun : string |
For example,
foreign import stdcall "RegCloseKey" regCloseKey :: Ptr a -> IO () |
states that the external function named RegCloseKey should be bound to the Haskell name regCloseKey.
The details of where exactly the external name can be found, such as whether or not it is dynamically linked, and which library it might come from, are implementation dependent. This information is expected to be provided using a compiler-specific method (eg. GHC uses either packages or command-line options to specify libraries and extra include files).
If the Haskell name of the imported function is identical to the external name, the ext_fun can be omitted. e.g.:
foreign import sin :: Double -> IO Double |
is identical to
foreign import "sin" sin :: Double -> IO Double |
The number of calling conventions supported is fixed:
callconv : ccall | stdcall |
The 'default' calling convention on a platform, i.e., the one used to do (C) function calls.
In the case of x86 platforms, the caller pushes function arguments from right to left on the C stack before calling. The caller is responsible for popping the arguments off of the C stack on return.
A Win32 specific calling convention. The same as ccall, except that the callee cleans up the C stack before returning. [2]
Some remarks:
Interoperating well with external code is the name of the game here, so the guiding principle when deciding on what calling conventions to include in callconv is that there's a demonstrated need for a particular calling convention. Should it emerge that the inclusion of other calling conventions will generally improve the quality of this Haskell FFI, they will be considered for future inclusion in callconv.
Supporting stdcall (and perhaps other platform-specific calling conventions) raises the issue of whether a Haskell FFI should allow the user to write platform-specific Haskell code. The calling convention is clearly an integral part of an external function's interface, so if the one used differs from the standard one specified by the platform's ABI and that convention is used by a non-trivial amount of external functions, the view of the FFI authors is that a Haskell FFI should support it.
For foreign import (and other foreign declarations), supplying the calling convention is optional. If it isn't supplied, it is treated as if ccall was specified. Users are encouraged to leave out the specification of the calling convention, if possible.
The range of types that can be passed as arguments to an external function is restricted (as are the range of results coming back):
prim_type : IO prim_result | prim_result | prim_arg '->' prim_type |
If you associate a non-IO type with an external function, you have the same 'proof obligations' as when you make use of IOExts.unsafePerformIO in your Haskell programs.
The external function is strict in all its arguments.
Section 8.2.4.2 defines prim_result; Section 8.2.4.1 defines prim_arg.
The external function expects zero or more arguments. The set of legal argument types is restricted to the following set:
prim_arg : ext_ty | new_ty | ForeignPtr a new_ty : a Haskell newtype of a prim_arg. ext_ty : int_ty | word_ty | float_ty | Ptr a | Char | StablePtr a | Bool int_ty : Int | Int8 | Int16 | Int32 | Int64 word_ty : Word8 | Word16 | Word32 | Word64 float_ty : Float | Double |
ext_ty represent the set of basic types supported by C-like languages, although the numeric types are explicitly sized. The stable pointer StablePtr type looks out of place in this list of C-like types, but it has a well-defined and simple C mapping, see Section 8.2.5 for details.
prim_arg represent the set of permissible argument types. In addition to ext_ty, ForeignPtr is also included. The ForeignPtr type represent values that are pointers to some external entity/object. It differs from the Ptr type in that ForeignPtrs are finalized, i.e., once the garbage collector determines that a ForeignPtr is unreachable, it will invoke a finalising procedure attached to the ForeignPtr to notify the outside world that we're through with using it.
Haskell newtypes that wrap up a prim_arg type can also be passed to external functions.
Haskell type synonyms for any of the above can also be used in foreign import declarations. Qualified names likewise, i.e. Word.Word32 is legal.
foreign import does not support the binding to external constants/variables. A foreign import declaration that takes no arguments represent a binding to a function with no arguments.
A GHC extension is the support for unboxed types:
prim_arg : ... | unboxed_h_ty ext_ty : .... | unboxed_ext_ty unboxed_ext_ty : Int# | Word# | Char# | Float# | Double# | Addr# | StablePtr# a unboxed_h_ty : MutableByteArray# | ForeignObj# | ByteArray# |
An external function is permitted to return the following range of types:
prim_result : ext_ty | new_ext_ty | () new_ext_ty : a Haskell newtype of an ext_ty. |
where () represents void / no result.
External functions cannot raise exceptions (IO exceptions or non-IO ones.) It is the responsibility of the foreign import user to layer any error handling on top of an external function.
Only external types (ext_ty) can be passed back, i.e., returning ForeignPtrs is not supported/allowed.
Haskell newtypes that wrap up ext_ty are also permitted.
For the FFI to be of any practical use, the properties and sizes of the various types that can be communicated between the Haskell world and the outside, needs to be precisely defined. We do this by presenting a mapping to C, as it is commonly used and most other languages define a mapping to it. Table Table 8-1 defines the mapping between Haskell and C types.
Table 8-1. Mapping of Haskell types to C types
Haskell type | C type | requirement | range (9) | ||
Char | HsChar | unspec. integral type | HS_CHAR_MIN .. HS_CHAR_MAX | ||
Int | HsInt | signed integral of unspec. size(4) | HS_INT_MIN .. HS_INT_MAX | ||
Int8 (2) | HsInt8 | 8 bit signed integral | HS_INT8_MIN .. HS_INT8_MAX | ||
Int16 (2) | HsInt16 | 16 bit signed integral | HS_INT16_MIN .. HS_INT16_MAX | ||
Int32 (2) | HsInt32 | 32 bit signed integral | HS_INT32_MIN .. HS_INT32_MAX | ||
Int64 (2,3) | HsInt64 | 64 bit signed integral (3) | HS_INT64_MIN .. HS_INT64_MAX | ||
Word8 (2) | HsWord8 | 8 bit unsigned integral | 0 .. HS_WORD8_MAX | ||
Word16 (2) | HsWord16 | 16 bit unsigned integral | 0 .. HS_WORD16_MAX | ||
Word32 (2) | HsWord32 | 32 bit unsigned integral | 0 .. HS_WORD32_MAX | ||
Word64 (2,3) | HsWord64 | 64 bit unsigned integral (3) | 0 .. HS_WORD64_MAX | ||
Float | HsFloat | floating point of unspec. size (5) | (10) | ||
Double | HsDouble | floating point of unspec. size (5) | (10) | ||
Bool | HsBool | unspec. integral type | (11) | ||
Ptr a | HsPtr | void* (6) | |||
ForeignPtr a | HsForeignPtr | void* (7) | |||
StablePtr a | HsStablePtr | void* (8) |
Some remarks:
A Haskell system that implements the FFI will supply a header file HsFFI.h that includes target platform specific definitions for the above types and values.
The sized numeric types Hs{Int,Word}{8,16,32,64} have a 1-1 mapping to ISO C 99's {,u}int{8,16,32,64}_t. For systems that doesn't support this revision of ISO C, a best-fit mapping onto the supported C types is provided.
An implementation which does not support 64 bit integral types on the C side should implement Hs{Int,Word}64 as a struct. In this case the bounds HS_INT64_{MIN,MAX} and HS_WORD64_MAX are undefined.
A valid Haskell representation of Int has to be equal to or wider than 30 bits. The HsInt synonym is guaranteed to map onto a C type that satisifies Haskell's requirement for Int.
It is guaranteed that Hs{Float,Double} are one of C's floating-point types float/double/long double.
It is guaranteed that HsAddr is of the same size as void*, so any other pointer type can be converted to and from HsAddr without any loss of information (K&R, Appendix A6.8).
Foreign objects are handled like Ptr by the FFI, so there is again the guarantee that HsForeignPtr is the same as void*. The separate name is meant as a reminder that there is a finalizer attached to the object pointed to.
Stable pointers are passed as addresses by the FFI, but this is only because a void* is used as a generic container in most APIs, not because they are real addresses. To make this special case clear, a separate C type is used here.
The bounds are preprocessor macros, so they can be used in #if and for array bounds.
Floating-point limits are a little bit more complicated, so preprocessor macros mirroring ISO C's float.h are provided:
HS_{FLOAT,DOUBLE}_RADIX HS_{FLOAT,DOUBLE}_ROUNDS HS_{FLOAT,DOUBLE}_EPSILON HS_{FLOAT,DOUBLE}_DIG HS_{FLOAT,DOUBLE}_MANT_DIG HS_{FLOAT,DOUBLE}_MIN HS_{FLOAT,DOUBLE}_MIN_EXP HS_{FLOAT,DOUBLE}_MIN_10_EXP HS_{FLOAT,DOUBLE}_MAX HS_{FLOAT,DOUBLE}_MAX_EXP HS_{FLOAT,DOUBLE}_MAX_10_EXP |
It is guaranteed that Haskell's False/True map to C's 0/1, respectively, and vice versa. The mapping of any other integral value to Bool is left unspecified.
To avoid name clashes, identifiers starting with Hs and macros starting with HS_ are reserved for the FFI.
GHC only: The GHC specific types ByteArray and MutableByteArray both map to char*.
By default, a foreign import function is safe. A safe external function may cause a Haskell garbage collection as a result of being called. This will typically happen when the imported function end up calling Haskell functions that reside in the same 'Haskell world' (i.e., shares the same storage manager heap) -- see Section 8.4 for details of how the FFI let's you call Haskell functions from the outside. If the programmer can guarantee that the imported function won't call back into Haskell, the foreign import can be marked as 'unsafe' (see Section 8.2 for details of how to do this.) Unsafe calls are cheaper than safe ones, so distinguishing the two classes of external calls may be worth your while if you're extra conscious about performance.
A foreign imported function should clearly not need to know that it is being called from Haskell. One consequence of this is that the lifetimes of the arguments that are passed from Haskell must equal that of a normal C call. For instance, for the following decl,
foreign import "mumble" mumble :: ForeignPtr a -> IO () f :: Ptr a -> IO () f ptr = do fo <- newForeignObj ptr myFinalizer mumble fo |
[1] | Notice that with Haskell 98, underscore ('_') is included in the character class small. |
[2] | The stdcall is a Microsoft Win32 specific wrinkle; it's used throughout the Win32 API, for instance. On platforms where stdcall isn't meaningful, it should be treated as being equal to ccall. |