[Git][ghc/ghc][wip/T13869] Improve GHCi response to unloading modules and reloading when no modules are present.

Jade (@Jade) gitlab at gitlab.haskell.org
Sat Jan 27 23:15:29 UTC 2024



Jade pushed to branch wip/T13869 at Glasgow Haskell Compiler / GHC


Commits:
95e835a9 by Jade at 2024-01-28T00:19:08+01:00
Improve GHCi response to unloading modules and reloading when no modules are present.

Fixes #13869

- - - - -


11 changed files:

- ghc/GHCi/UI.hs
- testsuite/tests/driver/T8526/T8526.stdout
- testsuite/tests/ghci/prog018/prog018.stdout
- testsuite/tests/ghci/scripts/T13997.stdout
- testsuite/tests/ghci/scripts/T17669.stdout
- testsuite/tests/ghci/scripts/T1914.stdout
- testsuite/tests/ghci/scripts/T20217.stdout
- testsuite/tests/ghci/scripts/T20587.stdout
- testsuite/tests/ghci/scripts/T6105.stdout
- testsuite/tests/ghci/scripts/T8042.stdout
- testsuite/tests/ghci/should_run/all.T


Changes:

=====================================
ghc/GHCi/UI.hs
=====================================
@@ -101,7 +101,7 @@ import qualified GHC.Linker.Loader as Loader
 import GHC.Data.Maybe ( orElse, expectJust )
 import GHC.Types.Name.Set
 import GHC.Utils.Panic hiding ( showException, try )
-import GHC.Utils.Misc
+import GHC.Utils.Misc hiding (applyWhen)
 import qualified GHC.LanguageExtensions as LangExt
 import GHC.Data.Bag (unitBag)
 import qualified GHC.Data.Strict as Strict
@@ -136,6 +136,7 @@ import Data.Time.Format ( formatTime, defaultTimeLocale )
 import Data.Version ( showVersion )
 import qualified Data.Semigroup as S
 import Prelude hiding ((<>))
+import qualified Prelude ((<>))
 
 import GHC.Utils.Exception as Exception hiding (catch, mask, handle)
 import Foreign hiding (void)
@@ -1901,7 +1902,7 @@ checkModule m = do
                         (text "local  names: " <+> ppr loc)
              _ -> empty
           return True
-  afterLoad (successIf ok) False
+  afterLoad (successIf ok) Check
 
 -----------------------------------------------------------------------------
 -- :doc
@@ -2006,6 +2007,13 @@ instancesCmd s = do
 -----------------------------------------------------------------------------
 -- :load, :add, :unadd, :reload
 
+-- these are mainly used for displaying a more informative response
+data LoadType = Add Int | Unadd Int | Load | Reload | Check
+
+isReload :: LoadType -> Bool
+isReload Reload = True
+isReload _      = False
+
 -- | Sets '-fdefer-type-errors' if 'defer' is true, executes 'load' and unsets
 -- '-fdefer-type-errors' again if it has not been set before.
 wrapDeferTypeErrors :: GHC.GhcMonad m => m a -> m a
@@ -2053,7 +2061,7 @@ loadModule' files = do
         clearCaches
 
         GHC.setTargets targets
-        doLoadAndCollectInfo False LoadAllTargets
+        doLoadAndCollectInfo Load LoadAllTargets
 
   if gopt Opt_GhciLeakCheck dflags
     then do
