Hi folks
Sorry, meant to send this around, not just to Klaus
Conor
--- Begin Message ---
Hi Klaus
Deep breath!
Klaus Ostermann wrote:
Hi all,
I have a problem which is probably not a problem at all for Haskell experts,
but I am struggling with it nevertheless.
I want to model the following situation. I have ASTs for a language in two
variatns: A "simple" form and a "labelled" form, e.g.
data SimpleExp = Num Int | Add SimpleExp SimpleExp
data LabelledExp = LNum Int String | LAdd LabelledExp LabelledExp String
I wonder what would be the best way to model this situation without
repeating the structure of the AST.
A trick we use all the time in the implementation of Epigram, for pretty
much the purpose you suggest, is to abstract over a type constructor
which packs recursive nodes. Thus
> type Node exp node = node (exp node)
> -- Node :: ((* -> *) -> *) -> (* -> *) -> *
> data Exp node = Num Int | Add (Node Exp node) (Node Exp node)
> -- Exp :: (* -> *) -> *
So now, with
> data Id x = An x
you get
> type SimpleExp = Node Exp Id
> type LabelledExp = Node Exp ((,) String)
Being incremental programmers, us Epigram folk also like syntax with holes
> type UnfinishedExp = Node Exp Maybe
Now we can make a node reshaping gadget like this
> renode :: ((Exp m -> Exp n) -> Node Exp m -> Node Exp n) ->
> Node Exp m -> Node Exp n
> renode transform me = transform inside me where
> inside (Num i) = Num i
> inside (Add me1 me2) = Add (renode transform me1) (renode
transform me2)
> unlabel :: LabelledExp -> SimpleExp
> unlabel = renode (\f (_,x) -> An (f x))
Of course, to see what's going on, you might want something like {-
needs -fglasgow-exts -}
> instance Show SimpleExp where
> show (An (Num i)) = "(Num " ++ show i ++ ")"
> show (An (Add x y)) = "(Add " ++ show x ++ " " ++ show y ++ ")"
So you get {- genuine output -}
*Nodes> unlabel ("fred", Add ("jim", Num 1) ("sheila", Num 2))
(Add (Num 1) (Num 2))
Of course, you can also play the same sort of game, making Node
explicitly a fixpoint operator and removingthe recursion from Exp, like
this:
newtype Node exp node = Node (node (exp (Node exp node)))
data Exp exp = Num Int | Add exp exp
but we don't, because it makes mutually defined syntactic categories get
way out of hand.
Third order programming. It's a whole other order.
Enjoy
Conor
--- End Message ---
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe