Designing DSL with explicit sharing [was: I love purity, but it's killing me]

Tom Hawkins wrote: ] My DSLs invariably define a datatype to capture expressions; something ] like this: ] ] data Expression ] = Add Expression Expression ] | Sub Expression Expression ] | Variable String ] | Constant Int ] deriving Eq ] The problem comes when I want to generate efficient code from an ] Expression (ie. to C or some other target language). The method I use ] invovles converting the tree of subexpressions into an acyclic graphic ] to eliminate common subexpressions. The nodes are then topologically ] ordered and assigned an instruction, or statement for each node. For ] example: ] ] let a = Add (Constant 10) (Variable "i1") ] b = Sub (Variable "i2") (Constant 2) ] c = Add a b ] The process of converting an expression tree to a graph uses either Eq ] or Ord (either derived or a custom instance) to search and build a set ] of unique nodes to be ordered for execution. In this case "a", then ] "b", then "c". The problem is expressions often have shared, ] equivalent subnodes, which dramatically grows the size of the tree. ] For example: ] ] let d = Add c c ] e = Add d d -- "e" now as 16 leaf nodes. ] ] As these trees grow in size, the equality comparison in graph ] construction quickly becomes the bottleneck for DSL compilation. We show the design of the same sort of DSL that explicitly maintains sharing information and where node comparisons are quick, because we are comparing hashes rather than trees themselves. Our approach is assuredly safe, pure, and Haskell98 (save for disabling of the monomorphism restriction, which is done solely to avoid writing signatures). No GHC-specific behavior is relied upon.
{-# OPTIONS_GHC -fno-monomorphism-restriction #-}
module DSL where
import Data.IntMap as IM import Control.Monad.State
The approach is based on the final tagless representation. Here is our DSL:
class Exp repr where constant :: Int -> repr Int variable :: String -> repr Int add :: repr Int -> repr Int -> repr Int sub :: repr Int -> repr Int -> repr Int
Tom Hawkins' test expressions now look as follows
a = add (constant 10) (variable "i1") b = sub (variable "i2") (constant 2) c = add a b d = add c c e = add d d
which is the same as before modulo the case of the identifiers: everything is in lower case. We can show the expressions as before: showing is one way of evaluating things
newtype S t = S{unS :: String}
instance Exp S where constant x = S $ show x variable x = S x add e1 e2 = S( unS e1 ++ " + " ++ unS e2) sub e1 e2 = S( unS e1 ++ " - " ++ unS e2)
test_showe = unS e
*DSL> test_showe "10 + i1 + i2 - 2 + 10 + i1 + i2 - 2 + 10 + i1 + i2 - 2 + 10 + i1 + i2 - 2" We can write an evaluator for the expressions
type REnv = [(String,Int)] newtype R t = R{unR :: REnv -> t} -- A reader Monad, actually
instance Exp R where constant x = R $ const x variable x = R ( \env -> maybe (error $ "no var: " ++ x) id $ Prelude.lookup x env) add e1 e2 = R(\env -> unR e1 env + unR e2 env) sub e1 e2 = R(\env -> unR e1 env - unR e2 env)
test_vale = unR e [("i1",5),("i2",10)] -- 92
We stress: we are using exactly the same expression e as before. We are only evaluating it differently. The gist of the final tagless approach is to write an expression once and evaluate it many times. Now, we chose a different representation: to make sharing explicit We chose not to rely on GHC; we don't care if in (add c c), the two c are shared or copied. It is not observable in pure Haskell, and we don't care. We build our acyclic graph nevertheless.
type ExpHash = Int
We stress: ACode is NOT a recursive data structure, so the comparison of ACode values takes constant time!
data ACode = AConst ExpHash | AVar ExpHash | AAdd ExpHash | ASub ExpHash deriving (Eq,Show)
data ExpMaps = ExpMaps{ hashcnt :: ExpHash, -- to generate new Hash ctmap :: IntMap Int, vrmap :: IntMap String, admap :: IntMap (ACode,ACode), sumap :: IntMap (ACode,ACode)} deriving Show exmap0 = ExpMaps 0 IM.empty IM.empty IM.empty IM.empty
newtype A t = A{unA :: State ExpMaps ACode}
Granted, the following could be done far more efficiently: we need bimaps.
loookupv :: Eq v => v -> IntMap v -> Maybe Int loookupv v = IM.foldWithKey (\k e z -> maybe (if e == v then Just k else Nothing) (const z) z) Nothing
record con prj upd x = do s <- get maybe (do let s' = upd (s{hashcnt = succ (hashcnt s)}) (IM.insert (hashcnt s) x (prj s)) put s' return (con $ hashcnt s)) (return . con) $ loookupv x (prj s)
instance Exp A where constant x = A(record AConst ctmap (\s e -> s{ctmap = e}) x) variable x = A(record AVar vrmap (\s e -> s{vrmap = e}) x) add e1 e2 = A(do h1 <- unA e1 h2 <- unA e2 record AAdd admap (\s e -> s{admap = e}) (h1,h2)) sub e1 e2 = A(do h1 <- unA e1 h2 <- unA e2 record ASub sumap (\s e -> s{sumap = e}) (h1,h2))
Again, we are using the very same expression e we wrote at the very beginning:
test_sme = runState (unA e) exmap0
*DSL> test_sme (AAdd 8, ExpMaps {hashcnt = 9, ctmap = fromList [(0,10),(4,2)], vrmap = fromList [(1,"i1"),(3,"i2")], admap = fromList [(2,(AConst 0,AVar 1)),(6,(AAdd 2,ASub 5)), (7,(AAdd 6,AAdd 6)),(8,(AAdd 7,AAdd 7))], sumap = fromList [(5,(AVar 3,AConst 4))]}) We retain all the information about expression 'e'. In addition, all sharing is fully explicit. As we can see, the evaluation process finds common subexpressions automatically.

On Feb 13, 2008 9:33 AM,
The approach is based on the final tagless representation. Here is our DSL:
class Exp repr where constant :: Int -> repr Int variable :: String -> repr Int add :: repr Int -> repr Int -> repr Int sub :: repr Int -> repr Int -> repr Int
This is very nice. May I ask, though, what is the purpose of all the Ints appearing as arguments to repr here? Looking over this code, it seems that it would work just as well if they were all omitted. Thanks, Luke

On Feb 13, 2008 5:36 AM, Luke Palmer
On Feb 13, 2008 9:33 AM,
wrote: The approach is based on the final tagless representation. Here is our DSL:
class Exp repr where constant :: Int -> repr Int variable :: String -> repr Int add :: repr Int -> repr Int -> repr Int sub :: repr Int -> repr Int -> repr Int
This is very nice. May I ask, though, what is the purpose of all the Ints appearing as arguments to repr here? Looking over this code, it seems that it would work just as well if they were all omitted.
In this example, they could be omitted. But let's say you had a
language more than one type:
class Exp repr where
constant :: Int -> repr Int
variable :: String -> repr Int
add :: repr Int -> repr Int -> repr Int
sub :: repr Int -> repr Int -> repr Int
true :: repr Bool
false :: repr Bool
and :: repr Bool -> repr Bool -> repr Bool
less_than :: repr Int -> repr Int -> repr Bool
if_ :: repr Bool -> repr a -> repr a -> repr a
The argument to repr prevents you from writing ill-typed code like
"if_ (variable "x") (constant 0) false".
--
Dave Menendez

Hi Oleg, it's not immediately clear (to me at least) how efficient your method will be in "practice". Any method based on common sub-expression elimination surely must inspect every node in the flattened graph. In the worst case, an acyclic graph containing n nodes could have 2^n nodes when flattened to a tree: tricky 0 = constant 0 tricky d = add g g where g = tricky (d-1) Of course, in "practice" the worst case may not occur. Also, my mental model is big circuits, which may be different to yours and Tom's. (Sorry if I'm just pointing out the obvious.) Matt.

Hello again, since Oleg presented an approach to the sharing problem that works on acyclic graphs, I may as well mention an alternative, pure, standard Haskell solution which is to express the fork points in the circuit (or expression), i.e. the points at which an expression is duplicated. You need to introduce a fork primitive: fork :: Bit -> (Bit, Bit) or fork :: Exp -> (Exp, Exp) This fits quite naturally in the context of circuit description, and I called it "expressible sharing". Under some mild restrictions, it even works on cyclic graphs. In particular, it works nicely for regular circuits. The "tricky" example I mentioned earlier would be written: tricky 0 = constant 0 tricky d = add e0 e1 where (e0, e1) = fork (tricky (d-1)) However, in the end I admitted defeat and decided I preferred observable sharing! Matt.

tricky 0 = constant 0 tricky d = add e0 e1 where (e0, e1) = fork (tricky (d-1))
Oops, I just realised that this isn't a very good example of expressible sharing! The problem is that it doesn't take any inputs, and expressible sharing just collapses (partially evaluates) operators when they are applied to constants. A better example would be something that takes an input, such as distrib a [] = [] distrib a (x:xs) = (a0, x) : distrib a1 xs where (a0, a1) = fork a Matt.
participants (4)
-
David Menendez
-
Luke Palmer
-
Matthew Naylor
-
oleg@okmij.org