Skip to content

Commit

Permalink
Show only the number of modules in ghci
Browse files Browse the repository at this point in the history
Reviewers: bgamari, austin, simonmar

Reviewed By: bgamari

Subscribers: mpickering, rwbarton, thomie

Differential Revision: https://phabricator.haskell.org/D3651
  • Loading branch information
bitonic authored and bgamari committed Jun 21, 2017
1 parent 88263f9 commit c85cd9b
Show file tree
Hide file tree
Showing 5 changed files with 18 additions and 27 deletions.
27 changes: 9 additions & 18 deletions ghc/GHCi/UI.hs
Expand Up @@ -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, msObjFilePath )
setInteractivePrintName, hsc_dflags )
import Module
import Name
import Packages ( trusted, getPackageDetails, getInstalledPackageDetails,
Expand Down Expand Up @@ -1721,7 +1721,7 @@ afterLoad ok retain_context = do
lift revertCAFs -- always revert CAFs on load.
lift discardTickArrays
loaded_mods <- getLoadedModules
modulesLoadedMsg ok loaded_mods
modulesLoadedMsg ok (length loaded_mods)
lift $ setContextAfterLoad retain_context loaded_mods

setContextAfterLoad :: Bool -> [GHC.ModSummary] -> GHCi ()
Expand Down Expand Up @@ -1796,27 +1796,18 @@ keepPackageImports = filterM is_pkg_import
mod_name = unLoc (ideclName d)


modulesLoadedMsg :: SuccessFlag -> [GHC.ModSummary] -> InputT GHCi ()
modulesLoadedMsg ok mods = do
modulesLoadedMsg :: SuccessFlag -> Int -> InputT GHCi ()
modulesLoadedMsg ok num_mods = do
dflags <- getDynFlags
unqual <- GHC.getPrintUnqual
let 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)
<> text " ("
<> text (normalise $ msObjFilePath mod)
<> text ")" -- fix #9887
mod_names <- mapM mod_name mods
let mod_commas
| null mods = text "none."
| otherwise = hsep (punctuate comma mod_names) <> text "."
status = case ok of
let status = case ok of
Failed -> text "Failed"
Succeeded -> text "Ok"

msg = status <> text ", modules loaded:" <+> mod_commas
num_mods_pp = if num_mods == 1
then "1 module"
else int num_mods <+> "modules"
msg = status <> text "," <+> num_mods_pp <+> "loaded."

when (verbosity dflags > 0) $
liftIO $ putStrLn $ showSDocForUser dflags unqual msg
Expand Down
4 changes: 2 additions & 2 deletions testsuite/tests/driver/T8526/T8526.stdout
@@ -1,6 +1,6 @@
[1 of 1] Compiling A ( A.hs, interpreted )
Ok, modules loaded: A.
Ok, 1 module loaded.
True
[1 of 1] Compiling A ( A.hs, interpreted )
Ok, modules loaded: A.
Ok, 1 module loaded.
False
6 changes: 3 additions & 3 deletions 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, modules loaded: T1914A, T1914B.
Ok, 2 modules loaded.
[2 of 2] Compiling T1914A ( T1914A.hs, interpreted )
Failed, modules loaded: T1914B.
Failed, 1 module loaded.
[2 of 2] Compiling T1914A ( T1914A.hs, interpreted )
Ok, modules loaded: T1914A, T1914B.
Ok, 2 modules loaded.
4 changes: 2 additions & 2 deletions testsuite/tests/ghci/scripts/T6105.stdout
@@ -1,4 +1,4 @@
[1 of 1] Compiling T6105 ( T6105.hs, interpreted )
Ok, modules loaded: T6105.
Ok, 1 module loaded.
[1 of 1] Compiling T6105 ( T6105.hs, interpreted )
Ok, modules loaded: T6105.
Ok, 1 module loaded.
4 changes: 2 additions & 2 deletions testsuite/tests/ghci/scripts/ghci058.stdout
@@ -1,4 +1,4 @@
Ok, modules loaded: Ghci058 (Ghci058.o).
Ok, 1 module loaded.
'a'
Ok, modules loaded: Ghci058 (Ghci058.o).
Ok, 1 module loaded.
'b'

0 comments on commit c85cd9b

Please sign in to comment.