[Git][ghc/ghc][wip/t22884] Suggestions

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Wed May 3 08:33:17 UTC 2023



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


Commits:
f936f148 by sheaf at 2023-05-03T08:33:15+00:00
Suggestions
- - - - -


2 changed files:

- compiler/GHC/Iface/Errors/Ppr.hs
- ghc/GHCi/UI/Exception.hs


Changes:

=====================================
compiler/GHC/Iface/Errors/Ppr.hs
=====================================
@@ -135,20 +135,20 @@ cantFindError :: IfaceMessageOpts
   -> FindingModuleOrInterface
   -> CantFindInstalled
   -> SDoc
-cantFindError opts = cantFindErrorX (pkgHiddenHint (const empty) (ifaceBuildingCabalPackage opts)) (mayShowLocations "-v" (ifaceShowTriedFiles opts))
-  where
+cantFindError opts =
+  cantFindErrorX
+    (pkgHiddenHint (const empty) (ifaceBuildingCabalPackage opts))
+    (mayShowLocations "-v" (ifaceShowTriedFiles opts))
 
-pkgHiddenHint :: (UnitInfo -> SDoc) -> BuildingCabalPackage
-                  -> Maybe UnitInfo -> SDoc
-pkgHiddenHint 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."
 
- | otherwise
-     = hint pkg
-pkgHiddenHint _ _ Nothing = empty
+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
@@ -161,8 +161,8 @@ mayShowLocations option verbose 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
@@ -194,7 +194,7 @@ cantFindErrorX pkg_hidden_hint mayShowLocations mod_or_interface (CantFindInstal
     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
@@ -236,7 +236,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
@@ -254,7 +254,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
@@ -274,7 +274,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 =


=====================================
ghc/GHCi/UI/Exception.hs
=====================================
@@ -4,21 +4,29 @@
 module GHCi.UI.Exception(printGhciException) where
 
 import GHC.Prelude
-import GHC.Utils.Logger
-import Control.Monad.IO.Class
-import GHC.Driver.Session
-import GHC.Types.SourceError
+
+import GHC.Driver.Config.Diagnostic
+import GHC.Driver.Errors
 import GHC.Driver.Errors.Types
-import GHC.Types.Error
+import GHC.Driver.Session
+
+import GHC.Iface.Errors.Ppr
 import GHC.Iface.Errors.Types
-import GHC.Tc.Errors.Types
+
 import GHC.Tc.Errors.Ppr
-import GHC.Iface.Errors.Ppr
-import GHC.Driver.Config.Diagnostic
-import GHC.Driver.Errors
-import GHC.Utils.Outputable
+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.
 printGhciException :: (HasLogger m, MonadIO m, HasDynFlags m) => SourceError -> m ()



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f936f1486533581027073040256693477766703b
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/20230503/dd3f892a/attachment-0001.html>


More information about the ghc-commits mailing list