[GHC] #16129: Incorrect non-exhaustive pattern warning with PatternSynonyms, ViewPatterns and TypeFamilies

#16129: Incorrect non-exhaustive pattern warning with PatternSynonyms, ViewPatterns and TypeFamilies -------------------------------------+------------------------------------- Reporter: sjakobi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Keywords: | Operating System: Unknown/Multiple PatternMatchWarnings | Architecture: | Type of failure: Incorrect Unknown/Multiple | error/warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# language PatternSynonyms #-} {-# language ViewPatterns #-} {-# language TypeFamilies #-} module Bug where newtype GenLocated e = L e newtype WithSourceText a = WithSourceText a type StringLiteral = WithSourceText String {-# COMPLETE StringLiteral #-} pattern StringLiteral sl_s = WithSourceText sl_s type family SrcSpanLess a class HasSrcSpan a where decomposeSrcSpan :: a -> GenLocated (SrcSpanLess a) type instance SrcSpanLess (GenLocated e) = e instance HasSrcSpan (GenLocated a) where decomposeSrcSpan = id bug :: GenLocated StringLiteral -> String bug (decomposeSrcSpan->L (StringLiteral s)) = s workaround :: GenLocated StringLiteral -> String workaround (decomposeSrcSpan->L sl) = s where StringLiteral s = sl }}} {{{ $ ghci -Wincomplete-patterns Bug.hs GHCi, version 8.7.20190103: https://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/simon/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:27:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘bug’: Patterns not matched: _ | 27 | bug (decomposeSrcSpan->L (StringLiteral s)) = s | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Ok, one module loaded. }}} I've been able to reproduce the issue with all versions of GHC >= 7.8. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16129 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16129: Incorrect non-exhaustive pattern warning with PatternSynonyms -------------------------------------+------------------------------------- Reporter: sjakobi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: | Keywords: | PatternMatchWarnings, | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15753 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: PatternMatchWarnings => PatternMatchWarnings, PatternSynonyms * related: => #15753 Comment: Here is a simpler version without `ViewPatterns` or `TypeFamilies` (they aren't essential to triggering this bug): {{{#!hs {-# LANGUAGE PatternSynonyms #-} module Bug where import Data.Functor.Identity pattern Id :: a -> Identity a pattern Id x = Identity x bug, workaround1, workaround2 :: Identity a -> a bug ia | Id a <- ia = a workaround1 ia | let ia' = ia , Identity a <- ia' = a workaround2 ia = a where Id a = ia }}} While this doesn't appear to be exactly the same bug as #15753, they feel related somehow. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16129#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16129: Incorrect non-exhaustive pattern warning with PatternSynonyms -------------------------------------+------------------------------------- Reporter: sjakobi | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 Resolution: duplicate | Keywords: | PatternMatchWarnings, | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15753 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate Comment: Urk, please ignore what I wrote in comment:1. I forgot to add a `COMPLETE` pragma on `Id`, and that makes the whole example invalid. Here is my second attempt at a minimal example: {{{#!hs {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ViewPatterns #-} module Bug where import Data.Functor.Identity {-# COMPLETE Id #-} pattern Id :: a -> Identity a pattern Id x = Identity x class Hm a where hm :: a -> a instance Hm (Identity a) where hm = id bug, workaround1, workaround2 :: Identity a -> a bug ia | Id a <- hm ia = a workaround1 ia | let ia' = hm ia , Identity a <- ia' = a workaround2 ia = a where Id a = hm ia }}} This time, I'm convinced that this is a duplicate of #15753, as this has the distinctive function-application-in-pattern-guard look that #15753 has. Closing as a duplicate. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16129#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC