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

Roel van Dijk vandijk.roel at gmail.com
Tue Mar 8 21:43:12 CET 2011


Hello everyone,

I am stuck rewriting some code in the tagless style. My problem can be
thought of as an interpreter for a very simple language:

> data Exp = Lit Integer
>          | Add Exp Exp
>          | Mul Exp Exp
>            deriving (Show)

But some complexity is added by the fact that my interpreter also
needs to know the context in which literals appear in an
expression. So given the example

> t1 :: Exp
> t1 = (Lit 3 `Add` Lit 4) `Mul` Lit 2

I want to have access to the fact that the literal 3 appears on
the left side of an addition. Therefore I created a type:

> data Ctx = Empty
>          | AddL Exp Ctx
>          | AddR Exp Ctx
>          | MulL Exp Ctx
>          | MulR Exp Ctx
>            deriving (Show)

This is almost a zipper over the Exp type. I left out a context for
literals themselves because it wasn't necessary. Now I can create a
simple evaluation function:

> eval :: (a -> a -> a)
>      -> (a -> a -> a)
>      -> (Integer -> Ctx -> a)
>      -> Exp
>      -> a
> eval add mul lit = go Empty
>     where
>       go ctx (Lit n)   = lit n ctx
>       go ctx (Add x y) = let x' = go (AddL y ctx) x
>                              y' = go (AddR x ctx) y
>                          in x' `add` y'
>       go ctx (Mul x y) = let x' = go (MulL y ctx) x
>                              y' = go (MulR x ctx) y
>                          in x' `mul` y'

This function can evaluate an expression to any type 'a', but it needs
some additional functions to accomplish that: add, mul and lit. Notice
how the 'lit' function has access to a literal's context. To interpret
an Exp as an Integer I use:

> evalInt :: Exp -> Integer
> evalInt = eval (+) (*) const

Or as a String:

> evalStr1 :: Exp -> String
> evalStr1 = eval addStr mulStr (const . show)

> addStr x y = "(" ++ x ++ " + " ++ y ++ ")"
> mulStr x y = "(" ++ x ++ " * " ++ y ++ ")"

Or a silly example which uses the context:

> evalStr2 :: Exp -> String
> evalStr2 = eval addStr mulStr lit
>     where
>       lit _ (AddL (Lit 4) (MulL _ _)) = "Foo!"
>       lit n _ = show n

The silly example replaces a literal with "Foo!" if it appears on the
left side of an addition with 4, and the whole addition is the left
side of a multiplication, like in (x + 4) * ?.

All of this works. But I want to be able to add additional
constructors to the Exp language without changing existing code. This
looks like the expression problem.

Ignoring the zipper-like context I came up with the following:

First define the language:
> class Lit a where lit :: Integer -> a
> class Add a where add :: a -> a -> a
> class Mul a where mul :: a -> a -> a

Integer interpreter:
> instance Lit Integer where lit = fromInteger
> instance Add Integer where add = (+)
> instance Mul Integer where mul = (*)

String interpreter, using a newtype so I don't need
TypeSynonymInstances:
> newtype Str = Str {unS :: String}
> instance Show Str where show = show . unS

> instance Lit Str where lit = Str . show
> instance Add Str where add x y = Str $ addStr (unS x) (unS y)
> instance Mul Str where mul x y = Str $ mulStr (unS x) (unS y)

Same example expression, now polymorphic:
> t1 :: (Lit a, Add a, Mul a) => a
> t1 = (lit 3 `add` lit 4) `mul` lit 2

This expression can now be interpreted in multiple ways:
> t1 :: Integer
>> 14
> t1 :: Str
>> "((3 + 4) * 2)"

This solves the expression problem. I can add new structures to my
language in other modules without having to change existing code. The
necessary parts are mentioned in the type constraint (Lit a, Add a,
Mul a).

But I lost the power of the context! How do I get it back?

Attached are the two approaches, WithTags.hs and Tagless.hs (but
without context).

Any help would be greatly appreciated!
-------------- next part --------------
A non-text attachment was scrubbed...
Name: WithTags.hs
Type: text/x-haskell
Size: 1121 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110308/721cfad9/attachment.hs>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: Tagless.hs
Type: text/x-haskell
Size: 700 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110308/721cfad9/attachment-0001.hs>


More information about the Haskell-Cafe mailing list