warn-incomplete-patterns and GADTs
 
            Hi, is warn-incomplete-patterns (in GHC 6.10.3) less clever than it could be? {-# OPTIONS_GHC -fglasgow-exts #-} {-# OPTIONS_GHC -fwarn-incomplete-patterns #-} module Vec where data Z data S a data Vec n a where VNil :: Vec Z a VCons :: a -> Vec m a -> Vec (S m) a instance Eq a => Eq (Vec n a) where VNil == VNil = True VCons x vx == VCons y vy = x==y && vx == vy give the warning: Warning: Pattern match(es) are non-exhaustive In the definition of `==': Patterns not matched: VNil (VCons _ _) (VCons _ _) VNil but of course VNil and VCons can never have the same type. Tom
 
            See these bugs:
http://hackage.haskell.org/trac/ghc2/ticket/366
http://hackage.haskell.org/trac/ghc2/ticket/595
  -- ryan
On Fri, Aug 27, 2010 at 6:40 AM, Tom Nielsen 
Hi,
is warn-incomplete-patterns (in GHC 6.10.3) less clever than it could be?
{-# OPTIONS_GHC -fglasgow-exts #-} {-# OPTIONS_GHC -fwarn-incomplete-patterns #-} module Vec where
data Z data S a
data Vec n a where VNil :: Vec Z a VCons :: a -> Vec m a -> Vec (S m) a
instance Eq a => Eq (Vec n a) where VNil == VNil = True VCons x vx == VCons y vy = x==y && vx == vy
give the warning: Warning: Pattern match(es) are non-exhaustive In the definition of `==': Patterns not matched: VNil (VCons _ _) (VCons _ _) VNil
but of course VNil and VCons can never have the same type.
Tom _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
- 
                 Ryan Ingram Ryan Ingram
- 
                 Tom Nielsen Tom Nielsen