[Git][ghc/ghc][wip/t22884] error messages: Don't display ghci specific hints for missing packages

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Thu May 11 15:25:28 UTC 2023



Matthew Pickering pushed to branch wip/t22884 at Glasgow Haskell Compiler / GHC


Commits:
04197c6b by Matthew Pickering at 2023-05-11T16:25:18+01:00
error messages: Don't display ghci specific hints for missing packages

Tickets like #22884 suggest that it is confusing that GHC used on the
command line can suggest options which only work in GHCi.

This ticket uses the error message infrastructure to override certain
error messages which displayed GHCi specific information so that this
information is only showed when using GHCi.

The main annoyance is that we mostly want to display errors in the same
way as before, but with some additional information. This means that the
error rendering code has to be exported from the Iface/Errors/Ppr.hs
module.

I am unsure about whether the approach taken here is the best or most
maintainable solution.

Fixes #22884

- - - - -


26 changed files:

- compiler/GHC/Iface/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- ghc/GHCi/UI/Exception.hs
- testsuite/tests/driver/multipleHomeUnits/multipleHomeUnitsModuleVisibility.stderr
- testsuite/tests/ghc-api/target-contents/TargetContents.stderr
- testsuite/tests/ghc-e/should_run/T2636.stderr
- testsuite/tests/module/mod1.stderr
- testsuite/tests/module/mod2.stderr
- + testsuite/tests/package/T22884.hs
- + testsuite/tests/package/T22884.stderr
- + testsuite/tests/package/T22884_interactive.script
- + testsuite/tests/package/T22884_interactive.stderr
- testsuite/tests/package/T4806.stderr
- + testsuite/tests/package/T4806_interactive.script
- + testsuite/tests/package/T4806_interactive.stderr
- testsuite/tests/package/T4806a.stderr
- testsuite/tests/package/all.T
- testsuite/tests/package/package01e.stderr
- testsuite/tests/package/package06e.stderr
- testsuite/tests/package/package07e.stderr
- testsuite/tests/package/package08e.stderr
- testsuite/tests/perf/compiler/parsing001.stderr
- testsuite/tests/plugins/T11244.stderr
- testsuite/tests/plugins/plugins03.stderr
- testsuite/tests/safeHaskell/safeLanguage/SafeLang07.stderr
- testsuite/tests/typecheck/should_fail/tcfail082.stderr


Changes:

=====================================
compiler/GHC/Iface/Errors/Ppr.hs
=====================================
@@ -19,6 +19,11 @@ module GHC.Iface.Errors.Ppr
   , missingInterfaceErrorReason
   , missingInterfaceErrorDiagnostic
   , readInterfaceErrorDiagnostic
+
+  , lookingForHerald
+  , cantFindErrorX
+  , mayShowLocations
+  , pkgHiddenHint
   )
   where
 
@@ -129,34 +134,34 @@ cantFindError :: IfaceMessageOpts
   -> FindingModuleOrInterface
   -> CantFindInstalled
   -> SDoc
-cantFindError opts = cantFindErrorX (pkg_hidden_hint (ifaceBuildingCabalPackage opts)) (mayShowLocations (ifaceShowTriedFiles opts))
-  where
-    pkg_hidden_hint using_cabal (Just pkg)
-     | using_cabal == YesBuildingCabalPackage
-        = text "Perhaps you need to add" <+>
-              quotes (ppr (unitPackageName pkg)) <+>
-              text "to the build-depends in your .cabal file."
-    -- MP: This is ghci specific, remove
-     | otherwise
-         = text "You can run" <+>
-           quotes (text ":set -package " <> ppr (unitPackageName pkg)) <+>
-           text "to expose it." $$
-           text "(Note: this unloads all the modules in the current scope.)"
-    pkg_hidden_hint _ Nothing = empty
-
-mayShowLocations :: Bool -> [FilePath] -> SDoc
-mayShowLocations verbose files
+cantFindError opts =
+  cantFindErrorX
+    (pkgHiddenHint (const empty) (ifaceBuildingCabalPackage opts))
+    (mayShowLocations "-v" (ifaceShowTriedFiles opts))
+
+
+pkgHiddenHint :: (UnitInfo -> SDoc) -> BuildingCabalPackage
+              -> UnitInfo -> SDoc
+pkgHiddenHint _hint YesBuildingCabalPackage pkg
+ = text "Perhaps you need to add" <+>
+   quotes (ppr (unitPackageName pkg)) <+>
+   text "to the build-depends in your .cabal file."
+pkgHiddenHint hint _not_cabal pkg
+ = hint pkg
+
+mayShowLocations :: String -> Bool -> [FilePath] -> SDoc
+mayShowLocations option verbose files
     | null files = empty
     | not verbose =
