mkTopLevEnv: not interpreted main:Main
Simon Marlow
marlowsd at gmail.com
Thu Oct 6 14:21:43 CEST 2011
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 at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list