Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Printing an AST with variable names

Tags:

haskell

dsl

I am trying to implement an EDSL in Haskell. I would like to pretty print the AST with the variable names that are bound (if I can't get the real names then some generated names would do).

This is how far I have got with a simple example:

import Control.Monad.State

data Free f a = Roll (f (Free f a))
              | Pure a

instance Functor f => Monad (Free f) where
  return         = Pure
  (Pure a) >>= f = f a
  (Roll f) >>= g = Roll $ fmap (>>= g) f

data Expr a = I a
            | Plus (Expr a) (Expr a)
            deriving (Show)

data StackProgram a next = Pop  (a -> next)
                         | Push a next

instance Functor (StackProgram a) where
  fmap f (Pop    k) = Pop (f.k)
  fmap f (Push i x) = Push i (f x)

liftF :: Functor f => f a -> Free f a
liftF l = Roll $ fmap return l

push :: a -> Free (StackProgram a) ()
push i = liftF $ Push i ()

pop :: Free (StackProgram a) a
pop = liftF $ Pop id

prog3 :: Free (StackProgram (Expr Int)) (Expr Int)
prog3 = do
  push (I 3)
  push (I 4)
  a <- pop
  b <- pop
  return (Plus a b)

showSP' :: (Show a, Show b) => Free (StackProgram a) b -> [a] -> State Int String
showSP' (Pure a)           _        = return $ "return " ++ show a
showSP' (Roll (Pop f))    (a:stack) = do 
  i <- get
  put (i+1)
  rest <- showSP' (f a) stack
  return $ "var" ++ show i ++ " <- pop " ++ show (a:stack) ++ "\n" ++ rest
showSP' (Roll (Push i n))  stack    = do
  rest <- showSP' n (i:stack) 
  return $ "push " ++ show i ++ " " ++ show stack ++ "\n" ++ rest

showSP :: (Show a, Show b) => Free (StackProgram a) b -> [a] -> String
showSP prg stk = fst $ runState (showSP' prg stk) 0

Running this gives:

*Main> putStrLn $ showSP prog3 []
push I 3 []
push I 4 [I 3]
var0 <- pop [I 4,I 3]
var1 <- pop [I 3]
return Plus (I 4) (I 3)

So what I want is to replace Plus (I 4) (I 3) with Plus var0 var1. I have thought about walking through the rest of the tree and replacing the bound variables with name-value tuples, but I am not 100% sure if/how that would work. I'd also prefer to keep the original variable names, but I can't think of an easy way of doing this. I would prefer to have a fairly light-weight syntax in haskell (kind of as above).

I would also appreciate pointers to material that teaches me how to best do these kinds of things. I have read a bit on free monads and GADTs, but I guess I am missing how to put it all together.

like image 389
Paul Avatar asked Feb 15 '13 21:02

Paul


People also ask

Can you print variable name?

To print a variable's name: Use a formatted string literal to get the variable's name and value. Split the string on the equal sign and get the variable's name. Use the print() function to print the variable's name.

Can I create a variable with the name print in Python?

You can't, as there are no variables in Python but only names.


1 Answers

With the structure you have, you can't do this in "pure" Haskell code, because once your code is compiled, you can't distinguish (Plus a b) from (Plus (I 4) (I 3)) and keep "referential transparency" - the interchangeability of variables and their values.

However there are unsafe hacks - i.e. not guaranteed to work - that can let you do this kind of thing. They generally go under the name "observable sharing" and are based on getting access to the internals of how values are represented, using StableName. Essentially that gives you a pointer equality operation that allows you to distinguish between the reference to a and a new copy of the value (I 4).

One package that helps wrap up this functionality is data-reify.

The actual variable names used in your source will be irretrievably lost during compilation. In Paradise we use a preprocessor to translate foo <~ bar into foo <- withName "foo" $ bar before compilation, but it's hacky and it slows down builds quite a bit.

like image 131
GS - Apologise to Monica Avatar answered Oct 05 '22 23:10

GS - Apologise to Monica