KURE - A Haskell Hosted DSL for Writing Transformation Systemsandygill/talks/20090715-kure.pdf ·...

Preview:

Citation preview

KUREA Haskell Hosted DSL for Writing Transformation Systems

Andy Gill

The University of Kansas

July 15, 2009

Andy Gill (The University of Kansas) KURE July 15, 2009 1 / 27

Domain Specific Languages in Haskell

An Embedded Domain Specific Language is

simply a style of (Haskell) library.

You need to know Haskell!

User-code written in the DSL are centered

round a specific type (or types).

This talk: How to design a DSL using Haskell.

Andy Gill (The University of Kansas) KURE July 15, 2009 2 / 27

DSL Formula

Propose a small set of primitives;

Unify these combinators round a small number of type(s);

Postulate the monad that implements the primitives;

Wrap some structure round this monad, our principal type.

After this, the primitives in this shallow embedding are easy toimplement, using the monad, typically

Construction of our type, the atoms of our solution;

Combinators for our type, to compose solutions;

Execution of our type, to give a result.

Andy Gill (The University of Kansas) KURE July 15, 2009 3 / 27

Example Shallow Embedding

-- our principal type, Exprnewtype Expr = Expr (Maybe Int)

-- our way of constructing Expr’slit :: Int -> Exprlit n = Expr (Just n)

-- our way of composing Expr’splus :: Expr -> Expr -> Exprplus (Expr (Just v1)) (Expr (Just v2))

= Expr (Just (v1 + v2))plus _ _ = Expr Nothing

-- our way of running Expr’srunExpr :: Expr -> Maybe IntrunExpr (Expr v) = v

Andy Gill (The University of Kansas) KURE July 15, 2009 4 / 27

divide :: Expr -> Expr -> Exprdivide (Expr (Just v1)) (Expr (Just v2))

| v2 /= 0 = Expr (Just (v1 ‘div‘ v2))divide _ _ = Expr Nothing

*Main> runExpr (lit 1)Just 1*Main> runExpr (lit 1 ‘plus‘ lit 2)Just 3*Main> runExpr (lit 1 ‘divide‘ lit 2)Just 0*Main> runExpr (lit 1 ‘divide‘ lit 0)Nothing

Andy Gill (The University of Kansas) KURE July 15, 2009 5 / 27

What do we want our DSL to do?

Consider the first case rewriting rule from the Haskell 98 Report.

(a) case e of { alts } = (\v -> case v of { alts }) ewhere v is a new variable

Writing a rule that expresses this syntactical rewrite is straightforward.

rule_a :: ExpE -> Q ExpErule_a (CaseE e alts) = dov <- newName "v"return $ AppE (mkLamE [VarP v]

$ CaseE (VarE v) alts) erule_a _ = fail "rule_a not applicable"

KURE is a DSL that allows the structured promotion of locally acting rulesinto globally acting rules.

Andy Gill (The University of Kansas) KURE July 15, 2009 6 / 27

Basis of a Rewrite DSL

Combinator Purpose

id identity strategyfail always failing strategyS <+ S local backtrackingS ; S sequencingall(S) apply S to each immediate child<S> term apply S to term, giving a term result

Andy Gill (The University of Kansas) KURE July 15, 2009 7 / 27

Stratego Examples

Try a rewrite, and if it fails, do nothing.

try(s) = s <+ id

Repeatedly apply a rewrite, until it fails.

repeat(s) = try(s ; repeat(s))

Apply a rewrite in a topdown manner.

topdown(s) = s ; all(topdown(s))

New function for constant folding on an Add node.

EvalAdd : Add(Int(i),Int(j)) -> Int(<addS>(i,j))

Andy Gill (The University of Kansas) KURE July 15, 2009 8 / 27

What is our Principal Type?

T t1 t2

R t = T t t

Andy Gill (The University of Kansas) KURE July 15, 2009 9 / 27

Basic Operations in KURE

Combinator Type

