
{-# LANGUAGE TemplateHaskell #-} import Language.Haskell.TH typeChecker :: String -> Q Exp
numberP :: SchemeVal -> SchemeVal numberP = $(typeChecker "Number")
TH is a rather big hammer for this nail, isn't it?-) Spelling out one of the two simpler suggestions from this thread (the other was to define your own constructor tags and a mapping from SchemeVal to those tags): import Data.Data -- you'd need to derive Data for SchemeVal -- see DeriveDataTypeable constructorP :: (Data a) => String -> a -> Bool constructorP s = (s==) . showConstr . toConstr numberP :: SchemeVal -> SchemeVal numberP = Bool . constructorP "Number" Part of the difference between Haskell and Scheme is that reflection/meta-programming are not the first tools for common problems in Haskell. Not just because the evaluator is a rather heavyweight dependency, but because reflection tends to interfere with reasoning about programs (even the use of Data/Show is problematic in this respect - eg, when renaming some constructors, we would suddenly need to rename String values as well; so you might prefer the define-your-own-tags variant instead, if you care about maintenance/refactoring). For the scenic tour of pattern match (meta-)programming, see also QuasiQuotes, which allow you to construct patterns, or ViewPatterns, which allow you to call functions during pattern matching, or PatternGuards, which allow you to do pattern matching in guards). Those language options are documented here: http://haskell.org/ghc/docs/latest/html/users_guide/flag-reference.html#id59... There are some alternatives for reducing the boilerplate - not necessarily recommended, but useful to know. I'll use Either and its Left constructor, for simplicity. - we can avoid layout, to make the failure cases less prominent - low tech, but succinct: leftP x = case x of Left{} -> True; _->False - pattern match failure in list comprehensions gives empty lists, so we can write -- count the 'Left _' in the singleton list [x] leftP x = not.null $ [ () | Left{} <- [x] ] That is a bit of a hack, but it points in the right direction: - we'd really like to write out only the matching cases of constructor predicates, as the failure cases are boilerplate; but we need a handle on pattern match failure, to add in the default code for the non-matching cases. -- handle successful match only, -- use Maybe to indicate pattern match success/failure leftP' x = case x of Left{} -> Just True;_->Nothing -- add in default result for failure case leftP = maybe False id . leftP' Sadly, that doesn't save us typing here, but it shows how to decompose code that relies on pattern match failure and fall-through semantics (it is surprising how often people think that cannot be done). A slight variation uses the fact that pattern-match failure in do-notation calls the Monad method fail, which -for the Maybe Monad- returns Nothing: leftP' x = do Left{} <- Just x; Just True leftP = maybe False id . leftP'
From there, it isn't far until we define our own pattern combinators..
int n x = Just (n==x) left pat x = do Left l <- Just x; pat l right pat x = do Right r <- Just x; pat r a+++b = \x->a x `mplus` b x left (left (int 0)) +++ left (right (int 0)) $ (Left (Right 0)) -> Just True left (left (int 0)) +++ left (right (int 0)) $ (Left (Right 1)) -> Just False But that is just an appetizer for those who like to play with these things, not a recommended way of writing programs for beginners;-) Claus