
When the pattern match checker requests a set of constructors for a type constructor `T`, we now return a list of sets which include the normal data constructor set and also any `COMPLETE` pragmas of type `T`. We then
#13964: Pattern-match warnings for datatypes with COMPLETE sets break abstraction -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: | PatternSynonyms, | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Another way of phrasing the problem is that the observed behavior here doesn't match the specification laid out in [https://ghc.haskell.org/trac/ghc/wiki/PatternSynonyms/CompleteSigs#ErrorMess... the GHC wiki] (and which I'm attempting to enshrine in the GHC users' guide in Phab:D4005). Quoth the wiki: try each of these sets, not warning if any of them are a perfect match. In the case the match isn't perfect, we select one of the branches of the search depending on how good the result is.
The results are prioritised in this order.
1. Fewest uncovered clauses 2. Fewest redundant clauses 3. Fewest inaccessible clauses 4. Whether the match comes from a `COMPLETE` pragma or the built-in set
of data constructors for a type constructor. Going to back to the original example: {{{#!hs {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ViewPatterns #-} module Bug (Boolean(F, TooGoodToBeTrue), catchAll) where data Boolean = F | T deriving Eq pattern TooGoodToBeTrue :: Boolean pattern TooGoodToBeTrue <- ((== T) -> True) where TooGoodToBeTrue = T {-# COMPLETE F, TooGoodToBeTrue #-} }}} {{{#!hs module Foo where import Bug catchAll2 :: Boolean -> Int catchAll2 F = 0 -- catchAll2 TooGoodToBeTrue = 1 }}} Here, we have two sets of conlikes to consider: the original set of data constructors `{F, T}`, as well as the `COMPLETE` set `{F, TooGoodToBeTrue}`. Both sets have exactly one uncovered clause and no redundant or inaccessible clauses, so to break the tie, it must use the fourth rule, which states that the `COMPLETE` pragma should be favored over the built-in set of data constructors. But this isn't happening here, since the original data constructor `T` is being warned about. So we could "fix" this example by just tightening the implementation to actually match the specification. Granted, one could tweak this example slightly to the point where the original data constructor set is once again favored over the `COMPLETE` set (while still following the specification), once again breaking abstraction. In such a scenario, we should consider revising the specification to factor in whether all of the conlikes in a particular set are in-scope. That should supplant "Fewest uncovered clauses" as the new top priority, I believe. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13964#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler