Sunteți pe pagina 1din 294

Compiler Construction

Lecture 01

Lent Term, 2007

Lecturer: Timothy G. Griffin

Computer Laboratory
University of Cambridge
1
Compilation is a type of Translation

A good compiler should …


Java C++
Program Program • be correct in the
translate sense that meaning
is preserved
compile • be efficient

Trade offs abound!!


• generate efficient
code
Pentium III
code • produce usable error
messages
• be well-structured
Compilation is a translation
From “high level” to “low level” and maintainable
2
All Hail Grace Hopper !

Wrote first compiler in 1951


for the Short Code language,
while working for Remington Rand.

The compiler was called A-0.

She wrote it because she found the


normal process of compiling Short Code by
hand was boring and tedious, and she
wanted to spend her time doing “interesting
mathematics” instead of tasks that
could be done by a stupid machine.

(note: as with all claims of priority this


one will be endlessly disputed….) 3
Why Study Compilers?

• Although many of the basic ideas where


developed over 30 years ago, compiler
construction is still an evolving and active
area of research and development.
• Compilers are intimately related to
programming language design and evolution.
• Compilers are a Computer Science success
story that illustrate the hallmarks of our field
--- high-level abstractions implemented with
low-level resources.
• You are computer scientist. Nothing done
with machines should be mysterious to you!
4
http://merd.sourceforge.net/pixel/language-study/diagram.html more here

Lines of descent should


not be taken too seriously.
Perl from Algol 60?

5
OCAML
http://caml.inria.fr/

Ocaml is a dialect of ML

This course will frequently mine the Ocaml


compiler for examples.

let rec map f l =


match l with
[] -> []
| head::tail -> (f head) :: (map f tail)

Inferred type is

(‘a -> ‘b) -> ‘a list -> ‘b list


6
MinCaml:
A Simple and Efficient Compiler
for a Minimal Functional Language
SIGPLAN :Proceedings of the 2005 workshop on
Functional and declarative programming in education

美しい日本の ML コンパイラ
Eijiro Sumii
Tohoku University
http://www.kb.ecei.tohoku.ac.jp/~sumii/

http://min-caml.sourceforge.net/
7
The MinCaml Language
A minimal functional language

8
Mind The Gap
let rec gcd m n = MinCaml
if m = 0 then n else
if m <= n then gcd m (n - m) else gcd n (m - n)
in print_int (gcd 21600 337500)

.section ".rodata"
.global min_caml_start
.align 8
min_caml_start:
.section ".text"
save %sp, -112, %sp
gcd.7:
set 21600, %i2
cmp %i2, 0
set 337500, %i3
bne be_else.19
Compile st %o7, [%i0 + 4]
nop
call gcd.7
mov %i3, %i2
add %i0, 8, %i0 ! delay slot
retl
sub %i0, 8, %i0
nop
ld [%i0 + 4], %o7
be_else.19:
st %o7, [%i0 + 4]
cmp %i2, %i3
call min_caml_print_int
bg ble_else.20
add %i0, 8, %i0 ! delay slot
nop
sub %i0, 8, %i0
sub %i3, %i2, %i3
ld [%i0 + 4], %o7
b gcd.7
ret
nop
restore
ble_else.20:
sub %i2, %i3, %i2
mov %i3, %o4
mov %i2, %i3 SPARC assember
mov %o4, %i2 9
b gcd.7
nop
A closer look at the Gap

High Level Language Assembly Language

• Machine independent • Machine specific


• Complex syntax • Simple syntax
• Variables • Locations and registers
• Nested scope • One flat scope
• Complex data types • Bytes, words
• Procedures, functions • A simple stack
• … • …
10
Our Approach ---
Compilation as a sequence of transformations

Intermediate languages Target


Source language
language (assembler)

L1 ⇒L2 ⇒ L3 ⇒⋯⇒ Ln−1 ⇒ L n

• Each transformation preserves semantics


• Each transformation addresses only one aspect
of “the gap”
• Each transformation is fairly easy to understand.
11
The Shape of a Compiler

The Compiler
Hardware
targeted
Program executable
Front-end Middle-end Back-end
Text code

Hardware independent
intermediate code INTERPRET!

Interpreter
(example: JVM) RUN!

Operating System
Something to Ponder:
A compiler is just a program.
But how did it get compiled?
Raw Metal
Is this a chicken-and-egg
problem? 12
The Shape of a Front End

Front-end Error messages


indicating syntactic
errors in program
Program text
Lexical
Text Parsing
analysis lexical
tokens Parse Tree
(Abstract Syntax
Tree)

Lexical theory based Parsing Theory


on finite automaton based on push-down
and regular automaton and
expressions context-free grammars

13
The Shape of a “Middle End”

middle-end

Intermediate-Code
Parse Tree
Analysis of symbol Type Intermediate
definition and use. code
Checking Annotated generation
Annotated
Parse tree Parse tree

Error reporting. Error reporting.


“variable x on line “variable x declared
17 of file main.c not as a string but used This phase may
declared” as an integer” involve many
passes,
several distinct
… there is a lot of diversity in the intermediate
“middle-end” -- some compilers are complex languages, and
while others are very simple… multiple optimization
algorithms. 14
The Shape of a Back End

Assembly code
Back end

x86 code generation x86 code

Intermediate
ARM code generation ARM code
code
Target?
SPARC code generation SPARC code



PDP-11 code generation PDP-11 code

15
Assembly, Linking, Loading

assembly
code file
assembly
code file
… assembly
code file
(main tasks)

From symbolic


names and
addresses to
assembler assembler assembler numeric codes
and numeric


addresses

object object object


code file code file code file

Name
Object code linker resolution,
Link errors creation of
libraries single address
space
single executable object code file
RUN! Address
relocation,
Operating System memory
loader allocation,
dynamic
16
linking
Reading

• Compiler Design in Java/C/ML (3 books). Appel.


(1996)
Main Text

• Compilers --- Principles, Techniques, and Tools.


Aho, Sethi, and Ullman (1986)
• Compiler Design. Wilhelm, Maurer (1995)
• Introduction to Compiling Techniques. Bennett
(1990).
• A Retargetable C Compiler: Design and
Implementation. Frazer, Hanson (1995)
• Compiler Construction. Waite, Goos (1984)
• High-level Languages and Their Compilers. Watson
(1989)
17
The Shape of this Course
1. Overvi ew
2. Le xical An alys is
3. The ory of Con te xt Fr ee
January 2007 Gra mma rs ( CF Gs) and P red ictive Front End
M T W T F S S (re cur siv e d esce nt ) P ar sing
1 2 3 4 5 6 7 4. LR P arsi ng I
5. LR P arsi ng I I
8 9 10 11 12 13 14
15 16 17 18 19 20 21 7. Type ch eck ing
22 23 24 25 26 27 28 Middle and
8. Var iab le S cop e
29 30 31 9. Fu nct ion Clo sure s
back-end.
10. Usin g th e S ta ck I Using
February 2007 11. Usin g th e S ta ck II Min-Caml as
M T W T F S S 12. As semb ler , lin ke r, ob jec t f iles running
1 2 3 4 13. As semb ler ge ne ra tio n example
14. As semb ler ge ne ra tio n
5 6 7 8 9 10 11
12 13 14 15 16 17 18 16. Con tin uat ions
19 20 21 22 23 24 25 17. Objec t O rien ta tion
26 27 28 18. Garb ag e Co llec tio n Special
19. Inte rp re te rs , By te Co de topics
inte rp re te rs, vir tu al ma ch in es

21. Revi ew
18
Compiler Construction
Lecture 02
Lexical Analysis

Lent Term, 2007

Lecturer: Timothy G. Griffin

Computer Laboratory
University of Cambridge
1
The Front-End

Front-end Error messages


indicating syntactic
errors in program
Program text
Lexical
Text Parsing
analysis lexical
tokens Parse Tree
(Abstract Syntax
Tree)

Lexical theory based Parsing Theory


on finite automaton based on push-down
and regular automaton and
expressions context-free grammars

2
From Character Streams to Token Streams

float match0(char *s) /* find a zero */


{
if (!strncmp(s, “0.0”, 3))
return 0. ;
}

lexer

T
FLOAT ID(match0) LPAREN CHAR STAR
O
ID(s) RPAREN LBRACE IF LPAREN BANG
K
ID(strncmp) LPAREN ID(s) COMMA STRING(0.0)
E
COMMA NUM(3) RPAREN RPAREN RETURN
N
REAL(0.0) SEMI RBRACE EOF
S

3
Note that white-space and comments have vanished!
Regular Sets

Let Σ be a finite alphabet.


1. Φ is a regular set over ∑ (the empty
set)
2. {Λ} is a regular set over ∑ (Λ is the
string of length zero)
3. ∀a ∈ Σ, {a} is a regular set over ∑.
4. If P and Q are regular sets over ∑,
a. (Set Union) P ∪ Q is a regular set over ∑.
b. (String Concatenation) PQ is a regular set
over ∑.
c. (Kleene Closure) P* is a regular set over ∑
5. Nothing else is a regular set over ∑.

“Representation of Nerve Nets and Finite Automata”


Kleene (1956) S. C. Klenne 4
Regular Expressions

Regular Expressions: A concise notation for regular sets


(1) Φ denotes the regular set Φ.
(2) Λ denotes the regular set {Λ}.
(3) α denotes the regular set {α}.
(4) If p and q are regular expressions denoting the regular
sets P and Q
respectively, then
(a) (p | q) denotes P ∪ Q
(b) (pq) denotes P Q
(c) (p)* denotes P*
(5) Nothing else is a regular expression.

Notation:
(p)+ = ((p)* p)

5
Operations on Regular Expressions

RE Regular language Description

a|b {a,b}
(a|b)(a|b) {aa, ab, ba, bb}
a* {e, a, aa, aaa, …}
a*b {b,ab, aab, aaab, …}
(a|b)* {e, a, b, ab, ba, aa, bb, ….
abbbabbab}
a*|b* {e, a, aa, aaa, …, b, bb, bbb…}

6
Finite Automata
Deterministic Finite Automaton (DFA)
M = (Q, ∑, δ, i , F)
where
(1) Q is a finite non-empty set of states
(2) ∑ is a finite set of input symbols
(3) i ∈Q (initial state)
(4) F ⊆ Q (final states)
(5) δ is a partial mapping from Q x ∑ to Q
(transition function: move function)

Non-deterministic Finite Automaton (NFA)

• May have a choice of moves, i.e. δ is a


mapping from Q x ∑ to 2Q
• Also allows ∈ -transitions, i.e., δ (q, ∈) ⊆ Q 7
NFA Example

(a|b)*abb = { abb, aabb, babb, aaabb,


bbabb,…}

start 0 a 1 b 2 b 3

8
DFA Example

b b
a b
0 1 2 b 3
a
a
a

DFA:
• No state has an e-transition
• For each state S and input symbol a, there is at
most one edge labeled a leaving S. 9
Define Tokens with Regular Expressions (Finite
Automata)

Keyword: if

1 2 3
i f

This FA is really shorthand for:

1 2 3
i f

Σ-{f}
Σ-{i} Σ

“dead state” 0 Σ 10
Define Tokens with Regular Expressions (Finite
Automata)

Regular Expression Finite Automata Token

Keyword: 1 2 3
i f KEY(IF)
if

Keyword: 1 2 3
then t h
KEY(then)
e
n
5 4

[a-zA-Z0-9]

Identifier: 1 2
[a-zA-Z] ID(s)
[a-zA-Z][a-zA-Z0-9]*
11
Define Tokens with Regular Expressions (Finite
Automata)

Regular Expression Finite Automata Token

[0-9]

number: 1 2
[0-9] NUM(n)
[0-9][0-9]*

[0-9]
real: 1 2
[0-9] NUM(n)
([0-9]+ ‘.’ [0-9]*)
| ([0-9]* ‘.’ [0-9]+) .
[0-9]
. 3

4 [0-9]
5 12
[0-9]
No Tokens for “White-Space”

[A-za-z0-9’ ‘]
1 2
%
White-space: ‘‘ \n
(‘ ‘ | ‘\n’ | ‘\t’)+ \t
| ‘%’ [A-Za-z0-9’ ‘]+’\n’ 3
\n

13
Traditional Regular Language Problem

Given a regular expression,

e
and an input string w, determine if w∈Le 
.

One method: Construct a DFA M from e and test if it accepts w.

14
What is the “lexing problem”?

Given a set of regular expressions,

e1 e2 … ek
and an input string w, find a partition

w=w 1 w 2 ...w n
such that for each wj there is a ei such that w j ∈L e i  .

WHITE-SPACE

if then 2006 hello


15
IF THEN NUM ID
Ambiguity…..

ifthen2006hello

??

LEX
??

ID(Ifthen2006hello)

ID(ifthen) NUM(2006) ID(hello)

KEY(IF) KEY(THEN) NUM(2006) ID(hello)

ID(i) ID(f) KEY(then) NUM(2) NUM(0) NUM(0) NUM(6) ID(hello)


16
Disambiguation

• Longest Match: the next token is associated


with the longest possible matching prefix of
the input.
• Rule Priority: for a particular longest match,
use rule (automata) with highest priority.

ifthen2006hello
LEX

ID(Ifthen2006hello)

17
White-Space is NOT Ignored!

if then 2006 hello

LEX
KEY(IF) KEY(THEN) NUM(2006) ID(hello)

ifthen2006hello
LEX

ID(Ifthen2006hello)

18
Constructing a Lexer
INPUT:
Construct all Construct a single Construct a single
an ordered
corresponding non-deterministic deterministic
list of regular
finite automata finite automata finite automata
expressions
e1 NFA 1
e2 NFA 2
use priority NFA DFA

ek NFA k

1 2:ID 3:ID
t h
(1) Keyword : then

z]
e

[a-su

gi-
‘‘
f-z]

[a-
(2) Ident : [a-z][a-z]* - d 4:ID
-z] [a
(2) White-space: ‘ ‘ 7:W - m o -z]
6:ID [a n

[a [a-z] 19
-z 5:THEN
]
What about longest match?

| = current position, $ = EOF


Start in initial state,
Repeat: current state
(1) read input until dead state is Input
last accepting state
reached. Emit token associated |then thenx$ 1 0
with last accepting state. t|hen thenx$ 2 2
(2) reset state to start state th|en thenx$ 3 3
the|n thenx$ 4 4
then| thenx$ 5 5
1 2:ID 3:ID then |thenx$ 0 5 EMIT KEY(THEN)
t h
then| thenx$ 1 0 RESET
z]

e
[a-su

gi-

z]
‘‘ then |thenx$ 7 7
f-
[a-

- d then t|henx$ 0 7 EMIT WHITE(‘ ‘)


4:ID
[a then |thenx$ 1 0 RESET
-z]

7:W - m o -z] then t|henx$ 2 2


6:ID [a n
then th|enx$ 3 3
[a [a-z] then the|nx$ 4 4
-z 5:THEN
] then then|x$ 5 5
then thenx|$ 6 6 20
then thenx$| 0 6 EMIT ID(thenx)
The real lexing problem

Given an ordered list of regular expressions,

e1 e2 … ek
and an input string w, find a list of pairs

i1 ,w 1 , i2 ,w 2 , ... i n, w n 


such that
1 w=w 1 w 2 ...w n
2  w j ∈L ei 
j

3 w j ∈L es  i j ≤s  priority rule


.
4 ∀ j : ∀ u∈prefixw j1 w j2⋯w n :u≠ε
 ∀ s:w j u∉Les  longest match 21
Generating Lexical Analyzers

Source Lexical
tokens Parser
Program Analyzer
DFA Transitions
Ordered List of Scanner
Regular Expressions Generator
“LEX”

RE NFA DFA Minimal DFA


Thompson’s Subset Hopcroft
Contruction Contruction Minimization
22
From Mini-Caml (using Ocaml-lex)
{
open Parser
open Type
}

let space = [' ' '\t' '\n' '\r']


let digit = ['0'-'9']
let lower = ['a'-'z']
let upper = ['A'-'Z']

rule token = parse


| space+ { token lexbuf }
| "(*" { comment lexbuf; token lexbuf }
| '(' { LPAREN }
| ')' { RPAREN }
| "true" { BOOL(true) }
| "false" { BOOL(false) }
| "not" { NOT }
| digit+ { INT(int_of_string (Lexing.lexeme lexbuf)) }
| digit+('.' digit*)? (['e' 'E'] ['+' '-']? digit+)?
{ FLOAT(float_of_string (Lexing.lexeme lexbuf)) }
| '-' { MINUS }
| '+' { PLUS }
| "-." { MINUS_DOT }
| "+." { PLUS_DOT }
| "*." { AST_DOT }
| "/." { SLASH_DOT }
| '=' { EQUAL }
| "<>" { LESS_GREATER } 23
| "<=" { LESS_EQUAL }
| ">=" { GREATER_EQUAL }
| '<‘ { LESS }
| '>' { GREATER } ocamllex produces a DFA
| "if" { IF }
| "then" { THEN } with 77 states and 2474 transitions
| "else“ { ELSE }
| "let" { LET }
| "in" { IN }
| "rec" { REC }
| ',' { COMMA }
| '_' { IDENT(Id.gentmp Type.Unit) }
| "Array.create" (* HACK *)
{ ARRAY_CREATE }
| '.' { DOT }
| "<-" { LESS_MINUS }
| ';' { SEMICOLON }
| eof { EOF }
| lower (digit|lower|upper|'_')*
{ IDENT(Lexing.lexeme lexbuf) }
| _ { failwith (Printf.sprintf "unknown token %s near characters %d-%d"
(Lexing.lexeme lexbuf)
(Lexing.lexeme_start lexbuf)
(Lexing.lexeme_end lexbuf)) }

and comment = parse


| "*)" { () }
| "(*" { comment lexbuf; comment lexbuf }
| eof { Format.eprintf "warning: unterminated comment@." }
| _ { comment lexbuf }

24
(some of the) OCAML Lexical Classes

Maximum ID Length?
letter ::= A … Z | a … z Every implementation
will have a limit. Ocaml’s is
ident ::= (letter | _) { letter | 0…9 | _ | ' } 16,000,000 characters

integer-literal ::= [-] (0…9) { 0…9 | _ }


| [-] (0x | 0X) (0…9 | A…F | a…f) { 0…9 | A…F | a…f | _ }
| [-] (0o | 0O) (0…7) { 0…7 | _ }
| [-] (0b | 0B) (0…1) { 0…1 | _ }

float-literal ::= [-] (0…9) { 0…9 | _ } [. { 0…9 | _ }] [(e | E) [+ | -] (0…9) { 0…9 | _ }]

char-literal ::= ‘regular-char ' | 'escape-sequence‘


escape-sequence ::= \ (\ | " | ' | n | t | b | r)
| \ (0…9) (0…9) (0…9)
| \x (0…9 | A…F | a…f) (0…9 | A…F | a…f)

string-literal ::= " { string-character } “


string-character ::= regular-char-str | escape-sequence 25
OCAML Keywords

and as assert asr begin class constraint do done downto else end
exception external false for fun function functor if in include inherit
initializer land lazy let lor lsl lsr lxor match method mod module
mutable new object of open or private rec sig struct then to true
try type val virtual when while with

!= # & && ‘ ( ) * + , - -. -> .


.. : :: := :> ; ;; < <- = > >] >} ?
?? [ [< [> [| ] _ ` { {< | |] } ~

ocamllex produces a DFA


with 151 states and 2911 transitions
26
Compiler Construction
Lecture 03
Context Free Grammars
and
Predictive Parsing

Lent Term, 2007

Lecturer: Timothy G. Griffin

Computer Laboratory
University of Cambridge
1
CFG Example

E ::= ID

E ::= NUM
E is a non-terminal symbol
E ::= E * E
ID and NUM are lexical classes
E ::= E / E
*, (, ), +, and – are terminal symbols.
E ::= E + E
E ::= E + E is called a production rule.
E ::= E – E

E ::= ( E )

Usually will write this way


E ::= ID | NUM | E * E | E / E | E + E | E – E | ( E )
2
CFG Derivations
(G1) E ::= ID | NUM | ID | E * E | E / E | E + E | E – E | ( E )
E E*E Rightmost
E*(E)
E*(E–E)
derivation
E
 E * ( E – 10 )
 E * ( 2 – 10 )
E
* E
 ( E ) * ( 2 – 10 )
 ( E + E ) * (2 – 10 )
(E+4)*(2–E)
 ( 17 + 4 ) * ( 2 – 10 ) ( E ) ( E )

E E*E
E
+
E E
- E

( E )*E Leftmost
(E +E)*E derivation 17 4 2 10
 ( 17 + E ) * E
 ( 17 + 4 ) * E
 ( 17 + 4 ) * ( E )
 ( 17 + 4 ) * ( E – E ) The Derivation Tree for
 ( 17 + 4 ) * ( 2 – E ) ( 17 + 4 ) * (2 – 10 )
 ( 17 + 4 ) * ( 2 – 10 )
3
More formally, …

• A CFG is a quadruple G = (N, T, R, S) where


– N is the set of non-terminal symbols
– T is the set of terminal symbols (N and T disjoint)
– S ∈N is the start symbol
– R ⊆ N×(N∪T)* is a set of rules
• Example: The grammar of nested parentheses
G = (N, T, R, S) where
– N = {S}
– T ={ (, ) }
– R ={ (S, (S)) , (S, SS), (S, ) }

We will normally write R as S ::= (S) | SS |


4
Derivations, more formally…

• Start from start symbol (S)


• Productions are used to derive a sequence of tokens from the
start symbol
• For arbitrary strings α, β and γ comprised of both terminal and
non-terminal symbols,
and a production A → β,
a single step of derivation is
αAγ ⇒ αβγ
– i.e., substitute β for an occurrence of A
∀ α ⇒* β means that b can be derived from a in 0 or more single
steps
∀ α ⇒+ β means that b can be derived from a in 1 or more single
steps

5
L(G) = The Language Generated by Grammar G

The language generated by G is the set of all terminal strings


derivable from the start symbol S:

L G={w ∈T∗∣S ⇒w }


For any subset W of T*, if there exists a CFG G such
that L(G) = W, then W is called a Context-Free
Language (CFL) over T.

6
Ambiguity

(G1) E ::= ID | NUM | ID | E * E | E / E | E + E | E – E | ( E )

E E

E E E
* E
+
E E E E
+ 3 1 *
1 2 2 3
Both derivation trees correspond to the string

1+2*3

This type of ambiguity will cause problems when we try to


go from strings to derivation trees!
7
Solution: Modify the Grammar!
S

(G2) E
S :: = E$ (start, $ = EOF)

E ::= E + T (expressions)
E
+ T

| E–T T F
| T
1 *
F 3
T ::= T * F (terms)
| T/F
| F 2

F ::= NUM (factors) This is the unique derivation


| ID
|(E) tree for the string

1 + 2 * 3$
Note: L(G1) = L(G2). 8
Can you prove it?
Famously Ambiguous

(G3) S ::= if E then S else S | if E then S | blah-blah

What does

if e1 then if e2 then s1 else s3

mean?

S OR S

if E then S if E then S else S

if E then S else S if E then S

9
Rewrite?

(G4)
S ::= WE | NE
WE ::= if E the n WE else WE | bla h-b lah
NE ::= if E the n S
| if E the n WE else NE

Now, S

if e1 then if e2 then s1 else s3


NE
has a unique derivation.

if E then S

WE

Note: L(G3) = L(G4).


Can you prove it? if E then S else10 S
Fun Facts

See Hopcroft and Ullman, “Introduction to Automata


Theory, Languages, and Computation”

(1) Some context free languages are inherently ambiguous --- every
context-free grammar will be ambiguous. For example:

{a b c d } {a b c d ∣m≥1, n≥1}
n n m m n m m n
L= ∣m≥1, n≥1 ∪

(2) Checking for ambiguity in an arbitrary context-free


grammar is not decidable!

(3) Given two grammars G1 and G2, checking L(G1) = L(G2) is


not decidable!
11
Generation vs. Parsing

• Context-Free Grammars (CFGs) and


language generation,
– Derivation trees
– Ambiguity
• Parsing is the inverse of generation,
– Given an input string, is it in the language
generated by a CFG?
– If so, construct a derivation tree (normally called
a parse tree).
– Top-down parsing
– Bottom-up parsing
12
Predictive (Recursive Descent) Parsing

(G5) int tok = getToken();

void advance() {tok = getToken();}


S :: = if E then S else S void eat (int t) {if (tok == t) advance(); else error();}

| begin S L void S() {switch(tok) {


| print E case IF: eat(IF); E(); eat(THEN);
S(); eat(ELSE); S(); break;
case BEGIN: eat(BEGIN); S(); L(); break;
E ::= NUM = NUM case PRINT: eat(PRINT); E(); break;
default: error();
}}
L ::= end void L() {switch(tok) {
| ;SL case END: eat(END); break;
case SEMI: eat(SEMI); S(); L(); break;
default: error();
}}

void E() {eat(NUM) ; eat(EQ); eat(NUM); }

Parse corresponds to a left-most derivation


constructed in a “top-down” manner
13
From Andrew Appel, “Modern Compiler Implementation in Java” page 46
Can we automate this?
For each non-terminal X we need to compute

FIRST[X] = the set of terminal symbols that


can begin strings derived from X

FOLLOW[X] = the set of terminal symbols that


can immediately follow X in some
derivation

nullable[X] = true of X can derive the empty string,


false otherwise

nullable[Z] = false, for Z in T

nullable[Y1 Y2 … Yk] = nullable[Y1] and … nullable[Yk], for Y(i) in N union T.


FIRST[Z] = {Z}, for Z in T

FIRST[ X Y1 Y2 … Yk] = FIRST[X] if not nullable[X]

FIRST[ X Y1 Y2 … Yk] =FIRST[X] union FIRST[Y1 … Yk] otherwise 14


Computing First, Follow, and nullable

For each terminal symbol Z


FIRST[Z] := {Z};
nullable[Z] := false;

For each non-terminal symbol X


FIRST[X] := FOLLOW[X] := {};
nullable[X] := false;

repeat
for each production X  Y1 Y2 … Yk
if Y1, … Yk are all nullable, or k = 0
then nullable[X] := true
for each i from 1 to k, each j from i + I to k
if Y1 … Y(i-1) are all nullable or i = 1
then FIRST[X] := FIRST[X] union FIRST[Y(i)]
if Y(i+1) … Yk are all nullable or if i = k
then FOLLOW[Y(i)] := FOLLOW[Y(i)] union FOLLOW[X]
if Y(i+1) … Y(j-1) are all nullable or i+1 = j
then FOLLOW[Y(i)] := FOLLOW[Y(i)] union FIRST[Y(j)] 15
until there is no change
Eliminating Left Recursion
Note that
(G6)
E ::= T and
S :: = E$
E ::= E + T
will cause problems
E ::= T E’
since FIRST(T) will be included
(G2)
in FIRST(E + T) ---- so how can
S :: = E$ E’ ::= + T E’
we decide which poduction
| – T E’
To use based on next token?
E ::= E + T |
| E–T
Solution: eliminate “left recursion”!
| T T ::= F T’
E ::= T E’
T ::= T * F T’ ::= * F T’
| T/F | / F T’
E’ ::= + T E’
| F |
|
F ::= NUM F ::= NUM
| ID | ID
|(E) Eliminate left recursion |(E)
16
First, Follow, nullable table for G6

(G6)
S :: = E$
Nullable FIRST FOLLOW
E ::= T E’
S False { (, ID, NUM } {}
E’ ::= + T E’
E False { (, ID, NUM } { ), $ } | – T E’
|
E’ True { +, - } { ), $ }
T ::= F T’
T False { (, ID, NUM } { ), +, -, $ }
T’ ::= * F T’
T’ True { *, / } { ), +, -, $ } | / F T’
|
F False { (, ID, NUM } { ), *, /, +, -, $ }
F ::= NUM
| ID
|(E)
17
Predictive Parsing Table for G6
Table[ X, T ] = Set of productions NOTE: this could
lead to more than
X ::= Y1…Yk in Table[ X, T ] one entry! If so, out
of luck --- can’t do
if T in FIRST[Y1 … Yk] recursive descent parsing!
or if (T in FOLLOW[X] and nullable[Y1 … Yk])

+ * ( ) ID NUM $
S S ::= E$ S ::= E$ S ::= E$

E E ::= T E’ E ::= T E’ E ::= T E’

E’ E’ ::= + T E’ E’ ::= E’ ::=


T T ::= F T’ T ::= F T’ T ::= F T’

T’ T’ ::= T’ ::= * F T’ T’ ::= T’ ::=


F F ::= (E) F ::= ID F ::= NUM

(entries for /, - are similar…)


18
Left-most derivation is constructed
by recursive descent
Left-most derivation
(G6) call S()
S  E$
S :: = E$  T E’$ on ‘(‘ call E()
 F T’ E’$ on ‘(‘ call T()
E ::= T E’  ( E ) T’ E’$ .l..
 ( T E’ ) T’ E’$ …
E’ ::= + T E’  ( F T’ E’ ) T’ E’$
| – T E’  ( 17 T’ E’ ) T’ E’$
|  ( 17 E’ ) T’ E’$
 ( 17 + T E’ ) T’ E’$
 ( 17 + F T’ E’ ) T’ E’$
T ::= F T’  ( 17 + 4 T’ E’ ) T’ E’$
 ( 17 + 4 E’ ) T’ E’$
T’ ::= * F T’  ( 17 + 4 ) T’ E’$
| / F T’  ( 17 + 4 ) * F T’ E’$
| …
…
F ::= NUM  ( 17 + 4 ) * ( 2 – 10 ) T’ E’$
 ( 17 + 4 ) * ( 2 – 10 ) E’$
| ID
 ( 17 + 4 ) * ( 2 – 10 )
|(E)
19
As a stack machine

S  E$ E$
 T E’$ T E’$
 F T’ E’$ F T’ E’$
 ( E ) T’ E’$ ( E ) T’ E’$
 ( T E’ ) T’ E’$ ( T E’ ) T’ E’$
 ( F T’ E’ ) T’ E’$ ( F T’ E’ ) T’ E’$
 ( 17 T’ E’ ) T’ E’$ ( 17 T’ E’ ) T’ E’$
 ( 17 E’ ) T’ E’$ ( 17 E’ ) T’ E’$
 ( 17 + T E’ ) T’ E’$ ( 17 + T E’ ) T’ E’$
 ( 17 + F T’ E’ ) T’ E’$ ( 17 + F T’ E’ ) T’ E’$
 ( 17 + 4 T’ E’ ) T’ E’$ ( 17 + 4 T’ E’ ) T’ E’$
 ( 17 + 4 E’ ) T’ E’$ ( 17 + 4 E’ ) T’ E’$
 ( 17 + 4 ) T’ E’$ ( 17 + 4) T’ E’$
 ( 17 + 4 ) * F T’ E’$ ( 17 + 4)* F T’ E’$
… …
… …
 ( 17 + 4 ) * ( 2 – 10 ) T’ E’$ ( 17 + 4 ) * ( 2 – 10 ) T’ E’$
 ( 17 + 4 ) * ( 2 – 10 ) E’$ ( 17 + 4 ) * ( 2 – 10 ) E’$
 ( 17 + 4 ) * ( 2 – 10 ) ( 17 + 4 ) * ( 2 – 10 )

20
Compiler Construction
Lecture 04
LR Parsing --- PART I

Lent Term, 2007

Lecturer: Timothy G. Griffin

Computer Laboratory
University of Cambridge
1
But wait! What if there are conflicts in
the predictive parsing table?
(G7) Nullable FIRST FOLLOW

S :: = d | X Y S S false { c,d ,a} { }

Y ::= c | Y true {c} { c,d,a }

X ::= Y | a
X true { c,a } { c, a,d }

The resulting “predictive” table is not so predictive….

a c d

S { S ::= X Y S } { S ::= X Y S } { S ::= X Y S, S ::= d }

Y { Y ::= } { Y ::= , Y ::= c} { Y ::= }

X { X ::= a, X ::= Y } { X ::= Y } { X ::= Y } 2


LL(1), LL(k), LR(0), LR(1), …

• LL(k) : (L)eft-to-right parse, (L)eft-most


derivation, k-symbol lookahead. Based on
looking at the next k tokens, an LL(k) parser
must predict the next production. We have been
looking at LL(1).
• LR(k) : (L)eft-to-right parse, (R)ight-most
derivation, k-symbol lookahead. Postpone
production selection until the entire right-hand-
side has been seen (and as many as k symbols
beyond).
• LALR(1) : A special subclass of LR(1).
3
CFG World Map

Most programming
languages have
grammars in
LALR(1)

From Andrew Appel, “Modern Compiler Implementation in Java” page 466


Example

(G8)

S :: = S ; S | ID = E | print (L)

E ::= ID | NUM | E + E | (S, E)

L ::= E | L, E

To be consistent, I should write the following, but I won’t…


(G8)

S :: = S SEMI S | ID EQUAL E | PRINT LPAREN L RPAREN

E ::= ID | NUM | E PLUS E | LPAREN S COMMA E RPAREN

L ::= E | L COMMA E
5
A Right-most derivation …
S
(G8)  S;S
 S ; ID = E
S ::= S ; S  S ; ID = E + E
 S ; ID = E + ( S, E )
| ID = E
 S ; ID = E + ( S, ID )
| print (L)  S ; ID = E + ( S, d )
 S ; ID = E + ( ID = E, d )
E ::= ID  S ; ID = E + ( ID = E + E, d )
| NUM  S ; ID = E + ( ID = E + NUM, d )
|E+E  S ; ID = E + ( ID = E + 6, d )
| (S, E)  S ; ID = E + ( ID = NUM + 6, d )
 S ; ID = E + ( ID = 5 + 6, d )
 S ; ID = E + ( d = 5 + 6, d )
L ::= E
 S ; ID = ID + (d = 5 + 6, d )
| L, E  S ; ID = c + ( d = 5 + 6, d )
 S ; b = c + ( d = 5 + 6, d )
 ID = E ; b = c + ( d = 5 + 6, d )
 ID = NUM ; b = c + ( d = 5 + 6, d)
 ID = 7 ; b = c + ( d = 5 + 6, d )
 a = 7 ; b = c + ( d = 5 + 6, d )
6
Now, turn it upside down …
 a = 7 ; b = c + ( d = 5 + 6, d )
 ID = 7 ; b = c + ( d = 5 + 6, d )
 ID = NUM; b = c + ( d = 5 + 6, d )
 ID = E ; b = c + ( d = 5 + 6, d )
 S ; b = c + ( d = 5 + 6, d )
 S ; ID = c + ( d = 5 + 6, d )
 S ; ID = ID + ( d = 5 + 6, d)
 S ; ID = E + ( d = 5 + 6, d )
 S ; ID = E + ( ID = 5 + 6, d )
 S ; ID = E + ( ID = NUM + 6, d )
 S ; ID = E + ( ID = E + 6, d )
 S ; ID = E + ( ID = E + NUM, d )
 S ; ID = E + ( ID = E + E, d )
 S ; ID = E + ( ID = E, d )
 S ; ID = E + ( S, d )
 S ; ID = E + ( S, ID )
 S ; ID = E + ( S, E )
 S ; ID = E + E
 S ; ID = E
 S;S 7
S
Now, slice it down the middle…
a = 7 ; b = c + ( d = 5 + 6, d )
ID = 7 ; b = c + ( d = 5 + 6, d )
ID = NUM ; b = c + ( d = 5 + 6, d )
ID = E ; b = c + ( d = 5 + 6, d )
S ; b = c + ( d = 5 + 6, d )
S ; ID = c + ( d = 5 + 6, d )
S ; ID = ID + ( d = 5 + 6, d )
S ; ID = E + ( d = 5 + 6, d )
S ; ID = E + ( ID = 5 + 6, d )
S ; ID = E + ( ID = NUM + 6, d )
S ; ID = E + ( ID = E + 6, d )
S ; ID = E + ( ID = E + NUM , d )
S ; ID = E + ( ID = E + E , d )
S ; ID = E + ( ID = E , d )
S ; ID = E + ( S , d )
S ; ID = E + ( S, ID )
S ; ID = E + ( S, E )
S ; ID = E + E
S ; ID = E
S ; S
S
The rest of the input string
A stack of terminals and
non-terminals 8
Now, add some actions. s = SHIFT, r = REDUCE

a=7; b = c + ( d = 5 + 6, d ) s
ID =7; b = c + ( d = 5 + 6, d ) s, s
ID = NUM ; b = c + ( d = 5 + 6, d ) r E ::= NUM
ID = E
; b = c + ( d = 5 + 6, d ) r S ::= ID = E
S
S ; ID ; b = c + ( d = 5 + 6, d ) s, s
S ; ID = ID = c + ( d = 5 + 6, d ) s, s
S ; ID = E + ( d = 5 + 6, d ) r E ::= ID
S ; ID = E + ( ID + ( d = 5 + 6, d ) s, s, s
S ; ID = E + ( ID = NUM = 5 + 6, d ) s, s
S ; ID = E + ( ID = E + 6, d ) r E ::= NUM
S ; ID = E + ( ID = E + NUM + 6, d ) s, s
S ; ID = E + ( ID = E + E
,d) r E ::= NUM
S ; ID = E + ( ID = E
S ; ID = E + (S ,d) r E ::= E+E, s, s
S ; ID = E + ( S, ID ,d) r S ::= ID = E
S ; ID = E + ( S, E ) ) R E::= ID
S ; ID = E + E ) s, r E ::= (S, E)
S ; ID = E r E ::= E + E
S;S r S ::= ID = E
S r S ::= S ; S
SHIFT = LEX + move token to stack 9
ACTIONS
Q: How do we know when to shift and
when to reduce? A: Build a FSA from
LR(0) Items!
(G10) S ::= • A $
S ::= A • $
S : := A $
A ::= • (A)
A :: = ( A ) A ::= ( • A )
| ( ) A ::= ( A • )
A ::= ( A ) •
If
A ::= • ( )
X ::= αβ
A ::= ( • )
is a production, then A ::= ( ) •
LR(0) items indicate what is on the stack
X ::= α • β (to the left of the • ) and what is still in
the input stream (to the right of the • )
is an LR(0) item. 10
Key idea behind LR(0) items

• If the “current state” contains the item


A ::= α • c β and the current symbol in the input buffer is c
– the state prompts parser to perform a shift action
– next state will contain A ::= α c • β
• If the “state” contains the item A ::= α •
– the state prompts parser to perform a reduce action
• If the “state” contains the item S ::= α • $
and the input buffer is empty
– the state prompts parser to accept
• But How about A ::= α • X β where X is a nonterminal?

11
The NFA for LR(0) items

• The transition of LR(0) items can be represented


by an NFA, in which
– 1. each LR(0) item is a state,
– 2. there is a transition from item A ::= α • c β
to item A ::= αc • β with label c, where c is a terminal
symbol
– 3. there is an ε-transition from item A ::= α • X β to X
::= • γ, where X is a non-terminal
– 4. S ::= • A $ is the start state
– 5. A ::= α • is a final state.

12
Example NFA for Items

S :: = • A $ S : := A • $ A ::= • (A)
A ::= ( • A ) A ::= ( A • ) A ::= ( A) •
A ::= • ( ) A ::= ( •) A ::= ( ) •

A
S ::= • A $ S ::= A • $ A ::= (A) •

ε ε )
( A
A ::= • (A ) A ::= ( • A ) A ::= ( A • )
ε
( )
A ::= • ( ) A ::= ( • ) A ::= ( ) •
13
The DFA from LR(0) items
• After the NFA for LR(0) is constructed, the resulting DFA
for LR(0) parsing can be obtained by the usual
NFA2DFA construction.

• we thus require
– ε-closure (I)
– move(S, a)

Fixed Point Algorithm for Closure(I)


– Every item in I is also an item in Closure(I)
– If A ::= α • B β is in Closure(I) and B ::= • γ is an
item, then add B ::= • γ to Closure(I)
– Repeat until no more new items can be added to
Closure(I) 14
Examples of Closure

Closure({A ::= ( • A )}) = S ::= • A $


A ::= ( • A) S ::= A • $
A ::= • (A) A ::= • (A)
A ::= • ( ) A ::= ( • A )
A ::= ( A • )
• closure({S ::= • A $}) A ::= ( A ) •
A ::= • ( )
S ::= •A$ A ::= ( • )
A ::= • (A) A ::= ( ) •
A ::= • ( )
15
Goto() of a set of items

• Goto finds the new state after consuming a


grammar symbol while in the current state

• Algorithm for Goto(I, X)


where I is a set of items
and X is a non-terminal

Goto(I, X) = Closure( { A ::= |


α X • β A ::= α • X β in I })
• goto is the new set obtained by
“moving the dot” over X
16
Examples of Goto

• Goto ({A ::= •(A)}, ()


S ::= • A $
A ::= ( • A) S ::= A • $
A ::= • (A) A ::= • (A)
A ::= • ( ) A ::= ( • A )
A ::= ( A • )
• Goto ({A ::= ( • A)}, A)
A ::= ( A ) •
A ::= (A • ) A ::= • ( )
A ::= ( • )
A ::= ( ) •

17
Building the DFA states

• Essentially the usual NFA2DFA construction!!


• Let A be the start symbol and S a new start
symbol.
• Create a new rule S ::= A $
• Create the first state to be Closure({ S ::= • A $})
• Pick a state I
– for each item A ::= α • X β in I
• find Goto(I, X)
• if Goto(I, X) is not already a state, make one
• Add an edge X from state I to Goto(I, X) state
• Repeat until no more additions possible

18
DFA Example

s1
A S ::= A • $
s0
S ::= • A$ s2
A ::= • (A) A ::= ( • A) (
A ::= ( • )
A ::= • ( ) ( A ::= • (A)
s3
A ::= (A • )
A ::= • ( )
A
) )
s5 s4
A ::= ( ) • A ::= (A) •

19
Building
CreatingParse TableTable(s)
the Parse Example
State ( ) $ A
s0 shift to s2 goto s1
(G10)
s1 accept
• S ::=
s2 shift to s2 shift to s5 goto s3
A$
s3 shift to s4
• A ::= (A
) s4 reduce (2) reduce (2) reduce (2)
s5 reduce (3) reduce (3) reduce (3)
• A ::= (
) s1
A S ::= A • $
s0
S ::= • A$ s2
A ::= • (A) A ::= ( • A) (
A ::= ( • )
A ::= • ( ) ( A ::= • (A)
s3
A ::= (A • )
A ::= • ( )
A
) )
s5 s4
A ::= ( ) • A ::= (A) • 20
Parsing with an LR Table

Use table and top-of-stack and input symbol to get action:

If action is
shift sn : advance input one token,
push sn on stack
reduce X ::= α : pop stack 2* |α| times (grammar symbols
are paired with states). In the state
now on top of stack,
use goto table to get next
state sn,
push it on top of stack
accept : stop and accept
error : weep (actually, produce a good error
message)

21
Building Parse Table
Parsing, Example
again…
ACTION Goto
(G10) State ( ) $ A
• S ::= s0 shift to s2 goto s1
A$ s1 accept
• A : := (A s2 shift to s2 shift to s5 goto s3
) s3 shift to s4
• A : := ( s4 reduce (2) reduce (2) reduce (2)
) s5 reduce (3) reduce (3) reduce (3)

s0 (())$ shift s2
s0 ( s2 ())$ shift s2
s0 ( s2 ( s2 ))$ shift s5
s0 ( s2 ( s2 ) s5 )$ reduce A ::= ()
s0 ( s2 A )$ goto s3
s0 ( s2 A s3 )$ shift s4
s0 ( s2 A s3 ) s4 $ reduce A::= (A)
s0 A $ goto s1
s0 A s1 $ ACCEPT! 22
LR Parsing Algorithm

Stack of
a1 ... ai ... an $ input
states and
grammar symbols

sm
Ym LR Parsing output
Algorithm
sm-1
Ym-1
. Action Table Goto Table
terminals and $ non-terminal
. s
t four different
s
t each item is
a actions a a state
s1 t t number
e e
Y1 s s

23
s0
Compiler Construction
Lecture 05
LR Parsing --- PART II

Lent Term, 2006

Lecturer: Timothy G. Griffin

Computer Laboratory
University of Cambridge
1
Problem With LR(0) Parsing

• No lookahead
• Vulnerable to unnecessary
conflicts
– Shift/Reduce Conflicts (may reduce
too soon in some cases)
– Reduce/Reduce Conflicts
• Solutions:
– LR(1) parsing - systematic lookahead

2
LR(1) Items

• An LR(1) item is a pair:


(X ::= α. β, a)
– X ::= αβ is a production
– a is a terminal (the lookahead terminal)
– LR(1) means 1 lookahead terminal

• [X ::= α. β, a] describes a context of the parser


– We are trying to find an X followed by an a, and
– We have (at least) α already on top of the stack
– Thus we need to see next a prefix derived from βa
3
The Closure Operation

• Need to modify closure operation:.

Closure(Items) =
repeat
for each [X ::= α.Yβ, a] in Items
for each production Y ::= γ
for each b in First(βa)
add [Y ::=.γ, b] to Items
until Items is unchanged
4
Constructing the Parsing DFA (2)

• A DFA state is a closed set of LR(1) items

• The start state contains (S’ ::= .S$,


dummy)

• A state that contains [X ::= α., b] is


labeled with “reduce with X ::= α on
lookahead b”
5
The DFA Transitions

• A state s that contains [X ::= α.Yβ, b]


has a transition labeled y to the state
obtained from Transition(s, Y)
– Y can be a terminal or a non-terminal

Transition(s, Y)
Items ={}
for each [X ::= α.Yβ, b] in s
add [X ! αY.β, b] to Items
return Closure(Items) 6
LR(1)-the parse table

• Shift and goto as before


• Reduce
– state I with item (A→α., z) gives a reduce A→
α if z is the next character in the input.

• LR(1)-parse tables are very big

7
LR(1)-DFA

(G11)

S’ ::= S$

S ::= V = E
|E

E ::= V

V ::= x
| *E

From Andrew Appel, “Modern Compiler Implementation in Java” page 65


8
LR(1)-parse table

x * = $ S E V x * = $ S E V

1 s8 s6 g2 g5 g3 8 r4 r4

2 acc 9 r1

3 s4 r3 10 r5 r5

4 s11 s13 g9 g7 11 r4

5 r2 12 r3 r3

6 s8 s6 g10 g12 13 s11 s13 g14 g7

7 r3 14 r5

9
LALR States

• Consider for example the LR(1) states


{[X ::= α., a], [Y ::= β., c]}
{[X ::= α., b], [Y ::= β., d]}
• They have the same core and can be
merged to the state
{[X ::= α., a/b], [Y ::= β., c/d]}
• These are called LALR(1) states
– Stands for LookAhead LR
– Typically 10 times fewer LALR(1) states than
LR(1) 10
For LALR(1), Collapse States ...
Combine states 6 and 13, 7 and 12, 8 and 11, 10 and 14.

11
LALR(1)-parse-table

x * = $ S E V
1 s8 s6 g2 g5 g3
2 acc
3 s4 r3
4 s8 s6 g9 g7
5
6 s8 s6 g10 g7
7 r3 r3
8 r4 r4
9 r1
10 r5 r5

12
LALR vs. LR Parsing

• LALR languages are not “natural”


– They are an efficiency hack on LR languages

• You may see claims that any reasonable programming


language has a LALR(1) grammar, {Arguably this is
done by defining languages without an LALR(1)
grammar as unreasonable  }.

• In any case, LALR(1) has become a standard for


programming languages and for parser generators, in
spite of its apparent complexity.
13
Lexer and Parser Generators

http://catalog.compilertools.net/lexparse.html

ACCENT HAPPY
AFLEX AYACC HOLUB
ALE LEX
ANAGRAM LLGEN
BISON PCYACC
BISON/EIFFEL PRECC
BTYACC PROGRAMMAR
BYACC RDP
COGENCEE VISUALPARSE++
COCO YACC
DEPOT4 YACC++
FLEX …

I’ll use ocamllex and ocamlyacc ….


14
ast.ml

type binary_op = PlusOp | TimesOp | MinusOp | DivOp

type unary_op = UnaryMinusOp

type ast = Ident of string


| Number of int
| Unary of unary_op * ast
| Binary of binary_op * ast * ast

15
parser.mly
%token <int> INT
%token <string> IDENT
%token PLUS MINUS TIMES DIV
%token LPAREN RPAREN
%token EOF
%left PLUS MINUS /* lowest precedence */
%left TIMES DIV /* medium precedence */
%nonassoc UMINUS /* highest precedence */
%start parse_it /* the entry point */
%type <ast> parse_it
%%
parse_it:
expr EOF { $1 }
;
expr:
INT { Number($1) }
| IDENT { Ident($1) }
| LPAREN expr RPAREN { $2 }
| expr PLUS expr { Binary(PlusOp, $1, $3) }
| expr MINUS expr { Binary(MinusOp, $1, $3) }
| expr TIMES expr { Binary(TimesOp, $1, $3) }
| expr DIV expr { Binary(DivOp, $1, $3) }
| MINUS expr %prec UMINUS { Unary(UnaryMinusOp, $2) }
;
ocamlyacc parser.mly  parser.ml 16
(in this case producing a 21-state DFA)
lexer.mll

rule tokenize = parse


[' ' '\t' '\n' ] { tokenize lexbuf } (* skip white-space *)
| ['a'-'z' 'A'-'Z']['a'-'z' 'A'-'Z' '0'-'9']* as lxm
{ IDENT(lxm) }
| ['0'-'9']+ as lxm { INT(int_of_string lxm) }
| '+' { PLUS }
| '-' { MINUS }
| '*' { TIMES }
| '/' { DIV }
| '(' { LPAREN }
| ')' { RPAREN }
| eof { EOF }

ocamllex lexer.mll  lexer.ml

(in this case producing an 11-state DFA


with 342 transitions) 17
Now, Parse it!

let ast_of_string s =
let lexbuf = Lexing.from_string s in
parse_it tokenize lexbuf

ast_of_string "(9 - 10) + ((-xyz100) * 44)";;

Binary (PlusOp, Binary (MinusOp, Number 9, Number 10),


Binary (TimesOp, Unary (UnaryMinusOp, Ident "xyz100"), Number 44))

ast_of_string "9 - 10 + -xyz100 * 44";;

Binary (PlusOp, Binary (MinusOp, Number 9, Number 10),


Binary (TimesOp, Unary (UnaryMinusOp, Ident "xyz100"), Number 44))

18
Concrete vs. Abstract Syntax Trees

parse tree = S
derivation tree =
S + E
concrete syntax
tree E 5 Abstract Syntax Tree (AST)

( S ) +
+ 5
S + E
+ +
S+E (S)
E 2 S+E 1 2 3 4
1 E 4 An AST contains only the
information needed to generate an
3 intermediate representation

Normally a compiler constructs the concrete syntax tree only implicitly


(in the parsing process) and explicitly constructs the AST via semantic actions.
19
Compiler Construction
Lecture 07
Static Analysis --- Variables, Scope,
and Types

Lent Term, 2007

Lecturer: Timothy G. Griffin

Computer Laboratory
University of Cambridge
1
LL(k) vs. LR(k) reductions

A  β ⇒ w '  β ∈ T ∪N  , w '∈T 
¿ ¿ ¿

LLk  LRk 
w' w'
k token look
k token look ahead
ahead

A β (left-most
symbol at
(right-most
symbol at
β A
top) top)

Stack Stack

The language of this


2
Stack IS REGULAR!
LR(k) states (non-deterministic)

The state  A  α⋅β , a1 a2⋯ak 


should represent this situation:

Input: w' Stack:


α
(right-most
symbol at
top)

with
βa1 a2 ⋯ak ⇒ w ' ¿

3
Compiler Construction, Revised
• Overvi ew
• Le xical An alys is
• The ory of Con te xt Fr ee
January 2007 Gra mma rs ( CF Gs) and P red ictive front-end
M T W T F S S (re cur siv e d esce nt ) P ar sing
1 2 3 4 5 6 7 • LR P arsi ng I
• LR P arsi ng I I
8 9 10 11 12 13 14
• LR P arsi ng I II
15 16 17 18 19 20 21 • Var iab les, S cop e, T ypes
22 23 24 25 26 27 28 • Sta ck Mac hin e
29 30 31 • Pro ce dur es , F un ct ions I middle-end
• Pro ce dur es , F un ct ions I I
February 2007 • Reg is te r Ma chine & Min Ca ml
mid dle-e nd
M T W T F S S
1 2 3 4 • Assemb ly c ode , lin ke r, loa de r back-end
5 6 7 8 9 10 11 • Cod e Gen er at ion
12 13 14 15 16 17 18 • Min Ca ml ba ck -en d
19 20 21 22 23 24 25
26 27 28 • Garb ag e Co llec tio n Special
• Objec t O rien ta tion topics
• Inte rp re te rs , By te Co de
inte rp re te rs, vir tu al ma ch in es

• Revi ew
4
Names, binding, scope, type checking
static int x = 17;

void f(int x, int y)


{
int i, k;
• Names, variables …
• Binding i = i + x;

• Scope (visibility) }
• Type checking int g(int i, int x)
{
int k;

f(k, x);

f(i, k)

} 5
Scope

• Def: The scope of a variable is the range


of statements over which it is visible
• Def: The nonlocal variables of a program
unit are those that are visible but not
declared there
• The scope rules of a language determine
how references to names are associated
with variables
6
L-values vs. R-values

(in C) x = x + 3;

An L-value represents An R-value represents


a memory location. the value stored at the memory
location associated with x

An L-values may be
determined at run-time:
A[j*2] = j + 3;

7
Binding

Binding is not formally defined. Intuitively, we associate


(that is, bind) an attribute with an entity. Examples of
attributes are name, type, value.
Binding occurs at various times in the life of a program.
Three periods are usually considered:
compile time (actually, translation time, because binding
happens both in compilers and interpreters);
load time (preparing object code for execution, pulling in
the necessary code for built-in operations or operations
defined in libraries of modules);
run time (between starting the program's execution and
its termination).

8
Dynamic binding is just a BAD IDEA

let a = 1
let f() = a
let g(a) = f()
print g(2)

Static Scope Dynamic Scope

1 2
Although dynamic scoping is easier to implement, reading and
understanding code can be nearly impossible.

9
Types and Type Errors

x = “this” + 3;

Obvious type errors


int f(int x, int y) {…}

f(17)

A type systems imposes a discipline on programming that


ensures that the abstractions represented by types are
not violated by a correct program.

The rules can be enforced at compile-time or at run-time.

Static type Dynamic type


checking checking
10
What is a type error?

Is this a type error?

x = (if true then 8 else “this”) + 10;

It will never go wrong!

How about this?

x = (if g(x) then 8 else “this”) + 10;

If we can prove that g(x) is always true, then is will never go wrong!

But that might be too much to ask for a (static) type checking system, since
This looks like a undecidable problem…
11
Type Systems
• A language’s type system specifies how to construct
types and which operations are valid for which types
• Type systems provide a concise formalization of the
semantic checking rules
• Type systems can be thought of as a logic in which
some very weak assertions can be proved automatically.

{preconditions} program {postconditions}

{ x :int } y = x + 17; { y : int }

12
Another way to think of types as a logic…

Logic Typing

H |- A H |- a : A

axioms

------------- --------------------
H, A |- A H, x:A |- x : A

13
Conjunction and Pairing
Typing rules
Logical rules

H |- a : A H |- b : B
H |- A H |- B --------------------------------------
-------------------------------------- H |- (a, b) : A * B
H |- A * B

H |- p : A*B H |- p : A*B
H |- A*B H |- A*B -------------------- --------------------
-------------------- -------------------- H |- fst(p) : A H |- snd(p) : B
H |- A H |- B

14
Implication and function types.
Typing rules
Logical rules

H, A |- B
---------------- H, x:A |- e:B
H |- A  B --------------------------------
H |- fun x:A.e :A  B

H |- AB H |- A
--------------------------------- H |- f: AB H |- a: A
H |- B ---------------------------------------
H |- f(a) : B

15
Disjunction and Case Switch.
Logical rules

H |- A H |- B H |- A||B H,A |- C H,B|- C


---------------- ---------------- -------------------------------------------
H |- A || B H |- A || B H |- C

Typing rules

H |- a:A H |- b:A
-------------------------- --------------------------
H |- inr(a) : A || B H |- inl(b) : A || B

H |- d : A||B H, x:A |- e1 : C H, y:B |- e2 : C


-----------------------------------------------------------------------
H |- (case d of inr(x)  e1, inr(y)  e2) : C
16
De Morgan’s Laws as Code!

fun d: (AC) || (BC).


fun p : A*B.
case d of
inl(f)  f(fst p),
inr(g) -> g(snd p)

Has type
((A  C) || (B  C))  (A*B)  C
This is a generalization of De Morgan’s rule Think of ¬A
 ¬A∨¬B ¬ A∧B  as
A  false
and then replace
false by C
Can this same thing be done with all of De Morgan’s
other three rules? Yes? No?
17
Compiler Construction
Lecture 08
Stack Machine

Lent Term, 2006

Lecturer: Timothy G. Griffin

Computer Laboratory
University of Cambridge
1
SLANG: A (S)imple (LANG)uage (v0.1)
type name = string

type binary_op = PlusOp | TimesOp | MinusOp | DivOp


| Eq | Lt | Lte | Gt | Gte
| And | Or
ocaml
type unary_op = UnaryMinusOp | Not datatypes
for SLANG
type expression = Ident of name
| Number of int ASTs
| Unary of unary_op * expression
| Binary of binary_op * expression * expression
| Apply of name * (expression list)

type command = Assignment of name * expression


| Sequence of command list
| Condition of expression * command * command
| Return of expression
| While of expression * command
| Block of (local_declaration list) *command

and local_declaration = Var of name * expression

and global_declaration = Let of name * expression


| Fun of name * (name list) * (local_declaration list) *command

type slang = Slang of (global_declaration list) * expression

2
SLANG example, with AST
fun f(y, x)
{
let z = 17;
return z * (y + x);
}

let x = 19;
let y = 10;

20 * (f(x, y) - f(y, x))

Slang
([Fun ("f", ["y"; "x"], [Var ("z", Number 17)],
Return
(Binary (TimesOp, Ident "z",
Binary (PlusOp, Ident "y", Ident "x"))));
Let ("x", Number 19); Let ("y", Number 10)],
Binary (TimesOp, Number 20,
Binary (MinusOp, Apply ("f", [Ident "x"; Ident "y"]),
Apply ("f", [Ident "y"; Ident "x"]))))

3
We will translate SLANG to JARGON

Intermediate
Representation

SLANG ast Jargon Code

Jargon is my own
Invented abstract STACK
machine…

4
Jargon Virtual Machine (v0.1)

grows

stack sp shrinks
pointer

frame fp Stack
pointer
Four
special-purpose
“registers”

Code cp
pointer
Instructions

Status sr status
register
5
Stack Instructions: pop, popto

sp FREE
pop
value
sp FREE

stack
stack

sp FREE
value For local vars sp FREE

popto j

value Stack[fp+j]

6
fp fp
Stack Instructions: push, pushfrom

push value
sp FREE
sp FREE value

stack stack

sp FREE
sp FREE value
For local vars

pushfrom j

Stack[fp+j] value value

fp fp 7
Top-of-Stack swap and
Top-of-Stack arithmetic
sp FREE sp FREE
value 2 swap value 1
value 1 value 2

stack stack

sp FREE
result = (value 1) op (value 2)

value 2 arith op sp FREE


value 1 result

Op in { + , *, -, / , <, >, <=, >=, =, &&, ||} 8


goto, skip

goto k
cp j : goto k

k : …….. cp k : ……..

(set status to an error code if k is not in range…)

skip
cp j : skip j : skip
j+1 : …….. cp j+1 : ……..

9
test

If VALUE
test k cp j+1 : … is not 0
cp j : test k
j+1 : …

k : ……..
If VALUE
cp k : …….. is 0

sp FREE
VALUE sp FREE

stack stack
10
stop

cp cp j : stop
j : stop
stop

sr 0 sr 1

Status codes
0 = running
1 = stopped (program answer should be on top of stack)
2 = store index out of bounds
3 = call out of bounds
4 = stack overflow
5 = fp offset out of bounds
11
6 = return cp out of bounds
7 = arith error (div by 0)
JARGON Initial State
sp = 2 FREE

dummy return 0
fp = 0 0
Stack

cp = 0

Code

status = 0
12
Translation of expressions

Code to leave the


e value of e on
top of the stack

pushfrom offest

constant identifier (local variable)

pushfrom -offest
c push c x
(formal parameter)

load index
(global variable) 13
Translation of expressions

code for e1
e1 op e2
code for e2

arith op

0 : push 3
1 : push 8
2 : push 17
3 * ((8 + 17) * (2 - 6)) 3 : arith +
4 : push 2
5 : push 6
6 : arith -
7 : arith * 14
8 : arith *
Translation of commands

Code produce the


cmd side effects of
the command

popto offest
assignment (local variable)
code for e
x = e;
“update x”
pop

store index
(global variable) 15
Translation of commands

code for c_1


c_1; c_2; … c_n;
: :
: :

code for c_n

16
Conditionals, Loops

If e then c1 else c2 while e { c }

code for e m: code for e

test k test k

code for c1 code for c

goto m goto m

k: code for c2 k: skip

m: skip

17
0: push 0 ; slot for x
Conditional Example 1: push 0 ; slot for y
2: push 19 ;
3: popto 2 ; store x
fun f(x, y) { 4: push 10 ;
let a = 0; 5: popto 3 ; store y
6: load 2 ; load x
if x < y 7: load 3 ; load y
then a = 100; 8: call 14 ; call f
9: swap ; remove arg 2
else a = 500;
10 : pop ; ...
11 : swap ; remove arg 1
return a; 12 : pop ; ...
} 13 : stop ; that's all folks!
14 : push 0 ; slot for a
let x = 19; 15 : push 0 ;
let y = 10; 16 : popto 2 ; store a
17 : pushfrom -2 ; load x
18 : pushfrom -1 ; load y
f(x, y) 19 : arith < ;
20 : test 24 ; if (x < y)
21 : push 100 ;
22 : popto 2 ; store a
23 : goto 26 ; jump over else clause
24 : push 500 ;
If then else.. 25 : popto 2 ; store a
26 : skip ; end if
27 : pushfrom 2 ; load a
28 : return ;
18
Example, While loop 0:
1:
push 4
call 5
;
; call sum
2: swap ; remove arg 1
3: pop ; ...
4: stop ; that's all folks!
5: push 0 ; slot for k
6: push 0 ; slot for s
fun sum(x) { 7: pushfrom -1 ; load x
let k = x; 8: popto 2 ; store k
let s = 0; 9: push 0 ;
while 0 < k { 10 : popto 3 ; store s
s = s + k; 11 : push 0 ; begin while loop
k = k - 1; 12 : pushfrom 2 ; load k
} 13 : arith < ;
return s; 14 : test 24 ; check (0 < k)
} 15 : pushfrom 3 ; load s
16 : pushfrom 2 ; load k
sum(4) 17 : arith + ;
18 : popto 3 ; store s
19 : pushfrom 2 ; load k
20 : push 1 ;
21 : arith - ;
22 : popto 2 ; store k
23 : goto 11 ; while loop iterate
While loop 24 : skip ; end while
25 : pushfrom 3 ; load s 19
26 : return ;
Compiler Construction
Lecture 09
Functions I

Lent Term, 2006

Lecturer: Timothy G. Griffin

Computer Laboratory
University of Cambridge
1
Jargon Stack Frame

Stack[sp] = next available slot at


stack sp top of stack
pointer
Current “working stack”

Current stack frame


(activation record)
Stack[fp + 2] to Stack[fp + k]
frame fp values of local variables
Pointer
Stack[fp + 1] contains return cp
Stack[fp] contains the fp of the
calling procedure

Stack[fp - 1] to Stack[fp - n]
are arguments passed by caller
Previous stack frame
(of caller)
2
call

cp j : call k j : call k

k : …….. cp k : ……..

Code
Code call k

sp FREE
j+1
sp FREE fp

caller’s
frame

fp 3
return

cp j : return j : return

m : …….. cp m : ……..

Code Code

sp FREE
value return

m: sp FREE

fp value

fp 4
Translation of expressions

f(e_1, …, e_n) return e;

code for e_1


This will leave
: : the values of each
code for e
: : arg on the stack,
with the value of
e_n at the top return
code for e_n
k = address of
call k code for f

swap
pop Take n args off
the stack, always
: : leaving return
: : value at top

swap 5
pop
SLANG to JARGON 0:
1:
push 0
push 0
; slot for x
; slot for y
example 2:
3:
push 19
popto 2
;
; store x
4: push 10 ;
5: popto 3 ; store y
6: push 20 ;
7: pushfrom 2 ; load x
fun f(y, x) 8: pushfrom 3 ; load y
{ 9: call 24 ; call f
10 : swap ; remove arg 2
let z = 17; 11 : pop ; ...
return z * (y + x); 12 : swap ; remove arg 1
} 13 : pop ; ...
14 : pushfrom 3 ; load y
15 : pushfrom 2 ; load x
let x = 19; 16 : call 24 ; call f
let y = 10; 17 : swap ; remove arg 2
18 : pop ; ...
19 : swap ; remove arg 1
20 * (f(x, y) - f(y, x)) 20 : pop ; ...
21 : arith - ;
22 : arith * ;
23 : stop ; that's all folks!
24 : push 0 ; f entry, slot for z
25 : push 17 ;
26 : popto 2 ; store z
f 27 : pushfrom 2 ; load z
28 : pushfrom -2 ; load y
29 : pushfrom -1 ; load x
30 : arith + ;
31 : arith * ;
32 : return ; return from f
6
Q:Did we do something wrong?
fun fact(x) {
if x = 0
then return 1; 0: push 4 ;
else return x * fact(x-1); 1: call 5 ; call fact
} 2: swap ; remove arg 1
3: pop ; ...
fact(4) 4: stop ; that's all folks!
5: pushfrom -1 ; load x
6: push 0 ;
Implementation of 7: arith = ;
conditional contains 8: test 12 ; if (x = 0)
“dead code” at lines 11 9: push 1 ;
and 21 10 : return ;
11 : goto 21 ; jump over else clause
12 : pushfrom -1 ; load x
13 : pushfrom -1 ; load x
14 : push 1 ;
15 : arith - ;
A: Probably not. It might be better to 16 : call 5 ; call fact
keep the code generation phase clean, 17 : swap ; remove arg 1
and leave optimizations to another pass 18 : pop ; ...
19 : arith * ;
20 : return ; 7
21 : skip ; end if
Nested functions, procedures

fun f(x) {
let a = …; How this call to h
fun h(y) { b access the value of
let b = …; a and x?
h’s frame
fun g(w) {
let c = …;
if .. c
then return a;
else return h(c) g’s frame
}
return b + g(y); b
} h’s frame
return x + h(a);
}
a
f’s frame
f(17)
x 17 8
Alternative 1: Dijkstra Displays

fun f(x) {
let a = …;
Depth 0
Static frame pointer
h F[0]
fun h(y) { Depth 1
let b = …;
fun g(w) { Depth 2 : :
let c = …;
if .. g F[0]
then return a;
(+) at run-time F[1]
else return h(c)
} only need a fixed
return b + g(y); number of indirections
} to find the value of a
: :
}
return x + h(a); non-local variable
h
(-) can use a lot of space
b
on the stack, and slows F[0]
down function calls

If function g is at static nesting depth i,


: :
then use an array F of size i where f
F[j] is the frame pointer of the most recent a
stack frame for the enclosing function at
nesting depth j
x 9
Alternative 2: Single Static Link per Frame

fun f(x) {
let a = …;
Depth 0
Static frame pointer
h
fun h(y) { Depth 1
let b = …;
fun g(w) { Depth 2
let c = …; c
if .. g : :
then return a;
else return h(c) (+) uses less space, takes
} less time to set up and
return b + g(y); tear down.
} y
}
return x + h(a); (-) At run-time, need to
“chase pointers” to find
h : :
the value of a non-local
b
variable.

a
f : :
If function g is at static nesting depth i, a
then use a single static link to the most
recent frame for nesting depth i-1.
x 10
Single Static Link vs. Dijkstra Displays

Single Static Link Dijkstra Displays


fun f(x) {
Frame for let a = … ;
Frame for
j(…) fun g(y) { j(…)
let b = …;
fun h(z) { Linkage
let c = …; Info is an array
Of pointers
fun j(w) {…}
… j(…)…
}
… h(…) …
Frame for } Frame for
h(…) … g(…) … h(…)
}
: : … f(...)
: :
Frame for Frame for
g(…) g(…)

: : : :
Frame for Frame for
f(…) f(…) 11
Add commands to JARGON for non-local
variables, using single static links

fetch d j sp FREE
sp FREE
value

static-fp Stack[ fp + 2 ]

fp fp

get(0, fp) = fp
get(d + 1, fp) = get(d, Stack[fp+2])

value value = Stack[get(d, static-fp) + j]


j
12
get(d, static-fp)
Alternative 3: “Lambda Lifting”

fun f(x) { fun g’(w, x, a, y, b) {


let a = …; let c = …;
fun h(y) { if ..
let b = …; then return a;
fun g(w) { else return h’(c, x, a )
let c = …; }
if .. fun h’(y, x, a) {
then return a; let b = …;
else return h(c) return b + g’(y, x, a, y, b)
} }
return b + g(y);
} fun f’(x) {
return x + h(a); let a = …;
} return x + h’(a, x, a);
}
f(17)
f’(17)
13
Stack h’
Evaluation
a
x
c
fun g’(w, x, a, y, b) {
: : g’
let c = …;
if ..
then return a;
else return h’(c, x, a) b
} y
fun h’(y, x, a) { a
let b = …; x
return b + g’(y, x, a, y, b) y
} : : h’
fun f’(x) {
b
let a = …;
return x + h’(a, x, a);
} a
x
f’(17) a f’
: :
a

x 14
Problem: a lot
h’
of
Duplication! a
x
c
fun g’(w, x, a, y, b) {
: : g’
let c = …;
if ..
then return a;
else return h’(c, x, a) b
} y
fun h’(y, x, a) { a
let b = …; x
return b + g’(y, x, a, y, b) y
} : : h’
fun f’(x) {
b
let a = …;
return x + h’(a, x, a);
} a
x
f’(17) a f’
: :
a

x 15
A Classic Trade Off

Static Pointer
Chains

Displays

Lower run-time Where we want Closure


cost of variable to be … conversion
access

Lower Call-time set up cost


(on a stack-oriented machine)

16
Compiler Construction
Lecture 10
Functions II

Lent Term, 2007

Lecturer: Timothy G. Griffin

Computer Laboratory
University of Cambridge
1
What about functions-as-values?

fun f(a : int) : int -> int


{
fun g(x :int) : int {return a + x;}
return g;
}

let add21 : int -> int = f(21);


let add17 : int -> int = f(17);

add17(3) + add21(-1)

Oh NO! Our previous approach to


“lambda lifting” no longer works!

2
Idea --- function values as “closures”

fun f(a : int) : int -> int


{
fun g(x :int) : int {return a + x;} A closure is a record containing
return g; the address of a function AND
} the values of its free variables

let add21 : int -> int = f(21);


let add17 : int -> int = f(17);

add17(3) + add21(-1)

add21 g address code


a  21 for
g

add17 g address
a  17

an address Where should these Code array 3


be stored??
Jargon Virtual Machine (v0.2)
Four heap[heal_limit]
special-purpose
grows
registers
Frame 2
stack sp shrinks
pointer heap[0]
heap
frame fp (array of values)
pointer frame 1

Code cp frame 0
pointer

Stack
(really array) Code
(array of instructions)

Status sr status 4
register
set

k : …….. k : value

set
heap heap

sp FREE
k
value sp FREE

fp fp 5
get

k : value

heap get

sp FREE sp FREE
k value

fp fp 6
SLANG Implementation Convention
stack heap

free
space

allocated We will talk


space about “garbage
Stack[2] Points to collection”
first free cell another day…
in heap

Tack this onto every jargon program:


__allocate : load 2 ; entry point for allocate
: copy ;
: push 1 ;
: arith + ;
: store 2 ;
: return ; exit allocate
7
Address of code may not be known at
compile-time…

fun f(a : int) : int -> int


{
fun g(x :int) : int {return a + x;}
fun h(x :int) : int {return a * x;}
if a < 20 then return g else return h;
}

let f21 : int -> int = f(21);


let f17 : int -> int = f(17);

f17(3) + f21(-1)

8
Closure conversion (similar to “lambda lifting”)

fun f(a)
{
fun g(x) {return a + x;}
fun h(x) {return a * x;}
if a < 20 then return g else return h;
}

fun g(c, x) {return c.1 + x;}


fun h(c, x) {return c.1 * x;}
fun f(c, a)
{
if a < 20 then return (g, [a]) else return (h, [a]);
}
c.0 = code pointer ….
c.1 = array of values 9
(or some other data structure…)
calla : gets address from stack top

cp j : calla j : calla

cp k : ……..

Code
Code calla

sp FREE
j+1
sp FREE
k fp

caller’s
frame

fp 10
How to translate Application…
k
e (e1, e2 … en) vn
: :
v1
code for e v closure k: code
code for e1 for for
function function

: : :
code for en
code to extract Stack Heap
Code

address of function
Situation just before calla
from heap, leaving
it on top of stack NB: code for function must treat v as
An implicit parameter in order to access
calla Non-local variables on heap.
11
This works for functions-as-arguments

fun f(a : int) : int -> int


{
fun g(x :int) : int {return a + x;}
fun h(x :int) : int {return a * x;}
if a < 20 then return g else return h;
}
fun j(x: int, k: int-> int) { return k(k(x));}

j(3, f(21)) + j(-1, f(17))

12
Similar problem with reference cell
lifetimes…

fun f(a : int) : int ref


{
let b : int ref := a;
return b;
}

let z : int ref = f(17);

!z

13
References

let x : int = 22;


Push 22 on stack. fun sum(x : int) : int {
keep track of offset for let k : int ref := x;
later uses of x…
let s : int ref := 0;
while 0 < !k {
s := !s + !k;
k := !k - 1;
}
let x : int ref := 22; return !s;
}
Allocate space for x on heap,
push address of x on stack.
keep track of offset for sum(10)
later uses of x…

14
Translation of references..

let x : int ref := e;

… code to push value of e on stack …


push 0 ; space for x’s address
call __allocate ; get free space
copy ; duplicate top of stack
popto offset ; store address of x
set ; store value of x in heap
expression

x := e; !x

… code to push value of e on stack … pushfrom offset ; x’s address …


pushfrom offset ; x’s address get ; x’s value
set ;

15
Compiler Construction
Lecture 11
Register Machines and the
Min-Caml Middle-End

Lent Term, 2007

Lecturer: Timothy G. Griffin

Computer Laboratory
University of Cambridge
1
Register Machines
Basic (Abstract) Operations

RL Move data from memory location L to register R


Move data from memory location stored in R2
R1  [R2]
to register R1

LR Move data from register R to memory location L

[R2]  R1 Move data from register R1 to memory location


stored in R2

Perform operation op in values in registers R2 and R3,


R1  R2 op R3 And then store the result in register R1.

2
Stack Machine to Register Machine

A simple translation that produces terrible code:

SP SP - 1
R2  [SP]
arith op
SP SP - 1
R3  [SP]
R1  R2 op R3
[SP] R1
But this defeats the whole point of registers ---
they are FAST local memory that should SP SP + 1
be used to reduce CPU to memory traffic.

This assumes that stack grows


upwards, and SP always points
to the next free slot 3
A Better way…

Give explicit Generate code


Program AST names to all for an abstract
Intermediate Machine with an infinite
values number of registers

Perform “Register Allocation” –


map abstract registers to
actual machine registers,
Emit assembler
“spilling” registers into memory
only when you run out of actual
registers.

4
Let’s look at the MinCaml Middle-End!

type t =
| Unit
| Bool of bool syntax.ml
| Int of int
| Float of float
| Not of t
| Neg of t
| Add of t * t
| Sub of t * t
| FNeg of t
| FAdd of t * t
| FSub of t * t
| FMul of t * t
| FDiv of t * t
| Eq of t * t
| LE of t * t
| If of t * t * t
| Let of (Id.t * Type.t) * t * t
| Var of Id.t
| LetRec of fundef * t
| App of t * t list
| Tuple of t list
| LetTuple of (Id.t * Type.t) list * t * t
| Array of t * t
| Get of t * t
| Put of t * t * t
and fundef =
{ name : Id.t * Type.t;
args : (Id.t * Type.t) list;
body : t }

5
http://min-caml.sourceforge.net/
MinCaml Compiler Roadmap

Stages, with lines of ocaml code…

Lexer Parser Typing KNormal Alpha


100 168 165 181 46

Const
Elim Inline Assoc Beta
Fold
34 46 33 18 38
Reg
Closure Virtual Simm13 Emit
Alloc
104 163 42 256
262
6
Putting it all together…
let rec iter n e =
if n = 0 then e else
let e' = Elim.f (ConstFold.f (Inline.f (Assoc.f (Beta.f e)))) in
if e = e' then e else iter (n - 1) e‘

let lexbuf outchan l =


Id.counter := 0;
Typing.extenv := M.empty;
Emit.f outchan
(RegAlloc.f From min-caml/main.ml
(Simm13.f
(Virtual.f
(Closure.f
(iter !limit
(Alpha.f
(KNormal.f
(Typing.f
(Parser.exp Lexer.token l)))))))))

Clean code!! 7
K-Normalization

a+b+c*d

let tmp1 = a + b in
let tmp2 = c * d in
tmp1 + tmp2
• Nesting is allowed
let x = (let y = M1 in M2) in M3

8
Example.
let x = 17
in
let rec f y =
let rec g z = ((x + y) + z)
in g
in
let first = (f 21)
in
let second = (f 88)
in
let result = ((first 99) + (second 44))
in (print_int result)

Typing
let x : int = 17
in
let rec f : (int) -> (int) -> int y : int =
let rec g : (int) -> int z : int = ((x + y) + z)
in g
in
let first : (int) -> int = (f 21)
in
let second : (int) -> int = (f 88)
in
let result : int = ((first 99) + (second 44))
in (print_int result)
9
Knormalization
let x : int = 17
in
let rec f : (int) -> (int) -> int y : int =
let rec g : (int) -> int z : int = ((x + y) + z)
in g
in
let first : (int) -> int = (f 21)
in
let second : (int) -> int = (f 88)
in
let result : int = ((first 99) + (second 44))
in (print_int result)

let x : int = 17 in

let f : (int) -> (int) -> int y : int =


let g : (int) -> int z : int =
let Ti7 : int = (x + y) in
(Ti7 + z)
in g
in
let first : (int) -> int = let Ti1 : int = 21 in (f Ti1) in

let second : (int) -> int = let Ti2 : int = 88 in (f Ti2) in

let result : int = let Ti4 : int = let Ti3 : int = 99 in (first Ti3) in
let Ti6 : int = let Ti5 : int = 44 in (second Ti5) in
(Ti4 + Ti6)
in
EXTERN(print_int result)
10
KNormalization
type t = type t =
| Unit
| Bool of bool syntax.ml | Unit
| Int of int knormal.ml
| Int of int | Float of float
| Float of float | Neg of Id.t
| Not of t | Add of Id.t * Id.t
| Neg of t | Sub of Id.t * Id.t
| Add of t * t | FNeg of Id.t
| Sub of t * t | FAdd of Id.t * Id.t
| FNeg of t | FSub of Id.t * Id.t
| FAdd of t * t | FMul of Id.t * Id.t
| FSub of t * t | FDiv of Id.t * Id.t
| FMul of t * t | IfEq of Id.t * Id.t * t * t
| FDiv of t * t | IfLE of Id.t * Id.t * t * t
| Eq of t * t | Let of (Id.t * Type.t) * t * t
| LE of t * t | Var of Id.t
| If of t * t * t | LetRec of fundef * t
| Let of (Id.t * Type.t) * t * t | App of Id.t * Id.t list
| Var of Id.t | Tuple of Id.t list
| LetRec of fundef * t | LetTuple of (Id.t * Type.t) list * Id.t * t
| App of t * t list | Get of Id.t * Id.t
| Tuple of t list | Put of Id.t * Id.t * Id.t
| LetTuple of (Id.t * Type.t) list * t * t | ExtArray of Id.t
| Array of t * t | ExtFunApp of Id.t * Id.t list
| Get of t * t
| Put of t * t * t and fundef =
and fundef = { name : Id.t * Type.t;
{ name : Id.t * Type.t; args : (Id.t * Type.t) list;
args : (Id.t * Type.t) list; body : t }
body : t }

val Knormal.f : Syntax.t -> Knormal.t 11


Simplification: β-Reduction, Nested "Let"
Reduction

let x = y in M ⇒ [y/x]M

let y = (let x = M1 in M2) in M3



let x = M1 in let y = M2 in M3
12
Simplification: Inlining

Inlines all "small" functions


• Includes recursive ones
• "Small" = less than a constant size
– User-specified by "-inline" option
• Repeat for a constant number of times
– User-specified by "-iter" option

13
Simplification: Constant Folding and
Unused Variable Elimination

let x = 3 in let y = 7 in x + y

let x = 3 in let y = 7 in 10

10

Very effective after inlining!


14
Simplification
let x : int = 17 in

let f : (int) -> (int) -> int y : int =


let g : (int) -> int z : int =
let Ti7 : int = (x + y) in
(Ti7 + z)
in g
in
let first : (int) -> int = let Ti1 : int = 21 in (f Ti1) in

let second : (int) -> int = let Ti2 : int = 88 in (f Ti2) in

let result : int = let Ti4 : int = let Ti3 : int = 99 in (first Ti3) in
let Ti6 : int = let Ti5 : int = 44 in (second Ti5) in
(Ti4 + Ti6)
in
EXTERN(print_int result)

let x.8 : int = 17 in


let f.9 : (int) -> (int) -> in ty.10 : int =
let g.20 : (int) -> int z.21 : int =
let Ti7.22 : int = (x.8 + y.10) in
(Ti7.22 + z.21)
in g.20
in
let Ti1.19 : int = 21 in
let first.11 : (int) -> int = (f.9 Ti1.19) in
let Ti2.18 : int = 88 in
let second.12 : (int) -> int = (f.9 Ti2.18) in
let Ti3.17 : int = 99 in
let Ti4.14 : int = (first.11 Ti3.17) in
let Ti5.16 : int = 44 in
let Ti6.15 : int = (second.12 Ti5.16) in
let result.13 : int = (Ti4.14 + Ti6.15) in
EXTERN(print_int result.13) 15
Closure Conversion

Local function definitions (let rec)


+ function applications

Top-level function definitions


+
 Closure creations (make_closure)
 Closure applications (apply_closure)
 Known function calls (apply_direct) 16
Example 1:
Closure Creation/Application

let x = 3 in
let rec f y = x + y in
f7

let rec ftop [x] y = x + y in
let x = 3 in
make_closure f = (ftop, [x]) in
apply_closure f 7
17
Example 2: Known Function Call

let rec f x = x + 3 in
(f, f 7)

let rec ftop [] x = x + 3 ;;

make_closure f = (ftop, []) in


(f, apply_direct f 7)
18
Example 3:
Unused Closure Elimination

let rec f x = x + 3 in
f7

let rec ftop [] x = x + 3 ;;

apply_direct f 7

19
let x.8 : int = 17 in
let f.9 : (int) -> (int) -> in ty.10 : int =
Closure let g.20 : (int) -> int z.21 : int =
let Ti7.22 : int = (x.8 + y.10) in

Conversion (Ti7.22 + z.21)


in g.20
in
let Ti1.19 : int = 21 in
let first.11 : (int) -> int = (f.9 Ti1.19) in
let Ti2.18 : int = 88 in
let second.12 : (int) -> int = (f.9 Ti2.18) in
let Ti3.17 : int = 99 in
let Ti4.14 : int = (first.11 Ti3.17) in
let Ti5.16 : int = 44 in
let Ti6.15 : int = (second.12 Ti5.16) in
let result.13 : int = (Ti4.14 + Ti6.15) in
EXTERN(print_int result.13)

let LABEL(g.20) [x.8 : int, y.10 : int] z.21 : int =


let Ti7.22 : int = (x.8 + y.10) in (Ti7.22 + z.21)
in
let LABEL(f.9) [x.8 : int] y.10 : int =
let closure g.20 : (int) -> int = ( LABEL(g.20); [x.8, y.10] ) in g.20
in
let x.8 : int = 17 in
let closure f.9 : (int) -> (int) -> int = ( LABEL(f.9); [x.8] ) in
let Ti1.19 : int = 21 in
let first.11 : (int) -> int = APPLY_CLOSURE(f.9 Ti1.19) in
let Ti2.18 : int = 88 in
let second.12 : (int) -> int = APPLY_CLOSURE(f.9 Ti2.18) in
let Ti3.17 : int = 99 in
let Ti4.14 : int = APPLY_CLOSURE(first.11 Ti3.17) in
let Ti5.16 : int = 44 in
let Ti6.15 : int = APPLY_CLOSURE(second.12 Ti5.16) in 20
let result.13 : int = (Ti4.14 + Ti6.15) in
APPLY_DIRECT(LABEL(min_caml_print_int) result.13)
Closure Conversion
type closure = { entry : Id.l; actual_fv : Id.t list }
type t =
| Unit knormal.ml type t =
| Unit
| Int of int | Int of int
| Float of float | Float of float

closure.ml
| Neg of Id.t | Neg of Id.t
| Add of Id.t * Id.t | Add of Id.t * Id.t
| Sub of Id.t * Id.t | Sub of Id.t * Id.t
| FNeg of Id.t | FNeg of Id.t
| FAdd of Id.t * Id.t | FAdd of Id.t * Id.t
| FSub of Id.t * Id.t | FSub of Id.t * Id.t
| FMul of Id.t * Id.t | FMul of Id.t * Id.t
| FDiv of Id.t * Id.t | FDiv of Id.t * Id.t
| IfEq of Id.t * Id.t * t * t | IfEq of Id.t * Id.t * t * t
| IfLE of Id.t * Id.t * t * t | IfLE of Id.t * Id.t * t * t
| Let of (Id.t * Type.t) * t * t | Let of (Id.t * Type.t) * t * t
| Var of Id.t | Var of Id.t
| LetRec of fundef * t | MakeCls of (Id.t * Type.t) * closure * t
| App of Id.t * Id.t list | AppCls of Id.t * Id.t list
| Tuple of Id.t list | AppDir of Id.l * Id.t list
| LetTuple of (Id.t * Type.t) list * Id.t * t | Tuple of Id.t list
| Get of Id.t * Id.t | LetTuple of (Id.t * Type.t) list * Id.t * t
| Put of Id.t * Id.t * Id.t | Get of Id.t * Id.t
| ExtArray of Id.t | Put of Id.t * Id.t * Id.t
| ExtFunApp of Id.t * Id.t list | ExtArray of Id.l
type fundef = { name : Id.l * Type.t;
and fundef = args : Id.t * Type.t) list;
{ name : Id.t * Type.t; formal_fv : (Id.t * Type.t) list;
args : (Id.t * Type.t) list; body : t }
body : t } type prog = Prog of fundef list * t

val Closure.f : Knormal.t -> Closure.prog 21


Compilation as a sequence of small steps…

let x = 17
in
let rec f y =
let rec g z = ((x + y) + z)
• Lexing in g
• in
Parsing let first = (f 21)
• Typing in
• K-normalization let second = (f 88)
in
• Simplification let result = ((first 99) + (second 44))
• Closure conversion in (print_int result)

let LABEL(g.20) [x.8 : int, y.10 : int] z.21 : int =


let Ti7.22 : int = (x.8 + y.10) in (Ti7.22 + z.21)
in
let LABEL(f.9) [x.8 : int] y.10 : int =
let closure g.20 : (int) -> int = ( LABEL(g.20); [x.8, y.10] ) in g.20
in
let x.8 : int = 17 in
let closure f.9 : (int) -> (int) -> int = ( LABEL(f.9); [x.8] ) in
let Ti1.19 : int = 21 in
let first.11 : (int) -> int = APPLY_CLOSURE(f.9 Ti1.19) in
let Ti2.18 : int = 88 in
let second.12 : (int) -> int = APPLY_CLOSURE(f.9 Ti2.18) in
let Ti3.17 : int = 99 in
let Ti4.14 : int = APPLY_CLOSURE(first.11 Ti3.17) in
let Ti5.16 : int = 44 in
let Ti6.15 : int = APPLY_CLOSURE(second.12 Ti5.16) in 22
let result.13 : int = (Ti4.14 + Ti6.15) in
APPLY_DIRECT(LABEL(min_caml_print_int) result.13)
23
Another Example: ack.ml
let rec ack x y =
if (x <= 0)
then (y + 1)
else
if (y <= 0)
then (ack (x - 1) 1)
else (ack (x - 1) (ack x (y - 1)))
in (print_int (ack 3 10))

Typing

let rec ack : (int, int) -> int x : int y : int =


if (x <= 0)
then (y + 1)
else
if (y <= 0)
then (ack (x - 1) 1)
else (ack (x - 1) (ack x (y - 1)))
in (print_int (ack 3 10))

24
KNormalization

let ack : (int, int) -> int x : int y : int =


let Ti4 : int = 0
in
if x <= Ti4
then
let Ti5 : int = 1
in (y + Ti5)
else
let Ti6 : int = 0
in
if y <= Ti6
then
let Ti8 : int = let Ti7 : int = 1 in (x - Ti7) in
let Ti9 : int = 1 in (ack Ti8 Ti9)
else
let Ti11 : int = let Ti10 : int = 1 in (x - Ti10) in
let Ti14 : int = let Ti13 : int = (let Ti12 : int = 1 in (y - Ti12))
in (ack x Ti13)
in (ack Ti11 Ti14)
in
let Ti3 : int = let Ti1 : int = 3 in
let Ti2 : int = 10 in (ack Ti1 Ti2) in
EXTERN(print_int Ti3)

25
After Simplification
let ack.15 : (int, int) -> int x.16 : int y.17 : int =
let Ti4.21 : int = 0
in
if x.16 <= Ti4.21
then
let Ti5.31 : int = 1
in (y.17 + Ti5.31)
else
let Ti6.22 : int = 0
in
if y.17 <= Ti6.22
then
let Ti7.30 : int = 1 in
let Ti8.28 : int = (x.16 - Ti7.30) in
let Ti9.29 : int = 1
in (ack.15 Ti8.28 Ti9.29)
else
let Ti10.27 : int = 1 in
let Ti11.23 : int = (x.16 - Ti10.27) in
let Ti12.26 : int = 1 in
let Ti13.25 : int = (y.17 - Ti12.26) in
let Ti14.24 : int = (ack.15 x.16 Ti13.25)
in (ack.15 Ti11.23 Ti14.24)
in
let Ti1.19 : int = 3 in
let Ti2.20 : int = 10 in
let Ti3.18 : int = (ack.15 Ti1.19 Ti2.20)
in EXTERN(print_int Ti3.18)
26
Closure Conversion
let ack.15 : (int, int) -> int x.16 : int, y.17 : int =
let Ti4.21 : int = 0
in
if x.16 <= Ti4.21
then
let Ti5.31 : int = 1
in (y.17 + Ti5.31)
else
let Ti6.22 : int = 0
in
if y.17 <= Ti6.22
then
let Ti7.30 : int = 1 in
let Ti8.28 : int = (x.16 - Ti7.30) in
let Ti9.29 : int = 1
in APPLY_DIRECT(ack.15 Ti8.28 Ti9.29)
else
let Ti10.27 : int = 1 in
let Ti11.23 : int = (x.16 - Ti10.27) in
let Ti12.26 : int = 1 in
let Ti13.25 : int = (y.17 - Ti12.26) in
let Ti14.24 : int = APPLY_DIRECT(ack.15 x.16 Ti13.25)
in APPLY_DIRECT(ack.15 Ti11.23 Ti14.24)
In
let Ti1.19 : int = 3 in
let Ti2.20 : int = 10 in
let Ti3.18 : int = APPLY_DIRECT(ack.15 Ti1.19 Ti2.20)
in APPLY_DIRECT(min_caml_print_int Ti3.18)

27
Yet another example : funcomp.ml

let rec compose f g =


let rec composed x = g (f x) in
composed in
let rec dbl x = x + x in
let rec inc x = x + 1 in
let rec dec x = x - 1 in
let h = compose inc (compose dbl dec) in
print_int (h 123)

28
Compiler Construction
Lectures 12 & 13
Assembler, Linker, Loader.
MinCaml Back-End

Lent Term, 2007

Lecturer: Timothy G. Griffin

Computer Laboratory
University of Cambridge
1
Compiler, Assembler, Linker, Loader

Program Assembly Object


File Compiler Assembler File
Language

Program Assembly Object


Compiler Assembler
File Language File

Executable
Libraries Linker File
Object/Executable File =
Machine Code +
Bookkeeping Information (dynamic)

Operating System Loader

Grinding Machine 2
Assembler

• Translates assembly language to binary


machine language
– This may not be 11, since many assembly
languages contain pseudo-instructions that translated
to multiple machine instructions
• Replaces symbolic names with numeric
addresses
• Generates bookkeeping information in object file
– Symbols exported
– Symbols imported
– Relocation information (which absolute addresses
need to be re-written when code is relocated)
For example, see open source x86 assembler NASM: http://sourceforge.net/projects/nasm
3
Three kinds of object files

Relocation = rewrite binary files to move instructions to new locations.

• Relocatable object file


– binary code and data in a form that can be combined
with other relocatable object files at compile time to
create an executable object file.
• Shared object file
– a special type of relocatable object file that can be
loaded into memory and linked dynamically, either at
load time or at run time.
• Executable object file
– binary code and data in a form that can be directly
loaded into memory and executed.
4
Many Object File Formats…

• Early Unix
– a.out format
• System V
– COFF = Common Object File Format
• Modern Unix
– UNIX ELF (executable and linking format)
• Windows NT
– PE (Portable Executable) format, a variant of COFF
• ….

5
ELF Summary

6
Linker and Loader Tasks
.
• Program Loading
- This refers to copying a program image from hard disk to the main
memory in order to put the program in a ready-to-run state. In some
cases, program loading also might involve allocating storage space or
mapping virtual addresses to disk pages.
• Symbol Resolution
– A program is made up of multiple subprograms; reference of one
subprogram to another is made through symbols. A linker's job is to
resolve the reference by noting the symbol's location and patching the
caller's object code
• Relocation
– Compilers and assemblers generate the object code for each input
module with a starting address of zero. Relocation is the process of
assigning load addresses to different parts of the program by merging
all sections of the same type into one section. The code and data
section also are adjusted so they point to the correct runtime addresses.

Overlap exists between the functions of linkers and loaders:


the loader does the program loading;
the linker does the symbol resolution; and
either of them can do the relocation.
7
Unix Example: gcc a.c b.c
• Run preprocessor
– cpp [options] a.c /tmp/a.i
– cpp [options] b.c /tmp/b.i
• Run compiler
– cc1 [options] /tmp/a.i -o /tmp/a.s
– cc1 [options] /tmp/b.i -o /tmp/b.s
• Run assembler
– as [options] /tmp/a.s -o /tmp/a.o
– as [options] /tmp/b.s -o /tmp/b.o
• Run the linker
– ld [options] /tmp/a.o /tmp/b.o -o a.out
• Run it (invokes the loader, execve)
– ./a.out 8
Back to MinCaml !!

Lexer Parser Typing KNormal Alpha


100 168 165 181 46

Const
Elim Inline Assoc Beta
Fold
34 46 33 18 38
Reg
Closure Virtual Simm13 Emit
Alloc
104 163 42 256
262
Back-End
9
SPARC Registers

WINDOW

10
MinCaml Code Generation for Sparc

%i0 = stack pointer


%i1 = heap pointer MinCaml
%o7 = return address register
%o5 = closure address conventions
%o4 = temporary for swap

11
SPARC Addressing Modes

12
Some SPARC Instructions…

13
… more SPARC Instructions…

14
Delayed Branching

This pattern is common in MinCaml generated code :

call f
Space on stack is allocated
add %i0, 8, %i0 ! delay slot
BEFORE function call
sub %i0, 8, %i0

Space on stack is de-allocated


These two lines will be abbreviated 15
As STACK MAGIC
Register Allocation Example: spill.ml
let rec f a b c d =
let e = a + b in
let f = a + c in
let g = a + d in
let h = b + c in
let i = b + d in
let j = c + d in

let k = e + f in
let l = e + g in

We will run out


let m = e + h in
let n = e + i in

of registers!!
let o = e + j in
let p = f + g in
let q = f + h in
let r = f + i in
let s = f + j in
let t = g + h in
let u = g + i in
let v = g + j in
let w = h + i in
let x = h + j in
let y = i + j in

let z = a + b + c + d +
e + f + g + h + i + j +
k + l + m + n + o + p + q + r + s + t + u + v + w + x + y in
-z in
print_int (f 1 2 3 4)
16
Never Fear! Use the Stack!
f.29:
add %i2, %i3, %l0 add %i2, %l4, %i2
add %i2, %i4, %l1 add %i2, %l5, %i2
add %i2, %i5, %l2 add %i2, %l6, %i2
add %i3, %i4, %l3 add %i2, %l7, %i2
add %i3, %i5, %l4 add %i2, %o0, %i2
add %i4, %i5, %l5 add %i2, %o1, %i2
add %l0, %l1, %l6 add %i2, %o2, %i2
add %l0, %l2, %l7 add %i2, %o3, %i2
add %l0, %l3, %o0 add %i2, %o4, %i2
add %l0, %l4, %o1 ld [%i0 + 0], %i3
add %l0, %l5, %o2 add %i2, %i3, %i2
add %l1, %l2, %o3 ld [%i0 + 4], %i3
add %l1, %l3, %o4 add %i2, %i3, %i2
add %l1, %l4, %o5 ld [%i0 + 8], %i3
st %o5, [%i0 + 0] Retrieve add %i2, %i3, %i2
add %l1, %l5, %o5 the ld [%i0 + 12], %i3
st %o5, [%i0 + 4] add %i2, %i3, %i2
add %l2, %l3, %o5
values ld [%i0 + 16], %i3
st %o5, [%i0 + 8] add %i2, %i3, %i2
add %l2, %l4, %o5 Use stack to ld [%i0 + 20], %i3
st %o5, [%i0 + 12] add %i2, %i3, %i2
add %l2, %l5, %o5
store ld [%i0 + 24], %i3
st %o5, [%i0 + 16] intermediate add %i2, %i3, %i2
add %l3, %l4, %o5 values add %i2, %o5, %i2
st %o5, [%i0 + 20] (“register neg %i2, %i2
add %l3, %l5, %o5 spilling”) retl
st %o5, [%i0 + 24] nop
add %l4, %l5, %o5
add %i2, %i3, %i2

17
Simm13: 13-Bit Immediate Optimization

• Specific to SPARC
• “Inlining” or "constant folding"
for integers from -4096 to 4095

set 123, %r1


add %r1, %r2, %r3

add %r2, 123, %r3
18
simple.ml f : set
add
10, TMP1
TMP1, ARG1, RV
retl
nop
let rec f x = 10 + x in g : set 1, TMP2
add ARG1, TMP2, TMP3
let rec g y = mov TMP3, ARG1
(f (y + 1)) - (f (y + y)) in st RT, [SP + 4]
print_int (g 17) call f {{RV  TMP4}}
STACK MAGIC
ld [SP + 4], RT
To add ARG1, ARG1, TMP5
mov TMP5, ARG1
closure st RT, [SP + 4]
To virtual
form call f
SPARC STACK MAGIC
ld [SP + 4], RT
sub TMP4, RV, RV
let LABEL(f) [] x = let TMP1 = 10 in (TMP1 + x) in retl
nop
let LABEL(g) [] y = .global min_caml_start
let TMP2 = 1 in min_caml_start:
let TMP3 = y + TMP2 in save %sp, -112, %sp
let TMP4 = APPLY_DIRECT(LABEL(f) TMP3) in set 17, TMP7
mov TMP7, ARG1
let TMP5 = y + y in st RT, [SP + 4]
let TMP6 = APPLY_DIRECT(LABEL(f) TMP5) in call g
(TMP4 – TMP6) STACK MAGIC
In ld [SP + 4], RT
mov RV, ARG1
let TMP7 = 17 in st RT, [SP + 4]
call min_caml_print_int
STACK MAGIC
let TMP8 = APPLY_DIRECT(LABEL(g) TMP7) in ld [SP + 4], RT
APPLY_DIRECT(LABEL(min_caml_print_int) TMP8) ret
19
restore
f : set 10, TMP1 f:
add TMP1, ARG1, RV add ARG1, 10, RV
retl retl
nop nop
g : set 1, TMP2 g:
add ARG1, TMP2, TMP3 add ARG1, 1, TMP3
mov TMP3, ARG1 mov TMP3, ARG1
st RT, [SP + 4] st RT, [SP + 4]
call f {{RV  TMP4}} call f {{RV  TMP4}}
DELAY SLOT DELAY SLOT
ld [SP + 4], RT ld [SP + 4], RT
add ARG1, ARG1, TMP5 add ARG1, ARG1, TMP5
mov TMP5, ARG1 mov TMP5, ARG1
st RT, [SP + 4] st RT, [SP + 4]
call f call f
DELAY SLOT DELAY SLOT
ld [SP + 4], RT ld [SP + 4], RT
sub TMP4, RV, RV sub TMP4, RV, RV
retl retl
nop nop
.global min_caml_start .global min_caml_start
min_caml_start: min_caml_start:
save %sp, -112, %sp save %sp, -112, %sp
set 17, TMP7 set 17, TMP7
mov TMP7, ARG1 mov TMP7, ARG1
st RT, [SP + 4] st RT, [SP + 4]
call g call g
DELAY SLOT DELAY SLOT
ld [SP + 4], RT ld [SP + 4], RT
mov RV, ARG1 mov RV, ARG1
st RT, [SP + 4] st RT, [SP + 4]
call min_caml_print_int call min_caml_print_int
DELAY SLOT DELAY SLOT
ld [SP + 4], RT ld [SP + 4], RT
ret ret
restore restore

20
Simm13
f: f:
add ARG1, 10, RV add %i2, 10, %i2
retl retl
nop nop
g: g: st %i2, [%i0 + 0]
add ARG1, 1, TMP3 add %i2, 1, %i2
mov TMP3, ARG1
st RT, [SP + 4] st %o7, [%i0 + 4]
call f {{RV  TMP4}} call f
DELAY SLOT DELAY SLOT
ld [SP + 4], RT ld [%i0 + 4], %o7
Store TMP4 on stack
st %i2, [%i0 + 4]
ld [%i0 + 0], %i2
add ARG1, ARG1, TMP5 add %i2, %i2, %i2 Fetch ARG1 from stack
mov TMP5, ARG1
st RT, [SP + 4] st %o7, [%i0 + 12]
call f call f
DELAY SLOT DELAY SLOT
ld [SP + 4], RT ld [%i0 + 12], %o7 Fetch TMP4 from stack
ld [%i0 + 4], %i3
sub TMP4, RV, RV sub %i3, %i2, %i2
retl retl
nop nop
.global min_caml_start .global min_caml_start
min_caml_start: min_caml_start:
save %sp, -112, %sp save %sp, -112, %sp
set 17, TMP7 set 17, %i2
mov TMP7, ARG1
st RT, [SP + 4] st %o7, [%i0 + 4]
call g call g
DELAY SLOT DELAY SLOT
ld [SP + 4], RT ld [%i0 + 4], %o7
mov RV, ARG1
st RT, [SP + 4] st %o7, [%i0 + 4]
call min_caml_print_int call min_caml_print_int
DELAY SLOT DELAY SLOT
ld [SP + 4], RT ld [%i0 + 4], %o7
KEY
ret ret SP  %i0 = stack pointer
restore restore RT  %o7 = return address
RV  %i2 = return value
ARG1  %i2 = first argument (same as RV!)
Register allocation TMP3  %i2 21
: so must save ARG1 on stack!
TMP4  %i3 and stack
TMP5  %i2 : so must save TMP3 on stack!
Return to our Favorite Example:
let rec compose f g =
let rec composed x = g (f x) in
composed in
let rec dbl x = x + x in
let rec inc x = x + 1 in
let rec dec x = x - 1 in
let h = compose inc (compose dbl dec) in
print_int (h 123)

let LABEL(composed) [f, g] x = let TMP1 = APPLY_CLOSURE(f x) in APPLY_CLOSURE(g TMP1) in


let LABEL(compose) [] f g = let cl = (LABEL(composed); [f, g] ) in cl in

let LABEL(dbl) [] x = (x + x) in
let LABEL(inc) [] x = let TMP1 = 1 in (x + TMP1) in
let LABEL(dec) [] x = let TMP1 = 1 in (x – TMP1) in

let closure dbl = ( LABEL(dbl); [] ) in


let closure inc = ( LABEL(inc); [] ) in
let closure dec = ( LABEL(dec); [] ) in

let TMP2 = APPLY_DIRECT(LABEL(compose) dbl dec) in


let h = APPLY_DIRECT(LABEL(compose) inc TMP2) in
let TMP3 = 123 in
let TMP4 = APPLY_CLOSURE(h TMP3) in
APPLY_DIRECT(LABEL(min_caml_print_int) TMP4)
22
Easy stuff first …
RV = Return Value
RT = Return Address
SP = Stack Pointer
HP = Heap Pointer
CLP = Closure Pointer
ARG1 = Argument 1
ARG2 = Argument 2
let LABEL(dbl) [] x = x + x …

dbl.10: add ARG1, ARG1, RV


retl RV  %i2 = return value
ARG1  %i2 = first argument
dbl.10: add %i2, %i2, %i2 (same as RV!)
retl

Similar for inc and dec …


23
Code for compose
let LABEL(compose) [] f g = let cl = (LABEL(composed); [f, g] ) in cl in

To
virtual compose: compose:
SPARC mov HP, cl mov %i1, %i4
add HP, 16, HP add %i1, 16, %i1
set composed, TMP1 set composed, %i5
Allocate st TMP1, [cl + 0] st %i5, [%i4 + 0]
a closure st ARG2, [cl + 8] st %i3, [%i4 + 8]
on the st ARG1, [cl+ 4] st %i2, [%i4 + 4]
heap mov cl, RV mov %i4, %i2
retl retl

Register allocation

HP  %i1 = heap pointer


RV  %i2 = return value
ARG1  %i2 = first argument
ARG2  %i3 = second argument
TMP1  %i5
cl  %i4 24
Code for composed
let LABEL(composed) [f, g] x =
let TMP1 = APPLY_CLOSURE(f x)
in APPLY_CLOSURE(g, TMP1)

composed: composed:
ld [CLP + 8], g ld [%o5 + 8], %i3
st %i3, [%i0 + 0] save g on stack
ld [CLP + 4], f ld [%o5 + 4], %o5
mov x, ARG1
mov f, CLP
st RT, [SP + 4] st %o7, [%i0 + 4]
ld [CLP + 0], TMP2 ld [%o5 + 0], %o4
call TMP2 call %o4
STACK MAGIC STACK MAGIC
ld [SP + 4], RT ld [%i0 + 4], %o7
mov RV, ARG1
mov g, CLP ld [%i0 + 0], %o5 fetch g from stack
ld [CLP + 0], TMP2 ld [%o5 + 0], %o4
jmp TMP2 jmp %o4

Register allocation

SP  %i0 = stack pointer


RT  %o7 = return address
CLP  %o5 = closure address
TMP2  %o4 = temporary
RV  %i2 = return value
ARG1  %i2 = first argument (same as RV!) 25
g  %i3 and stack
f  %o5 : same as closure!
Build closures, apply compose
let closure dbl = ( LABEL(dbl); [] ) in
let closure inc = ( LABEL(inc); [] ) in
let closure dec = ( LABEL(dec); [] ) in
let TMP = APPLY_DIRECT(LABEL(compose) dbl dec) in

mov HP, TMP1 mov %i1, %i2


SP  %i0
add HP, 8, HP add %i1, 8, %i1 RT  %o7
set dbl, TMP2 set dbl, %i3 RV  %i2
st TMP2, [TMP1 + 0] st %i3, [%i2 + 0] ARG1  %i2
mov HP, TMP3 mov %i1, %i3 TMP1  %i2
st %i3, [%i0 + 0] ARG2  %i3
add HP, 8, HP TMP5  %i3
add %i1, 8, %i1
TMP3  %i3 and stack
set inc, TMP4 set inc, %i4 TMP4  %i4
st TMP4, [TMP3 + 0] st %i4, [%i3 + 0]
mov HP, TMP5 mov %i1, %i3
add HP, 8, HP add %i1, 8, %i1
set dec, TMP6 set dec, %i4
st TMP6, [TMP5 + 0] st %i4, [%i3 + 0]
mov TMP5, ARG2
mov TMP1, ARG1
St RT, [SP + 4] st %o7, [%i0 + 4]
call compose call compose
STACK MAGIC STACK MAGIC
ld [SP + 4], RT ld [%i0 + 4], %o7

Register allocation
26
sum.7:

Example:
cmp %i2, 0
bg ble_else.18
nop

sum.ml set
retl
0, %i2

nop
ble_else.18:
st %i2, [%i0 + 0]
sub %i2, 1, %i2
st %o7, [%i0 + 4]
call sum.7
add %i0, 8, %i0 ! delay slot
let rec sum x = sub %i0, 8, %i0
ld [%i0 + 4], %o7
if x <= 0 then 0 else ld [%i0 + 0], %i3
sum (x - 1) + x in add
retl
%i2, %i3, %i2

print_int (sum 10000) nop


.global min_caml_start
min_caml_start:
save %sp, -112, %sp
set 10000, %i2
st %o7, [%i0 + 4]
call sum.7
add %i0, 8, %i0 ! delay slot
sub %i0, 8, %i0
ld [%i0 + 4], %o7
st %o7, [%i0 + 4]
call min_caml_print_int
add %i0, 8, %i0 ! delay slot
sub %i0, 8, %i0
ld [%i0 + 4], %o7
ret 27
restore
Example: sum.8:
cmp %i3, 0

sum-tail.ml bg
nop
ble_else.19

retl
nop
ble_else.19:
add %i2, %i3, %i2
sub %i3, 1, %i3
b sum.8
let rec sum acc x = nop
if x <= 0 then acc else .global min_caml_start
sum (acc + x) (x - 1) in min_caml_start:
save %sp, -112, %sp
print_int (sum 0 10000)
set 0, %i2
set 10000, %i3
st %o7, [%i0 + 4]
call sum.8
add %i0, 8, %i0 ! delay slot
Tail-recursion is sub %i0, 8, %i0
identified and implemented ld [%i0 + 4], %o7
st %o7, [%i0 + 4]
with a loop --- stack not call min_caml_print_int
used!! add %i0, 8, %i0 ! delay slot
sub %i0, 8, %i0
ld [%i0 + 4], %o7
ret
restore 28
Compiler Construction
Lecture 14
Garbage
Collection
Lent Term 2007
Timothy G. Griffin
Computer Laboratory
University of Cambridge

1
What is Garbage?

A value is garbage if it will not be used in any subsequent


computation by the program.

In General, determining what is and is not garbage is not decidable.

Read Chapter 13 of Appel


2
Solutions

• Restrict programming language so the problem


goes away! That is, use FORTRAN.
• Force programmer to worry about it (use malloc
and free in C…)
• Automation
– Reference Counting
– Mark and Sweep
– Copy Collection
– Generational Collection
– … there are other techniques…

3
Restrict Languages? NO WAY!

• Every modern programming language allows


programmers to allocate new storage
dynamically
– New records, arrays, tuples, objects, closures, etc.
• Every modern language needs facilities for
reclaiming and recycling the storage used by
programs
• COST: It’s usually the most complex aspect of
the run-time system for any modern language
(Java, ML, Lisp, Scheme, Modula, …)

4
Explicit MM

• User library manages memory; programmer


decides when and where to allocate and
deallocate
– void* malloc(long n)
– void free(void *addr)
– Library calls OS for more pages when necessary
– Advantage: people are very clever primates!
– Disadvantage: people too clever and make mistakes.
Getting it right can be costly. And don’t we want to
automate-away tedium?
– Advantage: Allows us to implement Garbage
Collection!

5
Automation…
ROOT SET

stack

r1
r2 -------------------- HEAP ----------------------------------------
registers 6
… Identify Cells Reachable From Root Set…

stack

r1
r2
registers 7
… reclaim unreachable cells, and repeat …

stack

r1
r2
registers 8
Reference Counting, basic idea:

• Keep track of the number of pointers to each object (the reference


count).
• When Object is created, set count to 1.
• Every time a new pointer to the object is created, increment the
count.
• Every time an existing pointer to an object is destroyed, decrement
the count
• When the reference count goes to 0, the object is unreachable
garbage

Clearly --- this can be VERY costly….

9
Reference counting can’t detect cycles!

r1

stack
r2

10
Pros and Cons
• Cons
• Space/time overhead to maintain count.
• Memory leakage when cycles in data.
• Pros
• Incremental (no long pauses to collect…)
• Has many useful applications
• UNIX File System - Symbolic Links
• Java’s RMI management of Strings
• Pure Functional Languages

11
Mark and Sweep

• A two-phase algorithm
– Mark phase: Depth first traversal of object
graph from the roots to mark live data
– Sweep phase: iterate over entire heap,
adding the unmarked data back onto the free
list

12
Cost of Mark Sweep
• Cost of mark phase:
– O(R) where R is the # of reachable words
– Assume cost is c1 * R (c1 may be 10 instr’s)
• Cost of sweep phase:
– O(H) where H is the # of words in entire heap
– Assume cost is c2 * H (c2 may be 3 instr’s)
• Analysis
– The “good” = each collection returns H - R words reclaimed
– Amortized cost = time-collecting/amount-reclaimed
• ((c1 * R) + (c2 * H)) / (H - R)
• If R is close to H, then each collection reclaims little space..
– R / H must be sufficiently small or GC cost is high.
Could dynamically adjust. Say, if R / H is larger than .5, increase
heap size

13
Other Problems

• Depth-first search is usually implemented as a


recursive algorithm
– Uses stack space proportional to the longest path in
the graph of reachable objects
• one activation record/node in the path
• activation records are big
– If the heap is one long linked list, the stack space
used in the algorithm will be greater than the heap
size!!
– What do we do? Pointer reversal [See Appel]
• Fragmentation

14
Copying Collection

• Basic idea: use 2 heaps


– One used by program
– The other unused until GC time
• GC:
– Start at the roots & traverse the reachable data
– Copy reachable data from the active heap (from-
space) to the other heap (to-space)
– Dead objects are left behind in from space
– Heaps switch roles

15
Copying Collection

from-space to-space

roots

16
Copying GC

• Pros
– Simple & collects cycles
– Run-time proportional to # live objects
– Automatic compaction eliminates fragmentation
• Cons
– Precise type information required (pointer or not)
• Tag bits take extra space; normally use header word
– Twice as much memory used as program requires
• Usually, we anticipate live data will only be a small fragment
of store
• Allocate until 70% full
• From-space = 70% heap; to-space = 30%
– Long GC pauses = bad for interactive, real-time apps

17
OBSERVATION: for a copying garbage
collector

• 80% to 98% new objects die very quickly.


• An object that has survived several collections has a bigger
chance to become a long-lived one.
• It’s a inefficient that long-lived objects be copied over and over.

18
IDEA: Generational garbage collection

Segregate objects into multiple areas


by age, and collect areas containing
older objects less often than the
younger ones. 19
Other issues…

– When do we promote objects from young generation to


old generation
• Usually after an object survives a collection, it will be
promoted
– Need to keep track of older objects pointing to newer
ones!
– How big should the generations be?
• Appel says each should be exponentially larger than the last
– When do we collect the old generation?
• After several minor collections, we do a major collection
– Sometimes different GC algorithms are used for the new
and older generations.
• Why? Because the have different characteristics
• Copying collection for the new
– Less than 10% of the new data is usually live
– Copying collection cost is proportional to the live data
• Mark-sweep for the old

20
Compiler Construction
Lecture 15
Object Orientation
Lent Term, 2007
Lecturer: Timothy G. Griffin
Computer Laboratory
University of Cambridge

Some of the slides in this lecture are by Koen


Langendoen of Delft University of Technology
The Netherlands
1
Objects (with single inheritance)
let start := 10

class Vehicle extends Object {


var position := start
method move(int x) = {position := position + x}
}
class Car extends Vehicle {
var passengers := 0
method await(v : Vehicle) =
if (v.position < position)
then v.move(position – v.position)
else self.move(10)
}
class Truck extends Vehicle {
method move(int x) =
if x <= 55 then position := position +x method override
}
var t := new Truck
var c := new Car
var v : Vehicle := c
in
c.passengers := 2;
subtyping allows a
c.move(60); Truck or Car to be viewed and
v.move(70); used as a Vehicle
c.await(t)
end 2
Object Implementation?

– how do we access object fields?


• both inherited fields and fields for the current
object?
– how do we access method code?
• if the current class does not define a particular
method, where do we go to get the inherited
method code?
• how do we handle method override?
– How do we implement subtyping (“object
polymorphism”)?
• If B is derived from A, then need to be able to
treat a pointer to a B-object as if it were an A-
object.

3
Static & Dynamic Methods

• The result of compiling a method is some


machine code located at a particular
address
– at a method invocation point, we need to
figure out what code location to jump to
• Java has static & dynamic methods
– to resolve static method calls, we look at the
static type of the calling object
– to resolve dynamic method calls, we need the
dynamic type of the calling object
4
Object representation

An A object
class A { C++
public:
int a1, a2; a1
object data
a2
void m1(int i) {
a1 = i;
}
void m2(int i) {
a2 = a1 + i; m1_A method table
} m2_A
}

5
Inheritance (“pointer polymorphism”)

class B : public A {
public:
A B object
int b1;

a1
void m3(void) {
b1 = a1 + a2;
a2 object data
} b1
}
method table
m1_A
(code entry
m2_A
points =
m3_B
memory locations)

Note that a pointer to a B object can


6
be treated as if it were a pointer to an A object!
Method overriding

A C object
class C : public A {
public: a1
int c1; a2 object data
c1
void m3(void) {
b1 = a1 + a2;
}
m1_A_A method table
void m2(int i) {
m2_A_C
a2 = c1 + i;
} m3_C_C
}

declared defined
7
Example
Method table for
Rectangle
IsShape_Shape_Shape
abstract class Shape {
boolean IsShape() {return true;} IsRectangle_Shape_Rectangle
boolean IsRectangle() {return false;}
boolean IsSquare() {return false;} IsSquare_Shape_Shape
abstract double SurfaceArea();
} SurfaceArea_Shape_Rectangle
class Rectangle extends Shape {
double SurfaceArea { ... }
boolean IsRectangle() {return true;}
} Method table for Square
class Squrae extends Rectangle {
boolean IsSquare() {return true;} IsShape_Shape_Shape
}

IsRectangle_Shape_Rectangle

The compiler needs to us IsSquare_Shape_Square


a SYMBOL TABLE to keep track
of object types and relationships SurfaceArea_Shape_Rectangle
8
Static vs. Dynamic

• which method to invoke on overloaded


polymorphic types?

class C *c = ...; m2_A_A(a, 3); static


class A *a = c; ???
m2_A_C(a, 3); dynamic
a->m2(3);

9
Dynamic dispatch

• implementation: dispatch tables

ptr to C
Is also a ptr to A m1_A_A
a1 m2_A_C
a2 m3_C_C
b1

class C *c = ...;
class A *a = c; *(a->dispatch_table[1])(a, 3);

a->m2(3); 10
Dynamic typing:implementation
requires pointer subtyping

void m2(int i) {
a2 = c1 + i;
}

void m2_A_C(class_A *this_A, int i) {


class_C *this = convert_ptrA_to_ptrC(this_A);

this->a2 = this->c1 + i;
}

11
Multiple inheritance

class C { class D {
public: public:
int c1, c2; int d1;
void m1() {...} void m3() {...}
void m2() {...} void m4() {...}
} }

class E : public C, D {
public:
int e1;
void m2() {...}
void m4() {...}
void m5() {...}
}
12
Multiple inheritance

ptr to E
m1_C_C
ptr to C inside E
c1 m2_C_E
c2 m3_D_D
ptr to D inside E
m4_D_E
d1 m5_E_E
e1
supertyping E-object E-class
convert_ptrE_to_ptrC(e) ≈ e
convert_ptrE_to_ptrD(e) ≈ e + sizeof(Class_C)

subtyping

convert_ptrC_to_ptrE(c) ≈ c
13
convert_ptrD_to_ptrE(d) ≈ d - sizeof(Class_C)
given an object e of class E

e.m1() (*(e->dispatch_table[0]))((Class_C *) e)

e.m3() (*(e->dispatch_table[2]))(
(class_D *)((char *)e + sizeof(Class_C)))

e.m4() (*(e->dispatch_table[3]))(
(class_D *)((char *)e + sizeof(Class_C)))

14
Another OO Feature

• Protection mechanisms
– to encapsulate local state within an object,
Java has “private” “protected” and “public”
qualifiers
• private methods/fields can’t be called/used outside
of the class in which they are defined
– This is really a scope/visibility issue! Front-
end during semantic analysis (type checking
and so on), the compiler maintains this
information in the symbol table for each class
and enforces visibility rules.
15
Compiler Construction
Lecture 16
Continuation Passing Style (CPS)
OPTIONAL TOPIC:
WILL NOT BE EXAMINED

Lent Term, 2007

Lecturer: Timothy G. Griffin

Computer Laboratory
University of Cambridge
1
Continuation Passing Style

let rec fact n =


if n <= 0
then 1
CPS conversion
else n * (fact (n-1))

All functions are


let rec fact_cps n r = given an extra
if n <= 0 argument representing
then r(1) the rest of the
else fact_cps (n-1) (function x -> r(n * x)) computation.
let new_fact n = fact_cps n (function x -> x) Functions “never return” ---
they just call other
functions!

2
CPS on Lambda Terms

e::=c∣x∣ee∣λx.e
c = λk .kc
x = λk .kx
λx.e=λk .k λx.e 
e1 e2=λk .e1  λm.e2  λn.mnk 
e⇒ c  e  λx . x  ⇒ c
¿ ¿
3
Can use CPS as intermediate form in a
Compiler!

Code

Main advantages:
CPS
Can avoid using a stack!

Can easily implement complex control constructs.


CP S- Sty le Code

Compile

See “Compiling with Continuations” by Andrew Appel

4
callcc and throw in SML of NJ

- val throw = SMLofNJ.Cont.throw;

throw : 'a ?.cont -> 'a -> 'b

-val callcc = SMLofNJ.Cont.callcc;

callcc : ('a ?.cont -> 'a) -> 'a

Represents the rest of the computation

5
CPS on Extended Lambda Terms

e::=c∣x∣ee∣λx.e∣callcc e∣throw k e

callcc e=λk. e  λm.m λz . λd.kz k 


' '' ' ''
throw k e=k 'e=λk . e  λn.k nk 

callcc λj.e=λk . λk.k  λj .e  λm.m λz . λd.kz k 


⇒ λk .e [ j ::=λz. λd .kz]k
¿

' '' '' ' '


throw j c=λk . λk .k c λn. λz . λd.kz nk ⇒ λk .kc
¿
6
Recall: De Morgan’s Laws as Code!

fun d: (AC) || (BC).


fun p : A*B.
case d of
inl(f)  f(fst p),
inr(g) -> g(snd p)

Has type
((A  C) || (B  C))  (A*B)  C
This is a generalization of De Morgan’s rule Think of ¬A
 ¬A∨¬B ¬ A∧B  as
A  false
and then replace
false by C
Can this same thing be done with all of De Morgan’s
other three rules? Yes? No?
7
Propositions as Types, in SML

datatype ('a,'b) And = Pair of 'a * 'b;

(*
first : ('a,'b) And -> 'a
*)
fun first (Pair(a,b)) = a ;

(*
second : ('a,'b) And -> 'b
*)
fun second (Pair(a,b)) = b;

datatype ('a,'b) Or = Left of 'a | Right of 'b;

This is using Standard ML of New Jersey, which has a slightly different


syntax from Ocaml.
http://www.smlnj.org/ 8
dm1, dm2, dm3

(*
dm1 : ('a -> 'b,'c -> 'b) Or -> ('a,'c) And -> 'b
*)
fun dm1 d p = case d of
Left f => f(first p)
| Right g => g(second p)

(*
dm2: (('a,'b) Or -> 'c) -> ('a -> 'c,'b -> 'c) And
*)
fun dm2 f = Pair(fn a => f(Left a), fn b => f(Right b))

(*
dm3 : ('a -> 'b,'c -> 'b) And -> ('a,'c) Or -> 'b
*)
fun dm3 p d = case d of
Left a => ((first p) a)
| Right b => ((second p) b)
9
dm4? This is a “classical” result!

(*
dm4 : : (('a,'b) And -> 'c) -> ('a -> ‘c,'b -> 'c) Or
*)
val callcc = SMLofNJ.Cont.callcc;
val throw = SMLofNJ.Cont.throw;

fun dm4 f = callcc(fn k => Left(fn a =>


throw k (Right(fn b => f(Pair(a,b))))));

Operational interpretation:

E[callcc (fn j => Left(fn a => (..)))] % capture current continuation


E[Left(fn a=> (..))] % proceed as if left branch is true
..
E’[(fn a=>(..))V] % if the function is ever applied to a value,
E[Right(fn b => Pair(V, b))] % then jump back to the original context

10
Compiler Construction
Lecture 17
Java Virtual Machine

Lent Term, 2007

Lecturer: Timothy G. Griffin

Computer Laboratory
University of Cambridge
1
Java system overview

The JVM does


not depend on Java

Machine Independent

OS independent

2
What Is in the JVM Spec?

• Bytecodes – the instruction set for Java


Virtual Machine
• Class File Format – The platform
independent representation of Java binary
code
• Verification Rules – the algorithm for
identifying programs that cannot
compromise the integrity of the JVM
JVM Specification does not specify
how a JVM is implemented 3
Instruction-set: typed instructions!
JVM instructions are explicitly typed: different opCodes for
instructions for integers, floats, arrays and reference types.

This is reflected by a naming convention in the first letter of the


opCode mnemonics.

iload integer load


lload long load
fload float load
dload double load
aload reference-type load

4
Instruction set: kinds of operands

JVM instructions have three kinds of operands:


- from the top of the operand stack
- from the bytes following the opCode
- part of the opCode
One instructions may have different “forms” supporting different
kinds of operands.

Assembly code Binary layout


iload_0 26
iload_1 27
iload_2 28
iload_3 29
iload n 21 n

iload n = push the n-th local var on the stack 5


Instruction-set examples
Arithmethic
add:  iadd, ladd, fadd, dadd
subtract:  isub, lsub, fsub, dsub
multiply:  imul, lmul, fmul, dmul
Conversion
i2l, i2f, i2d
l2f, l2d, f2s
f2i, d2i, …

Operand stack manipulation
pop, pop2, dup, dup2, dup_x1, swap, …
Control transfer
Unconditional : goto, goto_w, jsr, ret, …
Conditional: ifeq, iflt, ifgt, … 6
…Instruction-set …

Method invocation:
invokevirtual: usual instruction for calling a method on an object.
invokeinterface: same as invokevirtual, but used when the called
method is declared in an interface. (requires different kind of method lookup)
invokespecial: for calling things such as constructors. These are not
dynamically dispatched (this instruction is also known as
invokenonvirtual)
invokestatic: for calling methods that have the “static” modifier (these
methods “belong” to a class, rather an object)
Returning from methods:
return, ireturn, lreturn, areturn, freturn, …

Create new class instance (object):


new
Create new array:
newarray: for creating arrays of primitive types.
anewarray, multianewarray: for arrays of reference types
7
Goto instruction – 3 and 5 byte versions

PC goto PC goto_w

branchbyte1 branchbyte1

branchbyte2 branchbyte2

branchbyte3
branchbyte4

PC := PC + (branchbyte1 << 8) | branchbyte2 PC := PC + (branchbyte1 << 24) |


(branchbyte2 << 16) |
(branchbyte3 << 8) |
branchbyte4.
16-bit branch offset
(signed 2’s compliment representation)
32-bit branch offset

The target address must be that of an


opcode of an instruction within the
method that contains
this goto (or goto_w) instruction. 8
Fib onacci Fore ver
http://www.artima.com/insidejvm/applets/FibonacciForever.html

1, 1, 2, 3, 5, 8, 13, 21, 34, 55, …

0 lconst_1 % Push long constant 1


class Fibonacci { 1 lstore_0 % Pop long into local vars 0 & 1: long a = 1;
static void calcSequence() { 2 lconst_1 % Push long constant 1
long fiboNum = 1; 3 lstore_2 % Pop long into local vars 2 & 3: long b = 1;
long a = 1; 4 lconst_1 % Push long constant 1
long b = 1; 5 lstore 4 % Pop long into local vars 4 & 5: long fiboNum = 1;
for (;;) { 7 lload_0 % Push long from local vars 0 & 1
fiboNum = a + b; 8 lload_2 % Push long from local vars 2 & 3
a = b; 9 ladd % Pop two longs, add them, push result
b = fiboNum; 10 lstore 4 % Pop long into local vars 4 & 5: fiboNum = a + b;
} 12 lload_2 % Push long from local vars 2 & 3
} 13 lstore_0 % Pop long into local vars 0 & 1: a = b;
} 14 lload 4 % Push long from local vars 4 & 5
16 lstore_2 % Pop long into local vars 2 & 3: b = fiboNum;
17 goto 7 % Jump back to offset 7: for (;;) {}

BYTE CODES: 0a 3f 0a 41 0a 37 04 le 20 61 37 04 20 3f 16 04 41 a7 ff f6
lstore 4 lstore 4 goto 7
(“assembles” to goto -10)

9
Organization of JVM

Class Area
Class Information
Native
Heap Stack
Constant Pool Stack
Method Area

Interne
t PC, FP, SP
*.class Registers Native
Class Interface
Loader Execution
Engine
File System Native
*.class Methods
10
Class Loader
• Loading: finding and importing the binary data for
a class
• Linking:
• Verification: ensuring the correctness of the imported
type
• Preparation: allocating memory for class variables and
initializing the memory to default values
• Resolution: transforming symbolic references from the
type into direct references.
• Initialization: invoking Java code that initializes
class variables to their proper starting values

11
Class File
• Table of constants. ClassFile {
• Tables describing the u4 magic;
class u2 minor_version;
u2 major_version;
– name, superclass, u2 constant_pool_count;
interfaces cp_info constant_pool[constant_pool_count-1];
– attributes, constructor u2 access_flags;
u2 this_class;
• Tables describing fields u2 super_class;
and methods u2 interfaces_count;
– name, type/signature u2 interfaces[interfaces_count];
u2 fields_count;
– attributes (private, field_info fields[fields_count];
public, etc) u2 methods_count;
method_info methods[methods_count];
• The code for methods. u2 attributes_count;
attribute_info attributes[attributes_count];
}

12
Stack Frame
SP→
Inter-
public class A Mediate Operand
{ Data Stack
... ...
Values
void f(int x)
{
int i; i Local
for(i=0; i<x; i++) Variable
{
... ...
x Array
} Caller’s SP
... ...
} Caller’s FP
FP→Return PC
13
Stack – Each Thread Has its own Stack
Heap
Thread 1 Thread 2 Thread 3

Frame Frame Frame

Frame Frame Frame

Frame Frame

Stack
14
Heap

• All Java objects are allocated in the heap


• Java applications cannot explicitly free an
object
• The Garbage Collector is invoked from time
to time automatically to reclaim the objects
that are no longer needed by the application
• The heap is shared by all Java threads

15
Java Objects in the Heap

clazz
Fields 1
Fields 2
……
class Object
Fields n
class A
class B clazz

……
clazz
Class Area

……
Heap 16
Bytecode Interpreter

while(program not end ) {


• Advantage fetch next bytecode => b
switch(b) {
– Ease to implement case ILOAD:
load an integer from the local
– Does not need extra variable array and push on top
of current operand stack;
memory to store case ISTORE:
compiled code pop an integer from the top of
current operand stack and store
• Disadvantage it into the local variable array;
case ALOAD:
– Much slower than ... ...
execution of native } // end of switch
} // end of while
code

17
Just-In-Time Compiler
• Dynamically compiles bytecode into native code at runtime, usually in
method granularity
• Execution of native code is much faster than interpretation of
bytecode
• Compilation is time consuming and may slow down the application
• Tradeoffs between execution time and compilation time

Interpretation JIT Compilation


Bytecode
Bytecode
Native JIT
Code Compiler
Interpreter

CPU CPU 18
Adaptive Compiler

• Observation: less than 20% of the methods


account for more than 80% of execution time
– Methods contains loop with large number of iteration;
– Methods that are frequently invoked
• Idea 1: only compile the methods where the
application spends a lot of time
• Idea 2: perform advanced compiler optimization
for the hottest methods, simple or no compiler
optimization for less hot methods

19
How Adaptive Compiler Works
• Set three thresholds T1, T2 (T1<T2)
• Each method has a counter that is initialized to 0.
Whenever the method is invoked, increase its
counter by 1
• The methods with counter lower than T1 are
executed using interpreter
• When a method’s counter reaches T1, compile this
method with simple optimizations
• When a method’s counter reaches T2, recompile
this method with advanced optimizations

20

S-ar putea să vă placă și