Modern Compiler Implementation in ML

©1998 by Andrew W. Appel

Errors in the first edition, first printing (1998):

The following errors also appear in the 1999 reprinting of the book.

Page 53. After the sentence, "The resulting productions will not pose a problem for a predictive parser" add:
Although the grammar is still ambiguous -- the parsing table has two entries for the same slot -- we can resolve the ambiguity by using the "else S" action.

Page 54. 7th line from bottom: TIMES should not be in argument of skipto.

Page 64. First line of left-hand box: change ampersand (&) to $.

Page 77. Lines 21-22 should read,
3. Discard input symbols (if necessary) until a lookahead is reached that has a non-error action in the current state.

Page 97. The Tiger program shown is actually illegal, since g is declared to return no value but its body returns the value f().

Page 137. Table 6.4. The MIPS column of the table uses registers r2, r4, r5 for passing parameters. The use of r2 for the "zeroth parameter" is consistent with the MIPS convention of passing the static link in r2; the argument x1, by this point in the compilation, is really the static link.

Page 175. 11th line from bottom, change "whether two expressions commute" to "whether a statement commutes with an expression".

Page 215. Table 10.5 in the 4th iteration, the out set for statement 3 is c, when it should be b.

Page 225. Lines 4-8, replace all five occurrences of IGraph with Graph.

Page 235. Assignment statements on line 19 should say,
t:=M[bloc]; M[aloc]:=t.

Page 237. Figure 11.7, captions (a) and (b) are missing.

Page 239. Last sentence, swap "afterward" and "beforehand".

Page 242. Delete last bullet item entirely ("When u is coalesced ...").

Page 248. Line 8, change all three occurrences of "nodeMoves" to "moveList".
Insert new line, "EnableMoves(v)".

Page 262. Figure 12.1, line 15 should refer to Temp.label, not Tree.label.

Page 271. Algorithm 13.5, after second line, insert:
mark x

Page 366. 8th line from bottom, delete the word "not".

Page 519. 4th line from bottom, change both occurrences of "integer" to "int".

The following errors have been corrected in the 1999 reprinting of the book.

Page 27,28. The state labeled 5,6,7,8,15 should be 5,6,8,15.
The state labeled 10,11,12,13,15 should be 10,11,13,15.

Page 29. The first noncomment line of Program 2.9 should be

type lexresult = Tokens.token

Page 42. Figure 3.3, the rightmost semicolon should be a comma. Also, the part of the derivation corresponding to "c +" is missing from the tree.

Page 48. Lines 6-15 should read,

for each production X -> Y1Y2...Yk
    if Y1...Yk are all nullable (or if k=0)
        then nullable[X] = true
    for each i from 1 to k, each j from i+1 to k
        if Y1...Yi-1 are all nullable (or if i = 1)
            then FIRST[X] = FIRST[X] u FIRST[Yi]
        if Yi+1...Yk are all nullable (or if i = k)
            then FOLLOW[Yi] = FOLLOW[Yi] u FOLLOW[X]
        if Yi+1...Yj-1 are all nullable (or if i+1 = j)
            then FOLLOW[Yi] = FOLLOW[Yi] u FIRST[Yj]

Page 49. Algorithm 3.13, lines 6-15 should read,

for each production X -> Y1Y2...Yk
    if Y1...Yk are all nullable (or if k=0)
        then nullable[X] <- true
    for each i from 1 to k, each j from i+1 to k
        if Y1...Yi-1 are all nullable (or if i = 1)
            then FIRST[X] <- FIRST[X] u FIRST[Yi]
        if Yi+1...Yk are all nullable (or if i = k)
            then FOLLOW[Yi] <- FOLLOW[Yi] u FOLLOW[X]
        if Yi+1...Yj-1 are all nullable (or if i+1 = j)
            then FOLLOW[Yi] <- FOLLOW[Yi] u FIRST[Yj]

Page 52. Table 3.16 caption should refer to Grammar 3.15, not Grammar 3.8.

Page 56. Figure 3.18, 7th line from the bottom, the second occurrence of id should have subscript 20, not 4.
Figure 3.18, 5th line from the bottom, "(S;E)" should be "(S,E)" at the end of the line.

Page 57. Table 3.19, row 9, is missing some entries. In column "id" the entry should be "s20", in column "num" the entry should be "s10", and in column "(" the entry should be "s8".

Page 64. In the left-hand box, the lookahead for the last two lines should be =, not $.

The last two lines of the page should read,

For some grammars, the LALR(1) table contains reduce-reduce conflicts where the LR(1) table has none, but in practice the difference ...

