[Git][ghc/ghc][master] 2 commits: Use printGhciException in run{Stmt, Decls}

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Sep 12 08:32:19 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
f96fe681 by sheaf at 2023-09-12T04:31:44-04:00
Use printGhciException in run{Stmt, Decls}

When evaluating statements in GHCi, we need to use printGhciException
instead of the printException function that GHC provides in order to
get the appropriate error messages that are customised for ghci use.

- - - - -
d09b932b by psilospore at 2023-09-12T04:31:44-04:00
T23686: Suggest how to enable Language Extension when in ghci
Fixes #23686

- - - - -


21 changed files:

- compiler/GHC/Tc/Errors/Ppr.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Monad.hs
- testsuite/tests/gadt/gadtSyntaxFail001.stderr
- testsuite/tests/gadt/gadtSyntaxFail002.stderr
- testsuite/tests/gadt/gadtSyntaxFail003.stderr
- testsuite/tests/ghci/prog006/prog006.stderr
- testsuite/tests/ghci/prog011/prog011.stderr
- testsuite/tests/ghci/scripts/T13202a.stderr
- testsuite/tests/ghci/scripts/T14969.stderr
- + testsuite/tests/ghci/scripts/T23686.script
- + testsuite/tests/ghci/scripts/T23686.stderr
- + testsuite/tests/ghci/scripts/T23686A.hs
- + testsuite/tests/ghci/scripts/T23686B.hs
- testsuite/tests/ghci/scripts/T9293.stderr
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/ghci/scripts/ghci057.stderr
- testsuite/tests/ghci/should_run/T15806.stderr
- testsuite/tests/rename/should_fail/rnfail053.stderr
- testsuite/tests/safeHaskell/ghci/p16.stderr
- testsuite/tests/typecheck/should_fail/T12083a.stderr


Changes:

=====================================
compiler/GHC/Tc/Errors/Ppr.hs
=====================================
@@ -3015,8 +3015,7 @@ instance Diagnostic TcRnMessage where
     TcRnGADTsDisabled{}
       -> [suggestExtension LangExt.GADTs]
     TcRnExistentialQuantificationDisabled{}
-      -> [suggestExtension LangExt.ExistentialQuantification,
-          suggestExtension LangExt.GADTs]
+      -> [suggestAnyExtension [LangExt.ExistentialQuantification, LangExt.GADTs]]
     TcRnGADTDataContext{}
       -> noHints
     TcRnMultipleConForNewtype{}


=====================================
ghc/GHCi/UI/Exception.hs
=====================================
@@ -1,6 +1,7 @@
 {-# LANGUAGE TypeApplications #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE LambdaCase #-}
 module GHCi.UI.Exception(printGhciException, GHCiMessage(..)) where
 
 import GHC.Prelude
@@ -13,6 +14,8 @@ import GHC.Driver.Session
 import GHC.Iface.Errors.Ppr
 import GHC.Iface.Errors.Types
 
+import qualified GHC.LanguageExtensions as LangExt
+
 import GHC.Tc.Errors.Ppr
 import GHC.Tc.Errors.Types
 
@@ -47,10 +50,44 @@ instance Diagnostic GHCiMessage where
 
   diagnosticReason (GHCiMessage msg) = diagnosticReason msg
 
-  diagnosticHints (GHCiMessage msg) = diagnosticHints msg
+  diagnosticHints (GHCiMessage msg) = ghciDiagnosticHints msg
 
   diagnosticCode (GHCiMessage msg)  = diagnosticCode msg
 
+
+-- | Modifications to hint messages which we want to display in GHCi.
+ghciDiagnosticHints :: GhcMessage -> [GhcHint]
+ghciDiagnosticHints msg = map modifyHintForGHCi (diagnosticHints msg)
+  where
+    modifyHintForGHCi :: GhcHint -> GhcHint
+    modifyHintForGHCi = \case
+      SuggestExtension extHint -> SuggestExtension $ modifyExtHintForGHCi extHint
+      hint -> hint
+    modifyExtHintForGHCi :: LanguageExtensionHint -> LanguageExtensionHint
+    modifyExtHintForGHCi = \case
+      SuggestSingleExtension    doc ext  -> SuggestSingleExtension    (suggestSetExt [ext] doc False) ext
+      SuggestExtensionInOrderTo doc ext  -> SuggestExtensionInOrderTo (suggestSetExt [ext] doc False) ext
+      SuggestAnyExtension       doc exts -> SuggestAnyExtension       (suggestSetExt exts  doc True ) exts
+      SuggestExtensions         doc exts -> SuggestExtensions         (suggestSetExt exts  doc False) exts
+    -- Suggest enabling extension with :set -X<ext>
+    -- SuggestAnyExtension will be on multiple lines so the user can select which to enable without editing
+    suggestSetExt :: [LangExt.Extension] -> SDoc -> Bool -> SDoc
+    suggestSetExt exts doc enable_any = doc $$ hang header 2 exts_cmds
+      where
+        header = text "You may enable" <+> which <+> text "language extension" <> plural exts <+> text "in GHCi with:"
+        which
+          | [ _ext ] <- exts
+          = text "this"
+          | otherwise
+          = if enable_any
+            then text "these"
+            else text "all of these"
+        exts_cmds
+          | enable_any
+          = vcat $ map (\ext -> text ":set -X" <> ppr ext) exts
+          | otherwise
+          = text ":set" <> hcat (map (\ext -> text " -X" <> ppr ext) exts)
+
 -- Modifications to error messages which we want to display in GHCi
 ghciDiagnosticMessage :: GhcMessageOpts -> GhcMessage -> DecoratedSDoc
 ghciDiagnosticMessage ghc_opts msg =


=====================================
ghc/GHCi/UI/Monad.hs
=====================================
@@ -56,6 +56,7 @@ import GHC.Builtin.Names (gHC_GHCI_HELPERS)
 import GHC.Runtime.Interpreter
 import GHC.Runtime.Context
 import GHCi.RemoteTypes
+import GHCi.UI.Exception (printGhciException)
 import GHC.Hs (ImportDecl, GhcPs, GhciLStmt, LHsDecl)
 import GHC.Hs.Utils
 import GHC.Utils.Misc
@@ -399,7 +400,7 @@ runStmt
   => GhciLStmt GhcPs -> String -> GHC.SingleStep -> m (Maybe GHC.ExecResult)
 runStmt stmt stmt_text step = do
   st <- getGHCiState
-  GHC.handleSourceError (\e -> do GHC.printException e; return Nothing) $ do
+  GHC.handleSourceError (\e -> do printGhciException e; return Nothing) $ do
     let opts = GHC.execOptions
                   { GHC.execSourceFile = progname st
                   , GHC.execLineNumber = line_number st
@@ -415,7 +416,7 @@ runDecls decls = do
     withProgName (progname st) $
     withArgs (args st) $
       reflectGHCi x $ do
-        GHC.handleSourceError (\e -> do GHC.printException e;
+        GHC.handleSourceError (\e -> do printGhciException e
                                         return Nothing) $ do
           r <- GHC.runDeclsWithLocation (progname st) (line_number st) decls
           return (Just r)
@@ -428,7 +429,7 @@ runDecls' decls = do
     withArgs (args st) $
     reflectGHCi x $
       GHC.handleSourceError
-        (\e -> do GHC.printException e;
+        (\e -> do printGhciException e
                   return Nothing)
         (Just <$> GHC.runParsedDecls decls)
 


=====================================
testsuite/tests/gadt/gadtSyntaxFail001.stderr
=====================================
@@ -4,6 +4,5 @@ gadtSyntaxFail001.hs:9:5: error: [GHC-25709]
         C2 :: forall a. a -> Char -> Foo a Int
     • In the definition of data constructor ‘C2’
       In the data type declaration for ‘Foo’
-    Suggested fixes:
-       Perhaps you intended to use ExistentialQuantification
-       Perhaps you intended to use GADTs
+    Suggested fix:
+      Enable any of the following extensions: ExistentialQuantification, GADTs


=====================================
testsuite/tests/gadt/gadtSyntaxFail002.stderr
=====================================
@@ -4,6 +4,5 @@ gadtSyntaxFail002.hs:9:5: error: [GHC-25709]
         C2 :: forall a. a -> Char -> Foo a a
     • In the definition of data constructor ‘C2’
       In the data type declaration for ‘Foo’
-    Suggested fixes:
-       Perhaps you intended to use ExistentialQuantification
-       Perhaps you intended to use GADTs
+    Suggested fix:
+      Enable any of the following extensions: ExistentialQuantification, GADTs


=====================================
testsuite/tests/gadt/gadtSyntaxFail003.stderr
=====================================
@@ -4,6 +4,5 @@ gadtSyntaxFail003.hs:8:5: error: [GHC-25709]
         C1 :: forall a c b. a -> Int -> c -> Foo b a
     • In the definition of data constructor ‘C1’
       In the data type declaration for ‘Foo’
-    Suggested fixes:
-       Perhaps you intended to use ExistentialQuantification
-       Perhaps you intended to use GADTs
+    Suggested fix:
+      Enable any of the following extensions: ExistentialQuantification, GADTs


=====================================
testsuite/tests/ghci/prog006/prog006.stderr
=====================================
@@ -4,6 +4,8 @@ Boot.hs:6:13: error: [GHC-25709]
         D :: forall n. Class n => n -> Data
     • In the definition of data constructor ‘D’
       In the data type declaration for ‘Data’
-    Suggested fixes:
-       Perhaps you intended to use ExistentialQuantification
-       Perhaps you intended to use GADTs
+    Suggested fix:
+      Enable any of the following extensions: ExistentialQuantification, GADTs
+      You may enable these language extensions in GHCi with:
+        :set -XExistentialQuantification
+        :set -XGADTs


=====================================
testsuite/tests/ghci/prog011/prog011.stderr
=====================================
@@ -1,4 +1,7 @@
 
-prog011.hx:14:22: [GHC-82311] error:
+prog011.hx:14:22: error: [GHC-82311]
     Empty 'do' block
-    Suggested fix: Perhaps you intended to use NondecreasingIndentation
+    Suggested fix:
+      Perhaps you intended to use NondecreasingIndentation
+      You may enable this language extension in GHCi with:
+        :set -XNondecreasingIndentation


=====================================
testsuite/tests/ghci/scripts/T13202a.stderr
=====================================
@@ -3,4 +3,7 @@
     • Non type-variable argument in the constraint: HasField "name" r a
     • When checking the inferred type
         foo :: forall {r} {a}. HasField "name" r a => r -> a
-    Suggested fix: Perhaps you intended to use FlexibleContexts
+    Suggested fix:
+      Perhaps you intended to use FlexibleContexts
+      You may enable this language extension in GHCi with:
+        :set -XFlexibleContexts


=====================================
testsuite/tests/ghci/scripts/T14969.stderr
=====================================
@@ -4,4 +4,7 @@
         in the constraint: Num (t2 -> t1 -> t3)
     • When checking the inferred type
         it :: forall {t1} {t2} {t3}. (Num t1, Num (t2 -> t1 -> t3)) => t3
-    Suggested fix: Perhaps you intended to use FlexibleContexts
+    Suggested fix:
+      Perhaps you intended to use FlexibleContexts
+      You may enable this language extension in GHCi with:
+        :set -XFlexibleContexts


=====================================
testsuite/tests/ghci/scripts/T23686.script
=====================================
@@ -0,0 +1,2 @@
+:load T23686A
+:load T23686B


=====================================
testsuite/tests/ghci/scripts/T23686.stderr
=====================================
@@ -0,0 +1,18 @@
+
+T23686A.hs:4:1: error: [GHC-39191]
+    • Illegal family declaration for ‘GMap’
+    • In the data family declaration for ‘GMap’
+    Suggested fix:
+      Perhaps you intended to use TypeFamilies
+      You may enable this language extension in GHCi with:
+        :set -XTypeFamilies
+
+T23686B.hs:5:5: error: [GHC-62558]
+    • Syntax error on [| \ left right x -> left (right x) |]
+    • In the Template Haskell quotation
+        [| \ left right x -> left (right x) |]
+    Suggested fix:
+      Enable any of the following extensions: TemplateHaskell, TemplateHaskellQuotes
+      You may enable these language extensions in GHCi with:
+        :set -XTemplateHaskell
+        :set -XTemplateHaskellQuotes


=====================================
testsuite/tests/ghci/scripts/T23686A.hs
=====================================
@@ -0,0 +1,4 @@
+module T23686A where
+
+-- Tests that a single extension is suggested
+data family GMap k :: * -> *
\ No newline at end of file


=====================================
testsuite/tests/ghci/scripts/T23686B.hs
=====================================
@@ -0,0 +1,5 @@
+module T23686B where
+
+-- Tests that at least 1 extension is recommended from a list of extensions
+-- It should suggest on multiple lines so a user doesn't need to edit the command
+x = [|\left right x -> left (right x)|]
\ No newline at end of file


=====================================
testsuite/tests/ghci/scripts/T9293.stderr
=====================================
@@ -2,31 +2,39 @@
 <interactive>:4:1: error: [GHC-23894]
     • Illegal generalised algebraic data declaration for ‘T’
     • In the data declaration for ‘T’
-    Suggested fix: Perhaps you intended to use GADTs
+    Suggested fix:
+      Perhaps you intended to use GADTs
+      You may enable this language extension in GHCi with: :set -XGADTs
 
-<interactive>:4:16: [GHC-25709]
-     Data constructor ‘C’ has existential type variables, a context, or a specialised result type
+<interactive>:4:16: error: [GHC-25709]
+    • Data constructor ‘C’ has existential type variables, a context, or a specialised result type
         C :: T Int
-     In the definition of data constructor ‘C’
+    • In the definition of data constructor ‘C’
       In the data type declaration for ‘T’
-    Suggested fixes:
-       Perhaps you intended to use ExistentialQuantification
-       Perhaps you intended to use GADTs
+    Suggested fix:
+      Enable any of the following extensions: ExistentialQuantification, GADTs
+      You may enable these language extensions in GHCi with:
+        :set -XExistentialQuantification
+        :set -XGADTs
 
 ghci057.hs:4:3: error: [GHC-25709]
     • Data constructor ‘C’ has existential type variables, a context, or a specialised result type
         C :: T Int
     • In the definition of data constructor ‘C’
       In the data type declaration for ‘T’
-    Suggested fixes:
-       Perhaps you intended to use ExistentialQuantification
-       Perhaps you intended to use GADTs
+    Suggested fix:
+      Enable any of the following extensions: ExistentialQuantification, GADTs
+      You may enable these language extensions in GHCi with:
+        :set -XExistentialQuantification
+        :set -XGADTs
 
 ghci057.hs:4:3: error: [GHC-25709]
     • Data constructor ‘C’ has existential type variables, a context, or a specialised result type
         C :: T Int
     • In the definition of data constructor ‘C’
       In the data type declaration for ‘T’
-    Suggested fixes:
-       Perhaps you intended to use ExistentialQuantification
-       Perhaps you intended to use GADTs
+    Suggested fix:
+      Enable any of the following extensions: ExistentialQuantification, GADTs
+      You may enable these language extensions in GHCi with:
+        :set -XExistentialQuantification
+        :set -XGADTs


=====================================
testsuite/tests/ghci/scripts/all.T
=====================================
@@ -380,3 +380,4 @@ test('T22817', normal, ghci_script, ['T22817.script'])
 test('T22908', normal, ghci_script, ['T22908.script'])
 test('T23062', normal, ghci_script, ['T23062.script'])
 test('T16468', normal, ghci_script, ['T16468.script'])
+test('T23686', normal, ghci_script, ['T23686.script'])
\ No newline at end of file


=====================================
testsuite/tests/ghci/scripts/ghci057.stderr
=====================================
@@ -2,31 +2,39 @@
 <interactive>:4:1: error: [GHC-23894]
     • Illegal generalised algebraic data declaration for ‘T’
     • In the data declaration for ‘T’
-    Suggested fix: Perhaps you intended to use GADTs
+    Suggested fix:
+      Perhaps you intended to use GADTs
+      You may enable this language extension in GHCi with: :set -XGADTs
 
-<interactive>:4:16: [GHC-25709]
-     Data constructor ‘C’ has existential type variables, a context, or a specialised result type
+<interactive>:4:16: error: [GHC-25709]
+    • Data constructor ‘C’ has existential type variables, a context, or a specialised result type
         C :: T Int
-     In the definition of data constructor ‘C’
+    • In the definition of data constructor ‘C’
       In the data type declaration for ‘T’
-    Suggested fixes:
-       Perhaps you intended to use ExistentialQuantification
-       Perhaps you intended to use GADTs
+    Suggested fix:
+      Enable any of the following extensions: ExistentialQuantification, GADTs
+      You may enable these language extensions in GHCi with:
+        :set -XExistentialQuantification
+        :set -XGADTs
 
 ghci057.hs:4:3: error: [GHC-25709]
     • Data constructor ‘C’ has existential type variables, a context, or a specialised result type
         C :: T Int
     • In the definition of data constructor ‘C’
       In the data type declaration for ‘T’
-    Suggested fixes:
-       Perhaps you intended to use ExistentialQuantification
-       Perhaps you intended to use GADTs
+    Suggested fix:
+      Enable any of the following extensions: ExistentialQuantification, GADTs
+      You may enable these language extensions in GHCi with:
+        :set -XExistentialQuantification
+        :set -XGADTs
 
 ghci057.hs:4:3: error: [GHC-25709]
     • Data constructor ‘C’ has existential type variables, a context, or a specialised result type
         C :: T Int
     • In the definition of data constructor ‘C’
       In the data type declaration for ‘T’
-    Suggested fixes:
-       Perhaps you intended to use ExistentialQuantification
-       Perhaps you intended to use GADTs
+    Suggested fix:
+      Enable any of the following extensions: ExistentialQuantification, GADTs
+      You may enable these language extensions in GHCi with:
+        :set -XExistentialQuantification
+        :set -XGADTs


=====================================
testsuite/tests/ghci/should_run/T15806.stderr
=====================================
@@ -1,4 +1,7 @@
 
 <interactive>:1:1: error: [GHC-91510]
     Illegal polymorphic type: forall a. a -> a
-    Suggested fix: Perhaps you intended to use ImpredicativeTypes
+    Suggested fix:
+      Perhaps you intended to use ImpredicativeTypes
+      You may enable this language extension in GHCi with:
+        :set -XImpredicativeTypes


=====================================
testsuite/tests/rename/should_fail/rnfail053.stderr
=====================================
@@ -4,6 +4,5 @@ rnfail053.hs:6:10: error: [GHC-25709]
         MkT :: forall a. a -> T
     • In the definition of data constructor ‘MkT’
       In the data type declaration for ‘T’
-    Suggested fixes:
-       Perhaps you intended to use ExistentialQuantification
-       Perhaps you intended to use GADTs
+    Suggested fix:
+      Enable any of the following extensions: ExistentialQuantification, GADTs


=====================================
testsuite/tests/safeHaskell/ghci/p16.stderr
=====================================
@@ -9,6 +9,8 @@
     Suggested fix:
       Perhaps you intended to use GeneralizedNewtypeDeriving
       for GHC's newtype-deriving extension
+      You may enable this language extension in GHCi with:
+        :set -XGeneralizedNewtypeDeriving
 
 <interactive>:19:9: error: [GHC-88464]
     Data constructor not in scope: T2 :: T -> t


=====================================
testsuite/tests/typecheck/should_fail/T12083a.stderr
=====================================
@@ -9,6 +9,5 @@ T12083a.hs:10:26: error: [GHC-25709]
         ExistentiallyLost :: forall u. TC u => u -> ExistentiallyLost
     • In the definition of data constructor ‘ExistentiallyLost’
       In the data type declaration for ‘ExistentiallyLost’
-    Suggested fixes:
-       Perhaps you intended to use ExistentialQuantification
-       Perhaps you intended to use GADTs
+    Suggested fix:
+      Enable any of the following extensions: ExistentialQuantification, GADTs



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2b07bf2e8bcb24520fe78b469c3550b9f4099526...d09b932bc2e58f1a4e2137bda4794b65118f52b5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2b07bf2e8bcb24520fe78b469c3550b9f4099526...d09b932bc2e58f1a4e2137bda4794b65118f52b5
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/20230912/71509f63/attachment-0001.html>


More information about the ghc-commits mailing list