mkTopLevEnv: not interpreted main:Main
Chris Smith
cdsmith at gmail.com
Tue Oct 4 22:33:33 CEST 2011
Here's a version with fewer flags/features, that acts the same.
I tried removing the loading of an external module, and that did *not*
exhibit the problem. It also does *not* fail when the file name is
different each time, so the fact that it's the same file, A.hs, each
time is somehow part of the issue.
I'm getting to the point where I can't imagine what this could possibly
be about.
{-# 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.ghcLink = GHC.LinkInMemory }
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