32
Zelfgemaakt datatype voor bomen Met functies data Tree a = Bin (Tree a) (Tree a) | Leaf a foldTree :: Tree a foldTree (b,lf) (Bin le ri) = b (foldTree (b,lf) le) (foldTr foldTree (b,lf) (Leaf x) = lf x bbb ( , ) ab foldTree :: (bbb , ab)Tree a foldTree (b,lf) = f where f (Bin le ri) = b (f le) (f ri f (Leaf x) = lf x

Zelfgemaakt datatype voor bomen

  • Upload
    nailah

  • View
    29

  • Download
    0

Embed Size (px)

DESCRIPTION

Zelfgemaakt datatype voor bomen. data Tree a = Bin ( Tree a ) ( Tree a ) | Leaf a. Met functies. foldTree :: Tree a  b foldTree (b,lf) ( Bin le ri) = b (foldTree (b,lf) le) (foldTree (b,lf) ri) foldTree (b,lf) ( Leaf x) = lf x. - PowerPoint PPT Presentation

Citation preview

Page 1: Zelfgemaakt datatype voor bomen

Zelfgemaakt datatypevoor bomen

Met functies

data Tree a= Bin (Tree a) (Tree a)| Leaf a

foldTree :: Tree a b

foldTree (b,lf) (Bin le ri) = b (foldTree (b,lf) le) (foldTree (b,lf) ri)foldTree (b,lf) (Leaf x) = lf x

bbb( , )abfoldTree :: (bbb , ab)Tree a b

foldTree (b,lf) = f wheref (Bin le ri) = b (f le) (f ri)f (Leaf x) = lf x

Page 2: Zelfgemaakt datatype voor bomen

Voorbeelden van algebras

data Tree a= Bin (Tree a) (Tree a)| Leaf a

type TreeAlgebra a b = ( b b b , a b )

data Expr= Add Expr Expr| Mul Expr Expr| Con Int

type ExprAlgebra b = ( b b b , b b b , Int b )

data Expr= Add Expr Expr| Mul Expr Expr| Con Int| Var String

type ExprAlgebra b = ( b b b , b b b , Int b , String b )

Page 3: Zelfgemaakt datatype voor bomen

Definitie “een algebra”

Een algebrabestaat uit een type

functies in een tupel

countLeafsFuns :: TreeAlgebra a IntcountLeafsFuns = ( (+) , \x1 )

Een algebrabestaat uit een type

dat het resultaat is van een fold, die functies in een tupel

neerzet in plaats van constructorfuncties

Een algebra voor een datatypebestaat uit een type

dat het resultaat is van een fold, die functies in een tupel

neerzet in plaats van constructorfuncties van dat datatype

“carrier set”

“semantiek”

Page 4: Zelfgemaakt datatype voor bomen

Algebras voor wederzijdsrecursieve datatypes

data Stat a= Assign String (Expr a)| Print (Expr a)| Block [Stat a]data Expr a= Con a| Var String| Add (Expr a) (Expr a)

type StatExprAlgebra a s e= ( ( String e s , e s , [ s ] s ) , ( a e , String e , e e e ) )

foldStatExpr :: StatExprAlgebra a s e Stat a sfoldStatExpr ((f1,f2,f3),(g1,g2,g3)) = f where f (Assign x e) = f1 x (g e) f (Print e) = f2 (g e) f (Block ss) = f3 (map f ss) g (Con c) = g1 c g (Var x) = g2 x g (Add e1 e2)= g3 (g e1) (g e2)

Page 5: Zelfgemaakt datatype voor bomen

Definitie van foldExpr

data Expr= Add Expr Expr| Mul Expr Expr| Con Int

type ExprAlgebra b = ( b b b , b b b , Int b )

foldExpr :: ExprAlgebra b Expr bfoldExpr (a,m,c) = f where f (Add e1 e2) = a (f e1) (f e2) f (Mul e1 e2) = m(f e1) (f e2) f (Con n) = c n

Page 6: Zelfgemaakt datatype voor bomen

Gebruik van ExprAlgebra

data Expr= Add Expr Expr| Mul Expr Expr| Con Int

type ExprAlgebra b = ( b b b , b b b , Int b )

evalExpr :: Expr IntevalExpr = foldExpr evalExprAlgebra

evalExprAlgebra :: ExprAlgebra IntevalExprAlgebra = ( (+) , (*) , id )

Page 7: Zelfgemaakt datatype voor bomen

Taal: syntax en semantiek

“ 3 + 4 * 5 ”

Add (Con 3) (Mul (Con 4) (Con 5))

parseExpr

evalExpr

23

= start p where p = …<|>…<*>…

= fold a where a = (…,…,…,…)

Page 8: Zelfgemaakt datatype voor bomen

Compositionaliteit

Een semantiek is compositioneel als de betekenis van een geheel een functie is van de betekenissen van de deleneval (Add x y) = add (eval x) (eval y)

Een compositionele semantiekkun je schrijven als fold over de expressiewaarbij een algebra vervangingen geeftvoor de constructoren

Page 9: Zelfgemaakt datatype voor bomen

Verschillende semantieken

“ 3 + 4 * 5 ”

Add (Con 3) (Mul (Con 4) (Con 5))

23

evalExpr compileExpr

Push 3Push 4Push 5Apply (*)Apply (+)

runExpr

parseExpr

:: String

:: Expr

:: Int :: Code

= fold a where a = (…,…,…,…) a::ExprAlgebra Int

= fold a where a = (…,…,…,…) a::ExprAlgebra Code

Page 10: Zelfgemaakt datatype voor bomen

De compileer-semantiek

Wat is “machinecode” ?

Wat is een “machine-instructie” ?

type Code = [ Instr ]

data Instr = Push Int | Apply (IntIntInt)

Page 11: Zelfgemaakt datatype voor bomen

Compiler:genereren van Code

data Expr= Add Expr Expr| Mul Expr Expr| Con Int

type ExprAlgebra b = ( b b b , b b b , Int b )

evalExpr :: Expr IntevalExpr = foldExpr evalExprAlgebra where evalExprAlgebra :: ExprAlgebra Int evalExprAlgebra = ( (+) , (*) , id )

compExpr :: Expr CodecompExpr = foldExpr compExprAlgebra where compExprAlgebra :: ExprAlgebra Code compExprAlgebra = ( add , mul , con )

mul :: Code Code Codemul c1 c2 = c1 ++ c2 ++ [Apply (*)]con n = [ Push n ]

Page 12: Zelfgemaakt datatype voor bomen

Verschillende semantieken

“ 3 + 4 * 5 ”

Add (Con 3) (Mul (Con 4) (Con 5))

23

evalExpr compileExpr

Push 3Push 4Push 5Apply (*)Apply (+)

runExpr

parseExpr

:: String

:: Expr

:: Int :: Code

= fold a where a = (…,…,…,…) a::ExprAlgebra Int

= fold a where a = (…,…,…,…) a::ExprAlgebra Code

Page 13: Zelfgemaakt datatype voor bomen

Runner:simulatie van processor

run :: Code Stack Stackrun [ ] stack = stackrun (instr:rest) stack = exec instr stackrun rest ( )

exec :: Instr Stack Stackexec (Push x) stack = x : stackexec (Apply f) (y:x:stack) = f x y : stack

runExpr :: Code IntrunExpr prog = run prog [ ]head ( )

Page 14: Zelfgemaakt datatype voor bomen

Compiler correctheid

evalExpr

“ 3 + 4 * 5 ”

Add (Con 3) (Mul (Con 4) (Con 5))

23

compileExpr

Push 3Push 4Push 5Apply (*)Apply (+)

runExpr

parseExpr

runExpr (compileExpr e)=

evalExpr e

Page 15: Zelfgemaakt datatype voor bomen

Uitrekenen vanexpressies met variabelen

data Expr= Add Expr Expr| Mul Expr Expr| Con Int

type ExprAlgebra b = ( b b b , b b b , Int b )

evalExpr :: Expr IntevalExpr = foldExpr eAlgebra where eAlgebra :: ExprAlgebra Int eAlgebra = ( (+) , (*) , id )

data Expr= Add Expr Expr| Mul Expr Expr| Con Int| Var String

type ExprAlgebra b = ( b b b , b b b , Int b , String b )

, ???? )

evalExpr :: Env Expr IntevalExpr env = foldExpr eAlgebra where eAlgebra :: ExprAlgebra Int eAlgebra = ( (+) , (*) , id , ???? ), (env ?) )

