[GHC] #15385: -Wincomplete-patterns gets confused when combining GADTs and pattern guards

#15385: -Wincomplete-patterns gets confused when combining GADTs and pattern guards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple PatternMatchWarnings | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider the following code: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -Wincomplete-patterns #-} module Bug where import Data.Kind data family Sing :: forall k. k -> Type newtype Id a = MkId a data So :: Bool -> Type where Oh :: So True data instance Sing :: Bool -> Type where SFalse :: Sing False STrue :: Sing True data instance Sing :: Ordering -> Type where SLT :: Sing LT SEQ :: Sing EQ SGT :: Sing GT data instance Sing :: forall a. Id a -> Type where SMkId :: Sing x -> Sing (MkId x) class POrd a where type (x :: a) `Compare` (y :: a) :: Ordering class SOrd a where sCompare :: forall (x :: a) (y :: a). Sing x -> Sing y -> Sing (x `Compare` y) type family (x :: a) <= (y :: a) :: Bool where x <= y = LeqCase (x `Compare` y) type family LeqCase (o :: Ordering) :: Bool where LeqCase LT = True LeqCase EQ = True LeqCase GT = False (%<=) :: forall a (x :: a) (y :: a). SOrd a => Sing x -> Sing y -> Sing (x <= y) sx %<= sy = case sx `sCompare` sy of SLT -> STrue SEQ -> STrue SGT -> SFalse class (POrd a, SOrd a) => VOrd a where leqReflexive :: forall (x :: a). Sing x -> So (x <= x) instance POrd a => POrd (Id a) where type MkId x `Compare` MkId y = x `Compare` y instance SOrd a => SOrd (Id a) where SMkId sx `sCompare` SMkId sy = sx `sCompare` sy ----- instance VOrd a => VOrd (Id a) where leqReflexive (SMkId sa) | Oh <- leqReflexive sa = case sa `sCompare` sa of SLT -> Oh SEQ -> Oh -- SGT -> undefined }}} What exactly this code does isn't terribly important. The important bit is that last instance (`VOrd (Id a)`). That //should// be total, but GHC disagrees: {{{ GHCi, version 8.6.0.20180627: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:63:7: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: SGT | 63 | = case sa `sCompare` sa of | ^^^^^^^^^^^^^^^^^^^^^^^^... }}} As evidence that this warning is bogus, if you uncomment the last line, then GHC correctly observes that that line is inaccessible: {{{ GHCi, version 8.6.0.20180627: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:66:9: warning: [-Winaccessible-code] • Couldn't match type ‘'True’ with ‘'False’ Inaccessible code in a pattern with constructor: SGT :: Sing 'GT, in a case alternative • In the pattern: SGT In a case alternative: SGT -> undefined In the expression: case sa `sCompare` sa of SLT -> Oh SEQ -> Oh SGT -> undefined | 66 | SGT -> undefined | ^^^ }}} Clearly, something is afoot in the coverage checker. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15385 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15385: -Wincomplete-patterns gets confused when combining GADTs and pattern guards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Actually, this is even simpler than I made it out to be: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -Wincomplete-patterns #-} module Bug where import Data.Type.Equality data T a where TInt :: T Int TBool :: T Bool f :: a :~: Int -> T a -> () f eq t | Refl <- eq = case t of TInt -> () -- TBool -> () }}} {{{ GHCi, version 8.6.0.20180627: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug3.hs, interpreted ) Bug3.hs:15:5: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: TBool | 15 | = case t of | ^^^^^^^^^... }}} Stunning. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15385#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15385: -Wincomplete-patterns gets confused when combining GADTs and pattern guards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4968 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4968 Comment: It turns out that when GHC desugars patterns bound by pattern guards, it completely forgets to update the local dictionaries in scope with `addDictsDs`! I have no idea how this oversight went unnoticed for so long... In any case, I have a patch for this at Phab:D4968. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15385#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15385: -Wincomplete-patterns gets confused when combining GADTs and pattern guards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4968 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Gah. The deeper I dig the less happy I am. The `addDictsDs` is ok, but I'm worried about `genCaseTmCs1` and `genCaseTmCs2` The basic idea here is that when we see (in source Haskell) {{{ case x of { (a, Just b) -> blah } }}} we want to desugar `blah` in the knowledge that {{{ x ~ (a, Just b) }}} Reason: suppose that somewhere inside `blah` we see {{{ case x of { (a, Nothing) -> blah2 } }}} Then we want to declare this branch as unreachable. But what if the original expression was {{{ case x of (a, Just _) -> blah }}} Now what equality do we generate? Maybe we make a fresh variable? And maybe that is waht we want. This conversion from a pattern to a `PmExpr` is all hidden inside the cryptic line {{{ [e] <- map vaToPmExpr . coercePatVec <$> translatePat fam_insts p }}} I have very little idea of what this does. Returning to our case expression, we'll end up using `genCaseTmCs2` in `matchWrapper`. And that seems to generate ''two'' equalities {{{ v ~ (a, Just b) v ~ x }}} That seems terribly indirect, although perhaps not actually wrong. I suppose that it might work in cases like {{{ case (p,q) of (a, Just b) -> blah }}} but they probably never happen -- and at very least it could do with explanation. Bottom line so far: no actual bugs, but pretty tough going. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15385#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15385: -Wincomplete-patterns gets confused when combining GADTs and pattern guards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4968 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): To be clear, the problems you're describing in comment:3 aren't unique to pattern guards, but rather anything that generates term equalities for the coverage checker (which includes `case` expressions)? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15385#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

To be clear, the problems you're describing in comment:3 aren't unique to pattern guards, but rather anything that generates term equalities for
#15385: -Wincomplete-patterns gets confused when combining GADTs and pattern guards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4968 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): the coverage checker (which includes case expressions)? Correct, yes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15385#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15385: -Wincomplete-patterns gets confused when combining GADTs and pattern guards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4968 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): OK. Well, I simply went along with the status quo (adapting from the code for `case` expressions in `matchWrapper`) when writing Phab:D4968. At the very least, I'd like to get that patch in to 8.6, and then perhaps we can revisit the design of term equalities later. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15385#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15385: -Wincomplete-patterns gets confused when combining GADTs and pattern guards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4968 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes fine. I've commented on Phab. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15385#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15385: -Wincomplete-patterns gets confused when combining GADTs and pattern guards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4968 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): And I've replied on Phab. (Unfortunately, Phab notifications appear to be dysfunctional at the moment...) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15385#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15385: -Wincomplete-patterns gets confused when combining GADTs and pattern guards
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.5
Resolution: | Keywords:
| PatternMatchWarnings
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4968
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#15385: -Wincomplete-patterns gets confused when combining GADTs and pattern guards
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.5
Resolution: | Keywords:
| PatternMatchWarnings
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4968
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#15385: -Wincomplete-patterns gets confused when combining GADTs and pattern guards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | pmcheck/should_compile/T15385 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4968 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => pmcheck/should_compile/T15385 * status: patch => merge Comment: This fixes a pretty serious incompleteness in the pattern-match coverage checker, so I'd humbly request that the commits in comment:9 and comment:10 be merged to 8.6. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15385#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15385: -Wincomplete-patterns gets confused when combining GADTs and pattern guards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | pmcheck/should_compile/T15385 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4968 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: comment:9 merged in 42c51e2f39ce829fa4a380b604c9a7f5ea71d28d, comment:10 in e649085bb35628e10b08a9a1ef27095ad0510b40. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15385#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC