#4439: GHC doesn't detect trivial complete pattern with the combination of
ExistentialQuantification and ViewPatterns
---------------------------------+------------------------------------------
    Reporter:  batterseapower    |       Owner:                                 
  
        Type:  bug               |      Status:  new                            
  
    Priority:  normal            |   Component:  Compiler                       
  
     Version:  6.12.3            |    Keywords:                                 
  
    Testcase:                    |   Blockedby:                                 
  
          Os:  Unknown/Multiple  |    Blocking:                                 
  
Architecture:  Unknown/Multiple  |     Failure:  Incorrect warning at 
compile-time
---------------------------------+------------------------------------------
 This program exhibits the behaviour:

 {{{
 {-# LANGUAGE ViewPatterns, ExistentialQuantification #-}
 {-# OPTIONS_GHC -fwarn-incomplete-patterns #-}

 data Moo = Moo (Char -> Int)
 spqr (Moo _) = undefined      -- Exhaustive pattern
 foo (id -> Moo _) = undefined -- Exhaustive pattern


 data Exists = forall a. Exists (a -> Int)
 bar (Exists _) = undefined       -- Exhaustive pattern
 baz (id -> Exists _) = undefined -- "Warning: Pattern match(es) are non-
 exhaustive"
 }}}

 GHCs output is puzzling:

 {{{
 $ ghc -c Exhaustive.hs

 Exhaustive.hs:11:0:
     Warning: Pattern match(es) are non-exhaustive
              In the definition of `baz': Patterns not matched: _
 }}}

 It can detect exhaustivity if you use either existentials OR view patterns
 by themselves, but not with the combination of the two together. Weird!

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4439>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to