diff --git a/compiler/GHC/Parser.y b/compiler/GHC/Parser.y index bafed741be4e1c97f443cf2ef21952c8d1182c1a..7c0790da12528f0eee851716ab61f62a1ce624a8 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 0000000000000000000000000000000000000000..a796de7a392b86f2fd03320f0ec4b64014880c67 --- /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 1568a341ec8d348ac0bae1b75d5f43c52c27a727..8c7f0580629afd1913feb201cb151b6dabb6ff04 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 0000000000000000000000000000000000000000..dfd1389b808ec1864e2583e44c461e5d6b404e60 --- /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 0000000000000000000000000000000000000000..60887b079961d2a5062cecdaea28fde6ea5e15c0 --- /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 c6d691bed33d1df22782f65593c005ad9fc1bbfc..9d71019f3ebf99a48176d91b567a0f57f26e0d4b 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, [''])