Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
-
30341168
by Simon Peyton Jones at 2026-01-08T13:31:38-05:00
3 changed files:
- + testsuite/tests/pmcheck/should_compile/T24867.hs
- + testsuite/tests/pmcheck/should_compile/T24867.stderr
- testsuite/tests/pmcheck/should_compile/all.T
Changes:
| 1 | +{-# LANGUAGE DataKinds, TypeFamilies, GADTs #-}
|
|
| 2 | +{-# OPTIONS_GHC -Winaccessible-code -Werror #-}
|
|
| 3 | + |
|
| 4 | +module T24867 where
|
|
| 5 | + |
|
| 6 | +data T = Z | S
|
|
| 7 | + |
|
| 8 | +data ST n where
|
|
| 9 | + SS :: ST S
|
|
| 10 | + |
|
| 11 | +type family F n where
|
|
| 12 | + F Z = Z
|
|
| 13 | + F S = Z
|
|
| 14 | + |
|
| 15 | +-- Should be rejected with inaccessible RHS
|
|
| 16 | +f :: F m ~ n => ST m -> ST n -> ()
|
|
| 17 | +f _ SS = () |
| 1 | +T24867.hs:17:1: error: [GHC-94210] [-Woverlapping-patterns (in -Wdefault), Werror=overlapping-patterns]
|
|
| 2 | + Pattern match has inaccessible right hand side
|
|
| 3 | + In an equation for âfâ: f _ SS = ...
|
|
| 4 | + |
| ... | ... | @@ -181,3 +181,4 @@ test('T25257', normal, compile, [overlapping_incomplete]) |
| 181 | 181 | test('T24845', [], compile, [overlapping_incomplete])
|
| 182 | 182 | test('T22652', [], compile, [overlapping_incomplete])
|
| 183 | 183 | test('T22652a', [], compile, [overlapping_incomplete])
|
| 184 | +test('T24867', [], compile_fail, [overlapping_incomplete]) |