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

Jade (@Jade) gitlab at gitlab.haskell.org
Thu Feb 29 09:50:01 UTC 2024



Jade pushed to branch wip/T17879 at Glasgow Haskell Compiler / GHC


Commits:
c17d5607 by Jade at 2024-02-29T10:53:59+01: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

- - - - -


12 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/T17879.hs
- + testsuite/tests/parser/should_fail/T17879.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_Application -> text "Invalid application in type signature"
+           PsErrInvalidTypeSig_Other       -> text "Invalid type signature:" $$
+                                         text "A type signature should be of form" <+>
+                                         placeHolder "variables" <+> dcolon <+> placeHolder "type"
+            where placeHolder = angleBrackets . text
     PsErrUnexpectedTypeInDecl t what tc tparms equals_or_where
        -> mkSimpleDecorated $
             vcat [ text "Unexpected type" <+> quotes (ppr t)
@@ -760,15 +766,19 @@ 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_Application <- reason
+           -> [SuggestTypeSignatureForm InvalidTypeSig_Application]
+           | PsErrInvalidTypeSig_Qualified <- reason
+           -> [SuggestTypeSignatureForm InvalidTypeSig_Qualified]
            | 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)
@@ -478,6 +478,12 @@ data PsErrParseDetails
     -- ^ Did we parse a \"pattern\" keyword?
   }
 
+data PsInvalidTypeSignature
+  = PsErrInvalidTypeSig_Qualified
+  | PsErrInvalidTypeSig_DataCon
+  | PsErrInvalidTypeSig_Application
+  | PsErrInvalidTypeSig_Other
+
 -- | Is the parsed pattern recursive?
 data PatIsRecursive
   = YesPatIsRecursive
@@ -524,6 +530,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
=====================================
@@ -1368,13 +1368,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)
+  | HsVar _ lrdr@(L _ v) <- lhs_expr = check_var v lrdr
+  | HsApp _ _ _          <- lhs_expr = make_err PsErrInvalidTypeSig_Application
+  | otherwise                        = 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
=====================================
@@ -10,6 +10,7 @@ module GHC.Types.Hint (
   , SimilarName(..)
   , StarIsType(..)
   , UntickedPromotedThing(..)
+  , InvalidTypeSignatureSuggestion(..)
   , pprUntickedConstructor, isBareSymbol
   , suggestExtension
   , suggestExtensionWithInfo
@@ -54,6 +55,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
@@ -303,7 +305,7 @@ data GhcHint
         Triggered by: 'GHC.Parser.Errors.Types.PsErrInvalidTypeSignature'
         Test case(s): parser/should_fail/T3811
     -}
-  | SuggestTypeSignatureForm
+  | SuggestTypeSignatureForm InvalidTypeSignatureSuggestion
 
     {-| Suggests to move an orphan instance (for a typeclass or a type or data
         family), or to newtype-wrap it.
@@ -526,6 +528,13 @@ data UntickedPromotedThing
   = UntickedConstructor LexicalFixity Name
   | UntickedExplicitList
 
+-- | What kind of thing do we want to suggest in an invalid type signature
+data InvalidTypeSignatureSuggestion
+  -- | M.x :: ...    => Remove the qualifier
+  = InvalidTypeSig_Qualified
+  -- | f x :: ...    => Remove the application
+  | InvalidTypeSig_Application
+
 pprUntickedConstructor :: LexicalFixity -> Name -> SDoc
 pprUntickedConstructor fixity nm =
   case fixity of


=====================================
compiler/GHC/Types/Hint/Ppr.hs
=====================================
@@ -127,8 +127,10 @@ 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>"
+    SuggestTypeSignatureForm reason
+      -> case reason of
+           InvalidTypeSig_Qualified   -> text "Perhaps you meant to omit the qualifier"
+           InvalidTypeSig_Application -> text "Remove the application on the left hand side"
     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,4 @@
 
 NoPatternSynonyms.hs:3:1: error: [GHC-94426]
-    Invalid type signature: pattern P :: ...
+    Invalid application in type signature
     Suggested fix: Perhaps you intended to use PatternSynonyms


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


=====================================
testsuite/tests/parser/should_fail/T17879.stderr
=====================================
@@ -0,0 +1,4 @@
+
+T17879.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/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 application in type signature
+    Suggested fix: Remove the application on the left hand side


=====================================
testsuite/tests/parser/should_fail/all.T
=====================================
@@ -220,3 +220,4 @@ test('T20609b', normal, compile_fail, [''])
 test('T20609c', normal, compile_fail, [''])
 test('T20609d', normal, compile_fail, [''])
 test('SuffixAtFail', normal, compile_fail, ['-fdiagnostics-show-caret'])
+test('T17879', 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/c17d5607bd62c443033b05e071374e3fd6280397

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


More information about the ghc-commits mailing list