FFI complete examples
This is a repository of COMPLETE WORKING EXAMPLES on how to do FFI. The examples here don't require any tools other than their respective compilers (ghc or g++). In particular, no make files or helper tools such as c2hs, hsc2hs, or cabal are necessary to build and run these examples.
A complete novice with no experience in any of Haskell, C, C++, or Python should be able to get all of these examples working. All of the build commands are explicitly given for each example.
I am using ghc version 6.12.3.
When main is in Haskell
The following examples all involve a Haskell program calling into libraries in other languages. These are the simplest case to build, because ghc can usually do the heavy lifting for us.
Calling standard library functions
This example is adapted from FFI_Introduction.
Main.hs:
{-# LANGUAGE ForeignFunctionInterface #-}
module Main where
import Prelude hiding (sin)
import Foreign.C -- get the C types
import Foreign.Ptr (Ptr,nullPtr)
-- pure function
foreign import ccall "sin" c_sin :: CDouble -> CDouble
sin :: Double -> Double
sin d = realToFrac (c_sin (realToFrac d))
-- impure function
foreign import ccall "time" c_time :: Ptr a -> IO CTime
getTime :: IO CTime
getTime = c_time nullPtr
main = do
print . sin =<< readLn
print =<< getTime
To run:
$ ghc --make Main.hs [1 of 1] Compiling Main ( Main.hs, Main.o ) Linking Main ... $ ./Main 3.14159265358 9.793177720293495e-12 1291494446
Calling C functions when you have the source code
The FFI_Introduction page has a nice example of wrapping the termios libraries. Here is how to build the program without a make file:
$ ghc --make -main-is FfiEx FfiEx.hs termops.c [1 of 2] Compiling Termios ( Termios.hs, Termios.o ) Termios.hs:1:11: Warning: -#include and INCLUDE pragmas are deprecated: They no longer have any effect Termios.hs:2:11: Warning: -#include and INCLUDE pragmas are deprecated: They no longer have any effect [2 of 2] Compiling FfiEx ( FfiEx.hs, FfiEx.o ) Linking FfiEx ... $ ./FfiEx ? ayou typed a ? byou typed b ? cyou typed c ? qyou typed q
If you are running GHC 6.10 or higher (I am running 6.12.3), you can get rid of the warnings by removing the INCLUDE lines from Termios.hs.
Calling C functions when you don't have the source code
See the FFI_Introduction page for how to create the files termops.c, termops.h, Termios.hs, and FfiEx.hs. This example is essentially the same as the one on the FFI_Introduction, but we are running by hand the commands that make would normally run for us.
$ mkdir c $ mkdir hs $ cd c $ $EDITOR termops.c $ $EDITOR termops.h $ gcc -c -o termops.o termops.c $ cp termops.o ../hs $ cd ../hs
Now to build FfiEx.hs without access to the original c file:
$ $EDITOR Termios.hs $ $EDITOR FfiEx.hs $ ghc --make -main-is FfiEx -o ffi_ex FfiEx.hs termops.o [1 of 2] Compiling Termios ( Termios.hs, Termios.o ) Termios.hs:1:11: Warning: -#include and INCLUDE pragmas are deprecated: They no longer have any effect Termios.hs:2:11: Warning: -#include and INCLUDE pragmas are deprecated: They no longer have any effect [2 of 2] Compiling FfiEx ( FfiEx.hs, FfiEx.o ) Linking ffi_ex ... $ ./ffi_ex ? ayou typed a ? byou typed b ? cyou typed c ? qyou typed q
When main is in C++
These examples are for building Haskell libraries to be used in a C++ program. Because g++ is not Haskell aware, building is substantially more complicated, so you would normally use a tool for this.
Reading structs in Haskell
Foo.hs:
{-# LANGUAGE ForeignFunctionInterface #-}
module Foo where
import Foreign.Ptr
import Foreign.Storable
import Foreign.C.Types
-- pure function
foreign export ccall foo :: MyStruct -> Int
foo :: MyStruct -> Int
foo = const 42
-- impure function
foreign export ccall showStruct :: MyStruct -> IO ()
showStruct :: MyStruct -> IO ()
showStruct ss = peek ss >>= print
data MyStructType = MyStructType CInt CChar
deriving (Show, Read, Eq)
type MyStruct = Ptr MyStructType
instance Storable MyStructType where
sizeOf _ = 8
alignment = sizeOf
peek ptr = do
a <- peekByteOff ptr 0
b <- peekByteOff ptr 4
return (MyStructType a b)
test.cpp:
#include <iostream> #include "Foo_stub.h" struct MyStruct { int foo; char bar; }; int main(int argc, char *argv[]) { MyStruct myStruct; myStruct.foo = 7; myStruct.bar = 'x'; hs_init(&argc, &argv); std::cout << foo(&myStruct) << "\n"; showStruct(&myStruct); hs_exit(); return 0; }
Here's where it gets a bit hacky. We need to capture all of Haskell's library dependencies, so we will compile Foo.hs verbosely.
$ ghc Foo.hs -v >ghc_output 2>&1
This should produce Foo.hi, Foo.o, Foo_stub.c, Foo_stub.h, and Foo_stub.o. Take a look at ghc_output and look for "*** Linker" to see all of the libraries that we will need to let g++ know about.
$ grep -A 1 "*** Linker" ghc_output | tail -n 1 | grep -o -- "-L.*" > link_options
Now to build test.cpp:
$ g++ -c test.cpp -I`ghc --print-libdir`/include $ g++ -o test Foo.o Foo_stub.o test.o `cat link_options` $ ./test 42 MyStructType 7 120
When main is in Python
Using ctypes
This is described at the Python wiki page PythonVsHaskell, look for "Using both Python & Haskell with ctypes"
Using swig (and a c wrapper)
This example is adapted from The Swig Tutorial. The factorial function has been modified to call into Haskell.
Foo.hs:
{-# LANGUAGE ForeignFunctionInterface #-}
module Foo where
import Foreign.C.Types
foreign export ccall hs_fact :: CInt -> CInt
hs_fact :: CInt -> CInt
hs_fact n = product [1..n]
example.c:
#include "Foo_stub.h" void py_init(int argc, char *argv[]) { hs_init(&argc, &argv); } void py_exit() { hs_exit(); } int fact(int n) { return hs_fact(n); }
example.i:
%module example %{ /* Put header files here or function declarations like below */ extern int fact(int n); extern void py_init(int argc, char** argv); extern void py_exit(); %} %typemap(in) (int argc, char **argv) { /* Check if is a list */ if (PyList_Check($input)) { int i; $1 = PyList_Size($input); $2 = (char **) malloc(($1+1)*sizeof(char *)); for (i = 0; i < $1; i++) { PyObject *o = PyList_GetItem($input,i); if (PyString_Check(o)) $2[i] = PyString_AsString(PyList_GetItem($input,i)); else { PyErr_SetString(PyExc_TypeError,"list must contain strings"); free($2); return NULL; } } $2[i] = 0; } else { PyErr_SetString(PyExc_TypeError,"not a list"); return NULL; } } %typemap(freearg) (int argc, char **argv) { free((char *) $2); } extern int fact(int n); extern void py_init(int argc, char** argv); extern void py_exit();
run.py:
import example import sys example.py_init(sys.argv) print example.fact(5) example.py_exit()
To build (you may need to change the include path if you are using a different installation of python):
$ ghc -c -dynamic -fPIC Foo.hs $ swig -python example.i $ gcc -fpic -c example.c example_wrap.c -I/usr/include/python2.6 -I`ghc --print-libdir`/include $ ghc -o _example.so -shared -dynamic -fPIC example.o example_wrap.o Foo.o Foo_stub.o -lHSrts-ghc6.12.3 $ python run.py