Neil Mitchell wrote:
Hi
isBool x = isLT x || isGT x
isNum x = not $ isBool x
isLT and isGT can be derived automatically using derve [1], with the
Is class (or DrIFT if you want).
You can also get a long way with GHC's built in derivations for Eq, Enum
and Show.
If an Enum instance is possible then you can write something like
isBool = (`elem` [LT .. GT])
isNum = (`elem` [Minus .. Mul])
If enum is not possible, because some of the constructors are not
nullary, then there is the following cute/ugly hack if you instead
derive Show:
constrName = takeWhile (/=' ') . show
and you can say
isBool x = constrName x `elem` ["LT","GT"]
isNum x = constrName x `elem` ["Minus","Plus","Mul"]
What this leads us towards is that it might be rather nice (perhaps even
nice enough to build into a compiler) to be able to derive, for each
type with multiple constructors, a type 'which is the enumeration of the
constructors'. I.e. a type with the same constructors (up to some
namespace fix like prepending with C) but all nullary:
data Atom = Null | MyInt Int | MyString String
derives...
data AtomCons = CNull | CMyInt | CMyString deriving (Ord,Eq,Enum,Show)
and a function
constr :: Atom -> AtomCons
Jules
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe