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
3 changed files:
Changes:
1 | +{-# LANGUAGE GADTs #-}
|
|
2 | +module T23298 where
|
|
3 | + |
|
4 | +import Data.Kind (Type)
|
|
5 | + |
|
6 | +type HList :: Type -> Type
|
|
7 | +data HList a where
|
|
8 | + HCons :: HList x -> HList (Maybe x)
|
|
9 | + |
|
10 | +eq :: HList a -> Bool
|
|
11 | +eq x = case x of
|
|
12 | + HCons ms -> True
|
|
13 | + |
|
14 | +go (HCons x) = go x
|
|
15 | + |
|
16 | +{- go :: HList alpha -> beta
|
|
17 | + |
|
18 | +Under HCons
|
|
19 | + [G] alpha ~ Maybe x
|
|
20 | + [W] HList x ~ HList alpha
|
|
21 | +==>
|
|
22 | + [W] x ~ alpha
|
|
23 | +==>
|
|
24 | + [W] x ~ Maybe x
|
|
25 | +-} |
1 | + T23298.hs:14:16: error: [GHC-25897]
|
|
2 | + • Couldn't match type ‘x’ with ‘Maybe x’
|
|
3 | + Expected: HList x -> t
|
|
4 | + Actual: HList a -> t
|
|
5 | + ‘x’ is a rigid type variable bound by
|
|
6 | + a pattern with constructor:
|
|
7 | + HCons :: forall x. HList x -> HList (Maybe x),
|
|
8 | + in an equation for ‘go’
|
|
9 | + at T23298.hs:14:5-11
|
|
10 | + • In the expression: go x
|
|
11 | + In an equation for ‘go’: go (HCons x) = go x
|
|
12 | + • Relevant bindings include x :: HList x (bound at T23298.hs:14:11) |
... | ... | @@ -131,3 +131,4 @@ test('T19847a', normalise_version('base'), compile, ['-ddump-types']) |
131 | 131 | test('T19847b', normal, compile, [''])
|
132 | 132 | test('T23022', normal, compile, ['-dcore-lint'])
|
133 | 133 | test('T23023', normal, compile_fail, ['-O -dcore-lint']) # todo: move this test?
|
134 | +test('T23298', normal, compile_fail, ['']) |