Author: Eiko

Tags: haskell, ffi, foreign function interface, C, Storable, ForeignPtr, c2hs, inline-c

Time: 2025-01-19 10:47:53 - 2025-01-20 16:11:56 (UTC)

FFI In Haskell

FFI (Foreign Function Interface) is a mechanism to call code from other languages. The Haskell FFI are often used to bind or wrap C libraries. Sometimes it can also be used to export routines to be called from other languages.

C Header Files

C header files contain the function prototypes and type definitions that are needed to call C functions from Haskell, it’s a public interface to a C library.

Haskell FFI

Let’s see an example of how FFI is used in Haskell. We will use the sin function from the C library math.h and the rand function from the C library stdlib.h.

{-# LANGUAGE ForeignFunctionInterface #-}

import Foreign
import Foreign.C.Types

foreign import ccall unsafe "math.h sin"
  c_sin :: CDouble -> CDouble

foreign import ccall unsafe "stdlib.h rand"
  c_rand :: IO CUInt
  • Here safe and unsafe are two calling conventions in Haskell. safe is the default and it has some performance overhead (around 300 nanoseconds) because it does some extra checks and some runtime awareness. unsafe is primitive and faster, it is usually safe to use.

    When to use safe?

    • safe is required if foreign function can call back into Haskell.

    • safe is recommended if a foreign function can block for a long time, since the overhead (hundreds of nanoseconds) is negligible compared to the blocking time.

    • If you don’t specify a calling convention, Haskell will default to safe.

Handling Pointers

Consider the following functions in C that has pointer types,

int thing_get_version(thing_t *thing);

char* thing_get_name(thing_t *thing);

int thing_new(char *name, thing_t **p);

They are translated into Haskell as follows,

foreign import ccall unsafe "thing.h thing_get_version"
  c_thing_get_version :: Ptr Thing -> CInt

foreign import ccall unsafe "thing.h thing_get_name"
  c_thing_get_name :: Ptr Thing -> Ptr CChar

foreign import ccall unsafe "thing.h thing_new"
  c_thing_new :: Ptr CChar -> Ptr (Ptr Thing) -> IO CInt

Storable: Primitive Operations on Pointers

Storable is a type class that defines how to read and write a value to memory, with primitive operations on pointers. It is used to define how to marshal Haskell data types to and from C data types.

module Foreign.Storable where

class Storable a where
  {-# MINIMAL sizeOf
            , alignment
            , (peek | peekElemOff | peekByteOff)
            , (poke | pokeElemOff | pokeByteOff) 
            #-}

  sizeOf :: a -> Int
  -- ^ computes the storage requirements (in bytes) of the argument
  -- the argument is not used so you can pass `undefined`

  alignment :: a -> Int
  -- ^ computes the alignment constraint of the argument

  peek :: Ptr a -> IO a
  -- ^ read a value from a memory location

  poke :: Ptr a -> a -> IO ()
  -- ^ write a value to a memory location

  -- default implementations
  peekElemOff :: Ptr a -> Int -> IO a
  -- ^ peekElemOff p i reads a value from a memory location p + i * sizeOf a

  pokeElemOff :: Ptr a -> Int -> a -> IO ()
  -- ^ pokeElemOff p i writes a value to a memory location p + i * sizeOf a

  peekByteOff :: Ptr b -> Int -> IO a
  -- ^ peekByteOff p i reads a value from a memory location p + i

  pokeByteOff :: Ptr b -> Int -> a -> IO ()
  -- ^ pokeByteOff p i writes a value to a memory location p + i

Foreign.Marshal.Alloc

alloca :: Storable a => (Ptr a -> IO b) -> IO b
-- ^ allocates memory for a value of type a and passes a pointer to it to the computation

Foreign.ForeignPtr

The type ForeignPtr represents references to objects that are maintained in a foreign language, i.e., that are not part of the data structures usually managed by the Haskell storage manager. The essential difference between ForeignPtrs and vanilla memory references of type Ptr a is that the former may be associated with finalizers. A finalizerz is a routine that is invoked when the Haskell storage manager detects that - within the Haskell heap and stack - there are no more references left that are pointing to the ForeignPtr. Typically, the finalizer will, then, invoke routines in the foreign language that free the resources bound by the foreign object.

type FinalizerPtr a = FunPtr (Ptr a -> IO ())
-- ^ a finalizer is a pointer to a foreign function that will be called when the ForeignPtr is no longer referenced

newForeignPtr :: FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
-- ^ create a ForeignPtr with a finalizer

withForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
-- ^ perform an action on the pointer inside a ForeignPtr

Handling Strings

Using Foreign.C.String module, we can handle C strings in Haskell. The CString type is a pointer to a null-terminated array of CChar (which is an 8-bit character).

type CString = Ptr CChar
-- ^ this is the definition of CString in Foreign.C.String
-- so you can write CString instead of Ptr CChar

in the library Foreign.C.String there are functions that can be used to convert between CString and String,

peekCString :: CString -> IO String
-- ^ convert a CString to a Haskell String

withCString :: String -> (CString -> IO a) -> IO a
-- ^ convert a Haskell String to a CString

c2hs

c2hs is a preprocessor that converts C header files into Haskell modules. It is a tool that simplifies the process of writing FFI code. It generates Haskell code that uses the FFI to call C functions.

  • Preprocessor that simplifies binding C libraries to Haskell

  • Handles enum and typedef

  • Automatic foreign import generation

  • Uses .chs files and outputs .hs files

Enum

typedef enum {
  Alpha_alpha, Beta_beta, Gamma_gamma, Delta_delta
} some_enum;
{#enum some_enum as SomeEnum {underscoreToCase} deriving (Eq, Show) #}

-- this will generate the following code

data SomeEnum = AlphaAlpha | BetaBeta | GammaGamma | DeltaDelta
  deriving (Enum, Eq, Show)

Typedef

typedef struct {
  int x;
  int y;
} point_t;
{#pointer *point_t as PointT #}

-- this will generate the following code

Example Project

Here is a step by step example project that demonstrates how to use FFI in Haskell, setup C library and cabal configuration.

mkdir FFILearn
cd FFILearn
cabal init -n

mkdir c-src
mkdir include

Example C Library

// c-src/myclib.h
#ifndef MYCLIB_H
#define MYCLIB_H

// Function to add two integers, testing FFI
int mylib_add(int a, int b);

// Function to print a string, testing FFI
void mylib_print(const char* str);

// Function that returns a pointer to a string, testing FFI
const char* mylib_get_string();

#endif // MYCLIB_H
//include/myclib.c
#include "myclib.h"
#include <stdio.h>

// Function to add two integers, testing FFI
int mylib_add(int a, int b) {
    return a + b;
}

// Function to print a string, testing FFI
void mylib_print(const char* str) {
    printf("%s\n", str);
}

// Function that returns a pointer to a string, testing FFI
const char* mylib_get_string() {
    return "String from mylib!";
}

Haskell FFI

-- app/MyLib.hs
module MyLib where

import Foreign.C.Types
import Foreign.C.String

foreign import ccall "myclib.h mylib_add"
  c_mylib_add :: CInt -> CInt -> CInt

foreign import ccall "myclib.h mylib_print"
  c_mylib_print :: CString -> IO ()

foreign import ccall "myclib.h mylib_get_string"
  c_mylib_get_string :: IO CString

mylib_add :: Int -> Int -> Int
mylib_add a b = fromIntegral $ c_mylib_add (fromIntegral a) (fromIntegral b)

mylib_print :: String -> IO ()
mylib_print s = withCString s c_mylib_print

mylib_get_string :: IO String
mylib_get_string = do
  cs <- c_mylib_get_string
  peekCString cs
-- app/Main.hs
module Main where

import MyLib

main :: IO ()
main = do
  mylib_print $ "add 1 2 = " ++ show (mylib_add 1 2)
  mylib_print $ "add 3 4 = " ++ show (mylib_add 3 4)
  mylib_print "Hello from Haskell!"
  s <- mylib_get_string
  mylib_print $ "mylib_get_string = " ++ s

Cabal Configuration

executable FFILearn
    -- Import common warning flags.
    import:           warnings

    -- .hs or .lhs file containing the Main module.
    main-is:          Main.hs

    -- Modules included in this executable, other than Main.
    other-modules:    MyLib

    -- LANGUAGE extensions used by modules in this package.
    -- other-extensions:

    -- Other library packages from which modules are imported.
    build-depends:    base ^>=4.20.0.0

    -- Directories containing source files.
    hs-source-dirs:   app

    -- Base language which the package is written in.
    default-language: GHC2024

    include-dirs: include

    c-sources: c-src/myclib.c

Build and Run

cabal build
cabal run

Output:

add 1 2 = 3
add 3 4 = 7
Hello from Haskell!
mylib_get_string = String from mylib!

Other Interesting Tools

Community have also developed some interesting tools based on Template Haskell to make FFI easier,

  • inline-c - Inline C code in Haskell, allowing you to write C code directly in Haskell source files without the need for separate C files. Suitable for small C snippets.

  • They also provides inline-cpp and inlinc-c-cuda. The repo can be found here.

Inline-C Example

{-# LANGUAGE QuasiQuotes, TemplateHaskell #-}
module MyLib where

import qualified Language.C.Inline as C
import qualified Language.C.Inline.Unsafe as CU
import Foreign.C.String (newCString)
import System.IO.Unsafe (unsafeDupablePerformIO)

C.include "<stdio.h>"

myAdd :: Int -> Int -> Int
myAdd a b =
  let a' = fromIntegral a
      b' = fromIntegral b
  in fromIntegral [CU.pure| long { $(long a') + $(long b') } |]

myFib :: Int -> Int
myFib n =
  let n' = fromIntegral n
  in fromIntegral $ unsafeDupablePerformIO 
      -- unsafeDupablePerformIO avoids the overhead of unsafePerformIO
      [CU.block|
      long {
        long a = 0, b = 1, c;
        for (int i = 0; i < $(int n'); i++) {
          c = a + b;
          a = b;
          b = c;
        }
        return a;
      } |]

myPrint :: String -> IO ()
myPrint str = do
  cstr <- newCString str
  [CU.exp| void { printf("%s\n", $(const char *cstr)) } |]
module Main where

import MyLib

main :: IO ()
main = do
  myPrint $ "1 + 2 = " ++ show (myAdd 1 2)
  myPrint $ "fib 50 = " ++ show (myFib 50)
  myPrint "Hello, world! (from C using printf)"

Integration With Other Languages

  • R language: inline-r, part of the HaskellR project.

  • python : inline-python, this is a brand new project under development, I just found it on hackage and GitHub. Maybe we could look into it.

  • javascript: The GHCJS project provides javascript FFI. GHC also have a javascript backend , i.e. you can compile Haskell to javascript.

  • WebAssembly: GHC also have a WebAssembly backend, allowing compiling Haskell to WebAssembly.