@@ -2076,7 +2084,7 @@ addModule files = do
   -- remove old targets with the same id; e.g. for :add *M
   mapM_ GHC.removeTarget [ tid | Target { targetId = tid } <- targets' ]
   mapM_ GHC.addTarget targets'
-  _ <- doLoadAndCollectInfo False LoadAllTargets
+  _ <- doLoadAndCollectInfo (Add $ length targets') LoadAllTargets
   return ()
   where
     checkTarget :: GhciMonad m => Target -> m Bool
@@ -2108,8 +2116,9 @@ unAddModule :: GhciMonad m => [FilePath] -> m ()
 unAddModule files = do
   files' <- mapM expandPath files
   targets <- mapM (\m -> GHC.guessTarget m Nothing Nothing) files'
-  mapM_ GHC.removeTarget [ tid | Target { targetId = tid } <- targets ]
-  _ <- doLoadAndCollectInfo False LoadAllTargets
+  let removals = [ tid | Target { targetId = tid } <- targets ]
+  mapM_ GHC.removeTarget removals
+  _ <- doLoadAndCollectInfo (Unadd $ length removals) LoadAllTargets
   return ()
 
 -- | @:reload@ command
@@ -2117,7 +2126,7 @@ reloadModule :: GhciMonad m => String -> m ()
 reloadModule m = do
   session <- GHC.getSession
   let home_unit = homeUnitId (hsc_home_unit session)
-  ok <- doLoadAndCollectInfo True (loadTargets home_unit)
+  ok <- doLoadAndCollectInfo Reload (loadTargets home_unit)
   when (failed ok) failIfExprEvalMode
   where
     loadTargets hu | null m    = LoadAllTargets
@@ -2138,11 +2147,11 @@ reloadModuleDefer = wrapDeferTypeErrors . reloadModule
 -- since those commands are designed to be used by editors and
 -- tooling, it's useless to collect this data for normal GHCi
 -- sessions.
-doLoadAndCollectInfo :: GhciMonad m => Bool -> LoadHowMuch -> m SuccessFlag
-doLoadAndCollectInfo retain_context howmuch = do
+doLoadAndCollectInfo :: GhciMonad m => LoadType -> LoadHowMuch -> m SuccessFlag
+doLoadAndCollectInfo load_type howmuch = do
   doCollectInfo <- isOptionSet CollectInfo
 
-  doLoad retain_context howmuch >>= \case
+  doLoad load_type howmuch >>= \case
     Succeeded | doCollectInfo -> do
       mod_summaries <- GHC.mgModSummaries <$> getModuleGraph
       -- MP: :set +c code path only works in single package mode atm, hence
@@ -2155,8 +2164,8 @@ doLoadAndCollectInfo retain_context howmuch = do
       return Succeeded
     flag -> return flag
 
-doLoad :: GhciMonad m => Bool -> LoadHowMuch -> m SuccessFlag
-doLoad retain_context howmuch = do
+doLoad :: GhciMonad m => LoadType -> LoadHowMuch -> m SuccessFlag
+doLoad load_type howmuch = do
   -- turn off breakpoints before we load: we can't turn them off later, because
   -- the ModBreaks will have gone away.
   discardActiveBreakPoints
@@ -2174,22 +2183,22 @@ doLoad retain_context howmuch = do
       -- If GHCi message gets its own configuration at some stage then this will need to be
       -- modified to 'embedUnknownDiagnostic'.
       ok <- trySuccess $ GHC.loadWithCache (Just hmis) (mkUnknownDiagnostic . GHCiMessage) howmuch
-      afterLoad ok retain_context
+      afterLoad ok load_type
       return ok
 
 
 afterLoad
   :: GhciMonad m
   => SuccessFlag
-  -> Bool   -- keep the remembered_ctx, as far as possible (:reload)
+  -> LoadType
   -> m ()
-afterLoad ok retain_context = do
+afterLoad ok load_type = do
   revertCAFs  -- always revert CAFs on load.
   discardTickArrays
   loaded_mods <- getLoadedModules
-  modulesLoadedMsg ok loaded_mods
+  modulesLoadedMsg ok loaded_mods load_type
   graph <- GHC.getModuleGraph
-  setContextAfterLoad retain_context (Just graph)
+  setContextAfterLoad (isReload load_type) (Just graph)
 
 setContextAfterLoad :: GhciMonad m => Bool -> Maybe GHC.ModuleGraph -> m ()
 setContextAfterLoad keep_ctxt Nothing = do
@@ -2273,35 +2282,50 @@ keepPackageImports = filterM is_pkg_import
 
 
 
-modulesLoadedMsg :: GHC.GhcMonad m => SuccessFlag -> [GHC.ModSummary] -> m ()
-modulesLoadedMsg ok mods = do
+modulesLoadedMsg :: GHC.GhcMonad m => SuccessFlag -> [GHC.ModSummary] -> LoadType -> m ()
+modulesLoadedMsg ok mods load_type = do
   dflags <- getDynFlags
-  msg <- if gopt Opt_ShowLoadedModules dflags
-         then do
-               mod_names <- mapM mod_name mods
-               let mod_commas
-                     | null mods = text "none."
-                     | otherwise = hsep (punctuate comma mod_names) <> text "."
-               return $ status <> text ", modules loaded:" <+> mod_commas
-         else do
-               return $ status <> text ","
-                    <+> speakNOf (length mods) (text "module") <+> "loaded."
-
+  mod_names <- mapM mod_name mods
   when (verbosity dflags > 0) $ do
-     rendered_msg <- showSDocForUser' msg
+     let show_loaded_mods = gopt Opt_ShowLoadedModules dflags
+     rendered_msg <- showSDocForUser' $ applyWhen show_loaded_mods
+       ($$ all_loaded_mods mod_names) msg
      liftIO $ putStrLn rendered_msg
   where
-    status = case ok of
-                  Failed    -> text "Failed"
-                  Succeeded -> text "Ok"
+    num_mods = length mods
+    none_loaded = num_mods == 0
+
+    msg  = status <> comma <+> msg' <> dot
+    msg' = case load_type of
+      Reload  -> if none_loaded
+                   then "no modules to be reloaded"
+                   else n_mods num_mods "reloaded"
+      Load    -> if none_loaded
+                   then "unloaded all modules"
+                   else n_mods num_mods "loaded"
+      Check   -> n_mods 1 "checked"
+      Add   n -> n_mods n "added"
+      Unadd n -> n_mods n "unadded"
+
+    all_loaded_mods mod_names = nest 2 $ "all loaded modules:" <+>
+      (char '[' <> hsep (punctuate comma mod_names) <> char ']')
+
+
+      -- | show_loaded_mods = text "modules" <+> re_loaded <> colon <+> hsep (punctuate comma mod_ns)
+    n_mods amount action = speakNOf amount "module" <+> action
+
+    failIf = successIf . not
+    status = text $ case (failIf $ none_loaded && isReload load_type) Prelude.<> ok of
+                      Failed    -> "Failed"
+                      Succeeded -> "Ok"
 
     mod_name mod = do
         is_interpreted <- GHC.moduleIsBootOrNotObjectLinkable mod
-        return $ if is_interpreted
-                 then ppr (GHC.ms_mod mod)
-                 else ppr (GHC.ms_mod mod)
-                      <+> parens (text $ normalise $ msObjFilePath mod)
-                      -- Fix #9887
+        pure $ if is_interpreted
+               then ppr (GHC.ms_mod mod)
+               else ppr (GHC.ms_mod mod)
+                    <+> parens (text $ normalise $ msObjFilePath mod)
+                    -- Fix #9887
 
 -- | Run an 'ExceptT' wrapped 'GhcMonad' while handling source errors
 -- and printing 'throwE' strings to 'stderr'. If in expression


=====================================
testsuite/tests/driver/T8526/T8526.stdout
=====================================
@@ -2,5 +2,5 @@
 Ok, one module loaded.
 True
 [1 of 1] Compiling A                ( A.hs, interpreted )
-Ok, one module loaded.
+Ok, one module reloaded.
 False


=====================================
testsuite/tests/ghci/prog018/prog018.stdout
=====================================
@@ -22,4 +22,4 @@ Failed, two modules loaded.
 
 C.hs:6:7: error: [GHC-88464]
     Variable not in scope: variableNotInScope :: ()
-Failed, two modules loaded.
+Failed, two modules reloaded.


=====================================
testsuite/tests/ghci/scripts/T13997.stdout
=====================================
@@ -4,5 +4,5 @@ Ok, two modules loaded.
 [1 of 3] Compiling New              ( New.hs, New.o )
 [2 of 3] Compiling Bug2             ( Bug2.hs, Bug2.o ) [Source file changed]
 [3 of 3] Compiling Bug              ( Bug.hs, Bug.o ) [Bug2 changed]
-Ok, three modules loaded.
+Ok, three modules reloaded.
 True


=====================================
testsuite/tests/ghci/scripts/T17669.stdout
=====================================
@@ -2,5 +2,5 @@
 Ok, one module loaded.
 this
 [1 of 1] Compiling T17669           ( T17669.hs, T17669.o ) [Source file changed]
-Ok, one module loaded.
+Ok, one module reloaded.
 that


=====================================
testsuite/tests/ghci/scripts/T1914.stdout
=====================================
@@ -2,6 +2,6 @@
 [2 of 2] Compiling T1914A           ( T1914A.hs, interpreted )
 Ok, two modules loaded.
 [2 of 2] Compiling T1914A           ( T1914A.hs, interpreted ) [Source file changed]
-Failed, one module loaded.
+Failed, one module reloaded.
 [2 of 2] Compiling T1914A           ( T1914A.hs, interpreted )
-Ok, two modules loaded.
+Ok, two modules reloaded.


=====================================
testsuite/tests/ghci/scripts/T20217.stdout
=====================================
@@ -2,4 +2,4 @@
 [2 of 3] Compiling T20217A          ( T20217A.hs, nothing )
 [3 of 3] Compiling T20217           ( T20217.hs, nothing )
 Ok, three modules loaded.
-Ok, three modules loaded.
+Ok, three modules reloaded.


=====================================
testsuite/tests/ghci/scripts/T20587.stdout
=====================================
@@ -1,4 +1,4 @@
 [1 of 1] Compiling B
 Ok, one module loaded.
 [1 of 1] Compiling B [Source file changed]
-Ok, one module loaded.
+Ok, one module reloaded.


=====================================
testsuite/tests/ghci/scripts/T6105.stdout
=====================================
@@ -1,4 +1,4 @@
 [1 of 1] Compiling T6105            ( T6105.hs, interpreted )
 Ok, one module loaded.
 [1 of 1] Compiling T6105            ( T6105.hs, interpreted )
-Ok, one module loaded.
+Ok, one module reloaded.


=====================================
testsuite/tests/ghci/scripts/T8042.stdout
=====================================
@@ -3,7 +3,7 @@
 [3 of 3] Compiling T8042A           ( T8042A.hs, interpreted )
 Ok, three modules loaded.
 [3 of 3] Compiling T8042A           ( T8042A.hs, T8042A.o ) [Source file changed]
-Ok, three modules loaded.
+Ok, three modules reloaded.
 [2 of 3] Compiling T8042C           ( T8042C.hs, interpreted )
 [3 of 3] Compiling T8042A           ( T8042A.hs, interpreted )
 Ok, three modules loaded.


=====================================
testsuite/tests/ghci/should_run/all.T
=====================================
@@ -94,4 +94,5 @@ test('GhciMainIs', just_ghci, compile_and_run, ['-main-is otherMain'])
 test('LargeBCO', [extra_files(['LargeBCO_A.hs']), req_interp, extra_hc_opts("-O -fbyte-code-and-object-code -fprefer-byte-code")], compile_and_run, [''])
 
 test('T24115', just_ghci + [extra_run_opts("-e ':add T24115.hs'")], ghci_script, ['T24115.script'])
+test('module_loading', just_ghci + [extra_hc_opts("-XNoImplicitPrelude")], ghci_script, ['module_loading.script'])
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/95e835a9dd9513cb40ec63dc297c4d65158e224b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/95e835a9dd9513cb40ec63dc297c4d65158e224b
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/20240127/2860c02b/attachment-0001.html>


More information about the ghc-commits mailing list