BAD !!!

Page 16: Zelfgemaakt datatype voor bomen

Uitrekenen vanexpressies met variabelen

data Expr= Add Expr Expr| Mul Expr Expr| Con Int| Var String

type ExprAlgebra b = ( b b b , b b b , Int b , String b )

evalExpr :: Expr Env IntevalExpr env = foldExpr eAlgebra where eAlgebra :: ExprAlgebra Int eAlgebra = ( (+) , (*) , id , (env?) )

evalExpr :: Expr (EnvInt) evalExpr = foldExpr eAlgebra where eAlgebra :: ExprAlgebra Int eAlgebra = ( add, mul, con, var )

(EnvInt)

(EnvInt)

evalExpr’ :: Expr IntevalExpr’ expr = evalExpr expr [ ]

Page 17: Zelfgemaakt datatype voor bomen

Uitrekenen vanexpressies met definities

evalExpr :: Expr Env IntevalExpr env = foldExpr eAlgebra where eAlgebra :: ExprAlgebra (EnvInt) eAlgebra = ( add , mul , con , var )

data Expr= Add Expr Expr| Mul Expr Expr| Con Int| Var String

type ExprAlgebra b = ( b b b , b b b , Int b , String b )

, def )

data Expr= Add Expr Expr| Mul Expr Expr| Con Int| Var String| Def String Expr Expr

type ExprAlgebra b = ( b b b , b b b , Int b , String b , Stringbb b )

Page 18: Zelfgemaakt datatype voor bomen

Uitrekenen vanexpressies met definitiesadd :: b b b (EnvInt) (EnvInt) (EnvInt)Env Int

mul :: b b b (EnvInt) (EnvInt) (EnvInt)Env Int

con :: Int b Env Int

var :: String b Env Int

def :: String b b b (EnvInt) (EnvInt) (EnvInt)Env Int

mul f g e = f e * g e

con n e = n

var x e = e ? x

def x fd fb e =fb e(x, )( : )fd e

con = const

var = flip (?)

def = (<:=>)

add f g e = f e + g e

Page 19: Zelfgemaakt datatype voor bomen

Verschillende semantieken

“ 3 + 4 * 5 ”

Add (Con 3) (Mul (Con 4) (Con 5))

23

evalExpr compileExpr

Push 3Push 4Push 5Apply (*)Apply (+)

runExpr

parseExpr

:: String

:: Expr

:: Int :: Code

= fold a where a = (…,…,…,…) a::ExprAlgebra Int

= fold a where a = (…,…,…,…) a::ExprAlgebra Code

Page 20: Zelfgemaakt datatype voor bomen

add :: b b b

mul :: b b b

con :: Int b

var :: String b

def :: String b b b

Compileren vanexpressies met definities

mul f g e =

con n e = [ Push n ]

var x e = e ? x

def x fd fb e =fb ( (x, fd e) : e )

add f g e = f e ++ g e ++ [Apply (+)](EnvCode) (EnvCode) Env Code

Env Code

Env Code

(EnvCode) (EnvCode) Env Code

(EnvCode) (EnvCode) Env Code

f e ++ g e ++ [Apply (*)]

Page 21: Zelfgemaakt datatype voor bomen

Wat zit er in het Env ?

evalExpr

compExpr

type Env = [ (String, Int) ]

type Env = [ (String, Code) ]

Page 22: Zelfgemaakt datatype voor bomen

Compiler correctheidexpressies met definities

evalExpr

“ 3 + 4 * 5 ”

Add (Con 3) (Mul (Con 4) (Con 5))

23

compileExpr

Push 3Push 4Push 5Apply (*)Apply (+)

runExpr

parseExpr

hd (run (compileExpr e) s)=

evalExpr e

runExpr (compileExpr e env)=

evalExpr e env

Page 23: Zelfgemaakt datatype voor bomen

Voorbeeld compileren van expressie

“ 3+4*5 ”

Push 3Push 4Push 5Apply (*)Apply (+)

Push 3Push 2Push 2Apply (+)Push 5Apply (*)Apply (+)

parseExpr

compileExpr

“let x=2+2 in 3+x*5 ”

parseExpr

compileExpr

Push 2Push 2Apply (+)

x

Page 24: Zelfgemaakt datatype voor bomen

Voorbeeld compileren van expressie

Push 3Push 2Push 2Apply (+)Push 5Apply (*)Apply (+)

“let x=2+2 in 3+x*5 ”

parseExpr

compileExpr

Push 2Push 2Apply (+)

x

“let x=2+2 in 3+x*x ”

parseExpr

compileExpr

Push 3Push 2Push 2Apply (+)Push 2Push 2Apply (+)Apply (*)Apply (+)

Page 25: Zelfgemaakt datatype voor bomen

De compileer-semantiek

Wat is “machinecode” ?

Wat is een “machine-instructie” ?

type Code = [ Instr ]

data Instr = Push Int | Apply (IntIntInt)

data Instr = Push Int | Apply (IntIntInt) | Load Adres | Store Adres

Aanpassing van

Page 26: Zelfgemaakt datatype voor bomen

add :: b b b

mul :: b b b

con :: Int b

var :: String b

def :: String b b b

Efficient compileren vanexpressies met definities

mul f g e =

con n e = [ Push n ]

var x e = e ? x

def x fd fb e =fb ( (x, fd e) : e )

add f g e = f e ++ g e ++ [Apply (+)](EnvCode) (EnvCode) Env Code

Env Code

Env Code

(EnvCode) (EnvCode) Env Code

(EnvCode) (EnvCode) Env Code

f e ++ g e ++ [Apply (*)]

[ Load (e?x) ]

fd e ++ [Store a] ++ fb ((x,a):e)

where a = length e

Page 27: Zelfgemaakt datatype voor bomen

Wat zit er in het Env ?

evalExpr

compExpr

efficientCompExpr

type Env = [ (String, Int) ]

type Env = [ (String, Code) ]

type Env = [ (String, Adres) ]

Page 28: Zelfgemaakt datatype voor bomen

Runner:simulatie van processor

run :: Code Stack Stackrun [ ] stack = stackrun (instr:rest) stack = exec instr stackrun rest ( )

exec :: Instr Stack Stackexec (Push x) stack = x : stackexec (Apply f) (y:x:stack) = f x y : stack

runExpr :: Code IntrunExpr prog = run prog [ ]head ( )

Page 29: Zelfgemaakt datatype voor bomen

Runner: aangepastesimulatie van processor

run :: Code (Mem,Stack) (Mem,Stack)run [ ] ms = msrun (instr:rest) ms = exec instr msrun rest ( )

exec :: Instr (Mem,Stack) (Mem,Stack)exec (Push x) (m, st) = (m, x : st )exec (Apply f) (m, y:x:st)= (m, f x y : st )exec (Load a) (m, st) = (m, m!a : st )exec (Store a) (m, x: st) = (update m a x, st )

Page 30: Zelfgemaakt datatype voor bomen

Voorbeeld Blokgestructureerde talen“use x;dcl x;{ use z ; use y ; dcl x ; dcl z ; use x };dcl y;use y”

Enter (0,2)Access(0,0)Enter (1,2)Access (1,1)Access (0,1)Access (1,0)Leave (1,2)Access(0,1)Leave (0,2)

parse compile

Page 31: Zelfgemaakt datatype voor bomen

Definitie van Block-type, -algebra & -fold

data Block= Cons Stat Block| Emptydata Stat= Decl Naam| Use Naam| Blk Block

type BlockAlgebra b s= ( ( s b b , b ) , ( Naam s , Naam s , b s ) )

foldBlock :: BlockAlgebra b s Block bfoldBlock ((c,e),(d,u,b)) = f where f (Cons (s:b)) = c (g s) (f b) f Empty = e g (Decl x) = d x g (Use x) = u x g (Blk n) = b (f n)

Page 32: Zelfgemaakt datatype voor bomen

Compileren van een Block

compBlock :: Block CodecompBlock = foldBlock cAlg where

cAlg :: BlockAlgebra Code cAlg = ( (c,e), (d,u,b)) where

c = …e = …d = …u = …b = …

(EnvCode)

Env Code

(GEnv LEnvCode)

(GEnv LEnvCode)

(GEnv LEnv(LEnv,Code))

(GEnv LEnv(LEnv,Code))

InheritedattribuutInheritedattribuut

Inheritedattribuut

Synthesizedattribuut