[Haskell-cafe] ghc runtime linker problem on i386
Olaf Klinke
olf at aatal-apotheke.de
Fri Feb 14 23:03:54 UTC 2020
Dear Cafe,
I'm experiencing strange behaviour on an old i386 machine when interpreting Haskell code on the fly: The same code runs from GHCi and fails as compiled executable.
It might be a GHC runtime linker problem but I'm not sure. I successfully built haskintex and IHaskell with stack 2.1.3 on that machine. Both programs are supposed to interpret Haskell code at runtime: IHaskell uses the GHC API while haskintex uses hint, which itself is a wrapper for the GHC API. Therefore I suspect the problem lies in the usage of the GHC API itself. Both programs fail at runtime with the same error:
$LIBDIR/ghc-prim-0.5.3/HSghc-prim-0.5.3.o: unknown symbol `_GLOBAL_OFFSET_TABLE_`
When adding -dynamic to the ghc-options field in the package cabal file, the error goes away. Minimal code to reproduce is below. The i386 machine has no system ghc, no cabal, no ghcup and I wiped the $HOME/.stack directory before running "stack build". On x86-64 the error does not occur regardless of the -dynamic flag.
Should I file a bug report or is this expected behaviour? If this is a bug, who should I file the bug against?
Olaf
{-- put this as app/Main.hs in a new stack project --}
module Main where
import Language.Haskell.Interpreter -- hint
main :: IO ()
main = putStrLn =<< hintstuff
hintstuff :: IO String
hintstuff = fmap (either show show).runInterpreter $ do
setImports ["Prelude"]
interpret "1+2" (as :: Int)
More information about the Haskell-Cafe
mailing list