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

Miguel Mitrofanov miguelimo38 at yandex.ru
Thu Jan 14 16:19:08 EST 2010


Works fine here (Mac OS X 10.5):

MigMit:ngram MigMit$ ghc --make Main.hs srilm.o
[1 of 2] Compiling LM               ( LM.hs, LM.o )

LM.hs:9:0: Warning: possible missing & in foreign import of FunPtr
[2 of 2] Compiling Main             ( Main.hs, Main.o )
Linking Main ...
MigMit:ngram MigMit$ ls Main*
Main*     Main.hi   Main.hs   Main.hs~  Main.o
MigMit:ngram MigMit$ cat Main.hs
module Main where
import 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", "."]
MigMit:ngram MigMit$ cat LM.hs
{-# INCLUDE "srilm.h" #-}
{-# LANGUAGE ForeignFunctionInterface, EmptyDataDecls #-}
module LM where
import Foreign
import Foreign.C
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
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
MigMit:ngram MigMit$ cat srilm.h
#ifdef __cplusplus
extern "C" {
   class Ngram{};
#else
   typedef struct Ngram Ngram;
#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
MigMit:ngram MigMit$ cat srilm.c
#include "srilm.h"
Ngram* bldLM(int order, const char* filename) { return 0; }
void deleteLM(Ngram* ngram) {}
float getSeqProb(Ngram* ngram, const char* ngramstr, unsigned order,  
unsigned length) { return 0;}
MigMit:ngram MigMit$

Maybe you just need to recompile srilm.c or something.

On 14 Jan 2010, at 23:39, DNM wrote:

>
> Nope. Ubuntu Linux (Intrepid Ibex).  I wish it were that simple.
>
> --D.N.
>
>
> Daniel Fischer-4 wrote:
>>
>> Am Donnerstag 14 Januar 2010 20:42:42 schrieb DNM:
>>> Which is weird, because 'srilm.o'/'srilm.h' are the files that  
>>> define
>>> the mysterious "undefined references".  I'll keep plugging away and
>>> report back when (or whether) I make some progress.  In the  
>>> meanwhile,
>>> if anyone has a clue, I'm all ears.
>>>
>>> Best,
>>> D.N.
>>
>> Just an idea. Are you on windows?
>> If so, then your foreign calls would probably have to be
>>
>> foreign import stdcall "srilm.h whatever" ...
>>
>> instead of
>>
>> foreign import ccall "..."
>>
>>>
>>> Malcolm Wallace wrote:
>>>> However, if you are unsure of which Haskell packages are needed,  
>>>> it is
>>>> wise to let ghc work out the dependencies for you, e.g. with
>>>>     ghc --make Main.hs slirm.o
>>>>
>>>> It cannot work out the C/C++ dependencies though, so every time you
>>>> get "undefined reference" linking errors, you must discover which C
>>>> code provides those symbols, and add its object file to the
>>>> commandline by hand.
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>
> -- 
> View this message in context: http://old.nabble.com/FFI%2C-C-C%2B%2B-and-undefined-references-tp27139612p27167751.html
> Sent from the Haskell - Haskell-Cafe mailing list archive at  
> Nabble.com.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list