Page 65. Figure 3.27 shows the LR(1) states for Grammar 3.23, not for Grammar 3.26.
In Figure 3.27, states 4 and 7, the lookahead for T->x should be "$,+" and not just "$".

The LR(1) states for Grammar 3.26 are as follows:
LR(1) states for Grammar 3.26

Page 65. Table 3.28a, the last entry in row 13 should be g7, not f7.
Table 3.28b, the entry in row 7, column "=", should be r3 instead of blank.

Page 88. Program 4.1 caption should read,
Recursive-descent interpreter for part of Grammar 3.15.

Page 96. The bottom half of Program 4.7 should use constructor names consistent with Program 1.5, as shown here:

stm : stm SEMICOLON stm         (Absyn.CompoundStm(stm1,stm2))
stm : ID ASSIGN exp             (Absyn.AssignStm(ID,exp))
stm : PRINT LPAREN exps RPAREN  (Absyn.PrintStm(exps))

exps: exp                       ( exp :: nil )
exps: exp COMMA exps            ( exp :: exps )

exp : INT                       (Absyn.NumExp(INT))
exp : ID                        (Absyn.IdExp(ID))
exp : exp PLUS exp              (Absyn.OpExp(exp1,Absyn.Plus,exp2))
exp : exp MINUS exp             (Absyn.OpExp(exp1,Absyn.Minus,exp2))
exp : exp TIMES exp             (Absyn.OpExp(exp1,Absyn.Times,exp2))
exp : exp DIV exp               (Absyn.OpExp(exp1,Absyn.Div,exp2))
exp : stm COMMA exp             (Absyn.EseqExp(stm,exp))
exp : LPAREN exp RPAREN         ( exp )

Page 97. Line 8, A_SeqExp should be SeqExp.
Line 11, A_OpExp should be OpExp.

Page 99. At the bottom of the page, add the following sentence: "An empty statement () is represented by SeqExp(nil).

Page 104. Line 5 of the program fragment, delete the semicolon after print_int(j).

Page 113. The second program fragment should use := instead of = in the var declarations of a and b.

Page 116. Line 13 should be {exp=(),ty=Types.INT})
15th line from bottom, SOME(E.VarEntry{access,ty}) should be SOME(E.VarEntry{ty}).

Page 118. Lines 5-9 should be

fun transDec (venv,tenv,A.VarDec{name,typ=NONE,init,...}) =
    let val {exp,ty} = transExp(venv,tenv,init)
     in {tenv=tenv,
         venv=S.enter(venv,name,E.VarEntry{ty=ty})}
    end

Page 120. Line 14 should be

tenv' = S.enter(tenv,name,Types.NAME(name,ref NONE))
(with parentheses instead of braces).

Page 133. Program 6.3, line 14 should be indented one space less; and should read,

            output := concat(output, s);  write("\n"))

Page 136. Sixth line from the bottom should refer to "i1 and i2" instead of "i0 and i1".

Page 137. Table 6.4, column "Sparc", last two lines should refer to i1 and i2 instead of i0 and i1.

Page 141. Line 10, label should be Temp.label.
Line 27, access: access should be access: Translate.access.

Page 142. 7th line from the bottom should be,
Translate.newlevel{parent=levelg,name=f,formals=[false,false]}

Page 151. Lines 11-12 should read, "MOVE(MEM(e1),e2) Evaluate e1, yielding address a. Then evaluate e2, and store the result into wordSize bytes of memory starting at a."

Page 182. Algorithm 8.4, delete the comment "(All the successors of b are marked)" which is false (the algorithm is still correct).

Page 169. Line 20 has missing braces:

datatype frag = PROC of {body: Tree.stm, frame: frame}
Line 25 has missing braces:
val procEntryExit: {level: level, body: exp} -> unit
The last line on the page should refer to STRING fragments, not DATA fragments.

Page 194. Figure 9.4, the third tree for STORE uses a where it should use d.

Page 198. The program shown under 2. Classes of registers implements t3<-t1*t2, not t1<-t2*t3 as claimed.

Page 219. 7th line after figure, "prove that b*b>0" should be "prove that b*b>=0".

