mkTopLevEnv: not interpreted main:Main

Chris Smith cdsmith at gmail.com
Tue Oct 4 22:14:33 CEST 2011


Here's a test case: the complete source code is in the following.  I
compile it with:

    ghc -package ghc --make Test.hs

The GHC version is

    cdsmith at godel:~$ ghc --version
    The Glorious Glasgow Haskell Compilation System, version 7.2.1

Then run the application several times in a row.  If you count to 3
between runs, it's fine.  If you run it multiple times in a row rapidly,
you get intermittent errors, as so:

    cdsmith at godel:~$ ./Test
    Just 42
    cdsmith at godel:~$ ./Test
    Just 42
    cdsmith at godel:~$ ./Test
    Test: mkTopLevEnv: not interpreted main:Main
    cdsmith at godel:~$ ./Test
    Just 42
    cdsmith at godel:~$ ./Test
    Test: mkTopLevEnv: not interpreted main:Main
    cdsmith at godel:~$ ./Test
    Just 42
    cdsmith at godel:~$ ./Test
    Test: mkTopLevEnv: not interpreted main:Main

Note this isn't even in the same process!  But it's definitely caused by
running the test multiple times in a quick sequence.

Here's the complete source code for Test.hs

{-# LANGUAGE MagicHash #-}

import System.IO.Unsafe
import GHC.Exts  (unsafeCoerce#)
import GHC.Paths (libdir)

import qualified GHC      as GHC
import qualified DynFlags as GHC

compile :: IO (Maybe Int)
compile = GHC.runGhc (Just libdir) $ do
    dflags <- GHC.getSessionDynFlags
    let dflags' = dflags {
        GHC.ghcMode = GHC.CompManager,
        GHC.ghcLink = GHC.LinkInMemory,
        GHC.hscTarget = GHC.HscAsm,
        GHC.optLevel = 2,
        GHC.safeHaskell = GHC.Sf_Safe
        }
    GHC.setSessionDynFlags dflags'
    target <- GHC.guessTarget "A.hs" Nothing
    GHC.setTargets [target]
    r <- fmap GHC.succeeded (GHC.load GHC.LoadAllTargets)
    case r of
        True -> do
            mods <- GHC.getModuleGraph
            let mainMod = GHC.ms_mod (head mods)
            GHC.setContext [ mainMod ] [ ]
            v <- GHC.compileExpr "a :: Integer"
            return (Just (unsafeCoerce# v))
        False -> return Nothing

main = do
    writeFile "A.hs" "a = 42"
    print =<< compile





More information about the Glasgow-haskell-users mailing list