[Git][ghc/ghc][master] Don't require parentheses around via type (`-XDerivingVia'). Fixes #18130".
Marge Bot
gitlab at gitlab.haskell.org
Mon May 4 05:57:47 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
0bf640b1 by Baldur Blöndal at 2020-05-04T01:57:36-04:00
Don't require parentheses around via type (`-XDerivingVia'). Fixes #18130".
- - - - -
6 changed files:
- compiler/GHC/Parser.y
- + testsuite/tests/parser/should_compile/T18130.hs
- testsuite/tests/parser/should_compile/all.T
- + testsuite/tests/parser/should_fail/T18130Fail.hs
- + testsuite/tests/parser/should_fail/T18130Fail.stderr
- testsuite/tests/parser/should_fail/all.T
Changes:
=====================================
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)
=====================================
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
=====================================
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, [''])
=====================================
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
=====================================
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’
=====================================
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, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0bf640b19d7a7ad0800152752a71c1dd4e6c696d
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0bf640b19d7a7ad0800152752a71c1dd4e6c696d
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200504/2c049457/attachment-0001.html>
More information about the ghc-commits
mailing list