Difference between revisions of "FFI Introduction"

From HaskellWiki
Jump to navigation Jump to search
m (Remove section)
(→‎Complete example with GHC: Added a link to termios man page)
 
(2 intermediate revisions by one other user not shown)
Line 3: Line 3:
   
 
Haskell's FFI is used to call functions from other languages (basically C at this point), and for C to call Haskell functions.
 
Haskell's FFI is used to call functions from other languages (basically C at this point), and for C to call Haskell functions.
 
== Short version ==
 
 
There are many more useful examples in the [[FFI cook book]], but here's a few basic ones:
 
 
<haskell>
 
{-# INCLUDE <math.h> #-}
 
{-# LANGUAGE ForeignFunctionInterface #-}
 
module FfiExample where
 
import Foreign.C -- get the C types
 
 
-- pure function
 
foreign import ccall "sin" c_sin :: CDouble -> CDouble
 
sin :: Double -> Double
 
sin d = realToFrac (c_sin (realToFrac d))
 
</haskell>
 
 
Note that the FFI document recommends putting the header in the double quotes, like
 
 
<haskell>
 
foreign import ccall "math.h sin" c_sin :: CDouble -> CDouble
 
</haskell>
 
 
[http://www.haskell.org/ghc/docs/6.10.1/html/users_guide/ffi-ghc.html#glasgow-foreign-headers GHC since 6.10.x ignores] both the <tt>INCLUDE</tt> pragma (equivalently command line <tt>-#include</tt>) and the header in the double quotes. [http://www.haskell.org/ghc/docs/6.8.3/html/users_guide/ffi-ghc.html#glasgow-foreign-headers GHC 6.8.x and before prefers] the <tt>INCLUDE</tt> pragma (equivalently command line <tt>-#include</tt>) and in Cabal package descriptions. Other compilers probably prefer the header in the double quotes (if they compile via C) or ignore (if they do not compile via C)—check their documentations.
 
 
Notice that C types are not the same as Haskell types, and you have to import them from Foreign.C. Notice also that, as usual in Haskell, you have to explicitly convert to and from Haskell types. Using c_<name_of_c_function> for the raw C function is just my convention.
 
 
The Haskell report only guarantees that Int has 30 bits of signed precision, so converting CInt to Int is not safe! On the other hand, many classes have instances for Int and Integer but not CInt, so it's generally more convenient to convert from the C types. To convert, I suppose you could either write a <code>checkedFromIntegral</code> function if you're sure it's small or just use Integer.
 
 
For details on impure functions, pointers to objects, etc., see the cookbook.
 
   
 
== Compiling FFI-using modules ==
 
== Compiling FFI-using modules ==
 
=== GHC ===
 
 
Here's a makefile fragment to compile an FfiExample module that uses C functions from c_functions.c, which uses library functions from libcfuncs:
 
 
<pre>
 
HFLAGS=-I/path/to/lib/include -L/path/to/lib
 
 
_dummy_target: c_functions.o c_functions.h
 
ghc $(HFLAGS) -main-is FfiExample --make -o ffi_example c_functions.o -lcfuncs
 
</pre>
 
 
Notice the use of _dummy_target and --make. The idea is that you get make to compile what is necessary for C, and then always run ghc with --make, at which point it will figure out what is necessary to compile for Haskell.
 
 
Actually, this is broken, because ghc --make will not notice if a .o file has changed!
 
 
[ ''this is just my hack, anyone have a better way to do this?'' ]
 
   
 
== Complete example with GHC ==
 
== Complete example with GHC ==
   
GHC's libs don't (apparently?) support generic termios stuff. I could implement the whole tcgetattr / tcsetattr thing, but let's just turn ICANON on and off, so IO.getChar doesn't wait for a newline:
+
GHC's libs don't (apparently?) support generic [http://linux.die.net/man/3/termios termios] stuff. I could implement the whole tcgetattr / tcsetattr thing, but let's just turn ICANON on and off, so IO.getChar doesn't wait for a newline:
   
 
termops.c:
 
termops.c:

Latest revision as of 12:45, 17 February 2015


Haskell's FFI is used to call functions from other languages (basically C at this point), and for C to call Haskell functions.

Compiling FFI-using modules

Complete example with GHC

GHC's libs don't (apparently?) support generic termios stuff. I could implement the whole tcgetattr / tcsetattr thing, but let's just turn ICANON on and off, so IO.getChar doesn't wait for a newline:

termops.c:

#include <termios.h>
#include "termops.h"

void
set_icanon(int fd)
{
        struct termios term;
        tcgetattr(0, &term);
        term.c_lflag |= ICANON;
        tcsetattr(fd, TCSAFLUSH, &term);
}


void
unset_icanon(int fd)
{
        struct termios term;
        tcgetattr(0, &term);
        term.c_lflag &= ~ICANON;
        tcsetattr(fd, TCSAFLUSH, &term);
}

termops.h:

void set_icanon(int fd);
void unset_icanon(int fd);

Termios.hs:

{-# INCLUDE <termios.h> #-}
{-# INCLUDE "termops.h" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module Termios where
import Foreign.C

foreign import ccall "set_icanon" set_icanon :: CInt -> IO ()
foreign import ccall "unset_icanon" unset_icanon :: CInt -> IO ()

FfiEx.hs:

module FfiEx where
import Control.Exception
import System.IO
import qualified Termios
import Control.Monad (when)

main = bracket_ (Termios.unset_icanon 0) (Termios.set_icanon 0)
    (while_true prompt)
    
while_true op = do
    continue <- op
    when continue (while_true op)
    
prompt = do
    putStr "? "
    hFlush stdout
    c <- getChar
    putStrLn $ "you typed " ++ [c]
    return (c /= 'q')

makefile:

_ffi_ex: termops.o
    ghc --make -main-is FfiEx -o ffi_ex FfiEx.hs termops.o

[this only worked for me when I omitted termops.o at the end of the `ghc --make` command. Seems like it searches for and finds the .o automatically? --lodi ]


And now:


% make
gcc -c -o termops.o termops.c
ghc --make -main-is FfiEx -o ffi_ex FfiEx.hs termops.o
[1 of 2] Compiling Termios          ( Termios.hs, Termios.o )
[2 of 2] Compiling FfiEx            ( FfiEx.hs, FfiEx.o )
Linking ffi_ex ...
% ./ffi_ex
? you typed a
? you typed b
? you typed q
%