Compiling shared (dll) library

Hi, Haskellers.
I'm trying to compile following program (where Regex.Genex is a package
what I need to produce all possible expresions by the given pattern and
`adder' is just FFI sample):
-- genexlib.hs
{-# LANGUAGE BangPatterns, ForeignFunctionInterface #-}
module GenexLib where
import Regex.Genex
import System.IO
import System.Environment
adder :: Int -> Int -> IO Int -- gratuitous use of IO
adder x y = return (x+y)
foreign export stdcall adder :: Int -> Int -> IO Int
-- genexlib.hs end
// start.c
#include
ghc --version The Glorious Glasgow Haskell Compilation System, version 7.0.2
compiling:
ghc -c genexlib.hs ghc -c start.c ghc -shared -o genexlib.dll genexlib.o genexlib_stub.o start.o genexlib.o:fake:(.text+0xd1): undefined reference to `__stginit_regexzmgenexzm0zi3zi2_RegexziGenex_' Creating library file: genexlib.dll.a
collect2: ld returned 1 exit status
and get undefined reference. But If I try to compile the executable from similar code: -- genexlib.hs {-# LANGUAGE BangPatterns, ForeignFunctionInterface #-} -- module GenexLib where import Regex.Genex import System.IO import System.Environment defaultRegex :: String defaultRegex = "a(b|c)d{2,3}e*" main :: IO () main = do hSetBuffering stdout NoBuffering args <- getArgs case args of [] -> do prog <- getProgName if prog == "<interactive>" then run [defaultRegex] else do fail $ "Usage: " ++ prog ++ " regex [regex...]" rx -> run rx run :: [String] -> IO () run regex = do let s = genexPure regex mapM_ print s -- genexlib.hs end
ghc --make genexlib.hs -O2
it's ok, no errors, and you can see in GHCi: *Main> :main "abdd" "acdd" "abddd" "acddd" "abddeee" "acddeee" "abdddeee" "acdddeee" "abddee" "acddee" "abdddee" "acdddee" "abdde" "acdde" "abddde" "acddde" Where is my mistake? What am I doing wrong? In first case, when compiling shared dll, I tried to link libraries what I've found in `cabal' directory (like `libHSregex-genex-0.3.2.a') to work around errors but all in vain. -- Alexander Popov

On Monday 05 December 2011, 11:39:06, Alexander.Vladislav.Popov wrote:
Hi, Haskellers.
I'm trying to compile following program (where Regex.Genex is a package what I need to produce all possible expresions by the given pattern and `adder' is just FFI sample):
-- genexlib.hs {-# LANGUAGE BangPatterns, ForeignFunctionInterface #-}
module GenexLib where
import Regex.Genex import System.IO import System.Environment
adder :: Int -> Int -> IO Int -- gratuitous use of IO adder x y = return (x+y) foreign export stdcall adder :: Int -> Int -> IO Int -- genexlib.hs end
// start.c #include
void HsStart() { int argc = 1; char* argv[] = {"ghcDll", NULL}; // argv must end with NULL
// Initialize Haskell runtime char** args = argv; hs_init(&argc, &args); }
void HsEnd() { hs_exit(); } // start.c end
I'm using ghc
ghc --version
The Glorious Glasgow Haskell Compilation System, version 7.0.2
compiling:
ghc -c genexlib.hs ghc -c start.c ghc -shared -o genexlib.dll genexlib.o genexlib_stub.o start.o
Why the separate compilation? Can't you compile them in one go?
genexlib.o:fake:(.text+0xd1): undefined reference to `__stginit_regexzmgenexzm0zi3zi2_RegexziGenex_' Creating library file: genexlib.dll.a collect2: ld returned 1 exit status
and get undefined reference.
But If I try to compile the executable from similar code:
ghc --make genexlib.hs -O2
By the way, --make is the default mode from ghc-7.0 on, so you don't need it here.
Where is my mistake? What am I doing wrong? In first case, when compiling shared dll, I tried to link libraries what I've found in `cabal' directory (like `libHSregex-genex-0.3.2.a') to work around errors but all in vain.
The fundamental thing is that in --make mode, GHC figures out the required Haskell dependencies itself. So it sees the import and looks in which package it's provided and links (if necessary) with that package. But when you tell it to link a couple of .o files, it's not in --make mode, so apart from the specified files it links in only symbols from a few select packages (I think the wired-in packages), so then you have to tell it which other packages it needs to link in. $ ghc -shared -package regex-genex -o genexlib.dll genexlib.o genexlib_stub.o start.o should fix the undefined reference.

The fundamental thing is that in --make mode, GHC figures out the required Haskell dependencies itself. So it sees the import and looks in which package it's provided and links (if necessary) with that package. But when you tell it to link a couple of .o files, it's not in --make mode, so apart from the specified files it links in only symbols from a few select packages (I think the wired-in packages), so then you have to tell it which other packages it needs to link in. $ ghc -shared -package regex-genex -o genexlib.dll genexlib.o genexlib_stub.o start.o should fix the undefined reference.
Aaaaaaaaaaa! You are the Great Magician!
compiling:
ghc -c genexlib.hs ghc -c start.c ghc -shared -o genexlib.dll genexlib.o genexlib_stub.o start.o Why the separate compilation? Can't you compile them in one go?
Sorry for a stupid question, how is it? And one more question, please: how I can export genexPure :: [String] -> [String] to achieve all preferences of lazy list? Not all array at once, but to get someting like an iterator, what I can call to get new genex. -- Thanks a lot, Alexander Popov.

On Monday 05 December 2011, 13:44:25, Alexander.Vladislav.Popov wrote:
Why the separate compilation? Can't you compile them in one go?
Sorry for a stupid question, how is it?
Not stupid at all. I'm not an expert in matters FFI, so I don't know if it works in all situations, but for simple cases at least, you can compile in one go listing .hs and .c files on the command line. For a foreign import: // hsFibo.hs: {-# LANGUAGE ForeignFunctionInterface #-} module Main (main) where import System.Environment (getArgs) foreign import ccall unsafe "fibo" c_fibo :: Int -> Int main :: IO () main = do args <- getArgs let n = case args of (a:_) -> read a _ -> 14 print (c_fibo n) // Fibonacci.c int fibo(int n){ int a = (n&1) ? 0 : 1, b = (n&1) ? 1 : 0; while(n > 1){ a += b; b += a; n -= 2; } return b; } $ ghc -O2 hsFibo.hs Fibonacci.c [1 of 1] Compiling Main ( hsFibo.hs, hsFibo.o ) Linking hsFibo ... $ ./hsFibo 21 10946 For a foreign export it's a bit more complicated, as you would have to generate the .h file(s) first by other means (if all your exported functions are compatible with the implicit types for C functions [pre C99, iirc], you can get away without the header, but you'll get warnings about implicit declarations). But with appropriate headers, you can compile in one go, $ ghc -O2 -shared -dynamic -fPIC Export.hs useExport.c -o theexport.so (if you use a C main to create an executable, also pass -no-hs-main).
And one more question, please: how I can export genexPure :: [String] -> [String] to achieve all preferences of lazy list? Not all array at once, but to get someting like an iterator, what I can call to get new genex.
Pass. I have no idea how to do that.
participants (2)
-
Alexander.Vladislav.Popov
-
Daniel Fischer