[Haskell-beginners] Compiling shared (dll) library
Alexander.Vladislav.Popov
alexander.vladislav.popov at gmail.com
Mon Dec 5 11:39:06 CET 2011
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 <Rts.h>
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
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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20111205/322a160a/attachment.htm>
More information about the Beginners
mailing list