id ∀t1. T t1 t1fail ∀t1, t2. T t1 t2S <+ S ∀t1, t2. T t1 t2 → T t1 t2 → T t1 t2S ; S ∀t1, t2, t3. T t1 t2 → T t2 t3 → T t1 t3

Andy Gill (The University of Kansas) KURE July 15, 2009 10 / 27

The KURE Monad

We list our requirements, then build our monad. We want the ability to

Represent failure

Represent identity

create new global binders

have a context

We use a monad transformer

M α = envread → m((α× envwrite × countwrite) + Fail)

Andy Gill (The University of Kansas) KURE July 15, 2009 11 / 27

Transformations and Monads

translate :: (t1 →M t2)→ T t1 t2

apply :: T t1 t2 → t1 →M t2

rewrite :: (t →M t)→ R t

Andy Gill (The University of Kansas) KURE July 15, 2009 12 / 27

Example: fib

data Exp = Val Int | Fib Exp | Add Exp Exp | Dec Exp

fibR :: R ExpfibR = rewrite $ \ e -> case e ofFib (Val 0) -> return $ Val 1Fib (Val 1) -> return $ Val 1Fib (Val n) -> return $ Add (Fib (Dec (Val n)))

(Fib (Dec (Dec (Val n))))_ -> fail "no match for fib"

eExpFibR :: R ExpeExpFibR =

repeatR (bottomupR (tryR (fibR <+ arithR)).+ failR "topdown done")

Andy Gill (The University of Kansas) KURE July 15, 2009 13 / 27

Where are we?

KURE allow us to build rewrite engines out of

small parts.

We can perform shallow and deep

transformations over a single type.

Most abstract syntax trees are constructed of

trees of multiple types.

Challenge (and main technical contribution of the paper)

Can we extend our typed rewrites to work over

multiple types?

Andy Gill (The University of Kansas) KURE July 15, 2009 14 / 27

What is the type of all?

all :: ∀t1. R t1 → R t1

OR

all :: ∀t1, t2. R t1 → R t2

Andy Gill (The University of Kansas) KURE July 15, 2009 15 / 27

Using a Universal Type

TP = ∀t1〈Term t1〉 ⇒ R t1

all :: TP→ TP

With a way to construct TP, we can combine rewrites on different types.

adhocTP :: ∀t1〈Term t1〉 TP→ R t1 → TPfailTP :: TP

all ((failTP ‘adhocTP‘ rr1) ‘adhocTP‘ rr2)

Andy Gill (The University of Kansas) KURE July 15, 2009 16 / 27

Our Typed Solution: Build Your Own Universal

Conceptually we want to pass in a tuple

all :: ∀t, t1, . . . , tn〈ti ∈ childrenOf t〉⇒ (R t1 ×R t2 × . . .×R tn)→ R t

But instead we work over a sum type

all :: ∀t, t1, . . . , tn〈ti ∈ childrenOf t〉⇒ R (t1 + t2 + . . .+ tn)→ R t

We do this using a type function, G

all :: ∀t〈G t〉 ⇒ R (G t)→ R t

where G is defined as

G ti = t1 + t2 + . . .+ tn where 0 < i ≤ n

Andy Gill (The University of Kansas) KURE July 15, 2009 17 / 27

Our Typed Solution: Build Your Own Universal

Conceptually we want to pass in a tuple

all :: ∀t, t1, . . . , tn〈ti ∈ childrenOf t〉⇒ (R t1 ×R t2 × . . .×R tn)→ R t

But instead we work over a sum type

all :: ∀t, t1, . . . , tn〈ti ∈ childrenOf t〉⇒ R (t1 + t2 + . . .+ tn)→ R t

We do this using a type function, G

all :: ∀t〈G t〉 ⇒ R (G t)→ R t

where G is defined as

G ti = t1 + t2 + . . .+ tn where 0 < i ≤ n

Andy Gill (The University of Kansas) KURE July 15, 2009 17 / 27

Our Typed Solution: Build Your Own Universal

Conceptually we want to pass in a tuple

all :: ∀t, t1, . . . , tn〈ti ∈ childrenOf t〉⇒ (R t1 ×R t2 × . . .×R tn)→ R t

