A benefit of using type families and type classes instead of GADTs for this kind of thing when you can is they are usually cheaper. You can often write code that inlines perfectly with former but ends up being some recursive function that will never inline with the latter.
- Jake
I'm not sure if this answers your questions, but I think this particular problem has a cleaner solution with GADTs:{-# LANGUAGE GADTs #-}data Cmd s t wherePush :: a -> Cmd s (a,s)F1 :: (a -> b) -> Cmd (a,s) (b,s)F2 :: (a -> b -> c) -> Cmd (a,(b,s)) (c,s)data Prog s t where(:.) :: Cmd s t -> Prog t u -> Prog s uEnd :: Prog s sinfixr 5 :.cmd :: Cmd s t -> s -> tcmd (Push a) s = (a, s)cmd (F1 f) (a,s) = (f a, s)cmd (F2 f) (a,(b,s)) = (f a b, s)prog :: Prog s t -> s -> tprog (c :. p) s = prog p (cmd c s)prog End s = srun :: Prog () t -> trun p = prog p ()Then from GHCi:> run (Push 3 :. Push 4 :. F2 (+) :. F1 show :. End)("7",())Maybe you really want GADTs? :)-Eric
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe