
Thanks to everyone who replied (especially Dimitrios Vytiniotis and Joost Visser). I now know the standard way to write the GADT parser. But I'm still curious if anyone has comments pertaining to the version using type classes. It seems so close to doing what we want, and it is pretty straightforward to implement. The best way I can think to describe it would be to say it uses the type system to find what it should parse next, and dies of a pattern match failure if something unexpected shows up, instead of checking to see if we can assemble a type safe tree from pre-parsed parts (does that make any sense?). I'm curious if there could be a small change to the type system to make the fully general "my_read" possible, or if it suffers from an incurable defect. Thanks, Greg Buchholz
{-# OPTIONS -fglasgow-exts #-}
main = print test
test :: Int test = eval.my_read.read $ "(EIf (EIsZ (ELit 0)) " ++ " (EInc (ELit 1)) " ++ " (EFst (EPair (ELit 42) " ++ " (ELit 43))))"
class MyRead a where my_read :: Expr -> Term a
instance MyRead Int where my_read (ELit a) = Lit a my_read (EInc a) = Inc (my_read a) my_read (EIf p t e) = If (my_read p) (my_read t) (my_read e) my_read (EFst a) = Fst (my_read a :: Term (Int,Int)) my_read (ESnd a) = Snd (my_read a :: Term (Int,Int))
instance MyRead Bool where my_read (EIsZ a) = IsZ (my_read a) my_read (EIf p t e) = If (my_read p) (my_read t) (my_read e) my_read (EFst a) = Fst (my_read a :: Term (Bool,Bool)) my_read (ESnd a) = Snd (my_read a :: Term (Bool,Bool))
instance (MyRead a, MyRead x) => MyRead (a,x) where my_read (EPair a b) = Pair (my_read a) (my_read b) my_read (EIf p t e) = If (my_read p) (my_read t) (my_read e)
data Expr = ELit Int | EInc Expr | EIsZ Expr | EPair Expr Expr | EIf Expr Expr Expr | EFst Expr | ESnd Expr deriving (Read,Show)
data Term a where Lit :: Int -> Term Int Inc :: Term Int -> Term Int IsZ :: Term Int -> Term Bool If :: Term Bool -> Term a -> Term a -> Term a Pair :: Term a -> Term b -> Term (a,b) Fst :: Term (a,b) -> Term a Snd :: Term (a,b) -> Term b
eval :: Term a -> a eval (Lit i) = i eval (Inc t) = eval t + 1 eval (IsZ t) = eval t == 0 eval (If b t e) = if eval b then eval t else eval e eval (Pair a b) = (eval a, eval b) eval (Fst t) = fst (eval t) eval (Snd t) = snd (eval t)