But instead we work over a sum type

all :: ∀t, t1, . . . , tn〈ti ∈ childrenOf t〉⇒ R (t1 + t2 + . . .+ tn)→ R t

We do this using a type function, G

all :: ∀t〈G t〉 ⇒ R (G t)→ R t

where G is defined as

G ti = t1 + t2 + . . .+ tn where 0 < i ≤ n

Andy Gill (The University of Kansas) KURE July 15, 2009 17 / 27

The Term Class

class Term exp wheretype Generic *

-- | ’select’ selects into a ’Generic’ exp,-- to get the exp inside, or fails with Nothing.select :: Generic exp -> Maybe exp

-- | ’inject’ injects an exp into a ’Generic’ exp.inject :: exp -> Generic exp

Andy Gill (The University of Kansas) KURE July 15, 2009 18 / 27

Example instances of the Term Class

data OurGeneric = GStmt Stmt

| GExpr Expr

instance Term Stmt where

type Generic Stmt = OurGeneric

inject = GStmt

select (GStmt stmt) = Just stmt

select _ = Nothing

instance Term Expr where

...

Andy Gill (The University of Kansas) KURE July 15, 2009 19 / 27

The Walker Class, and other utils

class Term exp => Walker exp where

allR :: R (Generic exp) -> R exp

...

extractR :: (Term exp)

=> R (Generic exp) -> R exp

promoteR :: (Term exp)

=> R exp -> R (Generic exp)

Andy Gill (The University of Kansas) KURE July 15, 2009 20 / 27

Deep Traversals Attempt 1

-- INCORRECT TYPE, ATTEMPT 1

topdownR :: (Walker e)

=> R (Generic e)

-> R e

topdownR rr = extractR rr

>-> allR (promoteR (topdownR rr))

Type check failure!

Andy Gill (The University of Kansas) KURE July 15, 2009 21 / 27

Deep Traversals Attempt 2

-- INCORRECT TYPE, ATTEMPT 2

topdownR :: (Walker e)

=> R (Generic e)

-> R (Generic e)

topdownR rr = rr >-> allR (topdownR rr)

Problem: ‘Generic e’ itself is not an instance of G.

Andy Gill (The University of Kansas) KURE July 15, 2009 22 / 27

Universal Connector

tG

t1

77

Goooooooooooo

t2

??

G����

��

tn

gg

G OOOOOOOOOOOO

. . .

G..

Andy Gill (The University of Kansas) KURE July 15, 2009 23 / 27

Deep Traversals: Attempt 3

topdownR :: (Generic e ~ e, Walker e)=> R (Generic e)-> R (Generic e)

topdownR rr = rr >-> allR (topdownR rr)

Andy Gill (The University of Kansas) KURE July 15, 2009 24 / 27

Adding the OurGeneric instance

data OurGeneric = GStmt Stmt| GExpr Expr

instance Term Stmt wheretype Generic Stmt = OurGenericinject = GStmtselect (GStmt stmt) = Just stmtselect _ = Nothing

instance Term Expr where...

instance Term OurGeneric wheretype Generic OurGeneric = OurGenericinject e = eselect e = Just e

Andy Gill (The University of Kansas) KURE July 15, 2009 25 / 27

Review: DSL Formula

Propose a small set of primitives;

Unify these combinators round a small number of type(s);

Postulate the monad that implements the primitives;

Wrap some structure round this monad, our principal type.

After this, the primitives in this shallow embedding are easy toimplement, using the monad, typically

Construction of our type, the atoms of our solution;

Combinators for our type, to compose solutions;

Execution of our type, to give a result.

Andy Gill (The University of Kansas) KURE July 15, 2009 26 / 27

Considerations and Conclusions

DSLs are a way to structure code in a general purpose language.

Types Functions are a useful addition to Haskell.

Need to be a fan of the Haskell cool-aid.

What about debugging?

Andy Gill (The University of Kansas) KURE July 15, 2009 27 / 27

Recommended