[GHC] #14751: GHC wrongly warns of incomplete pattern matches when using pattern synonyms.

GHC ghc-devs at haskell.org
Thu Feb 1 20:01:27 UTC 2018


#14751: GHC wrongly warns of incomplete pattern matches when using pattern
synonyms.
-------------------------------------+-------------------------------------
           Reporter:  vanessamchale  |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  low            |         Milestone:
          Component:  Compiler       |           Version:  8.4.1-alpha1
           Keywords:                 |  Operating System:  Linux
       Architecture:  x86_64         |   Type of failure:  GHC rejects
  (amd64)                            |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 If one writes the following code:

 {{{
 {-# LANGUAGE PatternSynonyms #-}
 module Version where
 newtype Version = Version [Integer]
     deriving (Eq)
 pattern V :: [Integer] -> Version
 pattern V is = Version is
 instance Ord Version where
     (V []) <= (V []) = True
     (V []) <= _ = True
     _ <= (Version []) = False
     (V (x:xs)) <= (V (y:ys))
         | x == y = Version xs <= Version ys
         | otherwise = x <= y
 }}}

 and compiles with {{{ghc -Wall -Werror}}}, one gets the following message:

 {{{
 [1 of 1] Compiling Version          ( Bug.hs, Bug.o )
 Bug.hs:12:5: error: [-Wincomplete-patterns, -Werror=incomplete-patterns]
     Pattern match(es) are non-exhaustive
     In an equation for ‘<=’:
         Patterns not matched:
             _ _
             _ _
             _ _
             _ _
    |
 12 |     (V []) <= (V []) = True
    |     ^^^^^^^^^^^^^^^^^^^^^^^...
 }}}

 However, the following code compiles correctly without warnings:

 {{{
 {-# LANGUAGE PatternSynonyms #-}
 module Version where
 newtype Version = Version [Integer]
     deriving (Eq)
 instance Ord Version where
     (Version []) <= (Version []) = True
     (Version []) <= _ = True
     _ <= (Version []) = False
     (Version (x:xs)) <= (Version (y:ys))
         | x == y = Version xs <= Version ys
         | otherwise = x <= y
 }}}

 This bug appears in GHC 8.2.2 as well as GHC-8.4.1-alpha2.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14751>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list