[Haskell-cafe] FFI, C/C++ and undefined references

DNM dnmehay at gmail.com
Wed Jan 13 00:57:45 EST 2010


Note: I'm relatively new to Haskell, and my knowledge of C and C++ is
basically pretty
minimal -- I can read, modify and compile C/C++ programs (usually).

I'm trying to interface with some C++ code by writing a little bit of C code
that uses that C++ code,
and I'm getting "undefined reference" errors when I try to 'ghc --make' a
client application to test
it.

Actually, I'm modifying Nitin Madnani's (freely available) Python SRILM
toolkit wrapper code.  (SRILM, 
by the bye, is a C++-based toolkit for training and using statistical n-gram
language models.  I was 
surprised that no-one has tried to do this yet -- or at least not that they
have shared with the rest of us.)  
Anyhow, I've verified that my modification of Madnani's C code works by
compiling it and running it 
through a SWIG interface in Madnani's Python code, so I'm pretty confident
the C client of SRILM 
is solid.   The culprit is either my Haskell FFI code or the client of that
code.

Without cooking up a microcosm of my problem with little Foo's and Bar's,
I'll just give my
actual C, header file and Haskell code (or at least the relevant bits), and
then the error.

------------- srilm.h ----------------
#ifdef __cplusplus
  extern "C" {
#else
    typedef struct Ngram Ngram; /* dummy type to stand in for class */
#endif

Ngram* bldLM(int order, const char* filename);
void deleteLM(Ngram* ngram);
float getSeqProb(Ngram* ngram, const char* ngramstr, unsigned order,
unsigned length);

#ifdef __cplusplus
  }
#endif
-----------------------------------------

------------- srilm.c ----------------
// Initialize and read in the ngram model
Ngram* bldLM(int order, const char* filename) { ... }
...
// Delete the ngram model
void deleteLM(Ngram* ngram) {
  delete srilm_vocab;
  delete ngram;
}
...
// Get the ngram probability of the given string, given n-gram order 'order'
and string length
// 'length'.
float getSeqProb(Ngram* ngram, const char* ngramstr, unsigned order,
unsigned length) { ...}
-----------------------------

Next, the Haskell FFI specs and code that marshals data between Haskell and
C.

---------------- LM.hs ----------------------
{-# INCLUDE "srilm.h" #-}
{-# LANGUAGE ForeignFunctionInterface, EmptyDataDecls #-}
... module decl's, imports, etc.
{- | A dummy placeholder for SRILM n-gram model thingies. -}
data Ngram

data NGModel = NGModel {ng :: !(ForeignPtr Ngram)}

foreign import ccall "srilm.h bldLM"
    c_blm :: CInt -> CString -> Ptr Ngram

foreign import ccall "srilm.h deleteLM"
    c_dlm :: FunPtr ((Ptr Ngram) -> IO ())

foreign import ccall "srilm.h getSeqProb" 
    c_ngramProb :: Ptr Ngram -> CString -> CUInt -> CUInt -> CFloat

{- 
   | Given an n-gram model, an Int representing the n-gram order
     and a list of strings (word sequence), compute the 
     n-gram probability of the sequence.
-}
scoreSequence :: NGModel -> Int -> [String] -> Float
scoreSequence ngram order seq = 
    unsafePerformIO $ do
      stringSeq <- newCString (unwords seq)
      let sc = c_ngramProb (unsafeForeignPtrToPtr $ ng ngram) stringSeq
(fromIntegral order) (fromIntegral $ length seq)
      return (realToFrac sc)
...
buildLM :: Int -> String -> NGModel
buildLM order fname = 
    NGModel $ 
            unsafePerformIO $ do
              cFName <- newCString fname
              let ng = c_blm (fromIntegral order) cFName
              return $ unsafePerformIO $ newForeignPtr c_dlm ng
--------------------------------------------

Now, I've defined a simple app that tries to use this:

------------------- Main.hs -------------------------
module Main where
import SRILM.LM(scoreSequence, buildLM)

main :: IO ()
main = do
  let lm = buildLM 5 "eng.kn.5g.lm"
  putStrLn $ show $ scoreSequence lm 5 ["the", "prime", "minister", "gave",
"a", "speech", "."]
-----------------------------------------------------------

But when I try to compile it (after having successfully compiled the C code
with g++), I get:

$ ghc --make Main.hs
Linking Main ...
LM.o: In function `r18k_info':
(.text+0x122): undefined reference to `bldLM'
LM.o: In function `r18m_info':
(.text+0x14e): undefined reference to `deleteLM'
LM.o: In function `r18o_info':
(.text+0x28b): undefined reference to `getSeqProb'
collect2: ld returned 1 exit status

Any ideas?

Note that I'm not confident that everything on the Haskell side is correct,
but it seems
that ghc can't find my C client of SRILM.  As I said, I've compiled this
code
using g++, and it works when I interface with it through Python.

Sorry for the long-windedness, but I figured I'd err on the side of TMI so
that I don't
have to keep posting more and more code snippets and error messages.  Any
help
is greatly appreciated.  (And I'd be happy to share my interface to SRILM to
anyone
who's interested, once I get it working -- and I get permission from Nitin
Madnani to
distribute a modified version of his code.)

Thanks,
Dennis
-- 
View this message in context: http://old.nabble.com/FFI%2C-C-C%2B%2B-and-undefined-references-tp27139612p27139612.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.



More information about the Haskell-Cafe mailing list