Force recompilation of BCOs when they were compiled in HscNothing mode.
[ghc-hetmet.git] / compiler / main / GHC.hs
index 1d745a2..00b373a 100644 (file)
@@ -1040,9 +1040,9 @@ getModSummary mod = do
 -- Throws a 'SourceError' on parse error.
 parseModule :: GhcMonad m => ModSummary -> m ParsedModule
 parseModule ms = do
-   hsc_env0 <- getSession
-   let hsc_env = hsc_env0 { hsc_dflags = ms_hspp_opts ms }
-   rdr_module <- parseFile hsc_env ms
+   rdr_module <- withTempSession
+                     (\e -> e { hsc_dflags = ms_hspp_opts ms }) $
+                   hscParse ms
    return (ParsedModule ms rdr_module)
 
 -- | Typecheck and rename a parsed module.
@@ -1050,12 +1050,11 @@ parseModule ms = do
 -- Throws a 'SourceError' if either fails.
 typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModule
 typecheckModule pmod = do
-   let ms = modSummary pmod
-   hsc_env0 <- getSession
-   let hsc_env = hsc_env0 { hsc_dflags = ms_hspp_opts ms }
+ let ms = modSummary pmod
+ withTempSession (\e -> e { hsc_dflags = ms_hspp_opts ms }) $ do
    (tc_gbl_env, rn_info)
