[Haskell-cafe] Hint causes GHCi linker error under Windows

Martin Hofmann martin.hofmann at uni-bamberg.de
Mon Dec 14 06:22:20 EST 2009


The following module reproduces the error when loaded into ghci and main
is executed under Windows. It works fine when compiled.

\begin{code}

module Main where
 
import Language.Haskell.Interpreter

main = putStrLn "File to load: " >> getLine >>= erroneousLoad

erroneousLoad :: FilePath -> IO ()
erroneousLoad f = do
    ok <- runInterpreter $ loadModules [f]
    case ok of
        Right _  -> return ()
        Left e   -> fail (show e)

\end{code}
 
However in my current program I also encounter strange behaviour when
executing compiled code. I use 'haskeline' for a REP-loop. The user
input is parsed and passed to a function similar to 'erroneousLoad'.

When I type the path character by character, or when start with an empty
line by pressing return, again everything works fine. When I use the
completion function of 'haskeline' the program crashes with a
segmentation fault.

Changing the runInterpreter line to

        trace ("XXX " ++ (show f)) $ runInterpreter $ trace "YYY" $ loadModules $ trace "ZZZ" [f]

I get the following output:
        
        XXX "expl\\\\Examples.hs"
        Igor2.exe: internal error: evacuate(static): strange closure type 1094
            (GHC version 6.10.4 for i386_unknown_mingw32)
            Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
        
        This application has requested the Runtime to terminate it in an unusual way,
        Please contact the application's support team for more information.

Sometimes I get different types of the 'strange closure', e.g. 17408 or others.

I was not able to reproduce those errors on a smaller example than my
whole program. Under Linux none of those errors occurs.

Cheers,

Martin



More information about the Glasgow-haskell-users mailing list