#5424: Validate error under 7.2.1 caused by incomplete pattern warnings in new
code gen (GADTs)
---------------------------------+------------------------------------------
    Reporter:  dterei            |        Owner:  simonpj            
        Type:  bug               |       Status:  new                
    Priority:  normal            |    Milestone:                     
   Component:  Compiler          |      Version:  7.2.1              
    Keywords:                    |     Testcase:                     
   Blockedby:                    |   Difficulty:                     
          Os:  Unknown/Multiple  |     Blocking:                     
Architecture:  Unknown/Multiple  |      Failure:  Building GHC failed
---------------------------------+------------------------------------------
Changes (by igloo):

  * owner:  => simonpj


Comment:

 hoopl is compiled with -O0 by the bootstrapping compiler, and that causes
 this problem. I can't see why that should cause a problem, though.

 Cutdown example:

 `Q.hs`:
 {{{
 module Q where

 data X
 data Y
 }}}

 `W.hs`:
 {{{
 {-# LANGUAGE GADTs #-}

 module W where

 import Q

 data D a where
     C1 :: D X
     C2 :: D Y

 f :: D X -> Int
 f C1 = 1
 }}}

 {{{
 $ ghc -Wall -fforce-recomp -O -c Q.hs
 $ ghc -Wall -fforce-recomp -O -c W.hs
 $ ghc -Wall -fforce-recomp -O0 -c Q.hs
 $ ghc -Wall -fforce-recomp -O -c W.hs

 W.hs:13:1:
     Warning: Pattern match(es) are non-exhaustive
              In an equation for `f': Patterns not matched: C2
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5424#comment:2>
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