
#15753: Inconsistent pattern-match warnings when using guards versus case expressions -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.1 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Even simpler: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -Wincomplete-patterns #-} module Bug where import Data.Type.Equality data G a where GInt :: G Int GBool :: G Bool ex1, ex2, ex3 :: a :~: Int -> G a -> () ex1 Refl g | GInt <- id g = () ex2 Refl g | GInt <- g = () ex3 Refl g = case id g of GInt -> () }}} {{{ $ /opt/ghc/8.6.1/bin/ghci Bug.hs GHCi, version 8.6.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/ryanglscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:17:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘ex1’: Patterns not matched: Refl _ | 17 | ex1 Refl g | ^^^^^^^^^^... }}} This time, I've included three examples. In particular, note that `ex1` and `ex2` are //extremely// similar—the only difference is the use of `id`! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15753#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler