[Git][ghc/ghc][master] Error messages: Improve Error messages for Data constructors in type signatures.

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sat Mar 9 08:40:10 UTC 2024



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


Commits:
edb9bf77 by Jade at 2024-03-09T03:39:38-05:00
Error messages: Improve Error messages for Data constructors in type signatures.

This patch improves the error messages from invalid type signatures by
trying to guess what the user did and suggesting an appropriate fix.

Partially fixes: #17879

- - - - -


14 changed files:

- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- testsuite/tests/module/mod98.stderr
- testsuite/tests/parser/should_fail/NoPatternSynonyms.stderr
- + testsuite/tests/parser/should_fail/T17879a.hs
- + testsuite/tests/parser/should_fail/T17879a.stderr
- + testsuite/tests/parser/should_fail/T17879b.hs
- + testsuite/tests/parser/should_fail/T17879b.stderr
- testsuite/tests/parser/should_fail/T3811.stderr
- testsuite/tests/parser/should_fail/all.T
- testsuite/tests/parser/should_fail/readFail031.stderr


Changes:

=====================================
compiler/GHC/Parser/Errors/Ppr.hs
=====================================
@@ -455,11 +455,17 @@ instance Diagnostic PsMessage where
     PsErrIllegalRoleName role _nearby
       -> mkSimpleDecorated $
            text "Illegal role name" <+> quotes (ppr role)
-    PsErrInvalidTypeSignature lhs
-      -> mkSimpleDecorated $
-           text "Invalid type signature:"
-           <+> ppr lhs
-           <+> text ":: ..."
+    PsErrInvalidTypeSignature reason lhs
+      -> mkSimpleDecorated $ case reason of
+           PsErrInvalidTypeSig_DataCon   -> text "Invalid data constructor" <+> quotes (ppr lhs) <+>
+                                            text "in type signature" <> colon $$
+                                            text "You can only define data constructors in data type declarations."
+           PsErrInvalidTypeSig_Qualified -> text "Invalid qualified name in type signature."
+           PsErrInvalidTypeSig_Other     -> text "Invalid type signature" <> colon $$
+                                            text "A type signature should be of form" <+>
+                                            placeHolder "variables" <+> dcolon <+> placeHolder "type" <>
+                                            dot
+            where placeHolder = angleBrackets . text
     PsErrUnexpectedTypeInDecl t what tc tparms equals_or_where
        -> mkSimpleDecorated $
             vcat [ text "Unexpected type" <+> quotes (ppr t)
@@ -779,15 +785,17 @@ instance Diagnostic PsMessage where
         sug_missingdo _                                     = Nothing
     PsErrParseRightOpSectionInPat{}               -> noHints
     PsErrIllegalRoleName _ nearby                 -> [SuggestRoles nearby]
-    PsErrInvalidTypeSignature lhs                 ->
+    PsErrInvalidTypeSignature reason lhs          ->
         if | foreign_RDR `looks_like` lhs
            -> [suggestExtension LangExt.ForeignFunctionInterface]
            | default_RDR `looks_like` lhs
            -> [suggestExtension LangExt.DefaultSignatures]
            | pattern_RDR `looks_like` lhs
            -> [suggestExtension LangExt.PatternSynonyms]
+           | PsErrInvalidTypeSig_Qualified <- reason
+           -> [SuggestTypeSignatureRemoveQualifier]
            | otherwise
-           -> [SuggestTypeSignatureForm]
+           -> []
       where
         -- A common error is to forget the ForeignFunctionInterface flag
         -- so check for that, and suggest.  cf #3805


=====================================
compiler/GHC/Parser/Errors/Types.hs
=====================================
@@ -389,7 +389,7 @@ data PsMessage
    | PsErrIllegalRoleName !FastString [Role]
 
    -- | Invalid type signature
-   | PsErrInvalidTypeSignature !(LHsExpr GhcPs)
+   | PsErrInvalidTypeSignature !PsInvalidTypeSignature !(LHsExpr GhcPs)
 
    -- | Unexpected type in declaration
    | PsErrUnexpectedTypeInDecl !(LHsType GhcPs)
@@ -480,6 +480,11 @@ data PsErrParseDetails
     -- ^ Did we parse a \"pattern\" keyword?
   }
 
+data PsInvalidTypeSignature
+  = PsErrInvalidTypeSig_Qualified
+  | PsErrInvalidTypeSig_DataCon
+  | PsErrInvalidTypeSig_Other
+
 -- | Is the parsed pattern recursive?
 data PatIsRecursive
   = YesPatIsRecursive
@@ -531,6 +536,7 @@ data NumUnderscoreReason
    | NumUnderscore_Float
    deriving (Show,Eq,Ord)
 
+
 data LexErrKind
    = LexErrKind_EOF        -- ^ End of input
    | LexErrKind_UTF8       -- ^ UTF-8 decoding error


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -1398,13 +1398,19 @@ checkPatBind _loc annsIn lhs (L _ grhss) mult = do
 
 
 checkValSigLhs :: LHsExpr GhcPs -> P (LocatedN RdrName)
-checkValSigLhs (L _ (HsVar _ lrdr@(L _ v)))
-  | isUnqual v
-  , not (isDataOcc (rdrNameOcc v))
-  = return lrdr
+checkValSigLhs lhs@(L l lhs_expr) =
+  case lhs_expr of
+    HsVar _ lrdr@(L _ v) -> check_var v lrdr
+    _                    -> make_err PsErrInvalidTypeSig_Other
+  where
+    check_var v lrdr
+      | not (isUnqual v) = make_err PsErrInvalidTypeSig_Qualified
+      | isDataOcc occ_n  = make_err PsErrInvalidTypeSig_DataCon
+      | otherwise        = pure lrdr
+      where occ_n = rdrNameOcc v
+    make_err reason = addFatalError $
+      mkPlainErrorMsgEnvelope (locA l) (PsErrInvalidTypeSignature reason lhs)
 
-checkValSigLhs lhs@(L l _)
-  = addFatalError $ mkPlainErrorMsgEnvelope (locA l) $ PsErrInvalidTypeSignature lhs
 
 checkDoAndIfThenElse
   :: (Outputable a, Outputable b, Outputable c)


=====================================
compiler/GHC/Types/Hint.hs
=====================================
@@ -54,6 +54,7 @@ data AvailableBindings
   | UnnamedBinding
   -- ^ An unknown binding (i.e. too complicated to turn into a 'Name')
 
+
 data LanguageExtensionHint
   = -- | Suggest to enable the input extension. This is the hint that
     -- GHC emits if this is not a \"known\" fix, i.e. this is GHC giving
@@ -297,13 +298,13 @@ data GhcHint
     -}
   | SuggestQualifyStarOperator
 
-    {-| Suggests that a type signature should have form <variable> :: <type>
+    {-| Suggests that for a type signature 'M.x :: ...' the qualifier should be omitted
         in order to be accepted by GHC.
 
         Triggered by: 'GHC.Parser.Errors.Types.PsErrInvalidTypeSignature'
-        Test case(s): parser/should_fail/T3811
+        Test case(s): module/mod98
     -}
-  | SuggestTypeSignatureForm
+  | SuggestTypeSignatureRemoveQualifier
 
     {-| Suggests to move an orphan instance (for a typeclass or a type or data
         family), or to newtype-wrap it.


=====================================
compiler/GHC/Types/Hint/Ppr.hs
=====================================
@@ -127,8 +127,8 @@ instance Outputable GhcHint where
       -> text "To use (or export) this operator in"
             <+> text "modules with StarIsType,"
          $$ text "    including the definition module, you must qualify it."
-    SuggestTypeSignatureForm
-      -> text "A type signature should be of form <variables> :: <type>"
+    SuggestTypeSignatureRemoveQualifier
+      -> text "Perhaps you meant to omit the qualifier"
     SuggestAddToHSigExportList _name mb_mod
       -> let header = text "Try adding it to the export list of"
          in case mb_mod of


=====================================
testsuite/tests/module/mod98.stderr
=====================================
@@ -1,5 +1,4 @@
 
 mod98.hs:3:1: error: [GHC-94426]
-    Invalid type signature: M.x :: ...
-    Suggested fix:
-      A type signature should be of form <variables> :: <type>
+    Invalid qualified name in type signature.
+    Suggested fix: Perhaps you meant to omit the qualifier


=====================================
testsuite/tests/parser/should_fail/NoPatternSynonyms.stderr
=====================================
@@ -1,4 +1,5 @@
 
 NoPatternSynonyms.hs:3:1: error: [GHC-94426]
-    Invalid type signature: pattern P :: ...
+    Invalid type signature:
+    A type signature should be of form <variables> :: <type>.
     Suggested fix: Perhaps you intended to use PatternSynonyms


=====================================
testsuite/tests/parser/should_fail/T17879a.hs
=====================================
@@ -0,0 +1,4 @@
+module Main where
+
+Foo :: ()
+Foo = ()


=====================================
testsuite/tests/parser/should_fail/T17879a.stderr
=====================================
@@ -0,0 +1,4 @@
+
+T17879a.hs:3:1: error: [GHC-94426]
+    Invalid data constructor ‘Foo’ in type signature:
+    You can only define data constructors in data type declarations.


=====================================
testsuite/tests/parser/should_fail/T17879b.hs
=====================================
@@ -0,0 +1,4 @@
+module Main where
+
+_ :: ()
+_ = ()


=====================================
testsuite/tests/parser/should_fail/T17879b.stderr
=====================================
@@ -0,0 +1,4 @@
+
+T17879b.hs:3:1: error: [GHC-94426]
+    Invalid type signature:
+    A type signature should be of form <variables> :: <type>.


=====================================
testsuite/tests/parser/should_fail/T3811.stderr
=====================================
@@ -1,5 +1,4 @@
 
 T3811.hs:4:1: error: [GHC-94426]
-    Invalid type signature: f x :: ...
-    Suggested fix:
-      A type signature should be of form <variables> :: <type>
+    Invalid type signature:
+    A type signature should be of form <variables> :: <type>.


=====================================
testsuite/tests/parser/should_fail/all.T
=====================================
@@ -225,3 +225,5 @@ test('ListTuplePunsFail2', extra_files(['ListTuplePunsFail2.hs']), ghci_script,
 test('ListTuplePunsFail3', extra_files(['ListTuplePunsFail3.hs']), ghci_script, ['ListTuplePunsFail3.script'])
 test('ListTuplePunsFail4', extra_files(['ListTuplePunsFail4.hs']), ghci_script, ['ListTuplePunsFail4.script'])
 test('ListTuplePunsFail5', extra_files(['ListTuplePunsFail5.hs']), ghci_script, ['ListTuplePunsFail5.script'])
+test('T17879a', normal, compile_fail, [''])
+test('T17879b', normal, compile_fail, [''])


=====================================
testsuite/tests/parser/should_fail/readFail031.stderr
=====================================
@@ -1,5 +1,4 @@
 
 readFail031.hs:4:3: error: [GHC-94426]
-    Invalid type signature: (:+) :: ...
-    Suggested fix:
-      A type signature should be of form <variables> :: <type>
+    Invalid data constructor ‘(:+)’ in type signature:
+    You can only define data constructors in data type declarations.



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

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


More information about the ghc-commits mailing list