[Haskell-cafe] exporting Data.ByteString functions via FFI
kenny lu
haskellmail at gmail.com
Fri Jun 12 03:38:17 EDT 2009
Hi,
I was trying to write a FFI wrapper for my Haskell program which manipulates
ByteString. But I am unable to compile/link it.
Here is the toy program.
{-# LANGUAGE ForeignFunctionInterface #-}
module B where
import Foreign.C.Types
import Foreign.C.String
import qualified Data.ByteString as BS
rev :: BS.ByteString -> BS.ByteString
rev bstr = BS.reverse bstr
rev_hs :: CString -> IO CString
rev_hs cstr =
do { bstr <- BS.packCString cstr
; let bstr' = rev bstr
; cstr' <- newCString (show bstr')
; return cstr'
}
foreign export ccall rev_hs :: CString -> IO CString
And here is the C counter-part.
#include "B_stub.h"
#include <stdio.h>
int main(int argc, char *argv[]) {
char *str;
hs_init(&argc, &argv);
str = rev_hs("it works.");
printf("Rev: %s\n", str);
hs_exit();
return 0;
}
Compiling B.hs alone seems fine, but errors popped up when I was trying to
compile/link it with C.
$ ghc -c -O B.hs
$ ghc -optc-O test_b.c B.o B_stub.o -o test_b
Undefined symbols:
"___stginit_bytestringzm0zi9zi1zi4_DataziByteString_", referenced from:
___stginit_Lib_ in B.o
"_bytestringzm0zi9zi1zi4_DataziByteString_zdwreverse_info", referenced
from:
_s19w_info in B.o
"_bytestringzm0zi9zi1zi4_DataziByteStringziInternal_zdwshowsPrec_info",
referenced from:
_s19v_info in B.o
"_bytestringzm0zi9zi1zi4_DataziByteStringziInternal_zdwshowsPrec_closure",
referenced from:
_Lib_zdwa_srt in B.o
"_bytestringzm0zi9zi1zi4_DataziByteString_zdwa4_info", referenced from:
_Lib_zdwa_info in B.o
"_bytestringzm0zi9zi1zi4_DataziByteString_reverse_info", referenced from:
_Lib_rev_info in B.o
ld: symbol(s) not found
collect2: ld returned 1 exit status
If I replace ByteString with the ordinary String, the above programs can be
compiled and linked.
Can someone tell me what I did wrong here?
-Kenny
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090612/314a7c43/attachment.html
More information about the Haskell-Cafe
mailing list