[commit: ghc] master: Disallow empty where bindings in pattern synonym declarations. (8d95412)

git at git.haskell.org git at git.haskell.org
Sun Dec 20 23:47:44 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/8d954125604e4585167306c4f1d4807275be0a61/ghc

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

commit 8d954125604e4585167306c4f1d4807275be0a61
Author: Matthew Pickering <matthewtpickering at gmail.com>
Date:   Sun Dec 20 23:45:28 2015 +0000

    Disallow empty where bindings in pattern synonym declarations.
    
    Reviewers: austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D1665
    
    GHC Trac Issues: #10426


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

8d954125604e4585167306c4f1d4807275be0a61
 compiler/parser/RdrHsSyn.hs                                      | 8 +++++++-
 testsuite/tests/patsyn/should_compile/all.T                      | 1 -
 testsuite/tests/patsyn/{should_compile => should_fail}/T10426.hs | 0
 testsuite/tests/patsyn/should_fail/T10426.stderr                 | 4 ++++
 testsuite/tests/patsyn/should_fail/all.T                         | 1 +
 5 files changed, 12 insertions(+), 2 deletions(-)

diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs
index cc8a8ec..7e61172 100644
--- a/compiler/parser/RdrHsSyn.hs
+++ b/compiler/parser/RdrHsSyn.hs
@@ -465,8 +465,9 @@ recordPatSynErr loc pat =
 mkPatSynMatchGroup :: Located RdrName
                    -> Located (OrdList (LHsDecl RdrName))
                    -> P (MatchGroup RdrName (LHsExpr RdrName))
-mkPatSynMatchGroup (L _ patsyn_name) (L _ decls) =
+mkPatSynMatchGroup (L loc patsyn_name) (L _ decls) =
     do { matches <- mapM fromDecl (fromOL decls)
+       ; when (length matches /= 1) (wrongNumberErr loc)
        ; return $ mkMatchGroup FromSource matches }
   where
     fromDecl (L loc decl@(ValD (PatBind pat@(L _ (ConPatIn (L _ name) details)) rhs _ _ _))) =
@@ -490,6 +491,11 @@ mkPatSynMatchGroup (L _ patsyn_name) (L _ decls) =
         text "pattern synonym 'where' clause must bind the pattern synonym's name" <+>
         quotes (ppr patsyn_name) $$ ppr decl
 
+    wrongNumberErr loc =
+      parseErrorSDoc loc $
+      text "pattern synonym 'where' clause can not be empty." $$
+      text "In the pattern synonym declaration for: " <+> ppr (patsyn_name)
+
 mkConDeclH98 :: Located RdrName -> Maybe [LHsTyVarBndr RdrName]
                 -> LHsContext RdrName -> HsConDeclDetails RdrName
                 -> ConDecl RdrName
diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T
index 4452711..7ab5ac7 100644
--- a/testsuite/tests/patsyn/should_compile/all.T
+++ b/testsuite/tests/patsyn/should_compile/all.T
@@ -24,7 +24,6 @@ test('T9889', normal, compile, [''])
 test('T9867', normal, compile, [''])
 test('T9975a', normal, compile_fail, [''])
 test('T9975b', normal, compile, [''])
-test('T10426', [expect_broken(10426)], compile, [''])
 test('T10747', normal, compile, [''])
 test('T10997', [extra_clean(['T10997a.hi', 'T10997a.o'])], multimod_compile, ['T10997', '-v0'])
 test('T10997_1', [extra_clean(['T10997_1a.hi', 'T10997_1a.o'])], multimod_compile, ['T10997_1', '-v0'])
diff --git a/testsuite/tests/patsyn/should_compile/T10426.hs b/testsuite/tests/patsyn/should_fail/T10426.hs
similarity index 100%
rename from testsuite/tests/patsyn/should_compile/T10426.hs
rename to testsuite/tests/patsyn/should_fail/T10426.hs
diff --git a/testsuite/tests/patsyn/should_fail/T10426.stderr b/testsuite/tests/patsyn/should_fail/T10426.stderr
new file mode 100644
index 0000000..9b03e11
--- /dev/null
+++ b/testsuite/tests/patsyn/should_fail/T10426.stderr
@@ -0,0 +1,4 @@
+
+T10426.hs:3:9: error:
+    pattern synonym 'where' clause can not be empty.
+    In the pattern synonym declaration for:  Id
diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T
index 26c68ca..6ef64ae 100644
--- a/testsuite/tests/patsyn/should_fail/all.T
+++ b/testsuite/tests/patsyn/should_fail/all.T
@@ -26,3 +26,4 @@ test('export-super-class-fail', expect_broken(10653), compile_fail, [''])
 test('export-type-synonym', normal, compile_fail, [''])
 test('export-ps-rec-sel', normal, compile_fail, [''])
 test('T11053', normal, compile, ['-fwarn-missing-pat-syn-sigs'])
+test('T10426', normal, compile_fail, [''])



More information about the ghc-commits mailing list