[GHC] #11806: GHC does not warn for mistakenly empty case

#11806: GHC does not warn for mistakenly empty case -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC accepts Unknown/Multiple | invalid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE EmptyCase #-} {-# OPTIONS_GHC -Wall -fwarn-incomplete-uni-patterns #-} oops :: Int -> a oops x = case x of {} }}} Since `Int` is inhabited, I would expect a warning, but I get none. Since empty case is typically used in situations where programmers want GHC to see an absurdity, this seems most unfortunate. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11806 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11806: GHC does not warn for mistakenly empty case -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: gkaracha (added) Comment: Yes that is odd. If you have {{{ module T11806 where f1 :: Int -> Int f1 x = case x of { 1 -> 2 } f2 :: Bool -> Int f2 x = case x of { True -> 2 } }}} you get (with 8.0) {{{ T11806.hs:7:8: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: p where p is not one of {1} T11806.hs:10:8: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: False }}} but if you remove all the branches, you get no warnings at all! I'm adding George (who is responsible for pattern match overlap checks) in cc. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11806#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11806: GHC does not warn for mistakenly empty case -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gkaracha): Replying to [ticket:11806 dfeuer]:
{{{#!hs {-# LANGUAGE EmptyCase #-} {-# OPTIONS_GHC -Wall -fwarn-incomplete-uni-patterns #-}
oops :: Int -> a oops x = case x of {} }}}
Since `Int` is inhabited, I would expect a warning, but I get none. Since empty case is typically used in situations where programmers want GHC to see an absurdity, this seems most unfortunate.
Indeed. Yet, I feel like there is a big misconception here, from the you said
Since `Int` is inhabited
It is indeed inhabited, but **like any other type in Haskell**, where every type is inhabited. That is, for the following (see #11390) a warning should also be expected: {{{#!hs silly1 :: Void -> Void silly1 x = case x of {} }}} There have been separate discussions on this (see related tickets #10746, #7669, #11390) and I think that we have a design choice to make here. Unless you force the argument in some other way like: {{{#!hs silly2 :: Void -> Void silly2 x = x `seq` case x of {} }}} or {{{#!hs silly3 :: Void -> Void silly3 (!x) = case x of {} }}} then it is indeed non-exhaustive. This means that in almost all cases, an empty case expression will issue a warning (which I think is the right thing to do). Of course, in `silly2` and `silly3` the warning is too conservative but remember that type inhabitation is undecidable. Hence, I see two choices here. We can: 1. Always issue a non-exhaustive warning for empty case expressions, or 2. Never issue a non-exhaustive warning for empty case expressions. I am pointing this out because before #7669 we would issue the warning you seek here and it has been intentionally changed. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11806#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11806: GHC does not warn for mistakenly empty case -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: #10746, #7669, | Differential Rev(s): #11390 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by gkaracha): * related: => #10746, #7669, #11390 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11806#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11806: GHC does not warn for mistakenly empty case -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: #10746, #7669, | Differential Rev(s): #11390 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by gkaracha): * keywords: => PatternMatchWarnings -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11806#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11806: GHC does not warn for mistakenly empty case -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: #10746, #7669, | Differential Rev(s): #11390 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): gkaracha, you are right that dfeuer’s working is unfortunate. He probably should have said “inhabited by a value” (in contrast to “inhabited by ⊥”). I don’t follow your argument about `silly1` and your conclusion. I would say that an empty case should issue an warning whenever the type has a constructor (and in with GADTs, if GHC cannot prove this constructor to have an impossible type). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11806#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11806: GHC does not warn for mistakenly empty case -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: #10746, #7669, | Differential Rev(s): #11390 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): nomeata speaks my mind. When I said "inhabited", I meant properly inhabited. Empty case should issue a warning under the conditions he indicates. If the type of the scrutinee is not apart from the result types of all constructors, then I've made a mistake and I want to know about it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11806#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11806: GHC does not warn for mistakenly empty case -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: #10746, #7669, | Differential Rev(s): #11390 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Indeed. Another way to see it is via my examples in comment:1. It is extremely unexpected that removing one alternative from an exhaustive Boolean `case` would yield a warning, but removing both alternatives does not. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11806#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11806: GHC does not warn for mistakenly empty case -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: duplicate | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: #10746, #7669, | Differential Rev(s): #11390 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * status: new => closed * resolution: => duplicate Comment: This appears to be a duplicate of #10746 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11806#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC