[Haskell-cafe] Problems with Hs-Plugins

Philipp Volgger pvolgger at gmail.com
Sat May 5 12:24:17 EDT 2007


I tried following very simple program:
> module Main where
> import System.Eval.Haskell
>
> main = do i <- eval "1 + 6 :: Int" [] :: IO (Maybe Int)
>           if isJust i then putStrLn (show (fromJust i)) else return ()
I compile it with "ghc -c Main.hs" and everything seems fine.
When I run it with "ghc Main.o" I get following message:
> Main.o(.text+0x48):fake: undefined reference to 
> `AltDataziTypeable_zdfTypeableInt_closure'
> Main.o(.text+0x4d):fake: undefined reference to 
> `SystemziEvalziHaskell_eval_closure'
> Main.o(.text+0x36f):fake: undefined reference to 
> `__stginit_SystemziEvalziHaskell_'
> Main.o(.rodata+0x0):fake: undefined reference to 
> `SystemziEvalziHaskell_eval_closure'
> Main.o(.rodata+0x4):fake: undefined reference to 
> `AltDataziTypeable_zdfTypeableInt_closure'
> collect2: ld returned 1 exit status
When I run it with "runhaskell Main" I get:

>
> GHCi runtime linker: fatal error: I found a duplicate definition for 
> symbol
>    _GHCziWord_fromEnum1_closure
> whilst processing object file
>    c:/ghc/ghc-6-4-2/ghc-6.4.2/HSbase1.o
> This could be caused by:
>    * Loading two different object files which export the same symbol
>    * Specifying the same object file twice on the GHCi command line
>    * An incorrect `package.conf' entry, causing some object to be
>      loaded twice.
> GHCi cannot safely continue in this situation.  Exiting now.  Sorry.
So I did probably something totally wrong, but what?




More information about the Haskell-Cafe mailing list