[Haskell-cafe] Tagless interpreter, expression problem and zipper

Roel van Dijk vandijk.roel at gmail.com
Thu Mar 10 00:09:01 CET 2011


Both your replies where very helpful. I combined both approaches to
get nearer to what I want.

> class Lit α where lit ∷ Integer → α
> class Add α where add ∷ α → α → α

> instance Lit Integer where lit = fromInteger
> instance Add Integer where add = (+)

This time I require TypeSynonymInstances:
> instance Lit String where lit = show
> instance Add String where add x y = "(" ++ x ++ " + " ++ y ++ ")"

Felipe's generalized context type:
> data AddCtx α = Empty
>               | AddL α (AddCtx α)
>               | AddR α (AddCtx α)

Combination of Oleg's tagless transformer and Felipe's CtxInterpB:
> instance (Add α, Add β) ⇒ Add (AddCtx β → α, β) where
>     add (xa, xb) (ya, yb) = ( \c → add (xa (AddL yb c))
>                                        (ya (AddR xb c))
>                             , add xb yb
>                             )
The previous instance allows me to construct Strings while having
Integers in the context.

Silly interpreter, version 2.0
> instance Lit (AddCtx Integer → String, Integer) where
>     lit n = ( \c → case c of
>                      AddL 3 _ → "Foo!"
>                      _ → lit n
>             , lit n
>             )

Simple term:
> t1 ∷ (Lit α, Add α) ⇒ α
> t1 = lit 2 `add` lit 3

Interpret as a String:
> bar = let (f, x) = t1 ∷ (AddCtx Integer → String, Integer)
>       in f Empty

>> "(Foo! + 3)"

This is already an improvement to my current code. But I am not
entirely satisfied. I can pick and choose which structures to use in
my terms but the context type is still an ordinary data type. Each
module which extends the expression language with new structures needs
to define a complicated context type.

My plan is to define the context as a type class. Obviously I can't
perform case analysis on a polymorphic type so I'll have to add that
functionality to each context class in some way.

Thank you for your helpful replies!



More information about the Haskell-Cafe mailing list