From 0bf640b19d7a7ad0800152752a71c1dd4e6c696d Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Baldur=20Bl=C3=B6ndal?= <baldurpet@gmail.com>
Date: Sun, 3 May 2020 10:43:14 +0100
Subject: [PATCH] Don't require parentheses around via type (`-XDerivingVia').
 Fixes #18130".

---
 compiler/GHC/Parser.y                         |  4 ++--
 .../tests/parser/should_compile/T18130.hs     | 20 +++++++++++++++++++
 testsuite/tests/parser/should_compile/all.T   |  1 +
 .../tests/parser/should_fail/T18130Fail.hs    | 20 +++++++++++++++++++
 .../parser/should_fail/T18130Fail.stderr      |  4 ++++
 testsuite/tests/parser/should_fail/all.T      |  1 +
 6 files changed, 48 insertions(+), 2 deletions(-)
 create mode 100644 testsuite/tests/parser/should_compile/T18130.hs
 create mode 100644 testsuite/tests/parser/should_fail/T18130Fail.hs
 create mode 100644 testsuite/tests/parser/should_fail/T18130Fail.stderr

diff --git a/compiler/GHC/Parser.y b/compiler/GHC/Parser.y
index bafed741be4e..7c0790da1252 100644
--- a/compiler/GHC/Parser.y
+++ b/compiler/GHC/Parser.y
@@ -1209,8 +1209,8 @@ deriv_strategy_no_via :: { LDerivStrategy GhcPs }
                                        [mj AnnNewtype $1] }
 
 deriv_strategy_via :: { LDerivStrategy GhcPs }
-  : 'via' type              {% ams (sLL $1 $> (ViaStrategy (mkLHsSigType $2)))
-                                            [mj AnnVia $1] }
+  : 'via' ktype             {% ams (sLL $1 $> (ViaStrategy (mkLHsSigType $2)))
+                                       [mj AnnVia $1] }
 
 deriv_standalone_strategy :: { Maybe (LDerivStrategy GhcPs) }
   : 'stock'                     {% ajs (sL1 $1 StockStrategy)
diff --git a/testsuite/tests/parser/should_compile/T18130.hs b/testsuite/tests/parser/should_compile/T18130.hs
new file mode 100644
index 000000000000..a796de7a392b
--- /dev/null
+++ b/testsuite/tests/parser/should_compile/T18130.hs
@@ -0,0 +1,20 @@
+{-# Language DerivingVia #-}
+{-# Language KindSignatures #-}
+
+module T18130 where
+
+import Data.Functor.Classes
+import Data.Kind
+
+newtype Par a b = Par (a, b)
+  deriving Eq
+  via (a, b)
+   :: Type
+
+  deriving Eq1
+  via (,) a
+   :: Type -> Type
+
+  deriving Eq2
+  via (,)
+   :: Type -> Type -> Type
diff --git a/testsuite/tests/parser/should_compile/all.T b/testsuite/tests/parser/should_compile/all.T
index 1568a341ec8d..8c7f0580629a 100644
--- a/testsuite/tests/parser/should_compile/all.T
+++ b/testsuite/tests/parser/should_compile/all.T
@@ -166,3 +166,4 @@ test('proposal-229f',
      multimod_compile_and_run, ['proposal-229f.hs', ''])
 
 test('T15730a', normal, compile_and_run, [''])
+test('T18130', normal, compile, [''])
diff --git a/testsuite/tests/parser/should_fail/T18130Fail.hs b/testsuite/tests/parser/should_fail/T18130Fail.hs
new file mode 100644
index 000000000000..dfd1389b808e
--- /dev/null
+++ b/testsuite/tests/parser/should_fail/T18130Fail.hs
@@ -0,0 +1,20 @@
+{-# Language DerivingVia #-}
+{-# Language KindSignatures #-}
+
+module T18130Fail where
+
+import Data.Functor.Classes
+import Data.Kind
+
+newtype Par a b = Par (a, b)
+  deriving Eq
+  via (a, b)
+   :: Type -> Type
+
+  deriving Eq1
+  via (,) a
+   :: Type -> Type
+
+  deriving Eq2
+  via (,)
+   :: Type -> Type -> Type
diff --git a/testsuite/tests/parser/should_fail/T18130Fail.stderr b/testsuite/tests/parser/should_fail/T18130Fail.stderr
new file mode 100644
index 000000000000..60887b079961
--- /dev/null
+++ b/testsuite/tests/parser/should_fail/T18130Fail.stderr
@@ -0,0 +1,4 @@
+
+T18130Fail.hs:11:7: error:
+    • Expected kind ‘* -> *’, but ‘(a, b)’ has kind ‘*’
+    • In the newtype declaration for ‘Par’
diff --git a/testsuite/tests/parser/should_fail/all.T b/testsuite/tests/parser/should_fail/all.T
index c6d691bed33d..9d71019f3ebf 100644
--- a/testsuite/tests/parser/should_fail/all.T
+++ b/testsuite/tests/parser/should_fail/all.T
@@ -166,3 +166,4 @@ test('T17162', normal, compile_fail, [''])
 test('proposal-229c', normal, compile_fail, [''])
 test('T15730', normal, compile_fail, [''])
 test('T15730b', normal, compile_fail, [''])
+test('T18130Fail', normal, compile_fail, ['']) 
-- 
GitLab