views:

121

answers:

1

I have defined the following module to help me with FFI function export:

{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, TypeSynonymInstances #-}
module ExportFFI where

import Foreign
import Foreign.C


class FFI basic ffitype | basic -> ffitype where
    toFFI :: basic -> IO ffitype
    fromFFI :: ffitype -> IO basic
    freeFFI :: ffitype -> IO ()

instance FFI String CString where
    toFFI = newCString
    fromFFI = peekCString
    freeFFI = free

I'm struggling with the instance for functions. Can someone help me?

+2  A: 

There are two things you can do with functions involving the FFI: 1) Marshalling: this means converting a function to a type that can be exported through the FFI. This accomplished by FunPtr. 2) Exporting: this means creating a means for non-Haskell code to call into a Haskell function.

Your FFI class helps with marshalling, and first I create a few sample instances of how to marshal functions.

This is untested, but it compiles and I expect it would work. First, let's change the class slightly:

class FFI basic ffitype | basic -> ffitype, ffitype -> basic where
    toFFI :: basic -> IO ffitype
    fromFFI :: ffitype -> IO basic
    freeFFI :: ffitype -> IO ()

This says that given the type of either "basic" or "ffitype", the other is fixed[1]. This means it's no longer possible to marshal two different values to the same type, e.g. you can no longer have both

instance FFI Int CInt where

instance FFI Int32 CInt where

The reason for this is because freeFFI can't be used as you've defined it; there's no way to determine which instance to select from just the ffitype. Alternatively you could change the type to freeFFI :: ffitype -> basic -> IO (), or (better?) freeFFI :: ffitype -> IO basic. Then you wouldn't need fundeps at all.

The only way to allocate a FunPtr is with a "foreign import" statement, which only works with fully instantiated types. You also need to enable the ForeignFunctionInterface extension. As a result the toFFI function, which should return an IO (FunPtr x), can't be polymorphic over function types. In other words, you'd need this:

foreign import ccall "wrapper"
  mkIntFn :: (Int32 -> Int32) -> IO (FunPtr (Int32 -> Int32))

foreign import ccall "dynamic"
  dynIntFn :: FunPtr (Int32 -> Int32) -> (Int32 -> Int32)

instance FFI (Int32 -> Int32) (FunPtr (Int32 -> Int32)) where
    toFFI = mkIntFn
    fromFFI = return . dynIntFn
    freeFFI = freeHaskellFunPtr

for every different function type you want to marshal. You also need the FlexibleInstances extension for this instance. There are a few restrictions imposed by the FFI: every type must be a marshallable foreign type, and the function return type must be either a marshallable foreign type or an IO action which returns a marshallable foreign type.

For non-marshallable types (e.g. Strings) you need something slightly more complex. First of all, since marshalling happens in IO you can only marshal functions that result in an IO action. If you want to marshal pure functions, e.g. (String -> String), you need to lift them to the form (String -> IO String).[2] Let's define two helpers:

wrapFn :: (FFI a ca, FFI b cb) => (a -> IO b) -> (ca -> IO cb)
wrapFn fn = fromFFI >=> fn >=> toFFI

unwrapFn :: (FFI a ca, FFI b cb) => (ca -> IO cb) -> (a -> IO b)
unwrapFn fn a = bracket (toFFI a) freeFFI (fn >=> fromFFI)

These convert the types of functions to the appropriate marshalled values, e.g. wrapStrFn :: (String -> IO String) -> (CString -> IO CString); wrapStrFn = wrapFn. Note that unwrapFn uses "Control.Exception.bracket" to ensure the resource is freed in case of exceptions. Ignoring this you could write unwrapFn fn = toFFI >=> fn >=> fromFFI; see the similarity to wrapFn.

Now that we have these helpers we can start to write instances:

foreign import ccall "wrapper"
  mkStrFn :: (CString -> IO CString) -> IO (FunPtr (CString -> IO CString))

foreign import ccall "dynamic"
  dynStrFn :: FunPtr (CString -> IO CString) -> (CString -> IO CString)

instance FFI (String -> IO String) (FunPtr (CString -> IO CString)) where
    toFFI = mkStrFn . wrapFn
    fromFFI = return . unwrapFn . dynStrFn
    freeFFI = freeHaskellFunPtr

As before, it's not possible to make these functions polymorphic, which leads to my biggest reservation about this system. It's a lot of overhead because you need to create separate wrappers and instances for each type of function. Unless you're doing a lot of marshalling of functions, I would seriously doubt it's worth the effort.

That's how you can marshal functions, but what if you want to make them available to calling code? This other process is exporting the function, and we've already developed most of what's necessary.

Exported functions must have marshallable types, just like FunPtrs. We can simply re-use the wrapFn to do this. To export a few functions all you need to do is wrap them with wrapFn and export the wrapped versions:

f1 :: Int -> Int
f1 = (+2)

f2 :: String -> String
f2 = reverse

f3 :: String -> IO Int
f3 = return . length

foreign export ccall f1Wrapped :: CInt -> IO CInt
f1Wrapped = wrapFn (return . f1)

foreign export ccall f2Wrapped :: CString -> IO CString
f2Wrapped = wrapFn (return . f2)

foreign export ccall f3Wrapped :: CString -> IO CInt
f3Wrapped = wrapFn f3

Unfortunately this setup only works for single-argument functions. To support all functions, let's make another class:

class ExportFunction a b where
  exportFunction :: a -> b

instance (FFI a ca, FFI b cb) => ExportFunction (a->b) (ca -> IO cb) where
  exportFunction fn = (wrapFn (return . fn))

instance (FFI a ca, FFI b cb, FFI d cd) => ExportFunction (a->b->d) (ca->cb->IO cd) where
  exportFunction fn = \ca cb -> do
    a <- fromFFI ca
    b <- fromFFI cb
    toFFI $ fn a b

Now we can use exportFunction for functions with 1 and 2 arguments:

f4 :: Int -> Int -> Int
f4 = (+)

f4Wrapped :: CInt -> CInt -> IO CInt
f4Wrapped = exportFunction f4

foreign export ccall f4Wrapped :: CInt -> CInt -> IO CInt

f3Wrapped2 = :: CString -> IO CInt
f3Wrapped2 = exportFunction f3

foreign export ccall f3Wrapped2 :: CString -> IO CInt
f3Wrapped2 = exportFunction f3

Now you just need to write more instances of ExportFunction to automatically convert any function to the appropriate type for exporting. I think this is the best you can do without either either using some type of pre-processor or unsafePerformIO.

[1] Technically, I don't think there's any need for the "basic -> ffitype" fundep, so you could remove it to enable one basic type to map to multiple ffitypes. One reason to do so would be to map all sized ints to Integers, although the toFFI implementations would be lossy.

[2] A slight simplification. You could marshal a function String -> String to the FFI type of CString -> IO CString. But now you can't convert the CString -> IO CString function back to String -> String because of the IO in the return type.

John
Forgot to mention, this only applies to exporting Haskell functions. Importing functions through the FFI would best be handled with something like c2hs or GreenCard.
John
My primary focus is on `foreign export`. I'm not sure how would your solution map to exporting functions. FunPtr isn't really important here because of this.
Tener
You need a FunPtr to marshal a function, which is what your FFI class does (i.e. it marshals stuff). I've added a bit to explain how to use it to export functions, but there's still some work to do.
John