[Haskell-cafe] warn-incomplete-patterns and GADTs
Tom Nielsen
tanielsen at gmail.com
Fri Aug 27 09:40:13 EDT 2010
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
More information about the Haskell-Cafe
mailing list