[commit: ghc] master: Simplify rnLHsInstType (1c062b7)

git at git.haskell.org git at git.haskell.org
Mon Mar 5 14:45:41 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/1c062b794bf71a329f65813ce7b72fe2bd3935f0/ghc

>---------------------------------------------------------------

commit 1c062b794bf71a329f65813ce7b72fe2bd3935f0
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Mar 5 14:40:37 2018 +0000

    Simplify rnLHsInstType
    
    This patch is preparatory for the main fix for Trac #13324
    
    Here, we simplify rnLHsInstType so that it does not try
    to figure out the class name.  This turns out to have a good
    (rather than bad) effect on error messages, and it prepares
    the way for the main event.
    
    Plus, less code!


>---------------------------------------------------------------

1c062b794bf71a329f65813ce7b72fe2bd3935f0
 compiler/rename/RnTypes.hs                              | 17 +++--------------
 testsuite/tests/parser/should_fail/T3811c.stderr        |  5 ++++-
 .../should_fail/WildcardInInstanceHead.stderr           |  2 +-
 .../should_fail/WildcardInStandaloneDeriving.stderr     |  2 --
 testsuite/tests/rename/should_fail/T5513.stderr         |  4 +++-
 testsuite/tests/rename/should_fail/T5951.stderr         | 15 ++++++++++++++-
 6 files changed, 25 insertions(+), 20 deletions(-)

diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs
index 2305a04..b2dafb2 100644
--- a/compiler/rename/RnTypes.hs
+++ b/compiler/rename/RnTypes.hs
@@ -326,20 +326,8 @@ rnImplicitBndrs bind_free_tvs doc
 rnLHsInstType :: SDoc -> LHsSigType GhcPs -> RnM (LHsSigType GhcRn, FreeVars)
 -- Rename the type in an instance or standalone deriving decl
 -- The 'doc_str' is "an instance declaration" or "a VECTORISE pragma"
-rnLHsInstType doc_str inst_ty
-  | Just cls <- getLHsInstDeclClass_maybe inst_ty
-  , isTcOcc (rdrNameOcc (unLoc cls))
-         -- The guards check that the instance type looks like
-         --   blah => C ty1 .. tyn
-  = do { let full_doc = doc_str <+> text "for" <+> quotes (ppr cls)
-       ; rnHsSigType (GenericCtx full_doc) inst_ty }
-
-  | otherwise  -- The instance is malformed, but we'd still like
-               -- to make progress rather than failing outright, so
-               -- we report more errors.  So we rename it anyway.
-  = do { addErrAt (getLoc (hsSigType inst_ty)) $
-         text "Malformed instance:" <+> ppr inst_ty
-       ; rnHsSigType (GenericCtx doc_str) inst_ty }
+-- Do not try to decompose the inst_ty in case it is malformed
+rnLHsInstType doc inst_ty = rnHsSigType (GenericCtx doc) inst_ty
 
 mk_implicit_bndrs :: [Name]  -- implicitly bound
                   -> a           -- payload
@@ -351,6 +339,7 @@ mk_implicit_bndrs vars body fvs
          , hsib_closed = nameSetAll (not . isTyVarName) (vars `delFVs` fvs) }
 
 
+
 {- ******************************************************
 *                                                       *
            LHsType and HsType
diff --git a/testsuite/tests/parser/should_fail/T3811c.stderr b/testsuite/tests/parser/should_fail/T3811c.stderr
index 4a37116..dd21918 100644
--- a/testsuite/tests/parser/should_fail/T3811c.stderr
+++ b/testsuite/tests/parser/should_fail/T3811c.stderr
@@ -1,2 +1,5 @@
 
-T3811c.hs:6:10: Malformed instance: !Show D
+T3811c.hs:6:10: error:
+    • Unexpected strictness annotation: !Show
+      strictness annotation cannot appear nested inside a type
+    • In the instance declaration for ‘!Show D’
diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceHead.stderr b/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceHead.stderr
index 9090475..367e10a 100644
--- a/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceHead.stderr
+++ b/testsuite/tests/partial-sigs/should_fail/WildcardInInstanceHead.stderr
@@ -1,4 +1,4 @@
 
 WildcardInInstanceHead.hs:7:14: error:
     Wildcard ‘_’ not allowed
-      in an instance declaration for ‘Foo’
+      in an instance declaration
diff --git a/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr b/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr
index 8e98910..0609021 100644
--- a/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr
+++ b/testsuite/tests/partial-sigs/should_fail/WildcardInStandaloneDeriving.stderr
@@ -1,6 +1,4 @@
 
-WildcardInStandaloneDeriving.hs:4:19: error: Malformed instance: _
-
 WildcardInStandaloneDeriving.hs:4:19: error:
     Wildcard ‘_’ not allowed
       in a deriving declaration
diff --git a/testsuite/tests/rename/should_fail/T5513.stderr b/testsuite/tests/rename/should_fail/T5513.stderr
index 063f348..7e26622 100644
--- a/testsuite/tests/rename/should_fail/T5513.stderr
+++ b/testsuite/tests/rename/should_fail/T5513.stderr
@@ -1,2 +1,4 @@
 
-T5513.hs:4:19: Malformed instance: lowercase_name a
+T5513.hs:4:19: error:
+    • Instance head is not headed by a class
+    • In the stand-alone deriving instance for ‘lowercase_name a’
diff --git a/testsuite/tests/rename/should_fail/T5951.stderr b/testsuite/tests/rename/should_fail/T5951.stderr
index af0ee9d..8fda353 100644
--- a/testsuite/tests/rename/should_fail/T5951.stderr
+++ b/testsuite/tests/rename/should_fail/T5951.stderr
@@ -1,2 +1,15 @@
 
-T5951.hs:8:8: Malformed instance: A => B => C
+T5951.hs:8:8: error:
+    • Expecting one more argument to ‘A’
+      Expected a constraint, but ‘A’ has kind ‘* -> Constraint’
+    • In the instance declaration for ‘B => C’
+
+T5951.hs:9:8: error:
+    • Expecting one more argument to ‘B’
+      Expected a constraint, but ‘B’ has kind ‘* -> Constraint’
+    • In the instance declaration for ‘B => C’
+
+T5951.hs:10:8: error:
+    • Expecting one more argument to ‘C’
+      Expected a constraint, but ‘C’ has kind ‘* -> Constraint’
+    • In the instance declaration for ‘B => C’



More information about the ghc-commits mailing list