[Haskell-cafe] GHCi fails to load C++ object files (missing symbol)

Yves Parès yves.pares at gmail.com
Wed Mar 7 17:17:42 CET 2012


Hi, I'm trying to have GHCi load a haskell file that depends on a C++
object file, which causes GHCi to fail because of an unknown symbol (*and I
did link with **libstdc++*), whereas the link into an executable with ghc
works and runs perfectly.

I've reduced my code to the smallest one that produces the problem:
The C++ part defines a mere class and C externals that enable communication
with Haskell:

// Header Stuff.hpp
class Base {
    public:
        Base();
        ~Base();
}

extern "C" {
    Base* mkthing();
    void delthing(Base*);
}

-----------

// Source Stuff.cpp
#include <iostream>
#include "Stuff.hpp"
using namespace std;

Base::Base()
{
    cout << "Base created" << endl;
}

Base::~Base()
{
    cout << "Base deleted" << endl;
}

extern "C" {
    Base* mkthing()
    {
        return new Base();
    }

    void delthing(Base* b)
    {
        delete b;
    }
}

Haskell code (just for reference, but I'm not sure it's relevant), Main.hs:

{-# LANGUAGE ForeignFunctionInterface #-}
import Foreign
import Foreign.C

foreign import ccall unsafe "mkthing"
  mkthing :: IO (Ptr ())

foreign import ccall unsafe "delthing"
  delthing :: Ptr () -> IO ()

main = do
  p <- mkthing
  delthing p


I then compile it with:
g++ -c Stuff.cpp
ghci Main.hs Stuff.o -lstdc++

And then the error is:
Loading object (static) Stuff.o ... done
Loading object (dynamic)
/usr/lib/i386-linux-gnu/gcc/i686-linux-gnu/4.5.2/libstdc++.so ... done
final link ... ghc: Stuff.o: unknown symbol `__dso_handle'
linking extra libraries/objects failed

Whereas 'ghc Main.hs Stuff.o -lstdc++' works just fine.
Does GHCi lacks a link directive that regular GHC has?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120307/008dbcea/attachment.htm>


More information about the Haskell-Cafe mailing list