Foreign Function Interface
Ticket: #35
Brief Explanation
The Foreign Function Interface (FFI) adds support for invoking code and accessing data structures implemented in other programming languages and vice versa. The current proposal encompasses a general mechanism for inter-language operations as well as specific support for interoperating with the C programming language.
References
- FFI addendum to Haskell98.
- GHC specifics affecting the FFI
Pros
- Widely accepted and used addendum.
- Provides an essential facility.
Cons
- Inappropriate use can subvert all semantic guarantees provided by Haskell and can cause memory corruption and program crashes.
Integration into the report
The FFI addendum is already written and formatted in the style of the report — it should be straight forward to integrate. In addition the following changes relative to the original addendum will be applied.
Libraries
We use the hierarchical names from the standard library, instead of the names in the FFI addendum.
Moreover, the current libraries have grown somewhat since the original FFI Addendum. We include the additions listed in the following:
- In
Foreign.C.Error
:throwErrnoIfRetryMayBlock
,throwErrnoIfRetryMayBlock_
,throwErrnoIfMinus1RetryMayBlock
,throwErrnoIfMinus1RetryMayBlock_
,throwErrnoIfNullRetryMayBlock
,throwErrnoPath
,throwErrnoPathIf
,throwErrnoPathIf_
,throwErrnoPathIfNull
,throwErrnoPathIfMinus1
, &throwErrnoPathIfMinus1_
- In
Foreign.ForeignPtr
:finalizeForeignPtr
- In
Foreign.Marshal.Array
:withArrayLen
,withArrayLen0
-
Foreign.Marshal.Error
does actually omit some routines of the FFI Addendum . I think we need to keep them in the FFI specification.
Furthermore we add:
-
Add
castCharToCUChar
,castCUCharToChar
,castCharToCSChar
, andcastCSCharToChar
(i.e., not only for CChar of which it is platform-dependent whether it is signed or not). -
Add types from ISO C99 (with conversion routines):
WordPtr uintptr_t WordMax uintmax_t IntPtr intptr_t IntMax intmax_t ptrToWordPtr :: Ptr a -> WordPtr wordPtrToPtr :: WordPtr -> Ptr a ptrToIntPtr :: Ptr a -> IntPtr intPtrToPtr :: IntPtr -> Ptr a
NB:
- We do not include
Foreign.Marshal.Pool
in the standard as it doesn't appear to be widely used and doesn't have an efficient implementation at the moment. - We omit the functions that, in the standard libraries, have been moved from
Foreign.Marshal.Error
toSystem.IO.Error
(namely those to construct I/O errors). - Some issues have been raised with
Data.Bits
. However, any helpful changes would be too significant to consider at this stage. This is a minor problem as a future revision has to overhaul the libraries anyway.
unsafePerformIO
Instead of Foreign.unsafePerformIO
, we will have Foreign.Marshal.unsafeLocalState
. Moreover, we limit the support of the function to implementing memory management and memory access —and possibly, C-land initialisation— during marshalling for foreign functions that ought to get a pure Haskell type. Specifically, we will use the following wording (or something close):
Wrap a pure computation that uses local memory. The only IO operations permitted in the IO action passed to
unsafePerformIO
are (a) local allocation (alloca
,allocaBytes
and derived operations such aswithArray
andwithCString
), and (b) pointer operations (Foreign.Storable
andForeign.Ptr
) on the pointers to local storage, and © foreign functions whose only observable effect is to read and/or write the locally allocated memory. This primitive enables the packaging of external entities that are pure functions except that they pass arguments and/or results via pointers. It is expected that this operation will be replaced in a future revision of Haskell.
Alignment
Except for mallocBytes
& allocaBytes
, the original FFI addendum does not specify any constraints on alignment for allocated memory (by mallocForeignPtrBytes
and others). This is clearly an oversight. We add the following statement concerning alignment at the beginning of Section 5 (which describes the library modules):
All storage allocated by functions that allocate based on a size in bytes must be sufficiently aligned for any of the basic foreign types (see Section 3.2) that fits into the newly allocated storage. All storage allocated by functions that allocated based on a specific type must be sufficiently aligned for that type. Array allocation routines need to obey the same alignment constraints for each array element.
Transparent marshalling of newtypes
The FFI addendum defines in Section 3.2 that The argument types ati
produced by fatype
must be marshallable foreign types; that is, each ati
is either (1) a basic foreign type or (2) a type synonym or renamed datatype of a marshallable foreign type. We will improve on the second part of this statement as follows:
- As the transparent marshalling of newtypes (aka renamed datatypes) is a fairly significant features, we will dedicate a separate (sub)subsection to it.
- In contrast to the FFI addendum (and it's implementation in GHC), we require that a newtype in a foreign signature is not abstract. Only if its constructor is visible, can the newtype be transparently marshalled. (After all, marshalling makes only sense if we know the type of the value in foreign land.) This implies that we will export the newtypes in the modules
Foreign.C.Types
and - Clarify the connection between marshallable foreign types and the various flavours of foreign signatures discussed in Section 4.1.3. (E.g., in case of a
foreign import "dynamic"
the whole signature —grammar nonterminalftype
— doesn't need to be marshallable, only portions of it.) - We allow GHC's newtype wrapping of the IO monad.
- We add one or two examples.
Concurrency
Multi-threading support is implementation-specific.
Considerations for the future
As noted above, we expect that unsafePerformIO
will be replaced in a future revision (that supports rank-2 types) with a function that safely encapsulates the local state. A possible implementation would be the following:
{-# LANGUAGE RankNTypes, ForeignFunctionInterface, GeneralizedNewtypeDeriving #-}
module Example where
import Foreign.C.Types
import qualified Foreign.Marshal.Alloc as F
import qualified Foreign.Ptr as F
import qualified Foreign.Storable as F
import System.IO.Unsafe (unsafePerformIO)
-- Monad for memory regions, and type of pointers within such regions.
-- Ideally all the implementations would be hidden
newtype ST s a = UnsafeIOToST { unsafeSTToIO :: IO a } deriving Monad
newtype STPtr s a = STPtr (F.Ptr a)
runST :: (forall s. ST s a) -> a
peek :: F.Storable a => STPtr s a -> ST s a
poke :: F.Storable a => STPtr s a -> a -> ST s ()
alloca :: F.Storable a => (STPtr s a -> ST s b) -> ST s b
-- sample implementations
runST act = unsafePerformIO (unsafeSTToIO act)
peek (STPtr p) = UnsafeIOToST (F.peek p)
poke (STPtr p) v = UnsafeIOToST (F.poke p v)
alloca f = UnsafeIOToST (F.alloca (unsafeSTToIO . f . STPtr))
-- Example of a wrapping of an otherwise pure function using pass-by-reference
frexp :: Double -> (Double, Int)
frexp x = runST (alloca $ \ exp_ptr -> do
fraction <- c_frexp (realToFrac x) exp_ptr
exponent <- peek exp_ptr
return (realToFrac fraction, fromIntegral exponent))
foreign import ccall "math.h frexp"
c_frexp :: CDouble -> STPtr s CInt -> ST s CDouble