[Haskell] hs-plugins on MacOS X: unknown symbol
Ulf Norell
ulfn at cs.chalmers.se
Fri Aug 11 10:16:22 EDT 2006
Hi.
I'm playing with hs-plugins (recent darcs version) on MacOS X
(ghc-6.4.1) and I get some weird unresolved symbols. Here's what I'm
trying to do:
Test.hs
-------
module Test where
test = putStrLn "test"
Main.hs
-------
import System.Plugins
main = do
r <- load_ "Test.o" [] "test"
case r of
LoadFailure msg -> print msg
LoadSuccess _ m -> m
Now I do:
$ ghc -c Test.hs
$ ghc Main.hs -package plugins
$ ./a.out
a.out:
unknown symbol `_SystemziIO_putStrLn_closure'
a.out: user error (resolvedObjs failed.)
I get the same error when I try with plugins-0.9.10. I've tried to
use loadPackage "base" and resolveObjs to no avail. What does work
(not surprisingly) is to use putStrLn in Main.hs to force it to be
linked in but that's not really a solution. If someone knows what I'm
doing wrong I'd be very grateful.
/ Ulf
More information about the Haskell
mailing list