mkTopLevEnv: not interpreted main:Main

Simon Peyton-Jones simonpj at microsoft.com
Tue Oct 4 09:51:23 CEST 2011


| 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 afraid I still can't guess what's happening. It'd be really helpful if you could build a smaller test case.  

Are you using GHC HEAD (or at least 7.2?). There have been changes in this area, and I'm looking at the HEAD code.  So it's worth trying the latest version, lest we end up debugging something that is already fixed.

If you build the HEAD from source you can also look at the call to mkTopLevEnv and print out a bit more trace info to help narrow things down.

Sorry not to be more helpful.

Simon

| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-users-
| bounces at haskell.org] On Behalf Of Chris Smith
| Sent: 03 October 2011 14:43
| To: Simon Peyton-Jones
| Cc: glasgow-haskell-users at haskell.org
| Subject: RE: mkTopLevEnv: not interpreted main:Main
| 
| 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
| 
| 
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




More information about the Glasgow-haskell-users mailing list