
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 2e0c07ab by Simon Peyton Jones at 2025-04-24T00:29:43-04:00 Test for #23298 - - - - - 3 changed files: - + testsuite/tests/gadt/T23298.hs - + testsuite/tests/gadt/T23298.stderr - testsuite/tests/gadt/all.T Changes: ===================================== testsuite/tests/gadt/T23298.hs ===================================== @@ -0,0 +1,25 @@ +{-# LANGUAGE GADTs #-} +module T23298 where + +import Data.Kind (Type) + +type HList :: Type -> Type +data HList a where + HCons :: HList x -> HList (Maybe x) + +eq :: HList a -> Bool +eq x = case x of + HCons ms -> True + +go (HCons x) = go x + +{- go :: HList alpha -> beta + +Under HCons + [G] alpha ~ Maybe x + [W] HList x ~ HList alpha +==> + [W] x ~ alpha +==> + [W] x ~ Maybe x +-} ===================================== testsuite/tests/gadt/T23298.stderr ===================================== @@ -0,0 +1,12 @@ + T23298.hs:14:16: error: [GHC-25897] + • Couldn't match type ‘x’ with ‘Maybe x’ + Expected: HList x -> t + Actual: HList a -> t + ‘x’ is a rigid type variable bound by + a pattern with constructor: + HCons :: forall x. HList x -> HList (Maybe x), + in an equation for ‘go’ + at T23298.hs:14:5-11 + • In the expression: go x + In an equation for ‘go’: go (HCons x) = go x + • Relevant bindings include x :: HList x (bound at T23298.hs:14:11) ===================================== testsuite/tests/gadt/all.T ===================================== @@ -131,3 +131,4 @@ test('T19847a', normalise_version('base'), compile, ['-ddump-types']) test('T19847b', normal, compile, ['']) test('T23022', normal, compile, ['-dcore-lint']) test('T23023', normal, compile_fail, ['-O -dcore-lint']) # todo: move this test? +test('T23298', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2e0c07abc166560a974c0fc34efddc66... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2e0c07abc166560a974c0fc34efddc66... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)