[GHC] #13363: Wildcarn patterns and COMPLETE sets can lead to misleading redundant pattern-match warnings
GHC
ghc-devs at haskell.org
Thu Mar 2 14:39:42 UTC 2017
#13363: Wildcarn patterns and COMPLETE sets can lead to misleading redundant
pattern-match warnings
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
Keywords: | Operating System: Unknown/Multiple
PatternSynonyms |
Architecture: | Type of failure: Incorrect
Unknown/Multiple | error/warning at compile-time
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Consider this program:
{{{#!hs
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wincomplete-patterns #-}
module Bug where
data Boolean = F | T
deriving Eq
pattern TooGoodToBeTrue :: Boolean
pattern TooGoodToBeTrue <- ((== T) -> True)
where
TooGoodToBeTrue = T
{-# COMPLETE F, TooGoodToBeTrue #-}
catchAll :: Boolean -> Int
catchAll F = 0
catchAll TooGoodToBeTrue = 1
}}}
This compiles with no warnings with `-Wall`. But if you tweak `catchAll`
to add a catch-all case at the end:
{{{#!hs
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wincomplete-patterns #-}
module Bug where
data Boolean = F | T
deriving Eq
pattern TooGoodToBeTrue :: Boolean
pattern TooGoodToBeTrue <- ((== T) -> True)
where
TooGoodToBeTrue = T
{-# COMPLETE F, TooGoodToBeTrue #-}
catchAll :: Boolean -> Int
catchAll F = 0
catchAll TooGoodToBeTrue = 1
catchAll _ = error "impossible"
}}}
Then if you compile it with `-Wall`, you'll get a very misleading warning:
{{{
$ ~/Software/ghc2/inplace/bin/ghc-stage2 --interactive Bug.hs -Wall
GHCi, version 8.1.20170228: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Bug.hs:17:1: warning: [-Woverlapping-patterns]
Pattern match is redundant
In an equation for ‘catchAll’: catchAll TooGoodToBeTrue = ...
|
17 | catchAll TooGoodToBeTrue = 1
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^
}}}
I would have expected the warning to be on the `catchAll _ =
error "impossible"` case!
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13363>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list