
I'm starting to play around with GHC's support for view patterns, and I'm running into what appears to be an annoying limitation of the implementation. GHC 7.0.3 (32-bit), MacOS 10.6.8. First module; defines an abstract type & provides a (trivial) view for it. module Term(Term, TermView(..), view) where data Term = TVar String | TApp Term Term | TLam String Term data TermView = Var String | App Term Term | Lam String Term view :: Term -> TermView view (TVar x) = Var x view (TApp rator rand) = App rator rand view (TLam x body) = Lam x body Second module tries to use the view in a trivial function: {-# LANGUAGE ViewPatterns #-} module Client where import Term numVarRefs :: Term -> Integer numVarRefs (view -> Var _) = 1 numVarRefs (view -> App rator rand) = numVarRefs rator + numVarRefs rand numVarRefs (view -> Lam _ body) = numVarRefs body -- numVarRefs (view -> _) = error "bogus" f :: TermView -> Integer f (Var _) = 1 f (App rator rand) = f (view rator) + f (view rand) f (Lam _ body) = f (view body) GHCI complains when trying to load this second module: Client.hs:8:1: Warning: Pattern match(es) are non-exhaustive In an equation for `numVarRefs': Patterns not matched: _ (I have ":set -fwarn-incomplete-patterns" in my .ghci.) I wrote 'f' to make sure that my patterns for TermView are indeed exhaustive, and GHC doesn't complain about it all. If I uncomment the last definition for numVarRefs, the warning goes away. I did some searching around on the web, in the mailing list archives, and in the GHC bug database, and I see that early on, views had trouble giving useful diagnostics for overlapping or non-exhaustive patterns, but most of those problems seem to have been fixed. I also couldn't find a bug report for precisely this situation -- #4439 is the closest, but I'm not using existential types here at all. Should I file a bug, or am I overlooking something simple? Or is this a known limitation of the current implementation? Thanks, Richard