diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index 3ac0da32ccca9ddbbbd22489bf8cf7cb0d16b7f3..861d5b98c86a343edfa62e5422cc86ac84eb1093 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -1058,7 +1058,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 0000000000000000000000000000000000000000..b02d8d0d87a0f10457438f388065ac9017cd2305
--- /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 db6cfb57ec7923cc5df293e3920e5bfdd84ea76e..95291331140c0f3530a9038eed0406de78f3a3f1 100644
--- a/testsuite/tests/patsyn/should_compile/all.T
+++ b/testsuite/tests/patsyn/should_compile/all.T
@@ -21,3 +21,4 @@ test('T8968-3', normal, compile, [''])
 test('ImpExp_Imp', [extra_clean(['ImpExp_Exp.hi', 'ImpExp_Exp.o'])], multimod_compile, ['ImpExp_Imp', '-v0'])
 test('T9857', normal, compile, [''])
 test('T9889', normal, compile, [''])
+test('T10747', normal, compile, [''])