[Haskell-cafe] Design of a DSL in Haskell

Tillmann Rendel rendel at informatik.uni-marburg.de
Wed Dec 5 14:48:14 CET 2012


Hi Joerg,

Joerg Fritsch wrote:
> I am interested in the definition of deep vs shallow embedded

I would say:

In shallow embedding, a DSL is implemented as a library. Every
keyword of the DSL is a function of the library. The
implementation of the function directly computes the result of
executing that keyword.

For example, here's a shallowly embedded DSL for processing
streams of integers:

> {-# LANGUAGE TemplateHaskell #-}
> module Stream where
> import Prelude (Integer, (+), (*), (.))
> import Language.Haskell.TH
>
> data Stream = Stream Integer Stream
>   deriving Show
> cycle x = Stream x (cycle x)
> map f (Stream x xs) = Stream (f x) (map f xs)

There is one domain-specific type, Stream, and one
domain-specific operation, map. The body of map directly contains
the implementation of mapping over a stream. Correspondingly, DSL
programs are immediately evaluated to their values:

> shallow :: Stream
> shallow = map (+ 1) (map (* 2) (cycle 1))



In deep embedding, a DSL is implemented as a library. Every
keyword of the DSL is a function of the library. The implemention
of the function creates a structural representation of the DSL
program.

For example, here's a deeply embedded version of the above DSL:

> data Program = Cycle Integer | Map (Integer -> Integer) Program

Here, the domain-specific operations are data constructors. The example 
program:

> deep :: Program
> deep = Map (+ 1) (Map (* 2) (Cycle 1))

We need a separate interpreter for actually executing the
program. The implementation of the interpreter can reuse cycle
and map from the shallow embedding:

> eval :: Program -> Stream
> eval (Cycle x) = cycle x
> eval (Map f p) = map f (eval p)
>
> value :: Stream
> value = eval deep

The benefit of deep embedding is that we can inspect the program,
for example, to optimize it:

> optimize :: Program -> Program
> optimize (Cycle x) = Cycle x
> optimize (Map f (Cycle x)) = Cycle (f x)
> optimize (Map f (Map g s)) = optimize (Map (f . g) s)
>
> value' :: Stream
> value' = eval (optimize deep)

   Tillmann



More information about the Haskell-Cafe mailing list