[Haskell-cafe] Trouble with the FFI, Cabal, and GHCI -- installed libraries have invalid FFI pointers

John Millikin jmillikin at gmail.com
Tue Apr 27 14:42:34 EDT 2010


I have two modules. One is a library, installed with Cabal:

-------------------------------------------------------------------------
-- Data/Text/IDN/StringPrep.hs
{-# LANGUAGE ForeignFunctionInterface #-}
module Data.Text.IDN.StringPrep where
import Foreign

foreign import ccall "stringprep.h &stringprep_nameprep"
	profileNameprep :: Ptr ()
-------------------------------------------------------------------------

The other is the main program, either interpreted directly or compiled and run:

-------------------------------------------------------------------------
-- TestIDN.hs
{-# LANGUAGE ForeignFunctionInterface #-}
module Main where
import Foreign
import Data.Text.IDN.StringPrep

foreign import ccall "stringprep.h &stringprep_nameprep"
	stringprep_nameprep :: Ptr ()

main = do
	putStrLn $ "stringprep_nameprep = " ++ show stringprep_nameprep
	putStrLn $ "profileNameprep     = " ++ show profileNameprep
-------------------------------------------------------------------------

Now, given that both modules import the exact same C symbol, I would
expect that the pointers would be the same when running. This is the
case for compiled code:

-------------------------------------------------------------------------
$ ghc --make TestIDN
[1 of 1] Compiling Main             ( TestIDN.hs, TestIDN.o )
Linking TestIDN ...
$ ./TestIDN
stringprep_nameprep = 0x000000000067e3e0
profileNameprep     = 0x000000000067e3e0
-------------------------------------------------------------------------

However, if I use ghci / runhaskell, the pointers are different:

-------------------------------------------------------------------------
$ rm TestIDN TestIDN.o TestIDN.hi
$ runhaskell TestIDN.hs
stringprep_nameprep = 0x00007feebe5fe4e0
profileNameprep     = 0x0000000040a908bc
-------------------------------------------------------------------------

Specifically, the pointer loaded from the library ('profileNameprep')
is invalid -- attempting to pass it to libidn will result in errors,
and trying to poke around in it yields segmentation faults.

I'm using GHC 6.12.1, on Linux. This problem occurs with both dynamic
and static libraries.

Does anybody have suggestions about how to solve or work around it?


More information about the Haskell-Cafe mailing list