[Git][ghc/ghc][wip/24107] driver: Ensure we actually clear the interactive context before reloading

Zubin (@wz1000) gitlab at gitlab.haskell.org
Tue Nov 21 13:07:09 UTC 2023



Zubin pushed to branch wip/24107 at Glasgow Haskell Compiler / GHC


Commits:
337e4e2f by Zubin Duggal at 2023-11-21T18:36:59+05:30
driver: Ensure we actually clear the interactive context before reloading

Previously we called discardIC, but immediately after set the session
back to an old HscEnv that still contained the IC

Partially addresses #24107
Fixes #23405

- - - - -


4 changed files:

- compiler/GHC/Driver/Make.hs
- + testsuite/tests/ghci/T23405/T23405.hs
- + testsuite/tests/ghci/T23405/T23405.script
- + testsuite/tests/ghci/T23405/all.T


Changes:

=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -771,6 +771,7 @@ load' mhmi_cache how_much diag_wrapper mHscMessage mod_graph = do
 
     let pruneHomeUnitEnv hme = hme { homeUnitEnv_hpt = emptyHomePackageTable }
     setSession $ discardIC $ hscUpdateHUG (unitEnv_map pruneHomeUnitEnv) hsc_env
+    hsc_env <- getSession
 
     -- Unload everything
     liftIO $ unload interp hsc_env
@@ -780,7 +781,6 @@ load' mhmi_cache how_much diag_wrapper mHscMessage mod_graph = do
 
     worker_limit <- liftIO $ mkWorkerLimit dflags
 
-    setSession $ hscUpdateHUG (unitEnv_map pruneHomeUnitEnv) hsc_env
     (upsweep_ok, new_deps) <- withDeferredDiagnostics $ do
       hsc_env <- getSession
       liftIO $ upsweep worker_limit hsc_env mhmi_cache diag_wrapper mHscMessage (toCache pruned_cache) build_plan


=====================================
testsuite/tests/ghci/T23405/T23405.hs
=====================================
@@ -0,0 +1,11 @@
+{-# LANGUAGE TemplateHaskell #-}
+module T23405 (test) where
+
+import Language.Haskell.TH
+
+test :: IO ()
+test = do
+  let s = $(getDoc (DeclDoc ''Double) >>= \doc -> [|doc|])
+  print (s `seq` ())
+
+


=====================================
testsuite/tests/ghci/T23405/T23405.script
=====================================
@@ -0,0 +1,3 @@
+:load T23405.hs
+:! echo "-- an extra comment so that the hash changes" >> T18262.hs
+:reload


=====================================
testsuite/tests/ghci/T23405/all.T
=====================================
@@ -0,0 +1 @@
+test('T23405', [extra_files(['T23405.hs'])], ghci_script, ['T23405.script'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/337e4e2fff6d482385a924a99040b2f48fa4d72a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/337e4e2fff6d482385a924a99040b2f48fa4d72a
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20231121/1c86524c/attachment-0001.html>


More information about the ghc-commits mailing list