SCM Repository
Annotation of /sml/trunk/ckit/src/parser/grammar/c.grm
Parent Directory
|
Revision Log
Revision 639 - (view) (download)
1 : | dbm | 597 | (* DO NOT CHANGE THIS FILE -- this file was generated from cd.grm *) |
2 : | |||
3 : | (* Copyright (c) 1998 by Lucent Technologies *) | ||
4 : | |||
5 : | (* new comments from Satish Chandra, 6/21/99 *) | ||
6 : | (* Overriding design approach: | ||
7 : | * | ||
8 : | * Accept all legal programs, but possibly some illegal ones at this stage. | ||
9 : | * Do not attempt to make a really tight grammar. Our tools are supposed to | ||
10 : | * work on "correct" C programs (i.e. those that cc -ansi would compile without | ||
11 : | * warnings). Of course, a type checker on the parse tree can report some errors | ||
12 : | * as syntax errors. | ||
13 : | * | ||
14 : | * Note on MARK: | ||
15 : | * | ||
16 : | * externalDecl, statement, and expression are the non-terms that are marked. | ||
17 : | * Compound statements are not separately marked. | ||
18 : | * declarations eventually become either a statement or a externalDecl | ||
19 : | * if they are outside any function. They are marked accordingly. | ||
20 : | * | ||
21 : | * Note on function definitions: | ||
22 : | * | ||
23 : | * The order of the paramaters will always come from the FuncDecr. | ||
24 : | * The types of the parameter may come from the second declaration list | ||
25 : | * (in K&R style) | ||
26 : | * | ||
27 : | * Note on the structure of the grammar: | ||
28 : | * | ||
29 : | * It is difficult to write a LALR(1) grammar based on the grammar given at | ||
30 : | * the back of the K&R book. The basic difficulty is that both TYPE_NAME and | ||
31 : | * ID are tokens that are strings, but it depends on the context whether | ||
32 : | * a given string is to be treated as an ID or a TYPE_NAME. | ||
33 : | * We have borrowed the solution used in GCC's parser specification. In this | ||
34 : | * scheme, the lexer always return the token TYPE_NAME if a name has been | ||
35 : | * defined as a type name (via a typedef) in an applicable scope. The grammar | ||
36 : | * productions are heavily rearranged (from K&R's grammar) to do the right | ||
37 : | * thing. In this rearrangement, the basic idea is that a TYPE_NAME is | ||
38 : | * allowed to appear in a declaration as a plain identifier only after a type | ||
39 : | * specifier has previously appeared in the declaration. Also, a TYPE_NAME may | ||
40 : | * appear only once in a declaration as a type specifier. | ||
41 : | *) | ||
42 : | |||
43 : | (* old comments below *) | ||
44 : | (* Shortcomings *) | ||
45 : | (* 1. No floating-point whatsoever *) | ||
46 : | |||
47 : | (* Notes on MARK: | ||
48 : | * externalDecl and statement are the non-terms that are marked. | ||
49 : | * Compound statements are not separately marked. | ||
50 : | * expressions are not marked at all. | ||
51 : | * declarations eventually become either a statement or a externalDecl | ||
52 : | * if they are outside any function. they are marked accordingly. | ||
53 : | *) | ||
54 : | |||
55 : | (* Overriding theme: accept all legal programs, but also some illegal ones at this | ||
56 : | * stage. Do not attempt to make a really tight grammar. Our tools are supposed to | ||
57 : | * work on "correct" C programs (i.e. those that cc -ansi would compile without | ||
58 : | * warnings). Of course, a type checker on the parse tree can report some errors | ||
59 : | * as syntax errors. | ||
60 : | *) | ||
61 : | |||
62 : | (* About function definitions: | ||
63 : | * The order of the paramaters will always come from the FuncDecr thing | ||
64 : | * The types of the parameter may come from the second declaration list (in K&R style) | ||
65 : | *) | ||
66 : | |||
67 : | open ParseTree (* PortingHelp *) | ||
68 : | |||
69 : | fun markExternalDecl srcMap (d,left,right) = | ||
70 : | MARKexternalDecl(SourceMap.location srcMap (left,right), d) | ||
71 : | |||
72 : | fun markDeclaration srcMap (d,left,right) = | ||
73 : | MARKdeclaration(SourceMap.location srcMap (left,right), d) | ||
74 : | |||
75 : | fun markDeclarator srcMap (d,left,right) = | ||
76 : | MARKdeclarator(SourceMap.location srcMap (left,right), d) | ||
77 : | |||
78 : | fun markStatement srcMap (s,left,right) = | ||
79 : | MARKstatement(SourceMap.location srcMap (left, right), s) | ||
80 : | |||
81 : | fun markExpression srcMap (s,left,right) = | ||
82 : | MARKexpression(SourceMap.location srcMap (left, right), s) | ||
83 : | |||
84 : | val unknown = {storage=[],qualifiers=[],specifiers=[]}:decltype | ||
85 : | |||
86 : | (* this code duplicated in BuildAst in function processDeclarator *) | ||
87 : | fun ctypeDecrToTypeName (typ as {qualifiers, specifiers},decr) = | ||
88 : | let fun mkTyp spc = {qualifiers=[], specifiers=[spc]} | ||
89 : | fun addQual q = {qualifiers=q::qualifiers, specifiers=specifiers} | ||
90 : | in case decr | ||
91 : | of VarDecr x => (typ,SOME x) | ||
92 : | | PointerDecr x => | ||
93 : | ctypeDecrToTypeName (mkTyp (Pointer typ),x) | ||
94 : | | ArrayDecr (x,sz) => | ||
95 : | ctypeDecrToTypeName (mkTyp (Array (sz,typ)),x) | ||
96 : | | FuncDecr (x,lst) => | ||
97 : | ctypeDecrToTypeName (mkTyp (Function{retType=typ,params=lst}),x) | ||
98 : | | QualDecr (q,decr) => | ||
99 : | ctypeDecrToTypeName (addQual q, decr) | ||
100 : | | EmptyDecr => (typ, NONE) | ||
101 : | | EllipsesDecr => (mkTyp Ellipses, SOME("**ellipses**")) | ||
102 : | | DecrExt _ => (typ, NONE) (* should call decr extension? *) | ||
103 : | | MARKdeclarator(loc, decr) => ctypeDecrToTypeName(typ, decr) | ||
104 : | end | ||
105 : | |||
106 : | fun dclr2str dcl = | ||
107 : | (case ctypeDecrToTypeName ({qualifiers=[],specifiers=[]}, dcl) | ||
108 : | of (_,SOME s) => s | ||
109 : | | (_,NONE) => "") | ||
110 : | |||
111 : | fun combineDecltypes ( {qualifiers=q1,storage=st1,specifiers=sp1} | ||
112 : | , {qualifiers=q2,storage=st2,specifiers=sp2} | ||
113 : | ) = | ||
114 : | {qualifiers=q1@q2,storage=st1@st2,specifiers=sp1@sp2} (* @ ok *) | ||
115 : | |||
116 : | fun applyPointer (PointerDecr x,rest) = PointerDecr (applyPointer (x,rest)) | ||
117 : | | applyPointer (QualDecr (q,x),rest) = QualDecr (q, applyPointer (x,rest)) | ||
118 : | | applyPointer (EmptyDecr, rest) = rest | ||
119 : | | applyPointer (_, rest) = rest | ||
120 : | (* NCH/DBM[6/14/99]: this case can never occur *) | ||
121 : | |||
122 : | fun addStorage(st, {qualifiers,storage,specifiers}) = | ||
123 : | {qualifiers=qualifiers,storage=st::storage,specifiers=specifiers} | ||
124 : | |||
125 : | fun addQualifiers(qs, {qualifiers,storage,specifiers}) = | ||
126 : | {qualifiers=qs@qualifiers,storage=storage,specifiers=specifiers} (* @ ok *) | ||
127 : | |||
128 : | fun addQualifier(q, {qualifiers,storage,specifiers}) = | ||
129 : | {qualifiers=q::qualifiers,storage=storage,specifiers=specifiers} | ||
130 : | |||
131 : | fun addSpecifier(sp, {qualifiers,storage,specifiers}) = | ||
132 : | {qualifiers=qualifiers,storage=storage,specifiers=sp::specifiers} | ||
133 : | |||
134 : | val addAll = combineDecltypes | ||
135 : | |||
136 : | fun loopQd (q::rst, acc) = loopQd(rst, QualDecr(q, acc)) | ||
137 : | | loopQd (nil, acc) = acc | ||
138 : | |||
139 : | fun mkCtype typ = typ | ||
140 : | |||
141 : | (* DBM: major kludge, using TYPEDEF as storage class *) | ||
142 : | fun insertDeclNames ({storage,...}: decltype, idl) = | ||
143 : | case storage | ||
144 : | of [TYPEDEF] => List.app (fn x as (dcl,_) => TypeDefs.addTdef (dclr2str dcl)) idl | ||
145 : | | _ => List.app (fn x as (dcl,_) => TypeDefs.addNoTdef (dclr2str dcl)) idl | ||
146 : | |||
147 : | fun insertFuncName dcl = | ||
148 : | let | ||
149 : | val name = dclr2str dcl | ||
150 : | in | ||
151 : | TypeDefs.addNoTdef name | ||
152 : | end | ||
153 : | |||
154 : | fun insertFuncParams (FuncDecr (_,params)) : unit = | ||
155 : | let | ||
156 : | fun getName (ct, dclr) = dclr2str dclr | ||
157 : | val names = map getName params | ||
158 : | in | ||
159 : | List.app TypeDefs.addNoTdef names | ||
160 : | end | ||
161 : | | insertFuncParams (ArrayDecr(dcl,_)) = insertFuncParams dcl | ||
162 : | | insertFuncParams (PointerDecr dcl) = insertFuncParams dcl | ||
163 : | | insertFuncParams _ = () (* this is actually an error, but it will be caught in | ||
164 : | * BuildAst when processing a PT.FunctionDef *) | ||
165 : | |||
166 : | abstype 'a seq = SEQ of 'a list | ||
167 : | with val emptySeq = SEQ nil | ||
168 : | fun singletonSeq x = SEQ[x] | ||
169 : | fun addToSeq(x, SEQ yl) = SEQ(x :: yl) (* add to end of sequence! *) | ||
170 : | (* fun addListToEnd(xl, yl) = SEQ((List.rev xl) @ yl) *) | ||
171 : | fun addOptToEnd(NONE, yl) = yl | ||
172 : | | addOptToEnd(SOME x, SEQ yl) = SEQ(x :: yl) | ||
173 : | fun seqToList(SEQ yl) = List.rev yl | ||
174 : | end | ||
175 : | |||
176 : | %% | ||
177 : | |||
178 : | %header (functor LrValsFun(structure Token : TOKEN | ||
179 : | )) | ||
180 : | |||
181 : | %term | ||
182 : | EOF | ||
183 : | | COLON | SEMICOLON | LPAREN | RPAREN | LCURLY | RCURLY | ||
184 : | | LBRACE | RBRACE | DOT | ||
185 : | | COMMA | QUESTION | PERCENT | AMP | BAR | TILDE | DIVIDE | PLUS | ||
186 : | | MINUS | HAT | BANG | TIMES | ||
187 : | | INC | DEC | ARROW | ||
188 : | | ID of string | ||
189 : | | EQUALS | PLUSEQUALS | MINUSEQUALS | XOREQUALS | MODEQUALS | ||
190 : | | TIMESEQUALS | DIVEQUALS | OREQUALS | ANDEQUALS | LSHIFTEQUALS | ||
191 : | | RSHIFTEQUALS | ||
192 : | | LTE | GTE | LT | GT | EQ | NEQ | OR | AND | LSHIFT | RSHIFT | ||
193 : | | DECNUM of LargeInt.int | ||
194 : | | REALNUM of real | ||
195 : | | STRING of string | ||
196 : | | CCONST of LargeInt.int | ||
197 : | | EXTERN | AUTO | STATIC | REGISTER | CONST | VOLATILE | ||
198 : | | IF | THEN | ELSE | ||
199 : | | FOR | DO | SWITCH | CASE | DEFAULT | ||
200 : | | WHILE | RETURN | ||
201 : | | BREAK | CONTINUE | GOTO | ||
202 : | | CHAR | DOUBLE | ENUM | FLOAT | INT | LONG | SHORT | ||
203 : | | FRACTIONAL | SATURATE (* D *) | ||
204 : | | STRUCT | UNION | UNSIGNED | SIGNED | ||
205 : | | VOID | SIZEOF | TYPEDEF | UNARY | ||
206 : | | ELIPSIS | ||
207 : | | TYPE_NAME of string | ||
208 : | |||
209 : | %nonterm | ||
210 : | translationUnit of externalDecl list | ||
211 : | | tu of externalDecl seq | ||
212 : | | statement of statement | ||
213 : | | ostatementlist of statement list | ||
214 : | |||
215 : | | statementlist of statement seq | ||
216 : | | compoundStatement of statement | ||
217 : | | expr of expression | ||
218 : | | opExpr of expression | ||
219 : | | exprWComma of expression | ||
220 : | | unaryOperator of operator | ||
221 : | | argumentExprList of expression seq | ||
222 : | | trailingComma of bool | ||
223 : | | enumeratorList of (string * expression) seq | ||
224 : | | enumerator of (string * expression) | ||
225 : | | abstractDeclarator of declarator | ||
226 : | | directAbstractDeclarator of declarator | ||
227 : | | initDeclarator of (declarator * expression) | ||
228 : | | notypeInitDeclarator of (declarator * expression) | ||
229 : | | initDeclaratorList of (declarator * expression) seq | ||
230 : | | notypeInitDeclaratorList of (declarator * expression) seq | ||
231 : | | pointer of declarator | ||
232 : | | declarator of declarator | ||
233 : | | aftertypeDeclarator of declarator | ||
234 : | | notypeDeclarator of declarator | ||
235 : | | parmDeclarator of declarator | ||
236 : | | aftertypeDirectDeclarator of declarator | ||
237 : | | notypeDirectDeclarator of declarator | ||
238 : | | parmDirectDeclarator of declarator | ||
239 : | | declarationSpecifiers of decltype | ||
240 : | | declarationModifiers of decltype | ||
241 : | | reservedDeclarationSpecifier of decltype | ||
242 : | | specifierQualifierReserved of ctype | ||
243 : | | reservedSpecifierQualifiers of ctype | ||
244 : | | initializer of expression | ||
245 : | | initializerList of expression seq | ||
246 : | | storageClassSpecifier of storage | ||
247 : | | typeName of ctype | ||
248 : | | typeSpecifier of specifier | ||
249 : | | typeSpecifierReserved of specifier | ||
250 : | | typeQualifier of qualifier | ||
251 : | | typeQualifierList of qualifier list | ||
252 : | | specifierQualifierList of ctype | ||
253 : | | enumSpecifier of specifier | ||
254 : | | structOrUnionSpecifier of specifier | ||
255 : | | fDefDeclaration of (decltype * declarator) | ||
256 : | | declarationList of declaration seq | ||
257 : | dbm | 639 | | identlist of (string * int * int) seq |
258 : | dbm | 597 | | functionDefinition of externalDecl |
259 : | | declaration of declaration | ||
260 : | | declaration1 of declaration | ||
261 : | | externalDeclaration of externalDecl option | ||
262 : | | parameterList of (decltype * declarator) seq | ||
263 : | | parameterTypeList of (decltype * declarator) list | ||
264 : | | parameterDeclaration of (decltype * declarator) | ||
265 : | | structOrUnion of bool | ||
266 : | | structDeclarator of (declarator * expression) | ||
267 : | | notypeStructDeclarator of (declarator * expression) | ||
268 : | | structDeclaratorList of (declarator * expression) seq | ||
269 : | | notypeStructDeclaratorList of (declarator * expression) seq | ||
270 : | | structDeclarationList of (ctype * (declarator * expression) list) seq | ||
271 : | | structDeclaration of (ctype * (declarator * expression) list) | ||
272 : | | pushScope of unit | ||
273 : | | popScope of unit | ||
274 : | | strings of string | ||
275 : | |||
276 : | |||
277 : | |||
278 : | |||
279 : | |||
280 : | %pos int | ||
281 : | %verbose | ||
282 : | %pure | ||
283 : | %start translationUnit | ||
284 : | %eop EOF | ||
285 : | %noshift EOF | ||
286 : | %keyword QUESTION IF THEN ELSE FOR DO SWITCH CASE DEFAULT WHILE RETURN BREAK CONTINUE GOTO | ||
287 : | %subst TYPE_NAME for ID | ||
288 : | %value TYPE_NAME(Error.hint "Likely cause: missing typedef declaration.\n"; "bogus") | ||
289 : | |||
290 : | %arg (srcMap) : SourceMap.sourcemap | ||
291 : | |||
292 : | %name C | ||
293 : | |||
294 : | %left COMMA | ||
295 : | %right EQUALS PLUSEQUALS MINUSEQUALS TIMESEQUALS DIVEQUALS MODEQUALS XOREQUALS OREQUALS ANDEQUALS LSHIFTEQUALS RSHIFTEQUALS | ||
296 : | %right QUESTION | ||
297 : | %left OR | ||
298 : | %left AND | ||
299 : | %left BAR | ||
300 : | %left HAT | ||
301 : | %left AMP | ||
302 : | %left EQ NEQ | ||
303 : | %left LT GT LTE GTE | ||
304 : | %left LSHIFT RSHIFT | ||
305 : | %left PLUS MINUS | ||
306 : | %left TIMES DIVIDE PERCENT | ||
307 : | %right UNARY | ||
308 : | %right INC DEC SIZEOF | ||
309 : | %left LBRACE LPAREN ARROW DOT | ||
310 : | |||
311 : | %% | ||
312 : | |||
313 : | translationUnit: | ||
314 : | tu (seqToList tu) | ||
315 : | |||
316 : | tu: | ||
317 : | (emptySeq) | ||
318 : | | tu externalDeclaration (addOptToEnd(externalDeclaration, tu)) | ||
319 : | |||
320 : | externalDeclaration: | ||
321 : | declaration (SOME(markExternalDecl srcMap (ExternalDecl declaration, | ||
322 : | declarationleft, | ||
323 : | declarationright))) | ||
324 : | | SEMICOLON (NONE) | ||
325 : | | functionDefinition (SOME(markExternalDecl srcMap (functionDefinition, | ||
326 : | functionDefinitionleft, | ||
327 : | functionDefinitionright))) | ||
328 : | |||
329 : | statement: | ||
330 : | FOR LPAREN opExpr SEMICOLON opExpr SEMICOLON opExpr RPAREN statement | ||
331 : | (markStatement srcMap (For(opExpr1,opExpr2,opExpr3,statement), | ||
332 : | FORleft, statementright)) | ||
333 : | | WHILE LPAREN exprWComma RPAREN statement | ||
334 : | (markStatement srcMap (While(exprWComma,statement), | ||
335 : | WHILEleft, statementright)) | ||
336 : | | SWITCH LPAREN exprWComma RPAREN statement | ||
337 : | (markStatement srcMap (Switch(exprWComma,statement), | ||
338 : | SWITCHleft, statementright)) | ||
339 : | | DO statement WHILE LPAREN exprWComma RPAREN SEMICOLON | ||
340 : | (markStatement srcMap (Do(exprWComma,statement), | ||
341 : | DOleft, SEMICOLONright)) | ||
342 : | | BREAK SEMICOLON (markStatement srcMap (Break, | ||
343 : | BREAKleft, SEMICOLONright)) | ||
344 : | | CONTINUE SEMICOLON (markStatement srcMap (Continue, | ||
345 : | CONTINUEleft, SEMICOLONright)) | ||
346 : | | RETURN opExpr SEMICOLON (markStatement srcMap (Return(opExpr), | ||
347 : | RETURNleft, SEMICOLONright)) | ||
348 : | | GOTO ID SEMICOLON (markStatement srcMap (Goto(ID), | ||
349 : | GOTOleft, SEMICOLONright)) | ||
350 : | | compoundStatement (compoundStatement) | ||
351 : | | ID COLON statement (markStatement srcMap (Labeled(ID,statement), | ||
352 : | IDleft,statementright)) | ||
353 : | | DEFAULT COLON statement (markStatement srcMap (DefaultLabel(statement), | ||
354 : | DEFAULTleft, statementright)) | ||
355 : | | CASE exprWComma COLON statement | ||
356 : | (markStatement srcMap (CaseLabel(exprWComma,statement), | ||
357 : | CASEleft, statementright)) | ||
358 : | | IF LPAREN exprWComma RPAREN statement | ||
359 : | (markStatement srcMap (IfThen(exprWComma,statement), | ||
360 : | IFleft, statementright)) | ||
361 : | | IF LPAREN exprWComma RPAREN statement ELSE statement | ||
362 : | (markStatement srcMap (IfThenElse(exprWComma,statement1,statement2), | ||
363 : | IFleft, | ||
364 : | statement2right)) | ||
365 : | | exprWComma SEMICOLON (markStatement srcMap (Expr(exprWComma), | ||
366 : | exprWCommaleft, SEMICOLONright)) | ||
367 : | | SEMICOLON (markStatement srcMap (Expr(EmptyExpr), | ||
368 : | SEMICOLONleft, SEMICOLONright)) | ||
369 : | |||
370 : | |||
371 : | |||
372 : | |||
373 : | |||
374 : | |||
375 : | declaration: | ||
376 : | declaration1 SEMICOLON (declaration1) | ||
377 : | |||
378 : | |||
379 : | declaration1: | ||
380 : | declarationSpecifiers | ||
381 : | (insertDeclNames (declarationSpecifiers, []); | ||
382 : | markDeclaration srcMap | ||
383 : | (Declaration(declarationSpecifiers, []), | ||
384 : | declarationSpecifiersleft, declarationSpecifiersright)) | ||
385 : | |||
386 : | | declarationSpecifiers initDeclaratorList | ||
387 : | (let val decl = (declarationSpecifiers, seqToList initDeclaratorList) | ||
388 : | in insertDeclNames decl; | ||
389 : | markDeclaration srcMap | ||
390 : | (Declaration decl, declarationSpecifiersleft, initDeclaratorListright) | ||
391 : | end) | ||
392 : | |||
393 : | | declarationModifiers notypeInitDeclaratorList | ||
394 : | (let val decl = (declarationModifiers, seqToList notypeInitDeclaratorList) | ||
395 : | in insertDeclNames decl; | ||
396 : | markDeclaration srcMap | ||
397 : | (Declaration decl, declarationModifiersleft, notypeInitDeclaratorListright) | ||
398 : | end) | ||
399 : | |||
400 : | ostatementlist: | ||
401 : | statementlist (seqToList statementlist) | ||
402 : | | ([]) | ||
403 : | |||
404 : | statementlist: | ||
405 : | statement (singletonSeq statement) | ||
406 : | | statementlist statement (addToSeq(statement, statementlist)) | ||
407 : | |||
408 : | |||
409 : | (* original code: changed for "let" statements in D *) | ||
410 : | compoundStatement: | ||
411 : | LCURLY pushScope declarationList ostatementlist popScope RCURLY | ||
412 : | dbm | 639 | (markStatement srcMap (Compound ((map Decl (seqToList declarationList)) @ ostatementlist), LCURLYleft, RCURLYright)) |
413 : | dbm | 597 | | LCURLY ostatementlist RCURLY |
414 : | dbm | 639 | (markStatement srcMap (Compound (ostatementlist), LCURLYleft, RCURLYright)) |
415 : | dbm | 597 | (* *) |
416 : | |||
417 : | |||
418 : | |||
419 : | |||
420 : | |||
421 : | unaryOperator: | ||
422 : | AMP (AddrOf) | ||
423 : | | TIMES (Star) | ||
424 : | | PLUS (Uplus) | ||
425 : | | MINUS (Negate) | ||
426 : | | TILDE (BitNot) | ||
427 : | | BANG (Not) | ||
428 : | |||
429 : | expr: | ||
430 : | expr QUESTION expr COLON expr %prec QUESTION (markExpression srcMap (QuestionColon(expr1,expr2,expr3),expr1left,expr3right)) | ||
431 : | | expr PLUSEQUALS expr (markExpression srcMap (Binop(PlusAssign,expr1,expr2),expr1left,expr2right)) | ||
432 : | | expr MINUSEQUALS expr (markExpression srcMap (Binop(MinusAssign,expr1,expr2),expr1left,expr2right)) | ||
433 : | | expr TIMESEQUALS expr (markExpression srcMap (Binop(TimesAssign,expr1,expr2),expr1left,expr2right)) | ||
434 : | | expr DIVEQUALS expr (markExpression srcMap (Binop(DivAssign,expr1,expr2),expr1left,expr2right)) | ||
435 : | | expr MODEQUALS expr (markExpression srcMap (Binop(ModAssign,expr1,expr2),expr1left,expr2right)) | ||
436 : | | expr XOREQUALS expr (markExpression srcMap (Binop(XorAssign,expr1,expr2),expr1left,expr2right)) | ||
437 : | | expr OREQUALS expr (markExpression srcMap (Binop(OrAssign,expr1,expr2),expr1left,expr2right)) | ||
438 : | | expr ANDEQUALS expr (markExpression srcMap (Binop(AndAssign,expr1,expr2),expr1left,expr2right)) | ||
439 : | | expr LSHIFTEQUALS expr (markExpression srcMap (Binop(LshiftAssign,expr1,expr2),expr1left,expr2right)) | ||
440 : | | expr RSHIFTEQUALS expr (markExpression srcMap (Binop(RshiftAssign,expr1,expr2),expr1left,expr2right)) | ||
441 : | | expr EQUALS expr (markExpression srcMap (Binop(Assign,expr1,expr2),expr1left,expr2right)) | ||
442 : | | expr OR expr (markExpression srcMap (Binop(Or,expr1,expr2),expr1left,expr2right)) | ||
443 : | | expr AND expr (markExpression srcMap (Binop(And,expr1,expr2),expr1left,expr2right)) | ||
444 : | | expr BAR expr (markExpression srcMap (Binop(BitOr,expr1,expr2),expr1left,expr2right)) | ||
445 : | | expr HAT expr (markExpression srcMap (Binop(BitXor,expr1,expr2),expr1left,expr2right)) | ||
446 : | | expr AMP expr (markExpression srcMap (Binop(BitAnd,expr1,expr2),expr1left,expr2right)) | ||
447 : | | expr EQ expr (markExpression srcMap (Binop(Eq,expr1,expr2),expr1left,expr2right)) | ||
448 : | | expr NEQ expr (markExpression srcMap (Binop(Neq,expr1,expr2),expr1left,expr2right)) | ||
449 : | | expr LT expr (markExpression srcMap (Binop(Lt,expr1,expr2),expr1left,expr2right)) | ||
450 : | | expr GT expr (markExpression srcMap (Binop(Gt,expr1,expr2),expr1left,expr2right)) | ||
451 : | | expr LTE expr (markExpression srcMap (Binop(Lte,expr1,expr2),expr1left,expr2right)) | ||
452 : | | expr GTE expr (markExpression srcMap (Binop(Gte,expr1,expr2),expr1left,expr2right)) | ||
453 : | | expr LSHIFT expr (markExpression srcMap (Binop(Lshift,expr1,expr2),expr1left,expr2right)) | ||
454 : | | expr RSHIFT expr (markExpression srcMap (Binop(Rshift,expr1,expr2),expr1left,expr2right)) | ||
455 : | | expr PLUS expr (markExpression srcMap (Binop(Plus,expr1,expr2),expr1left,expr2right)) | ||
456 : | | expr MINUS expr (markExpression srcMap (Binop(Minus,expr1,expr2),expr1left,expr2right)) | ||
457 : | | expr TIMES expr (markExpression srcMap (Binop(Times,expr1,expr2),expr1left,expr2right)) | ||
458 : | | expr DIVIDE expr (markExpression srcMap (Binop(Divide,expr1,expr2),expr1left,expr2right)) | ||
459 : | | expr PERCENT expr (markExpression srcMap (Binop(Mod,expr1,expr2),expr1left,expr2right)) | ||
460 : | | expr INC %prec INC (markExpression srcMap (Unop(PostInc,expr),exprleft,INCright)) | ||
461 : | | expr DEC %prec INC (markExpression srcMap (Unop(PostDec,expr),exprleft,DECright)) | ||
462 : | | INC expr %prec INC (markExpression srcMap (Unop(PreInc,expr),INCleft,exprright)) | ||
463 : | | DEC expr %prec INC (markExpression srcMap (Unop(PreDec,expr),DECleft,exprright)) | ||
464 : | | unaryOperator expr %prec UNARY (markExpression srcMap (Unop(unaryOperator,expr),unaryOperatorleft,exprright)) | ||
465 : | | SIZEOF expr (markExpression srcMap (Unop(Sizeof,expr),SIZEOFleft,exprright)) | ||
466 : | | LPAREN typeName RPAREN expr %prec INC | ||
467 : | (markExpression srcMap (Cast (typeName,expr),LPARENleft,exprright)) | ||
468 : | | SIZEOF LPAREN typeName RPAREN %prec SIZEOF | ||
469 : | (markExpression srcMap (Unop(SizeofType typeName,EmptyExpr),SIZEOFleft,RPARENright)) | ||
470 : | | expr LBRACE exprWComma RBRACE | ||
471 : | (markExpression srcMap (Binop(Sub,expr,exprWComma),exprleft,RBRACEright)) | ||
472 : | |||
473 : | |||
474 : | |||
475 : | | expr LPAREN RPAREN (markExpression srcMap (Call(expr,[]),exprleft,RPARENright)) | ||
476 : | | expr LPAREN argumentExprList RPAREN | ||
477 : | (markExpression srcMap (Call(expr, seqToList argumentExprList),exprleft,RPARENright)) | ||
478 : | | expr DOT ID (markExpression srcMap (Binop(Dot,expr,Id(ID)),exprleft,IDright)) | ||
479 : | | expr ARROW ID (markExpression srcMap (Binop(Arrow,expr,Id(ID)),exprleft,IDright)) | ||
480 : | | expr DOT TYPE_NAME (markExpression srcMap (Binop(Dot,expr,Id(TYPE_NAME)),exprleft,TYPE_NAMEright)) | ||
481 : | | expr ARROW TYPE_NAME (markExpression srcMap (Binop(Arrow,expr,Id(TYPE_NAME)),exprleft,TYPE_NAMEright)) | ||
482 : | | LPAREN exprWComma RPAREN (markExpression srcMap (exprWComma,LPARENleft,RPARENright)) | ||
483 : | | DECNUM (markExpression srcMap (IntConst DECNUM,DECNUMleft,DECNUMright)) | ||
484 : | | REALNUM (markExpression srcMap (RealConst REALNUM, REALNUMleft,REALNUMright)) | ||
485 : | | CCONST (markExpression srcMap (IntConst CCONST, CCONSTleft,CCONSTright)) | ||
486 : | | ID (markExpression srcMap (Id(ID), IDleft, IDright)) | ||
487 : | | strings (markExpression srcMap (String(strings),stringsleft,stringsright)) | ||
488 : | |||
489 : | |||
490 : | strings: STRING (STRING) | ||
491 : | | STRING strings (STRING ^ strings) | ||
492 : | |||
493 : | |||
494 : | |||
495 : | exprWComma: | ||
496 : | expr (expr) | ||
497 : | | exprWComma COMMA expr (markExpression srcMap (Binop(Comma,exprWComma,expr),exprWCommaleft,exprright)) | ||
498 : | |||
499 : | opExpr: (EmptyExpr) | ||
500 : | | exprWComma (exprWComma) | ||
501 : | |||
502 : | |||
503 : | argumentExprList: | ||
504 : | expr (singletonSeq expr) | ||
505 : | | argumentExprList COMMA expr (addToSeq(expr, argumentExprList)) | ||
506 : | |||
507 : | typeName: | ||
508 : | specifierQualifierList (specifierQualifierList) | ||
509 : | | specifierQualifierList abstractDeclarator | ||
510 : | (#1 (ctypeDecrToTypeName (specifierQualifierList, abstractDeclarator))) | ||
511 : | |||
512 : | declarationSpecifiers: | ||
513 : | typeSpecifier reservedDeclarationSpecifier | ||
514 : | (addSpecifier (typeSpecifier, | ||
515 : | reservedDeclarationSpecifier)) | ||
516 : | | declarationModifiers typeSpecifier reservedDeclarationSpecifier | ||
517 : | (addAll (declarationModifiers, | ||
518 : | addSpecifier (typeSpecifier, | ||
519 : | reservedDeclarationSpecifier))) | ||
520 : | |||
521 : | reservedDeclarationSpecifier: | ||
522 : | (unknown) | ||
523 : | | reservedDeclarationSpecifier specifierQualifierReserved | ||
524 : | (let val {qualifiers,specifiers} = specifierQualifierReserved | ||
525 : | val decltype = {qualifiers=qualifiers,specifiers=specifiers,storage=[]} | ||
526 : | in addAll (decltype, reservedDeclarationSpecifier) end ) | ||
527 : | | reservedDeclarationSpecifier storageClassSpecifier | ||
528 : | (addStorage (storageClassSpecifier, | ||
529 : | reservedDeclarationSpecifier)) | ||
530 : | |||
531 : | specifierQualifierReserved: | ||
532 : | typeSpecifierReserved ({qualifiers=[],specifiers=[typeSpecifierReserved]}) | ||
533 : | | typeQualifier ({qualifiers=[typeQualifier],specifiers=[]}) | ||
534 : | | structOrUnionSpecifier ({qualifiers=[],specifiers=[structOrUnionSpecifier]}) | ||
535 : | | enumSpecifier ({qualifiers=[],specifiers=[enumSpecifier]}) | ||
536 : | |||
537 : | declarationModifiers: | ||
538 : | storageClassSpecifier | ||
539 : | ({storage = [storageClassSpecifier], | ||
540 : | qualifiers = [], | ||
541 : | specifiers = []}) | ||
542 : | | declarationModifiers storageClassSpecifier | ||
543 : | (addStorage(storageClassSpecifier,declarationModifiers)) | ||
544 : | | typeQualifier | ||
545 : | ({specifiers = [], | ||
546 : | storage = [], | ||
547 : | qualifiers = [typeQualifier]}) | ||
548 : | | declarationModifiers typeQualifier | ||
549 : | (addQualifier(typeQualifier, declarationModifiers)) | ||
550 : | |||
551 : | specifierQualifierList: | ||
552 : | typeSpecifier reservedSpecifierQualifiers | ||
553 : | (let val {specifiers, qualifiers} = reservedSpecifierQualifiers | ||
554 : | in {specifiers=typeSpecifier::specifiers,qualifiers=qualifiers} end) | ||
555 : | |||
556 : | | typeQualifierList typeSpecifier reservedSpecifierQualifiers | ||
557 : | (let val {specifiers, qualifiers} = reservedSpecifierQualifiers | ||
558 : | in {specifiers=typeSpecifier::specifiers | ||
559 : | ,qualifiers=typeQualifierList@qualifiers | ||
560 : | } | ||
561 : | end) | ||
562 : | |||
563 : | reservedSpecifierQualifiers: | ||
564 : | ({qualifiers=[],specifiers=[]}) | ||
565 : | | reservedSpecifierQualifiers specifierQualifierReserved | ||
566 : | (let val {specifiers=s1, qualifiers=q1} = reservedSpecifierQualifiers | ||
567 : | val {specifiers=s2, qualifiers=q2} = specifierQualifierReserved | ||
568 : | in {specifiers=s1@s2, qualifiers=q1@q2} end) | ||
569 : | |||
570 : | typeQualifierList: | ||
571 : | typeQualifier ([typeQualifier]) | ||
572 : | |||
573 : | | typeQualifier typeQualifierList | ||
574 : | (typeQualifier::typeQualifierList) | ||
575 : | |||
576 : | typeSpecifier: | ||
577 : | typeSpecifierReserved (typeSpecifierReserved) | ||
578 : | | structOrUnionSpecifier (structOrUnionSpecifier) | ||
579 : | | enumSpecifier (enumSpecifier) | ||
580 : | | TYPE_NAME (TypedefName TYPE_NAME) | ||
581 : | |||
582 : | typeSpecifierReserved: | ||
583 : | VOID (Void) | ||
584 : | | CHAR (Char) | ||
585 : | | SHORT (Short) | ||
586 : | | INT (Int) | ||
587 : | | LONG (Long) | ||
588 : | | FLOAT (Float) | ||
589 : | | DOUBLE (Double) | ||
590 : | | SIGNED (Signed) | ||
591 : | | UNSIGNED (Unsigned) | ||
592 : | |||
593 : | |||
594 : | structOrUnionSpecifier: | ||
595 : | structOrUnion LCURLY structDeclarationList RCURLY | ||
596 : | (Struct{isStruct=structOrUnion, tagOpt=NONE, members=seqToList structDeclarationList}) | ||
597 : | |||
598 : | | structOrUnion ID LCURLY structDeclarationList RCURLY | ||
599 : | (Struct{isStruct=structOrUnion, tagOpt=SOME ID, members=seqToList structDeclarationList}) | ||
600 : | |||
601 : | | structOrUnion TYPE_NAME LCURLY structDeclarationList RCURLY | ||
602 : | (Struct{isStruct=structOrUnion, tagOpt=SOME TYPE_NAME, members=seqToList structDeclarationList}) | ||
603 : | |||
604 : | | structOrUnion ID (StructTag {isStruct=structOrUnion, name=ID}) | ||
605 : | |||
606 : | | structOrUnion TYPE_NAME (StructTag {isStruct=structOrUnion, name=TYPE_NAME}) | ||
607 : | |||
608 : | (* humor me: consider true for struct *) | ||
609 : | structOrUnion: | ||
610 : | STRUCT (true) | ||
611 : | | UNION (false) | ||
612 : | |||
613 : | structDeclarationList: | ||
614 : | structDeclaration (singletonSeq structDeclaration) | ||
615 : | | structDeclarationList structDeclaration | ||
616 : | (addToSeq(structDeclaration, structDeclarationList)) | ||
617 : | |||
618 : | structDeclaration: | ||
619 : | specifierQualifierList structDeclaratorList SEMICOLON | ||
620 : | ((specifierQualifierList, seqToList structDeclaratorList)) | ||
621 : | | typeQualifierList notypeStructDeclaratorList SEMICOLON | ||
622 : | (let | ||
623 : | val ct = {qualifiers=typeQualifierList, specifiers=[]} | ||
624 : | in | ||
625 : | (ct, seqToList notypeStructDeclaratorList) | ||
626 : | end) | ||
627 : | |||
628 : | structDeclaratorList: | ||
629 : | structDeclarator (singletonSeq structDeclarator) | ||
630 : | | structDeclaratorList COMMA structDeclarator | ||
631 : | (addToSeq(structDeclarator, structDeclaratorList)) | ||
632 : | |||
633 : | notypeStructDeclaratorList: | ||
634 : | notypeStructDeclarator (singletonSeq notypeStructDeclarator) | ||
635 : | | notypeStructDeclaratorList COMMA structDeclarator | ||
636 : | (addToSeq(structDeclarator, notypeStructDeclaratorList)) | ||
637 : | |||
638 : | structDeclarator: | ||
639 : | declarator (declarator, EmptyExpr) | ||
640 : | | COLON expr (EmptyDecr, expr) | ||
641 : | | declarator COLON expr (declarator, expr) | ||
642 : | |||
643 : | notypeStructDeclarator: | ||
644 : | notypeDeclarator (notypeDeclarator, EmptyExpr) | ||
645 : | | COLON expr (EmptyDecr, expr) | ||
646 : | | notypeDeclarator COLON expr (notypeDeclarator, expr) | ||
647 : | |||
648 : | typeQualifier: | ||
649 : | CONST (CONST) | ||
650 : | | VOLATILE (VOLATILE) | ||
651 : | |||
652 : | enumSpecifier: | ||
653 : | ENUM LCURLY enumeratorList trailingComma RCURLY | ||
654 : | (Enum{tagOpt=NONE, enumerators=seqToList enumeratorList, trailingComma=trailingComma}) | ||
655 : | |||
656 : | | ENUM ID LCURLY enumeratorList trailingComma RCURLY | ||
657 : | (Enum{tagOpt=SOME(ID), enumerators=seqToList enumeratorList, trailingComma=trailingComma}) | ||
658 : | |||
659 : | | ENUM TYPE_NAME LCURLY enumeratorList trailingComma RCURLY | ||
660 : | (Enum{tagOpt=SOME(TYPE_NAME), enumerators=seqToList enumeratorList, trailingComma=trailingComma}) | ||
661 : | |||
662 : | | ENUM ID (EnumTag(ID)) | ||
663 : | |||
664 : | | ENUM TYPE_NAME (EnumTag(TYPE_NAME)) | ||
665 : | |||
666 : | enumeratorList: | ||
667 : | enumeratorList COMMA enumerator | ||
668 : | (addToSeq(enumerator, enumeratorList)) | ||
669 : | | enumerator ((TypeDefs.addNoTdef(#1(enumerator))); | ||
670 : | singletonSeq enumerator) | ||
671 : | |||
672 : | enumerator: | ||
673 : | ID ((ID,ParseTree.EmptyExpr)) | ||
674 : | | ID EQUALS expr (ID,expr) | ||
675 : | |||
676 : | storageClassSpecifier: | ||
677 : | EXTERN (EXTERN) | ||
678 : | | STATIC (STATIC) | ||
679 : | | AUTO (AUTO) | ||
680 : | | REGISTER (REGISTER) | ||
681 : | | TYPEDEF (TYPEDEF) | ||
682 : | |||
683 : | trailingComma: (false) | ||
684 : | | COMMA (true) | ||
685 : | |||
686 : | initDeclaratorList: | ||
687 : | initDeclarator (singletonSeq initDeclarator) | ||
688 : | | initDeclaratorList COMMA initDeclarator | ||
689 : | (addToSeq(initDeclarator, initDeclaratorList)) | ||
690 : | |||
691 : | initDeclarator: | ||
692 : | declarator ((declarator,EmptyExpr)) | ||
693 : | | declarator EQUALS initializer (declarator,initializer) | ||
694 : | |||
695 : | notypeInitDeclaratorList: | ||
696 : | notypeInitDeclarator (singletonSeq notypeInitDeclarator) | ||
697 : | | notypeInitDeclaratorList COMMA initDeclarator | ||
698 : | (addToSeq(initDeclarator, notypeInitDeclaratorList)) | ||
699 : | |||
700 : | notypeInitDeclarator: | ||
701 : | notypeDeclarator ((notypeDeclarator,EmptyExpr)) | ||
702 : | | notypeDeclarator EQUALS initializer | ||
703 : | (notypeDeclarator,initializer) | ||
704 : | |||
705 : | declarator: | ||
706 : | aftertypeDeclarator (aftertypeDeclarator) | ||
707 : | | notypeDeclarator (notypeDeclarator) | ||
708 : | |||
709 : | aftertypeDeclarator: | ||
710 : | aftertypeDirectDeclarator (aftertypeDirectDeclarator) | ||
711 : | | pointer aftertypeDirectDeclarator (applyPointer(pointer,aftertypeDirectDeclarator)) | ||
712 : | |||
713 : | notypeDeclarator: | ||
714 : | notypeDirectDeclarator (notypeDirectDeclarator) | ||
715 : | | pointer notypeDirectDeclarator | ||
716 : | (applyPointer(pointer, notypeDirectDeclarator)) | ||
717 : | |||
718 : | parmDeclarator: | ||
719 : | parmDirectDeclarator (parmDirectDeclarator) | ||
720 : | | pointer parmDirectDeclarator | ||
721 : | (applyPointer(pointer, parmDirectDeclarator)) | ||
722 : | |||
723 : | pointer: | ||
724 : | TIMES (PointerDecr(EmptyDecr)) | ||
725 : | | TIMES typeQualifierList | ||
726 : | (PointerDecr(loopQd(typeQualifierList,EmptyDecr))) | ||
727 : | | TIMES pointer (PointerDecr(pointer)) | ||
728 : | | TIMES typeQualifierList pointer | ||
729 : | (PointerDecr(loopQd(typeQualifierList,pointer))) | ||
730 : | |||
731 : | aftertypeDirectDeclarator: | ||
732 : | dbm | 639 | TYPE_NAME (markDeclarator srcMap (VarDecr TYPE_NAME,TYPE_NAMEleft,TYPE_NAMEright)) |
733 : | dbm | 597 | | LPAREN aftertypeDeclarator RPAREN |
734 : | (aftertypeDeclarator) | ||
735 : | | aftertypeDirectDeclarator LBRACE RBRACE %prec DOT | ||
736 : | (ArrayDecr (aftertypeDirectDeclarator,EmptyExpr)) | ||
737 : | | aftertypeDirectDeclarator LBRACE expr RBRACE %prec DOT | ||
738 : | (ArrayDecr (aftertypeDirectDeclarator,expr)) | ||
739 : | | aftertypeDirectDeclarator LPAREN RPAREN %prec DOT | ||
740 : | (FuncDecr (aftertypeDirectDeclarator,nil)) | ||
741 : | | aftertypeDirectDeclarator LPAREN parameterTypeList RPAREN %prec DOT | ||
742 : | (FuncDecr (aftertypeDirectDeclarator,parameterTypeList)) | ||
743 : | | aftertypeDirectDeclarator LPAREN identlist RPAREN %prec DOT | ||
744 : | (FuncDecr (aftertypeDirectDeclarator, | ||
745 : | dbm | 639 | map (fn (x,y,z) => (unknown,markDeclarator srcMap (VarDecr x,y,z))) (seqToList identlist))) |
746 : | dbm | 597 | |
747 : | notypeDirectDeclarator: | ||
748 : | dbm | 639 | ID (markDeclarator srcMap (VarDecr ID,IDleft,IDright)) |
749 : | dbm | 597 | | LPAREN notypeDeclarator RPAREN |
750 : | (notypeDeclarator) | ||
751 : | | notypeDirectDeclarator LBRACE RBRACE %prec DOT | ||
752 : | (ArrayDecr (notypeDirectDeclarator,EmptyExpr)) | ||
753 : | | notypeDirectDeclarator LBRACE expr RBRACE %prec DOT | ||
754 : | (ArrayDecr (notypeDirectDeclarator,expr)) | ||
755 : | | notypeDirectDeclarator LPAREN RPAREN %prec DOT | ||
756 : | (FuncDecr (notypeDirectDeclarator,nil)) | ||
757 : | | notypeDirectDeclarator LPAREN parameterTypeList RPAREN %prec DOT | ||
758 : | (FuncDecr (notypeDirectDeclarator,parameterTypeList)) | ||
759 : | | notypeDirectDeclarator LPAREN identlist RPAREN %prec DOT | ||
760 : | (FuncDecr (notypeDirectDeclarator, | ||
761 : | dbm | 639 | map (fn (x,y,z) => (unknown,markDeclarator srcMap (VarDecr x,y,z))) (seqToList identlist))) |
762 : | dbm | 597 | |
763 : | parmDirectDeclarator: | ||
764 : | dbm | 639 | TYPE_NAME (markDeclarator srcMap (VarDecr TYPE_NAME,TYPE_NAMEleft,TYPE_NAMEright)) |
765 : | dbm | 597 | | parmDirectDeclarator LBRACE RBRACE %prec DOT |
766 : | (ArrayDecr (parmDirectDeclarator,EmptyExpr)) | ||
767 : | | parmDirectDeclarator LBRACE expr RBRACE %prec DOT | ||
768 : | (ArrayDecr (parmDirectDeclarator,expr)) | ||
769 : | | parmDirectDeclarator LPAREN RPAREN %prec DOT | ||
770 : | (FuncDecr (parmDirectDeclarator,nil)) | ||
771 : | | parmDirectDeclarator LPAREN parameterTypeList RPAREN %prec DOT | ||
772 : | (FuncDecr (parmDirectDeclarator,parameterTypeList)) | ||
773 : | | parmDirectDeclarator LPAREN identlist RPAREN %prec DOT | ||
774 : | (FuncDecr (parmDirectDeclarator, | ||
775 : | dbm | 639 | map (fn (x,y,z) => (unknown,markDeclarator srcMap (VarDecr x,y,z))) (seqToList identlist))) |
776 : | dbm | 597 | |
777 : | initializer: | ||
778 : | expr (expr) | ||
779 : | | LCURLY initializerList trailingComma RCURLY | ||
780 : | (markExpression srcMap (InitList(seqToList initializerList),LCURLYleft,RCURLYright)) | ||
781 : | |||
782 : | initializerList: | ||
783 : | initializer (singletonSeq initializer) | ||
784 : | | initializerList COMMA initializer | ||
785 : | (addToSeq(initializer, initializerList)) | ||
786 : | |||
787 : | declarationList: | ||
788 : | declaration (singletonSeq(markDeclaration srcMap (declaration, | ||
789 : | declarationleft, | ||
790 : | declarationright))) | ||
791 : | | declarationList declaration (addToSeq(markDeclaration srcMap (declaration, | ||
792 : | declarationleft, | ||
793 : | declarationright), | ||
794 : | declarationList)) | ||
795 : | |||
796 : | identlist: | ||
797 : | dbm | 639 | ID (singletonSeq (ID,IDleft,IDright)) |
798 : | | identlist COMMA ID (addToSeq((ID,IDleft,IDright),identlist)) | ||
799 : | dbm | 597 | |
800 : | (* Put function name in the current scope and param names in a pushed scope. *) | ||
801 : | fDefDeclaration: | ||
802 : | notypeDeclarator | ||
803 : | (insertFuncName(notypeDeclarator); | ||
804 : | TypeDefs.pushScope(); | ||
805 : | insertFuncParams(notypeDeclarator); | ||
806 : | (unknown, notypeDeclarator)) | ||
807 : | | declarationSpecifiers declarator | ||
808 : | (insertFuncName(declarator); | ||
809 : | TypeDefs.pushScope(); | ||
810 : | insertFuncParams(declarator); | ||
811 : | (declarationSpecifiers, declarator)) | ||
812 : | |||
813 : | | declarationModifiers notypeDeclarator | ||
814 : | (insertFuncName(notypeDeclarator); | ||
815 : | TypeDefs.pushScope(); | ||
816 : | insertFuncParams(notypeDeclarator); | ||
817 : | (declarationModifiers, notypeDeclarator)) | ||
818 : | |||
819 : | functionDefinition: | ||
820 : | fDefDeclaration compoundStatement | ||
821 : | (TypeDefs.popScope(); | ||
822 : | FunctionDef | ||
823 : | {retType = #1 fDefDeclaration, | ||
824 : | funDecr = #2 fDefDeclaration, | ||
825 : | krParams = [], | ||
826 : | body = compoundStatement}) | ||
827 : | |||
828 : | | fDefDeclaration declarationList compoundStatement | ||
829 : | (TypeDefs.popScope(); | ||
830 : | FunctionDef | ||
831 : | {retType = #1 fDefDeclaration, | ||
832 : | funDecr = #2 fDefDeclaration, | ||
833 : | krParams = seqToList declarationList, | ||
834 : | body = compoundStatement}) | ||
835 : | |||
836 : | abstractDeclarator: | ||
837 : | pointer (applyPointer (pointer, EmptyDecr)) | ||
838 : | | directAbstractDeclarator (directAbstractDeclarator) | ||
839 : | | pointer directAbstractDeclarator | ||
840 : | (applyPointer(pointer, directAbstractDeclarator)) | ||
841 : | |||
842 : | directAbstractDeclarator: | ||
843 : | LPAREN abstractDeclarator RPAREN (abstractDeclarator) | ||
844 : | | LBRACE RBRACE (ArrayDecr(EmptyDecr, EmptyExpr)) | ||
845 : | | LBRACE expr RBRACE (ArrayDecr(EmptyDecr, expr)) | ||
846 : | | directAbstractDeclarator LBRACE RBRACE | ||
847 : | (ArrayDecr (directAbstractDeclarator,EmptyExpr)) | ||
848 : | | directAbstractDeclarator LBRACE expr RBRACE | ||
849 : | (ArrayDecr (directAbstractDeclarator,expr)) | ||
850 : | | LPAREN RPAREN (FuncDecr (EmptyDecr ,nil)) | ||
851 : | | LPAREN parameterTypeList RPAREN (FuncDecr (EmptyDecr, parameterTypeList)) | ||
852 : | | directAbstractDeclarator LPAREN RPAREN | ||
853 : | (FuncDecr (directAbstractDeclarator,nil)) | ||
854 : | | directAbstractDeclarator LPAREN parameterTypeList RPAREN | ||
855 : | (FuncDecr (directAbstractDeclarator, parameterTypeList)) | ||
856 : | |||
857 : | parameterTypeList: | ||
858 : | parameterList (seqToList parameterList) | ||
859 : | | parameterList COMMA ELIPSIS | ||
860 : | (let val decltype = {specifiers=[Ellipses],qualifiers=[],storage=[]} | ||
861 : | in (seqToList parameterList) @ [(decltype, EllipsesDecr)] end) | ||
862 : | |||
863 : | parameterList: | ||
864 : | parameterDeclaration | ||
865 : | (singletonSeq(#1 parameterDeclaration, | ||
866 : | markDeclarator srcMap (#2 parameterDeclaration, | ||
867 : | parameterDeclarationleft, | ||
868 : | parameterDeclarationright))) | ||
869 : | | parameterList COMMA parameterDeclaration | ||
870 : | (addToSeq((#1 parameterDeclaration, | ||
871 : | markDeclarator | ||
872 : | srcMap | ||
873 : | (#2 parameterDeclaration, | ||
874 : | parameterDeclarationleft, | ||
875 : | parameterDeclarationright)), | ||
876 : | parameterList)) | ||
877 : | |||
878 : | (* Decided not a push and pop a scope at the parameterDeclarations, because we | ||
879 : | * are not going to directly plug these names in the tdef table. If this is just | ||
880 : | * a function declaration, the names here do not matter to the tdef table. If | ||
881 : | * this will be part of func definition, we put all these names in tdef table at | ||
882 : | * proper scope correctly, later on. | ||
883 : | * Note: We miss syntax errors like int f(int foo, foo bar);, if foo was a typename | ||
884 : | *) | ||
885 : | parameterDeclaration: | ||
886 : | declarationSpecifiers notypeDeclarator | ||
887 : | ((declarationSpecifiers, notypeDeclarator)) | ||
888 : | | declarationSpecifiers parmDeclarator | ||
889 : | ((declarationSpecifiers, parmDeclarator)) | ||
890 : | |||
891 : | | declarationSpecifiers (* this case can arise for function prototypes *) | ||
892 : | ((declarationSpecifiers, EmptyDecr)) | ||
893 : | |||
894 : | | declarationSpecifiers abstractDeclarator | ||
895 : | ((declarationSpecifiers, abstractDeclarator)) | ||
896 : | |||
897 : | | declarationModifiers notypeDeclarator | ||
898 : | ((declarationModifiers, notypeDeclarator)) | ||
899 : | |||
900 : | | declarationModifiers abstractDeclarator | ||
901 : | ((declarationModifiers, abstractDeclarator)) | ||
902 : | |||
903 : | pushScope: | ||
904 : | (TypeDefs.pushScope()) | ||
905 : | |||
906 : | popScope: | ||
907 : | (TypeDefs.popScope()) | ||
908 : | |||
909 : |
root@smlnj-gforge.cs.uchicago.edu | ViewVC Help |
Powered by ViewVC 1.0.0 |