[commit: ghc] master: Allow non-operator infix pattern synonyms (69a6e42)

git at git.haskell.org git at git.haskell.org
Thu Oct 8 01:36:03 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/69a6e4258786894578ffed2a1d907a74c52d779b/ghc

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

commit 69a6e4258786894578ffed2a1d907a74c52d779b
Author: Matthew Pickering <matthewtpickering at gmail.com>
Date:   Wed Oct 7 20:36:38 2015 -0500

    Allow non-operator infix pattern synonyms
    
    For example
    
    ```
    pattern head `Cons` tail = head : tail
    ```
    
    Reviewed By: goldfire, austin
    
    Differential Revision: https://phabricator.haskell.org/D1295
    
    GHC Trac Issues: #10747


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

69a6e4258786894578ffed2a1d907a74c52d779b
 compiler/parser/Parser.y                        | 2 +-
 testsuite/tests/patsyn/should_compile/T10747.hs | 5 +++++
 testsuite/tests/patsyn/should_compile/all.T     | 1 +
 3 files changed, 7 insertions(+), 1 deletion(-)

diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index 7e7f579..7079a94 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -1148,7 +1148,7 @@ pattern_synonym_decl :: { LHsDecl RdrName }
 
 pattern_synonym_lhs :: { (Located RdrName, HsPatSynDetails (Located RdrName)) }
         : con vars0 { ($1, PrefixPatSyn $2) }
-        | varid consym varid { ($2, InfixPatSyn $1 $3) }
+        | varid conop varid { ($2, InfixPatSyn $1 $3) }
 
 vars0 :: { [Located RdrName] }
         : {- empty -}                 { [] }
diff --git a/testsuite/tests/patsyn/should_compile/T10747.hs b/testsuite/tests/patsyn/should_compile/T10747.hs
new file mode 100644
index 0000000..b02d8d0
--- /dev/null
+++ b/testsuite/tests/patsyn/should_compile/T10747.hs
@@ -0,0 +1,5 @@
+{-# LANGUAGE PatternSynonyms #-}
+
+module T10747 where
+
+pattern head `Cons` tail = head : tail
diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T
index b0776ac..5e86a99 100644
--- a/testsuite/tests/patsyn/should_compile/all.T
+++ b/testsuite/tests/patsyn/should_compile/all.T
@@ -24,3 +24,4 @@ test('T9889', normal, compile, [''])
 test('T9867', normal, compile, [''])
 test('T9975a', normal, compile_fail, [''])
 test('T9975b', normal, compile, [''])
+test('T10747', normal, compile, [''])



More information about the ghc-commits mailing list