-       <- typecheckRenameModule hsc_env ms (parsedSource pmod)
-   details <- liftIO $ makeSimpleDetails hsc_env tc_gbl_env
+       <- hscTypecheckRename ms (parsedSource pmod)
+   details <- makeSimpleDetails tc_gbl_env
    return $
      TypecheckedModule {
        tm_internals_          = (tc_gbl_env, details),
@@ -1076,11 +1075,10 @@ typecheckModule pmod = do
 -- | Desugar a typechecked module.
 desugarModule :: GhcMonad m => TypecheckedModule -> m DesugaredModule
 desugarModule tcm = do
-   let ms = modSummary tcm
-   hsc_env0 <- getSession
-   let hsc_env = hsc_env0 { hsc_dflags = ms_hspp_opts ms }
+ let ms = modSummary tcm
+ withTempSession (\e -> e { hsc_dflags = ms_hspp_opts ms }) $ do
    let (tcg, _) = tm_internals tcm
-   guts <- deSugarModule hsc_env ms tcg
+   guts <- hscDesugar ms tcg
    return $
      DesugaredModule {
        dm_typechecked_module = tcm,
@@ -1094,16 +1092,17 @@ loadModule :: (TypecheckedMod mod, GhcMonad m) => mod -> m mod
 loadModule tcm = do
    let ms = modSummary tcm
    let mod = ms_mod_name ms
-   hsc_env0 <- getSession
-   let hsc_env = hsc_env0 { hsc_dflags = ms_hspp_opts ms }
    let (tcg, details) = tm_internals tcm
-   (iface,_) <- liftIO $ makeSimpleIface hsc_env Nothing tcg details
-   let mod_info = HomeModInfo {
-                    hm_iface = iface,
-                    hm_details = details,
-                    hm_linkable = Nothing }
-   let hpt_new = addToUFM (hsc_HPT hsc_env) mod mod_info
-   modifySession $ \_ -> hsc_env0{ hsc_HPT = hpt_new }
+   hpt_new <-
+       withTempSession (\e -> e { hsc_dflags = ms_hspp_opts ms }) $ do
+         (iface, _) <- makeSimpleIface Nothing tcg details
+         let mod_info = HomeModInfo {
+                          hm_iface = iface,
+                          hm_details = details,
+                          hm_linkable = Nothing }
+         hsc_env <- getSession
+         return $ addToUFM (hsc_HPT hsc_env) mod mod_info
+   modifySession $ \e -> e{ hsc_HPT = hpt_new }
    return tcm
 
 -- | This is the way to get access to the Core bindings corresponding
@@ -1132,11 +1131,9 @@ compileToCore fn = do
 -- whether to run the simplifier.
 -- The resulting .o, .hi, and executable files, if any, are stored in the
 -- current directory, and named according to the module name.
--- Returns True iff compilation succeeded.
 -- This has only so far been tested with a single self-contained module.
 compileCoreToObj :: GhcMonad m => Bool -> CoreModule -> m ()
 compileCoreToObj simplify cm@(CoreModule{ cm_module = mName }) = do
-  hscEnv      <- getSession
   dflags      <- getSessionDynFlags
   currentTime <- liftIO $ getClockTime
   cwd         <- liftIO $ getCurrentDirectory
@@ -1161,15 +1158,13 @@ compileCoreToObj simplify cm@(CoreModule{ cm_module = mName }) = do
          ms_hspp_buf = Nothing
       }
 
-  ioMsgMaybe $ flip evalComp (CompState{ compHscEnv=hscEnv,
-                                         compModSummary=modSummary,
-                                         compOldIface=Nothing}) $
-     let maybe_simplify mod_guts | simplify = hscSimplify mod_guts
-                                 | otherwise = return mod_guts
-     in maybe_simplify (mkModGuts cm)
-          >>= hscNormalIface
-          >>= hscWriteIface
-          >>= hscOneShot
+  let maybe_simplify mod_guts | simplify = hscSimplify mod_guts
+                              | otherwise = return mod_guts
+  guts <- maybe_simplify (mkModGuts cm)
+  (iface, changed, _details, cgguts)
+      <- hscNormalIface guts Nothing
+  hscWriteIface iface changed modSummary
+  hscGenHardCode cgguts modSummary
   return ()
 
 -- Makes a "vanilla" ModGuts.
@@ -1211,6 +1206,7 @@ compileCore simplify fn = do
        -- Now we have the module name;
        -- parse, typecheck and desugar the module
        mod_guts <- coreModule `fmap`
+                      -- TODO: space leaky: call hsc* directly?
                       (desugarModule =<< typecheckModule =<< parseModule modSummary)
        liftM gutsToCoreModule $
          if simplify
@@ -1218,11 +1214,7 @@ compileCore simplify fn = do
              -- If simplify is true: simplify (hscSimplify), then tidy
              -- (tidyProgram).
              hsc_env <- getSession
-             simpl_guts <- ioMsg $ evalComp (hscSimplify mod_guts)
-                                    (CompState{
-                                       compHscEnv = hsc_env,
-                                       compModSummary = modSummary,
-                                       compOldIface = Nothing})
+             simpl_guts <- hscSimplify mod_guts
              tidy_guts <- liftIO $ tidyProgram hsc_env simpl_guts
              return $ Left tidy_guts
           else
@@ -1575,6 +1567,19 @@ upsweep_mod hsc_env old_hpt (stable_obj, stable_bco) summary mod_index nmods
             compile_it_discard_iface 
                         = compile hsc_env summary' mod_index nmods Nothing
 
+            -- With the HscNothing target we create empty linkables to avoid
+            -- recompilation.  We have to detect these to recompile anyway if
+            -- the target changed since the last compile.
+            is_fake_linkable
+               | Just hmi <- old_hmi, Just l <- hm_linkable hmi =
+                  null (linkableUnlinked l)
+               | otherwise =
+                   -- we have no linkable, so it cannot be fake
+                   False
+
+            implies False _ = True
+            implies True x  = x
+
         in
         case () of
          _
@@ -1597,7 +1602,8 @@ upsweep_mod hsc_env old_hpt (stable_obj, stable_bco) summary mod_index nmods
                 -- object is stable, but we need to load the interface
                 -- off disk to make a HMI.
 
-          | not (isObjectTarget target), is_stable_bco ->
+          | not (isObjectTarget target), is_stable_bco,
+            (target /= HscNothing) `implies` not is_fake_linkable ->
                 ASSERT(isJust old_hmi) -- must be in the old_hpt
                 let Just hmi = old_hmi in do
                 liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5
@@ -1609,6 +1615,7 @@ upsweep_mod hsc_env old_hpt (stable_obj, stable_bco) summary mod_index nmods
             Just hmi <- old_hmi,
             Just l <- hm_linkable hmi,
             not (isObjectLinkable l),
+            (target /= HscNothing) `implies` not is_fake_linkable,
             linkableTime l >= ms_hs_date summary -> do
                 liftIO $ debugTraceMsg (hsc_dflags hsc_env) 5
                            (text "compiling non-stable BCO mod:" <+> ppr this_mod_name)
@@ -2029,7 +2036,7 @@ summariseFile hsc_env old_summaries file mb_phase obj_allowed maybe_buf
        (dflags', hspp_fn, buf)
            <- preprocessFile hsc_env file mb_phase maybe_buf
 
-        (srcimps,the_imps, L _ mod_name) <- liftIO $ getImports dflags' buf hspp_fn file
+        (srcimps,the_imps, L _ mod_name) <- getImports dflags' buf hspp_fn file
 
        -- Make a ModLocation for this file
        location <- liftIO $ mkHomeModLocation dflags mod_name file
@@ -2161,7 +2168,7 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod)
        -- Preprocess the source file and get its imports
        -- The dflags' contains the OPTIONS pragmas
        (dflags', hspp_fn, buf) <- preprocessFile hsc_env src_fn Nothing maybe_buf
-        (srcimps, the_imps, L mod_loc mod_name) <- liftIO $ getImports dflags' buf hspp_fn src_fn
+        (srcimps, the_imps, L mod_loc mod_name) <- getImports dflags' buf hspp_fn src_fn
 
        when (mod_name /= wanted_mod) $
                throwOneError $ mkPlainErrMsg mod_loc $ 
@@ -2215,8 +2222,8 @@ preprocessFile hsc_env src_fn mb_phase (Just (buf, _time))
        --
        (dflags', leftovers, warns)
             <- parseDynamicNoPackageFlags dflags local_opts
-        liftIO $ checkProcessArgsResult leftovers -- XXX: throws exceptions
-        liftIO $ handleFlagWarnings dflags' warns -- XXX: throws exceptions
+        checkProcessArgsResult leftovers
+        handleFlagWarnings dflags' warns
 
        let
            needs_preprocessing