[commit: ghc] ghc-8.2: DynFlags: Introduce -show-mods-loaded flag (befd937)

git at git.haskell.org git at git.haskell.org
Thu Nov 9 00:42:58 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : ghc-8.2
Link       : http://ghc.haskell.org/trac/ghc/changeset/befd937353bee0f65197317410cde3f49fca521a/ghc

>---------------------------------------------------------------

commit befd937353bee0f65197317410cde3f49fca521a
Author: Ben Gamari <bgamari.foss at gmail.com>
Date:   Mon Nov 6 15:35:19 2017 -0500

    DynFlags: Introduce -show-mods-loaded flag
    
    This flag reintroduces the verbose module name output produced by GHCi's
    :load command behind a new flag, -show-mods-loaded. This was originally
    removed in D3651 but apparently some tools (e.g. haskell-mode) rely on
    this output.
    
    Addresses #14427.
    
    Test Plan: Validate
    
    Reviewers: svenpanne
    
    Reviewed By: svenpanne
    
    Subscribers: rwbarton, thomie
    
    Differential Revision: https://phabricator.haskell.org/D4164
    
    (cherry picked from commit 8613e61de62178e76cd0f8915bd1fbe9c200a039)


>---------------------------------------------------------------

befd937353bee0f65197317410cde3f49fca521a
 compiler/main/DynFlags.hs                   |  2 ++
 docs/users_guide/ghci.rst                   | 13 ++++++++++
 ghc/GHCi/UI.hs                              | 38 ++++++++++++++++++++---------
 testsuite/tests/driver/T8526/T8526.stdout   |  4 +--
 testsuite/tests/ghci/scripts/T1914.stdout   |  6 ++---
 testsuite/tests/ghci/scripts/T6105.stdout   |  4 +--
 testsuite/tests/ghci/scripts/ghci058.stdout |  4 +--
 7 files changed, 50 insertions(+), 21 deletions(-)

diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 4791525..f5f5f00 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -536,6 +536,7 @@ data GeneralFlag
    | Opt_PprCaseAsLet
    | Opt_PprShowTicks
    | Opt_ShowHoleConstraints
+   | Opt_ShowLoadedModules
 
    -- Suppress all coercions, them replacing with '...'
    | Opt_SuppressCoercions
@@ -3762,6 +3763,7 @@ fFlagsDeps = [
   flagSpec "show-warning-groups"              Opt_ShowWarnGroups,
   flagSpec "hide-source-paths"                Opt_HideSourcePaths,
   flagSpec "show-hole-constraints"            Opt_ShowHoleConstraints,
+  flagSpec "show-loaded-modules"              Opt_ShowLoadedModules,
   flagSpec "whole-archive-hs-libs"            Opt_WholeArchiveHsLibs
   ]
 
diff --git a/docs/users_guide/ghci.rst b/docs/users_guide/ghci.rst
index e2fb361..3bdc863 100644
--- a/docs/users_guide/ghci.rst
+++ b/docs/users_guide/ghci.rst
@@ -138,6 +138,19 @@ them all in dependency order.
    Windows, then the current directory is probably something like
    ``C:\Documents and Settings\user name``.
 
+.. ghc-flag:: -fshow-loaded-modules
+    :shortdesc: Show the names of modules that GHCi loaded after a
+                :ghci-cmd:`:load` command.
+    :type: dynamic
+    :default: off
+
+    :since: 8.2.2
+
+    Typically GHCi will show only the number of modules that it loaded after a
+    :ghci-cmd:`:load` command. With this flag, GHC will also list the loaded
+    modules' names. This was the default behavior prior to GHC 8.2.1 and can be
+    useful for some tooling users.
+
 
 .. _ghci-modules-filenames:
 
diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs
index 9173d75..f677e99 100644
--- a/ghc/GHCi/UI.hs
+++ b/ghc/GHCi/UI.hs
@@ -51,7 +51,7 @@ import GHC ( LoadHowMuch(..), Target(..),  TargetId(..), InteractiveImport(..),
 import HsImpExp
 import HsSyn
 import HscTypes ( tyThingParent_maybe, handleFlagWarnings, getSafeMode, hsc_IC,
-                  setInteractivePrintName, hsc_dflags )
+                  setInteractivePrintName, hsc_dflags, msObjFilePath )
 import Module
 import Name
 import Packages ( trusted, getPackageDetails, getInstalledPackageDetails,
@@ -1721,7 +1721,7 @@ afterLoad ok retain_context = do
   lift revertCAFs  -- always revert CAFs on load.
   lift discardTickArrays
   loaded_mods <- getLoadedModules
-  modulesLoadedMsg ok (length loaded_mods)
+  modulesLoadedMsg ok loaded_mods
   lift $ setContextAfterLoad retain_context loaded_mods
 
 setContextAfterLoad :: Bool -> [GHC.ModSummary] -> GHCi ()
@@ -1796,22 +1796,36 @@ keepPackageImports = filterM is_pkg_import
           mod_name = unLoc (ideclName d)
 
 
-modulesLoadedMsg :: SuccessFlag -> Int -> InputT GHCi ()
-modulesLoadedMsg ok num_mods = do
+modulesLoadedMsg :: SuccessFlag -> [GHC.ModSummary] -> InputT GHCi ()
+modulesLoadedMsg ok mods = do
   dflags <- getDynFlags
   unqual <- GHC.getPrintUnqual
-  let status = case ok of
-                   Failed    -> text "Failed"
-                   Succeeded -> text "Ok"
 
-      num_mods_pp = if num_mods == 1
-        then "1 module"
-        else int num_mods <+> "modules"
-      msg = status <> text "," <+> num_mods_pp <+> "loaded."
+  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."
 
   when (verbosity dflags > 0) $
      liftIO $ putStrLn $ showSDocForUser dflags unqual msg
-
+  where
+    status = case ok of
+                  Failed    -> text "Failed"
+                  Succeeded -> text "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
 
 -- | Run an 'ExceptT' wrapped 'GhcMonad' while handling source errors
 -- and printing 'throwE' strings to 'stderr'
diff --git a/testsuite/tests/driver/T8526/T8526.stdout b/testsuite/tests/driver/T8526/T8526.stdout
index 83b8f95..0255fa3 100644
--- a/testsuite/tests/driver/T8526/T8526.stdout
+++ b/testsuite/tests/driver/T8526/T8526.stdout
@@ -1,6 +1,6 @@
 [1 of 1] Compiling A                ( A.hs, interpreted )
-Ok, 1 module loaded.
+Ok, one module loaded.
 True
 [1 of 1] Compiling A                ( A.hs, interpreted )
-Ok, 1 module loaded.
+Ok, one module loaded.
 False
diff --git a/testsuite/tests/ghci/scripts/T1914.stdout b/testsuite/tests/ghci/scripts/T1914.stdout
index 2d1a82b..6612564 100644
--- a/testsuite/tests/ghci/scripts/T1914.stdout
+++ b/testsuite/tests/ghci/scripts/T1914.stdout
@@ -1,7 +1,7 @@
 [1 of 2] Compiling T1914B           ( T1914B.hs, interpreted )
 [2 of 2] Compiling T1914A           ( T1914A.hs, interpreted )
-Ok, 2 modules loaded.
+Ok, two modules loaded.
 [2 of 2] Compiling T1914A           ( T1914A.hs, interpreted )
-Failed, 1 module loaded.
+Failed, one module loaded.
 [2 of 2] Compiling T1914A           ( T1914A.hs, interpreted )
-Ok, 2 modules loaded.
+Ok, two modules loaded.
diff --git a/testsuite/tests/ghci/scripts/T6105.stdout b/testsuite/tests/ghci/scripts/T6105.stdout
index 6a846e3..9a8190f 100644
--- a/testsuite/tests/ghci/scripts/T6105.stdout
+++ b/testsuite/tests/ghci/scripts/T6105.stdout
@@ -1,4 +1,4 @@
 [1 of 1] Compiling T6105            ( T6105.hs, interpreted )
-Ok, 1 module loaded.
+Ok, one module loaded.
 [1 of 1] Compiling T6105            ( T6105.hs, interpreted )
-Ok, 1 module loaded.
+Ok, one module loaded.
diff --git a/testsuite/tests/ghci/scripts/ghci058.stdout b/testsuite/tests/ghci/scripts/ghci058.stdout
index 2028aee..83c8bbd 100644
--- a/testsuite/tests/ghci/scripts/ghci058.stdout
+++ b/testsuite/tests/ghci/scripts/ghci058.stdout
@@ -1,4 +1,4 @@
-Ok, 1 module loaded.
+Ok, one module loaded.
 'a'
-Ok, 1 module loaded.
+Ok, one module loaded.
 'b'



More information about the ghc-commits mailing list