[Haskell-cafe] Problems with Hs-Plugins

Donald Bruce Stewart dons at cse.unsw.edu.au
Sat May 5 12:27:57 EDT 2007


pvolgger:
> 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


You'll need to use --make to link aginst the 'plugins' package.
As in:

    ghc --make Main.hs


> When I run it with "runhaskell Main" I get:


Won't work on windows. You're trying to dynamically link the dynamic
linker, when using 'runhaskell'. (this is ok on ELF systems).

-- Don


More information about the Haskell-Cafe mailing list