3

I want to create a haskell interpreter that I can use from C++ on linux.

I have a file FFIInterpreter.hs which implements the interpreter in haskell and exports the functions via FFI to C++.

module FFIInterpreter where

import Language.Haskell.Interpreter

import Data.IORef
import Foreign.StablePtr
import Foreign.C.Types
import Foreign.C.String
import Control.Monad
import Foreign.Marshal.Alloc

type Session = Interpreter ()
type Context = StablePtr (IORef Session)

foreign export ccall createContext :: CString -> IO Context
createContext :: CString -> IO Context
createContext name = join ((liftM doCreateContext) (peekCString name))
  where
    doCreateContext :: ModuleName -> IO Context
    doCreateContext name 
      = do let session = newModule name 
           _ <- runInterpreter session
           liftIO $ newStablePtr =<< newIORef session

newModule :: ModuleName -> Session
newModule name = loadModules [name] >> setTopLevelModules [name]

foreign export ccall freeContext :: Context -> IO ()
freeContext :: Context -> IO ()
freeContext = freeStablePtr

foreign export ccall runExpr :: Context -> CString -> IO CString
runExpr :: Context -> CString -> IO CString
runExpr env input = join ((liftM newCString) (join (((liftM liftM) doRunExpr) env (peekCString input))))
  where
    doRunExpr :: Context -> String -> IO String
    doRunExpr env input
      = do env_value <- deRefStablePtr env
           tcs_value <- readIORef env_value
           result    <- runInterpreter (tcs_value >> eval input)
           return $ either show id result

foreign export ccall freeString :: CString -> IO ()
freeString :: CString -> IO ()
freeString = Foreign.Marshal.Alloc.free

When I compile the whole project with ghc, everything works fine. I use the following command:

ghc -no-hs-main FFIInterpreter.hs main.cpp -lstdc++

But the haskell module is only a small piece of the C++ project and I don't want the whole project to depend on ghc.

So I want to build a dynamic library with ghc and then link it to the project using g++.

$ ghc -shared -fPIC FFIInterpreter.hs module_init.c -lstdc++
[1 of 1] Compiling FFIInterpreter   ( FFIInterpreter.hs, FFIInterpreter.o )
Linking a.out ...
/usr/bin/ld: /usr/lib/haskell-packages/ghc/lib/hint-0.3.3.2/ghc-7.0.3/libHShint-0.3.3.2.a(Interpreter.o): relocation R_X86_64_32S against `.data' can not be used when making a shared object; recompile with -fPIC
/usr/lib/haskell-packages/ghc/lib/hint-0.3.3.2/ghc-7.0.3/libHShint-0.3.3.2.a: could not read symbols: Bad value
collect2: ld gab 1 als Ende-Status zurück

So I added the -dynamic keyword, but that also doesn't work:

$ ghc -dynamic -shared -fPIC FFIInterpreter.hs librarymain.cpp -lstdc++
FFIInterpreter.hs:3:8:
    Could not find module `Language.Haskell.Interpreter':
      Perhaps you haven't installed the "dyn" libraries for package `hint-0.3.3.2'?
      Use -v to see a list of the files searched for.

I searched my system for Interpreter.dyn_hi but didn't find it. Is there a way to get it? I also tried to install hint manually, but this also doesn't deliver the Interpreter.dyn_hi file.

Heinzi
  • 5,793
  • 4
  • 40
  • 69

1 Answers1

3

You have to install the library (and all it depends on) with the --enable-shared flag (using cabal-install) to get the .dyn_hi and .dyn_o files. You may consider setting that option in your ~/.cabal/config file.

Perhaps the easiest way is to uncomment the shared: XXX line in ~/.cabal/config, set the option to True and

cabal install --reinstall world

For safety, run that with the --dry-run option first to detect problems early. If the --dry-run output looks reasonable, go ahead and reinstall - it will take a while, though.

Daniel Fischer
  • 181,706
  • 17
  • 308
  • 431
  • This won't end well, Atleast it didn't for me. After he gets done recompiling all his libraries he'll run into the problem that the libraries shipped with GHC aren't compiled with dyn or -fPIC, So he'll have to grab the GHC source and recompile and edit the makefile. Then when he finished he'll still get an error that libFFI is not compiled with -fPIC, apparently, it doesn't inherit the settings from build.mk, so you edit that and recompile, and it still give you an error. That's where i'm stuck myself http://stackoverflow.com/questions/7652799/compiling-ghc-with-fpic-support – Phyx Jan 03 '12 at 13:23
  • Ah, pity. I don't remember when exactly and I don't know what changed, but not long ago the handling of libFFI was changed, _maybe_ that would make it possible. Have you tried HEAD? – Daniel Fischer Jan 03 '12 at 13:40
  • I'm using a 7.0.3 src, I'll give HEAD a try, see if that works. – Phyx Jan 03 '12 at 14:42