
#14059: COMPLETE sets don't work at all with data family instances -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: | PatternSynonyms, | 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): Unfortunately, this means that the non-data-family instance version has also //regressed//. That is to say, this program: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -Wincomplete-patterns #-} module Foo where data SBool (z :: Bool) where SFalse :: SBool False STrue :: SBool True pattern STooGoodToBeTrue :: forall (z :: Bool). () => z ~ True => SBool z pattern STooGoodToBeTrue = STrue {-# COMPLETE SFalse, STooGoodToBeTrue #-} wibble :: SBool z -> Bool wibble STrue = True wobble :: SBool z -> Bool wobble STooGoodToBeTrue = True }}} Used to give the right warning in GHC 8.2 (as shown in the original description), but on GHC 8.4, it now demonstrates the same problem as in the version with data families: {{{ $ /opt/ghc/8.4.2/bin/ghci Foo.hs GHCi, version 8.4.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Foo ( Foo.hs, interpreted ) Foo.hs:20:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘wibble’: Patterns not matched: SFalse | 20 | wibble STrue = True | ^^^^^^^^^^^^^^^^^^^ Foo.hs:23:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘wobble’: Patterns not matched: _ | 23 | wobble STooGoodToBeTrue = True | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} I suppose the uniformity is comforting, at least... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14059#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler