FFI Introduction

From HaskellWiki


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 %