-          text "Use -v (or `:set -v` in ghci) " <>
+          text "Use" <+> text option <+>
               text "to see a list of the files searched for."
     | otherwise =
           hang (text "Locations searched:") 2 $ vcat (map text files)
 
 -- | General version of cantFindError which has some holes which allow GHC/GHCi to display slightly different
 -- error messages.
-cantFindErrorX :: (Maybe UnitInfo -> SDoc) -> ([FilePath] -> SDoc) -> FindingModuleOrInterface -> CantFindInstalled -> SDoc
-cantFindErrorX pkg_hidden_hint mayShowLocations mod_or_interface (CantFindInstalled mod_name cfir) =
+cantFindErrorX :: (UnitInfo -> SDoc) -> ([FilePath] -> SDoc) -> FindingModuleOrInterface -> CantFindInstalled -> SDoc
+cantFindErrorX pkg_hidden_hint may_show_locations mod_or_interface (CantFindInstalled mod_name cfir) =
   let ambig = isAmbiguousInstalledReason cfir
       find_or_load = isLoadOrFindReason cfir
       ppr_what = prettyCantFindWhat find_or_load mod_or_interface ambig
@@ -184,11 +189,11 @@ cantFindErrorX pkg_hidden_hint mayShowLocations mod_or_interface (CantFindInstal
       text "There are files missing in the " <> quotes (ppr pkg) <+>
       text "package," $$
       text "try running 'ghc-pkg check'." $$
-      mayShowLocations files
+      may_show_locations files
     MissingPackageWayFiles build pkg files ->
       text "Perhaps you haven't installed the " <> text build <+>
       text "libraries for package " <> quotes (ppr pkg) <> char '?' $$
-      mayShowLocations files
+      may_show_locations files
     ModuleSuggestion ms fps ->
 
       let pp_suggestions :: [ModuleSuggestion] -> SDoc
@@ -230,7 +235,7 @@ cantFindErrorX pkg_hidden_hint mayShowLocations mod_or_interface (CantFindInstal
                           <+> ppr (mkUnit pkg))
                     | otherwise = empty
 
-        in pp_suggestions ms $$ mayShowLocations fps
+        in pp_suggestions ms $$ may_show_locations fps
     NotAModule -> text "It is not a module in the current program, or in any known package."
     CouldntFindInFiles fps -> vcat (map text fps)
     MultiplePackages mods
@@ -248,7 +253,7 @@ cantFindErrorX pkg_hidden_hint mayShowLocations mod_or_interface (CantFindInstal
       vcat (map pkg_hidden pkg_hiddens) $$
       vcat (map mod_hidden mod_hiddens) $$
       vcat (map unusable unusables) $$
-      mayShowLocations files
+      may_show_locations files
   where
     pprMod (m, o) = text "it is bound as" <+> ppr m <+>
                                 text "by" <+> pprOrigin m o
@@ -268,7 +273,7 @@ cantFindErrorX pkg_hidden_hint mayShowLocations mod_or_interface (CantFindInstal
         <+> quotes (ppr uid)
         --FIXME: we don't really want to show the unit id here we should
         -- show the source package id or installed package id if it's ambiguous
-        <> dot $$ pkg_hidden_hint uif
+        <> dot $$ maybe empty pkg_hidden_hint uif
 
 
     mod_hidden pkg =
@@ -285,21 +290,21 @@ interfaceErrorDiagnostic opts = \ case
   Can'tFindNameInInterface name relevant_tyThings ->
     missingDeclInInterface name relevant_tyThings
   Can'tFindInterface err looking_for ->
-    case looking_for of
-      LookingForName {} ->
-        missingInterfaceErrorDiagnostic opts err
-      LookingForModule {} ->
-        missingInterfaceErrorDiagnostic opts err
-      LookingForHiBoot mod ->
-        hang (text "Could not find hi-boot interface for" <+> quotes (ppr mod) <> colon)
-          2 (missingInterfaceErrorDiagnostic opts err)
-      LookingForSig sig ->
-        hang (text "Could not find interface file for signature" <+> quotes (ppr sig) <> colon)
-          2 (missingInterfaceErrorDiagnostic opts err)
+    hangNotEmpty (lookingForHerald looking_for) 2 (missingInterfaceErrorDiagnostic opts err)
   CircularImport mod ->
     text "Circular imports: module" <+> quotes (ppr mod)
     <+> text "depends on itself"
 
+lookingForHerald :: InterfaceLookingFor -> SDoc
+lookingForHerald looking_for =
+    case looking_for of
+      LookingForName {} -> empty
+      LookingForModule {} -> empty
+      LookingForHiBoot mod ->
+        text "Could not find hi-boot interface for" <+> quotes (ppr mod) <> colon
+      LookingForSig sig ->
+        text "Could not find interface file for signature" <+> quotes (ppr sig) <> colon
+
 readInterfaceErrorDiagnostic :: ReadInterfaceError -> SDoc
 readInterfaceErrorDiagnostic = \ case
   ExceptionOccurred fp ex ->


=====================================
compiler/GHC/Tc/Errors/Ppr.hs
=====================================
@@ -21,6 +21,10 @@ module GHC.Tc.Errors.Ppr
   , inHsDocContext
   , TcRnMessageOpts(..)
   , pprTyThingUsedWrong
+
+  -- | Useful when overriding message printing.
+  , messageWithInfoDiagnosticMessage
+  , messageWithHsDocContext
   )
   where
 
@@ -126,12 +130,8 @@ instance Diagnostic TcRnMessage where
                   (tcOptsShowContext opts)
                   (diagnosticMessage opts msg)
     TcRnWithHsDocContext ctxt msg
-      -> if tcOptsShowContext opts
-         then main_msg `unionDecoratedSDoc` ctxt_msg
-         else main_msg
-      where
-        main_msg = diagnosticMessage opts msg
-        ctxt_msg = mkSimpleDecorated (inHsDocContext ctxt)
+      -> messageWithHsDocContext opts ctxt (diagnosticMessage opts msg)
+
     TcRnSolverReport msg _ _
       -> mkSimpleDecorated $ pprSolverReportWithCtxt msg
     TcRnRedundantConstraints redundants (info, show_info)
@@ -3259,6 +3259,14 @@ messageWithInfoDiagnosticMessage unit_state ErrInfo{..} show_ctxt important =
       in (mapDecoratedSDoc (pprWithUnitState unit_state) important) `unionDecoratedSDoc`
          mkDecorated err_info'
 
+messageWithHsDocContext :: TcRnMessageOpts -> HsDocContext -> DecoratedSDoc -> DecoratedSDoc
+messageWithHsDocContext opts ctxt main_msg = do
+      if tcOptsShowContext opts
+         then main_msg `unionDecoratedSDoc` ctxt_msg
+         else main_msg
+      where
+        ctxt_msg = mkSimpleDecorated (inHsDocContext ctxt)
+
 dodgy_msg :: Outputable ie => SDoc -> GlobalRdrElt -> ie -> SDoc
 dodgy_msg kind tc ie
   = vcat [ text "The" <+> kind <+> text "item" <+> quotes (ppr ie) <+> text "suggests that"


=====================================
ghc/GHCi/UI/Exception.hs
=====================================
@@ -4,14 +4,28 @@
 module GHCi.UI.Exception(printGhciException, GHCiMessage(..)) where
 
 import GHC.Prelude
-import GHC.Utils.Logger
-import Control.Monad.IO.Class
-import GHC.Driver.Session
-import GHC.Types.SourceError
-import GHC.Driver.Errors.Types
-import GHC.Types.Error
+
 import GHC.Driver.Config.Diagnostic
 import GHC.Driver.Errors
+import GHC.Driver.Errors.Types
+import GHC.Driver.Session
+
+import GHC.Iface.Errors.Ppr
+import GHC.Iface.Errors.Types
+
+import GHC.Tc.Errors.Ppr
+import GHC.Tc.Errors.Types
+
+import GHC.Types.Error
+import GHC.Types.SourceError
+
+import GHC.Unit.State
+
+import GHC.Utils.Logger
+import GHC.Utils.Outputable
+
+import Control.Monad.IO.Class
+
 
 -- | Print the all diagnostics in a 'SourceError'.  Specialised for GHCi error reporting
 -- for some error messages.
@@ -24,15 +38,67 @@ printGhciException err = do
   liftIO $ printMessages logger print_config diag_opts (GHCiMessage <$> (srcErrorMessages err))
 
 
-newtype GHCiMessage = GHCiMessage { getGhciMessage :: GhcMessage }
+newtype GHCiMessage = GHCiMessage { _getGhciMessage :: GhcMessage }
 
 instance Diagnostic GHCiMessage where
   type DiagnosticOpts GHCiMessage = DiagnosticOpts GhcMessage
 
-  diagnosticMessage opts (GHCiMessage msg) = diagnosticMessage opts msg
+  diagnosticMessage opts (GHCiMessage msg) = ghciDiagnosticMessage opts msg
 
   diagnosticReason (GHCiMessage msg) = diagnosticReason msg
 
   diagnosticHints (GHCiMessage msg) = diagnosticHints msg
 
   diagnosticCode (GHCiMessage msg)  = diagnosticCode msg
+
+-- Modifications to error messages which we want to display in GHCi
+ghciDiagnosticMessage :: GhcMessageOpts -> GhcMessage -> DecoratedSDoc
+ghciDiagnosticMessage ghc_opts msg =
+  case msg of
+    GhcTcRnMessage tc_msg ->
+      case tcRnMessage (tcMessageOpts ghc_opts) tc_msg of
+        Nothing -> diagnosticMessage ghc_opts msg
+        Just sdoc -> sdoc
+    GhcDriverMessage  (DriverInterfaceError err) ->
+      case ghciInterfaceError err of
+        Just sdoc -> mkSimpleDecorated sdoc
+        Nothing -> diagnosticMessage ghc_opts msg
+    GhcDriverMessage {} -> diagnosticMessage ghc_opts msg
+    GhcPsMessage  {} -> diagnosticMessage ghc_opts msg
+    GhcDsMessage  {} -> diagnosticMessage ghc_opts msg
+    GhcUnknownMessage  {} -> diagnosticMessage ghc_opts msg
+  where
+    tcRnMessage tc_opts tc_msg =
+      case tc_msg of
+        TcRnInterfaceError err -> mkSimpleDecorated <$> (ghciInterfaceError err)
+        TcRnMessageWithInfo unit_state msg_with_info ->
+          case msg_with_info of
+           TcRnMessageDetailed err_info wrapped_msg
+             -> messageWithInfoDiagnosticMessage unit_state err_info
+                  (tcOptsShowContext tc_opts)
+                  <$> tcRnMessage tc_opts wrapped_msg
+        TcRnWithHsDocContext ctxt wrapped_msg ->
+          messageWithHsDocContext tc_opts ctxt <$> tcRnMessage tc_opts wrapped_msg
+        _ -> Nothing
+
+    opts = tcOptsIfaceOpts (tcMessageOpts ghc_opts)
+
+    ghciInterfaceError (Can'tFindInterface err looking_for) =
+      hangNotEmpty (lookingForHerald looking_for) 2 <$> ghciMissingInterfaceErrorDiagnostic err
+    ghciInterfaceError _ = Nothing
+
+    ghciMissingInterfaceErrorDiagnostic reason =
+      case reason of
+        CantFindErr us module_or_interface cfi -> Just (pprWithUnitState us $ cantFindErrorX pkg_hidden_hint may_show_locations module_or_interface cfi)
+        _ -> Nothing
+      where
+
+        may_show_locations = mayShowLocations ":set -v" (ifaceShowTriedFiles opts)
+
+        pkg_hidden_hint = pkgHiddenHint hidden_msg (ifaceBuildingCabalPackage opts)
+          where
+            hidden_msg pkg =
+              text "You can run" <+>
+              quotes (text ":set -package " <> ppr (unitPackageName pkg)) <+>
+              text "to expose it." $$
+              text "(Note: this unloads all the modules in the current scope.)"


=====================================
testsuite/tests/driver/multipleHomeUnits/multipleHomeUnitsModuleVisibility.stderr
=====================================
@@ -2,4 +2,4 @@
 module-visibility-import/MV.hs:5:1: error: [GHC-87110]
     Could not load module ‘MV2’.
     it is a hidden module in the package ‘mv’
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.


=====================================
testsuite/tests/ghc-api/target-contents/TargetContents.stderr
=====================================
@@ -18,7 +18,7 @@ B.hs:3:5: error: [GHC-88464] Variable not in scope: z
 
 A.hs:3:1: error: [GHC-87110]
     Could not find module ‘B’.
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.
 == Dep_DM_AB
 == Dep_Error_DM_AB
 
@@ -27,7 +27,7 @@ B.hs:3:5: error: [GHC-88464] Variable not in scope: z
 
 A.hs:3:1: error: [GHC-87110]
     Could not find module ‘B’.
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.
 == Dep_MD_AB
 == Dep_Error_MD_AB
 


=====================================
testsuite/tests/ghc-e/should_run/T2636.stderr
=====================================
@@ -1,4 +1,4 @@
 
 T2636.hs:1:1: error: [GHC-87110]
     Could not find module ‘MissingModule’.
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.


=====================================
testsuite/tests/module/mod1.stderr
=====================================
@@ -1,4 +1,4 @@
 
 mod1.hs:3:1: error: [GHC-87110]
     Could not find module ‘N’.
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.


=====================================
testsuite/tests/module/mod2.stderr
=====================================
@@ -1,4 +1,4 @@
 
 mod2.hs:3:1: error: [GHC-87110]
     Could not find module ‘N’.
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.


=====================================
testsuite/tests/package/T22884.hs
=====================================
@@ -0,0 +1,3 @@
+module T22884 where
+
+import Data.Text


=====================================
testsuite/tests/package/T22884.stderr
=====================================
@@ -0,0 +1,5 @@
+
+T22884.hs:3:1: error: [GHC-87110]
+    Could not load module ‘Data.Text’.
+    It is a member of the hidden package ‘text-2.0.2’.
+    Use -v to see a list of the files searched for.


=====================================
testsuite/tests/package/T22884_interactive.script
=====================================
@@ -0,0 +1,3 @@
+:set -hide-all-packages
+
+import Data.Text


=====================================
testsuite/tests/package/T22884_interactive.stderr
=====================================
@@ -0,0 +1,6 @@
+
+<no location info>: error: [GHC-87110]
+    Could not load module ‘Data.Text’.
+    It is a member of the hidden package ‘text-2.0.2’.
+    You can run ‘:set -package text’ to expose it.
+    (Note: this unloads all the modules in the current scope.)


=====================================
testsuite/tests/package/T4806.stderr
=====================================
@@ -3,4 +3,4 @@ T4806.hs:1:1: error: [GHC-87110]
     Could not load module ‘Data.Map’.
     It is a member of the package ‘containers-0.6.7’
     which is ignored due to an -ignore-package flag
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.


=====================================
testsuite/tests/package/T4806_interactive.script
=====================================
@@ -0,0 +1,3 @@
+:set -ignore-package containers
+
+:l T4806.hs


=====================================
testsuite/tests/package/T4806_interactive.stderr
=====================================
@@ -0,0 +1,6 @@
+
+T4806.hs:1:1: error: [GHC-87110]
+    Could not load module ‘Data.Map’.
+    It is a member of the package ‘containers-0.6.7’
+    which is ignored due to an -ignore-package flag
+    Use :set -v to see a list of the files searched for.


=====================================
testsuite/tests/package/T4806a.stderr
=====================================
@@ -4,4 +4,4 @@ T4806a.hs:1:1: error: [GHC-87110]
     It is a member of the package ‘containers-0.6.7’
     which is unusable because the -ignore-package flag was used to ignore at least one of its dependencies:
       deepseq-1.4.8.1 template-haskell-2.20.0.0
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.


=====================================
testsuite/tests/package/all.T
=====================================
@@ -20,3 +20,6 @@ test('package10',  normal, compile,      ['-hide-all-packages -package "ghc (GHC
 
 test('T4806', normalise_version('containers'), compile_fail, ['-ignore-package containers'])
 test('T4806a', normalise_version('deepseq', 'containers', 'template-haskell'), compile_fail, ['-ignore-package deepseq'])
+test('T22884', normalise_version('text'), compile_fail, ['-hide-package text'])
+test('T22884_interactive', normalise_version('text'), ghci_script, ['T22884_interactive.script'])
+test('T4806_interactive', [extra_files(['T4806.hs']), normalise_version('containers')], ghci_script, ['T4806_interactive.script'])


=====================================
testsuite/tests/package/package01e.stderr
=====================================
@@ -2,13 +2,9 @@
 package01e.hs:2:1: error: [GHC-87110]
     Could not load module ‘Data.Map’.
     It is a member of the hidden package ‘containers-0.6.7’.
-    You can run ‘:set -package containers’ to expose it.
-    (Note: this unloads all the modules in the current scope.)
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.
 
 package01e.hs:3:1: error: [GHC-87110]
     Could not load module ‘Data.IntMap’.
     It is a member of the hidden package ‘containers-0.6.7’.
-    You can run ‘:set -package containers’ to expose it.
-    (Note: this unloads all the modules in the current scope.)
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.


=====================================
testsuite/tests/package/package06e.stderr
=====================================
@@ -2,13 +2,9 @@
 package06e.hs:2:1: error: [GHC-87110]
     Could not load module ‘GHC.Hs.Type’.
     It is a member of the hidden package ‘ghc-9.7’.
-    You can run ‘:set -package ghc’ to expose it.
-    (Note: this unloads all the modules in the current scope.)
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.
 
 package06e.hs:3:1: error: [GHC-87110]
     Could not load module ‘GHC.Types.Unique.FM’.
     It is a member of the hidden package ‘ghc-9.7’.
-    You can run ‘:set -package ghc’ to expose it.
-    (Note: this unloads all the modules in the current scope.)
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.


=====================================
testsuite/tests/package/package07e.stderr
=====================================
@@ -5,25 +5,19 @@ package07e.hs:2:1: error: [GHC-61948]
       GHC.Hs.Type (needs flag -package-id ghc-9.7)
       GHC.Tc.Types (needs flag -package-id ghc-9.7)
       GHC.Hs.Syn.Type (needs flag -package-id ghc-9.7)
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.
 
 package07e.hs:3:1: error: [GHC-87110]
     Could not load module ‘GHC.Hs.Type’.
     It is a member of the hidden package ‘ghc-9.7’.
-    You can run ‘:set -package ghc’ to expose it.
-    (Note: this unloads all the modules in the current scope.)
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.
 
 package07e.hs:4:1: error: [GHC-87110]
     Could not load module ‘GHC.Hs.Utils’.
     It is a member of the hidden package ‘ghc-9.7’.
-    You can run ‘:set -package ghc’ to expose it.
-    (Note: this unloads all the modules in the current scope.)
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.
 
 package07e.hs:5:1: error: [GHC-87110]
     Could not load module ‘GHC.Types.Unique.FM’.
     It is a member of the hidden package ‘ghc-9.7’.
-    You can run ‘:set -package ghc’ to expose it.
-    (Note: this unloads all the modules in the current scope.)
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.


=====================================
testsuite/tests/package/package08e.stderr
=====================================
@@ -5,25 +5,19 @@ package08e.hs:2:1: error: [GHC-61948]
       GHC.Hs.Type (needs flag -package-id ghc-9.7)
       GHC.Tc.Types (needs flag -package-id ghc-9.7)
       GHC.Hs.Syn.Type (needs flag -package-id ghc-9.7)
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.
 
 package08e.hs:3:1: error: [GHC-87110]
     Could not load module ‘GHC.Hs.Type’.
     It is a member of the hidden package ‘ghc-9.7’.
-    You can run ‘:set -package ghc’ to expose it.
-    (Note: this unloads all the modules in the current scope.)
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.
 
 package08e.hs:4:1: error: [GHC-87110]
     Could not load module ‘GHC.Hs.Utils’.
     It is a member of the hidden package ‘ghc-9.7’.
-    You can run ‘:set -package ghc’ to expose it.
-    (Note: this unloads all the modules in the current scope.)
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.
 
 package08e.hs:5:1: error: [GHC-87110]
     Could not load module ‘GHC.Types.Unique.FM’.
     It is a member of the hidden package ‘ghc-9.7’.
-    You can run ‘:set -package ghc’ to expose it.
-    (Note: this unloads all the modules in the current scope.)
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.


=====================================
testsuite/tests/perf/compiler/parsing001.stderr
=====================================
@@ -1,4 +1,4 @@
 
 parsing001.hs:3:1: error: [GHC-87110]
     Could not find module ‘Wibble’.
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.


=====================================
testsuite/tests/plugins/T11244.stderr
=====================================
@@ -1,5 +1,3 @@
 <command line>: Could not load module ‘RuleDefiningPlugin’.
 It is a member of the hidden package ‘rule-defining-plugin-0.1’.
-You can run ‘:set -package rule-defining-plugin’ to expose it.
-(Note: this unloads all the modules in the current scope.)
-Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+Use -v to see a list of the files searched for.


=====================================
testsuite/tests/plugins/plugins03.stderr
=====================================
@@ -1,2 +1,2 @@
 <command line>: Could not find module ‘Simple.NonExistentPlugin’.
-Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+Use -v to see a list of the files searched for.


=====================================
testsuite/tests/safeHaskell/safeLanguage/SafeLang07.stderr
=====================================
@@ -4,4 +4,4 @@ SafeLang07.hs:2:14: warning:
 
 SafeLang07.hs:15:1: error: [GHC-87110]
     Could not find module ‘SafeLang07_A’.
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.


=====================================
testsuite/tests/typecheck/should_fail/tcfail082.stderr
=====================================
@@ -1,12 +1,12 @@
 
 tcfail082.hs:2:1: error: [GHC-87110]
     Could not find module ‘Data82’.
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.
 
 tcfail082.hs:3:1: error: [GHC-87110]
     Could not find module ‘Inst82_1’.
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.
 
 tcfail082.hs:4:1: error: [GHC-87110]
     Could not find module ‘Inst82_2’.
-    Use -v (or `:set -v` in ghci) to see a list of the files searched for.
+    Use -v to see a list of the files searched for.



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/04197c6b669a6bc3ba834d4dfecfaa8ab74a8982

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/04197c6b669a6bc3ba834d4dfecfaa8ab74a8982
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/20230511/fa749828/attachment-0001.html>


More information about the ghc-commits mailing list