
#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): Here is a slightly smaller example: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE EmptyCase #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -Wincomplete-patterns #-} module Bug where import Data.Kind (Type) import Data.Type.Equality ((:~:)(..)) import Data.Void (Void) data SBool :: Bool -> Type where SFalse :: SBool False STrue :: SBool True data SUnit :: () -> Type where SUnit :: SUnit '() type family IsUnit (u :: ()) :: Bool where IsUnit '() = True sIsUnit :: SUnit u -> SBool (IsUnit u) sIsUnit SUnit = STrue type family If (c :: Bool) (t :: Type) (f :: Type) :: Type where If True t _ = t If False _ f = f type family F (u1 :: ()) (u2 :: ()) :: Type where F u1 u2 = If (IsUnit u1) (Case u2) Int type family Case (u :: ()) :: Type where Case '() = Int g1 :: F u1 u2 :~: Char -> SUnit u1 -> SUnit u2 -> Void g1 Refl su1 su2 | STrue <- sIsUnit su1 = case su2 of {} g2 :: F u1 u2 :~: Char -> SUnit u1 -> SUnit u2 -> Void g2 Refl su1 su2 = case sIsUnit su1 of STrue -> case su2 of {} }}} {{{ $ /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/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:40:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g1’: Patterns not matched: Refl _ _ | 40 | g1 Refl su1 su2 | ^^^^^^^^^^^^^^^... Ok, one module loaded. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15753#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler