mkTopLevEnv: not interpreted main:Main

So I'm trying to fix a bug in a web application that's using the GHC API with GHC 7.2. If it helps, the application is gloss-web, source code at https://github.com/cdsmith/gloss-web and the relevant module is src/Source.hs. The error I'm getting is <no location info>: mkTopLevEnv: not interpreted main:MyModule I get this occasionally when two pieces of source code happen to get compiled at approximately the same time, but most of the time everything works fine. The module name there is whichever one I've defined in the source code I'm compiling. It's correct that the module is not interpreted; I'm specifying options hscTarget = HscAsm ghcLink = LinkInMemory But it's unclear to me why GHC occasionally decides to require that it be interpreted and complain, when compiling the code works fine in any other circumstance. Anyone else seen anything like this, or know what the cause is? A few notes: 1. It doesn't appear to be a straight-forward reentrancy issue, as wrapping uses of the GHC API with an MVar lock doesn't affect it at all. However, it definitely *is* correlated with multiple compiles at approximately the same time. Very odd there. 2. On a whim, I tried adding a performGC before and after each use of the compiler to try to isolate the uses of the GHC API more completely. Oddly enough, a performGC before the compile makes the problem much WORSE. I found that interesting; maybe it's a hint. 3. If you want to build my code and reproduce it, the easiest way is to comment out line 110 (keepAlive cmap digest 30) of src/Source.hs. Doing so will break the bit that caches recently compiled source code, making it much easier to actually call the GHC API several times in rapid succession just by rapidly clicking the Run button in the web app. If there's anything I can do to get more information, I'm happy to do so as well. I'm not terribly familiar with the flags or options for GHC, as I've never done this before. -- Chris Smith

I don't have a good answer here. FWIW * I believe that the only call to mkTopLevEnv is in InteractiveEval.findGlobalRdrEnv, which in turn only calls mkTopLev on imports which are specified by an IIModule specification (see HscTypes.InteractiveImport). * I think that IIModule things should always be interpreted modules else we don't *know* their full top-level environment * I can't account for how you are getting an IIModule of your main:MyModule, because all the places that create IIModule specs check that the module is interpreted. Could you be creating that IIModule yourself? (If so use IIDecl instead.) It's hard to say more without a reproducible test case -- and I'm not too keen on trying to build your entire project unless there is no alternative -- usually there are lots of other dependencies. maybe others have ideas too. Simon | -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Chris Smith | Sent: 02 October 2011 05:59 | To: glasgow-haskell-users@haskell.org | Subject: mkTopLevEnv: not interpreted main:Main | | So I'm trying to fix a bug in a web application that's using the GHC API | with GHC 7.2. If it helps, the application is gloss-web, source code at | https://github.com/cdsmith/gloss-web and the relevant module is | src/Source.hs. | | The error I'm getting is | | <no location info>: mkTopLevEnv: not interpreted main:MyModule | | I get this occasionally when two pieces of source code happen to get | compiled at approximately the same time, but most of the time everything | works fine. The module name there is whichever one I've defined in the | source code I'm compiling. It's correct that the module is not | interpreted; I'm specifying options | | hscTarget = HscAsm | ghcLink = LinkInMemory | | But it's unclear to me why GHC occasionally decides to require that it | be interpreted and complain, when compiling the code works fine in any | other circumstance. Anyone else seen anything like this, or know what | the cause is? | | A few notes: | | 1. It doesn't appear to be a straight-forward reentrancy issue, as | wrapping uses of the GHC API with an MVar lock doesn't affect it at all. | However, it definitely *is* correlated with multiple compiles at | approximately the same time. Very odd there. | | 2. On a whim, I tried adding a performGC before and after each use of | the compiler to try to isolate the uses of the GHC API more completely. | Oddly enough, a performGC before the compile makes the problem much | WORSE. I found that interesting; maybe it's a hint. | | 3. If you want to build my code and reproduce it, the easiest way is to | comment out line 110 (keepAlive cmap digest 30) of src/Source.hs. Doing | so will break the bit that caches recently compiled source code, making | it much easier to actually call the GHC API several times in rapid | succession just by rapidly clicking the Run button in the web app. | | If there's anything I can do to get more information, I'm happy to do so | as well. I'm not terribly familiar with the flags or options for GHC, | as I've never done this before. | | -- | Chris Smith | | | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

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

| 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@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Chris Smith | Sent: 03 October 2011 14:43 | To: Simon Peyton-Jones | Cc: glasgow-haskell-users@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@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

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@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@godel:~$ ./Test Just 42 cdsmith@godel:~$ ./Test Just 42 cdsmith@godel:~$ ./Test Test: mkTopLevEnv: not interpreted main:Main cdsmith@godel:~$ ./Test Just 42 cdsmith@godel:~$ ./Test Test: mkTopLevEnv: not interpreted main:Main cdsmith@godel:~$ ./Test Just 42 cdsmith@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

This may have something to do with timestamps on the files. I cannot reproduce the error with $ while ./T; do sleep 1; done ... However, I *am* able to reproduce the error with $ while ./T ; do sleep 0.9; done Just 42 Just 42 Just 42 Just 42 Just 42 T: mkTopLevEnv: not interpreted main:Main Note that this is on GHC 7.0.4 after removing the Safe Haskell line. Cheers, -- Felipe.

On Tue, Oct 4, 2011 at 5:32 PM, Felipe Almeida Lessa
This may have something to do with timestamps on the files. I cannot reproduce the error with
$ while ./T; do sleep 1; done ...
However, I *am* able to reproduce the error with
$ while ./T ; do sleep 0.9; done Just 42 Just 42 Just 42 Just 42 Just 42 T: mkTopLevEnv: not interpreted main:Main
Sorry for replying to myself. I'm also unable to reproduce the error with $ while ./T ; do rm A.hi A.o; done which runs ./T on a much faster rate. Cheers, -- Felipe.

Thanks everyone for the help! I'm working now on reproducing this with HEAD, and if I do, I'll write a ticket. On the other hand, it only seems to be an issue when one is recompiling a file within one second of the first attempt, and Felipe's workaround of deleting the .hi and .o files fixes it even then. I can't imagine recompiling a file multiple times per second is a common use case, so this is probably low priority! -- Chris

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

On 04/10/2011 21:33, Chris Smith wrote:
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.
Without trying it, I think I can explain what's going on. First of all, this line:
GHC.setContext [ mainMod ] [ ]
tells GHC to set the context to include the whole top-level scope of module Main. It's just like ":module *Main" in GHCi. It only works if Main is interpreted - normally GHCi checks that, but in this case the GHC API just falls over. That's probably bad, we should make it raise a proper exception. Anyway, that doesn't explain the whole problem - why is Main interpreted sometimes and not others? After all, you're creating the file A.hs before invoking GHC. Note that you're using HscAsm, which tells GHC to create an object file. So after running this once, you'll have A.hs, A.o and A.hi. The next time you run the script, A.hs will be recreated. If you're unlucky, A.hs and A.o will have the same timestamp (Unix filesystem timestamps only have 1-second accuracy). So GHC has to decide whether A.o is up to date or not. It makes the unsafe assumption that A.o is up to date, and uses it, which leads to your problem. But why is GHC being unsafe here? Well, a couple of reasons: - make also behaves this way - in practice build systems often generate files and then compile them immediately. If we erred on the safe side, we would see a lot of apparently unnecessary recompilation. I can imagine there's a case to be made for changing this. However, you can also fix it at your end, and arguably this is the right thing:
target<- GHC.guessTarget "*A.hs" Nothing
adding the '*' prefix tells GHC not to load the .o file. Cheers, Simon
{-# 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
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Simon, thank you! That makes sense then. I'd missed the fact that including the entire top-level scope requires the module to be interpreted. I suppose the "right" thing to do would be to not do that; but sadly, that seems to also mean that modules without a 'module Foo where' only export the single symbol 'main', and I liked the idea of students in my class not having to write out the module bit explicitly. So I've been actually using interpreted code the whole time? If so, I suppose there's no loss in taking out HscAsm entirely, then! -- Chris

On 06/10/2011 16:34, Chris Smith wrote:
Simon, thank you! That makes sense then.
I'd missed the fact that including the entire top-level scope requires the module to be interpreted. I suppose the "right" thing to do would be to not do that; but sadly, that seems to also mean that modules without a 'module Foo where' only export the single symbol 'main', and I liked the idea of students in my class not having to write out the module bit explicitly.
So I've been actually using interpreted code the whole time? If so, I suppose there's no loss in taking out HscAsm entirely, then!
Actually you haven't been using interpreted code, but you haven't been getting the full top-level scope of the compiled modules. I just tried a little test with ghci -fobject-code, and found that something is definitely amiss with this combination, so I created a ticket: http://hackage.haskell.org/trac/ghc/ticket/5534 Cheers, Simon
participants (4)
-
Chris Smith
-
Felipe Almeida Lessa
-
Simon Marlow
-
Simon Peyton-Jones