mkTopLevEnv: not interpreted main:Main

Chris Smith cdsmith at gmail.com
Mon Oct 3 15:42:59 CEST 2011


Thanks, Simon.

I will work on building a smaller complete test case that reproduces the
issue, and I could have done a better job of at least pointing out the
relevant code for you.  Sorry about that.

I'm definitely not building my own IIModule.  The use of the GHC API is
as follows.  (I'm fairly sure you can ignore doWithErrors, so I haven't
included it; it just sets up some log actions and exception and signal
handlers, runs its argument in the Ghc monad, and converts the result
from a Maybe to an Either that reports errors).

doWithErrors :: GHC.Ghc (Maybe a) -> IO (Either [String] a)

compile :: String -> String -> FilePath -> IO (Either [String] t)
compile vname tname fn = doWithErrors $ 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.packageFlags = [GHC.TrustPackage "gloss",
                            GHC.ExposePackage "gloss-web-adapters" ]
        }
    GHC.setSessionDynFlags dflags'
    target <- GHC.guessTarget fn 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 ]
                           [ GHC.simpleImportDecl
                               (GHC.mkModuleName "Graphics.Gloss"),
                             GHC.simpleImportDecl
                               (GHC.mkModuleName "GlossAdapters") ]
            v <- GHC.compileExpr $ vname ++ " :: " ++ tname
            return (Just (unsafeCoerce# v))
        False -> return Nothing

-- 
Chris




More information about the Glasgow-haskell-users mailing list