Page 252. Algorithm 11.11, line 8, should be:
unspill: reg[tright]:=`r(n+1)'; emit instruction to fetch reg[tright]

Page 324. Algorithm 15.10, box on the right: the formal parameters of f ' should be (a1,...,ai-1,ai+1,...an).

Page 334. Lines 13 and 14, the two assignments to th.memo and th.func should be to mythunk.memo and mythunk.func.

Page 337. "It is wasteful to build all three lists" should be "It is wasteful to build these lists."

Page 339. Line 2 of the main text, "(string of integer)" should be "(string or integer)".

Page 341. First paragraph should read, "If (f,(1,1,0)) is in the set H, then we know that f is non strict in its third argument. If (f,(1,1,0)) is never put into H, then f must be strict in its third argument."

Page 359. In the clause labeled "Occurrence of a variable", replace the word generalize with instantiate.

Page 360. Last line of the page should read, "Variable declaration with implicit type clause of Algorithm 16.10."

Page 385. In the table, in the column headed gen[s], delete each of the three instances of "-kill[s]".

Page 406. Figure 18.2b is misleading because the graph shown has two "start" nodes. It is intended as a subgraph of some larger graph with a single entry node.

Page 407. Third line from bottom, the two equations D[s0]=... and D[n]=... have been inadvertantly jammed together, and should be on separate lines.

Page 410. Lines 7-9, definition of Nested loops should be: If A and B are loops with headers a and b respectively, such that a not-equal b and b is in A, then the nodes of B are a proper subset of the nodes of A.

Page 410. Line 18 should be,
h2 if h2 is in loop[h1].

Page 412. In the paragraph headed by HOISTING, 5th line, replace "a<b" by "i>=N initially."

Page 412. Seventh line from bottom, "1. d dominates all loop exits, or t is not live-out of any loop exit node" is correct, but a better criterion is,
"1. d dominates all loop exits at which t is live-out;"

Page 416. Line 13-14 should be,
Assuming j is characterized by (i,a,b), then k is described by (i,a.c,b.c) or (i,a+d,b), depending on whether k's definition was j.c or j+d.

Page 418. Line 14, "invariant values" should be "invariant values and in definitions of itself,"
Line 19, "so therefore the comparison j<n can be written as" should be "so therefore the comparison k<n can be written as".

Page 420. Lines 13 and 14, labels L1 and L2 should be swapped:
if u>j goto L1 else goto L2
if u<=j goto L2 else goto L1

Page 421. Line 3 should have Delta in front of k1 and km:
k>=0 and Deltak1>=0 and . . . and Deltakm>=0

Page 422. Lines 24 and 25, labels L1 and L2 should be swapped:
if u'>=j goto L1 else goto L2
if u'<j goto L2 else goto L1

Page 431. Figure 19.4 (b,f,g), block 6 should increment k by 2, not by 1.

Page 432. Lines 10-11 should read,
1. If x is the ith argument of a phi function in block n, then the definition of x dominates the ith predecessor of n.

Page 435. Algorithm 19.6, lines 10 and 14, all references to Aphi[n] should refer to Aphi[Y].
Algorithm 19.6, line 15 should read "if a not in Aorig[Y]".
First full paragraph on page 435 should read,

Algorithm 19.6 starts with a set V of variables, a graph G of control-flow nodes -- each node is a basic block of statements -- and for each node n a set Aorig[n] of variables defined in node n. The algorithm computes Aphi[a], the set of nodes that must have phi-functions for variable a. Note that sometimes a node may contain an ordinary definition and a phi-function for the same variable; for example, in Figure 19.3b, a is in Aorig[2] and node 2 is in Aphi[a].

Page 438. Last paragraph should read,

Suppose there is a CFG path from a to b but a is not an ancestor of b. This means that some edge on the path is not a spanning-tree edge, so b must have been reached in the depth-first search before a was (otherwise, after visiting a the search would continue along tree-edges to b). Thus, dfnum(a) > dfnum(b).

Page 450. Figure 19.13 (a), block 6 should increment k2 by 2, not by 1.

Page 460. Figure 19.19, block 6 (on left), and else clause of if-statement (on right) should increment k2 by 2, not by 1.
Figure 19.19, right-hand side, line 8 should refer to j2, not j1.

Page 470. Line 4, "hypothetical machine" should be "MIPS R4000".

Page 471. Figure 20.2, lines 5-6 of the caption should read,

nor four cycles later (because of Add and Round hazards). But if there were two adders and two rounding units, then an ADD could be started four

Page 482. Figure 20.10, steps 2-4 should be as shown:
Figure 20.10, corrected

Page 487. The first full sentence should read,

A mispredict rate of 10% can result in very many stalled instructions -- if each mispredict stalls 11 instruction slots, as described in the example on page 484, and there is one mispredict every 10 branches, and one-sixth of all instructions are branches, then 18% of the processor's time is spent waiting for mispredicted instruction fetches.

Page 489. Exercise 20.2g, "Run Algorithm itermod" should be "Run Algorithm 20.9".

Page 519. 4th line from bottom, change both occurrences of "integer" to "int".