1 /*-----------------------------------------------------------------------
3 SDCC.y - parser definition file for sdcc :
4 Written By : Sandeep Dutta . sandeep.dutta@usa.net (1997)
6 This program is free software; you can redistribute it and/or modify it
7 under the terms of the GNU General Public License as published by the
8 Free Software Foundation; either version 2, or (at your option) any
11 This program is distributed in the hope that it will be useful,
12 but WITHOUT ANY WARRANTY; without even the implied warranty of
13 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
14 GNU General Public License for more details.
16 You should have received a copy of the GNU General Public License
17 along with this program; if not, write to the Free Software
18 Foundation, 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
20 In other words, you are welcome to use, share and improve this program.
21 You are forbidden to forbid anyone else to use, share and improve
22 what you give them. Help stamp out software-hoarding!
23 -------------------------------------------------------------------------*/
28 #include "SDCCglobl.h"
30 #include "SDCChasht.h"
39 extern int yyerror (char *);
41 int NestLevel = 0 ; /* current NestLevel */
42 int stackPtr = 1 ; /* stack pointer */
43 int xstackPtr = 0 ; /* xstack pointer */
45 int blockNo = 0 ; /* sequential block number */
48 int seqPointNo= 1 ; /* sequence point number */
49 int ignoreTypedefType=0;
53 char lbuff[1024]; /* local buffer */
55 /* break & continue stacks */
56 STACK_DCL(continueStack ,symbol *,MAX_NEST_LEVEL)
57 STACK_DCL(breakStack ,symbol *,MAX_NEST_LEVEL)
58 STACK_DCL(forStack ,symbol *,MAX_NEST_LEVEL)
59 STACK_DCL(swStk ,ast *,MAX_NEST_LEVEL)
60 STACK_DCL(blockNum,int,MAX_NEST_LEVEL*3)
62 value *cenum = NULL ; /* current enumeration type chain*/
63 bool uselessDecl = TRUE;
71 symbol *sym ; /* symbol table pointer */
72 structdef *sdef; /* structure definition */
73 char yychar[SDCC_NAME_MAX+1];
74 sym_link *lnk ; /* declarator or specifier */
75 int yyint; /* integer value returned */
76 value *val ; /* for integer constant */
77 initList *ilist; /* initial list */
78 const char *yyinline; /* inlined assembler code */
79 ast *asts; /* expression tree */
82 %token <yychar> IDENTIFIER TYPE_NAME
83 %token <val> CONSTANT STRING_LITERAL
85 %token PTR_OP INC_OP DEC_OP LEFT_OP RIGHT_OP LE_OP GE_OP EQ_OP NE_OP
87 %token <yyint> MUL_ASSIGN DIV_ASSIGN MOD_ASSIGN ADD_ASSIGN
88 %token <yyint> SUB_ASSIGN LEFT_ASSIGN RIGHT_ASSIGN AND_ASSIGN
89 %token <yyint> XOR_ASSIGN OR_ASSIGN
90 %token TYPEDEF EXTERN STATIC AUTO REGISTER CODE EEPROM INTERRUPT SFR AT SBIT
91 %token REENTRANT USING XDATA DATA IDATA PDATA VAR_ARGS CRITICAL NONBANKED BANKED
92 %token CHAR SHORT INT LONG SIGNED UNSIGNED FLOAT DOUBLE CONST VOLATILE VOID BIT
93 %token STRUCT UNION ENUM ELIPSIS RANGE FAR
94 %token CASE DEFAULT IF ELSE SWITCH WHILE DO FOR GOTO CONTINUE BREAK RETURN
95 %token NAKED JAVANATIVE OVERLAY
96 %token <yyinline> INLINEASM
97 %token IFX ADDRESS_OF GET_VALUE_AT_ADDRESS SPIL UNSPIL GETHBIT
98 %token BITWISEAND UNARYMINUS IPUSH IPOP PCALL ENDFUNCTION JUMPTABLE
100 %token CAST CALL PARAM NULLOP BLOCK LABEL RECEIVE SEND ARRAYINIT
101 %token DUMMY_READ_VOLATILE ENDCRITICAL SWAP
103 %type <yyint> Interrupt_storage
104 %type <sym> identifier declarator declarator2 declarator3 enumerator_list enumerator
105 %type <sym> struct_declarator function_declarator function_declarator2
106 %type <sym> struct_declarator_list struct_declaration struct_declaration_list
107 %type <sym> declaration init_declarator_list init_declarator
108 %type <sym> declaration_list identifier_list parameter_identifier_list
109 %type <sym> declarator2_function_attributes while do for critical
110 %type <lnk> pointer type_specifier_list type_specifier type_name
111 %type <lnk> storage_class_specifier struct_or_union_specifier
112 %type <lnk> declaration_specifiers sfr_reg_bit sfr_attributes type_specifier2
113 %type <lnk> function_attribute function_attributes enum_specifier
114 %type <lnk> abstract_declarator abstract_declarator2 unqualified_pointer
115 %type <val> parameter_type_list parameter_list parameter_declaration opt_assign_expr
116 %type <sdef> stag opt_stag
117 %type <asts> primary_expr
118 %type <asts> postfix_expr unary_expr cast_expr multiplicative_expr
119 %type <asts> additive_expr shift_expr relational_expr equality_expr
120 %type <asts> and_expr exclusive_or_expr inclusive_or_expr logical_or_expr
121 %type <asts> logical_and_expr conditional_expr assignment_expr constant_expr
122 %type <asts> expr argument_expr_list function_definition expr_opt
123 %type <asts> statement_list statement labeled_statement compound_statement
124 %type <asts> expression_statement selection_statement iteration_statement
125 %type <asts> jump_statement function_body else_statement string_literal
126 %type <asts> critical_statement
127 %type <ilist> initializer initializer_list
128 %type <yyint> unary_operator assignment_operator struct_or_union
135 : external_definition
136 | file external_definition
140 : function_definition {
144 ignoreTypedefType = 0;
146 && IS_FUNC($1->type))
148 /* The only legal storage classes for
149 * a function prototype (declaration)
150 * are extern and static. extern is the
151 * default. Thus, if this function isn't
152 * explicitly marked static, mark it
156 && IS_SPEC($1->etype)
157 && !SPEC_STAT($1->etype))
159 SPEC_EXTR($1->etype) = 1;
163 allocVariables ($1) ;
164 cleanUpLevel (SymbolTab,1);
169 : function_declarator function_body { /* function type not specified */
170 /* assume it to be 'int' */
171 addDecl($1,0,newIntLink());
172 $$ = createFunction($1,$2);
174 | declaration_specifiers function_declarator function_body
176 pointerTypes($2->type,copyLinkChain($1));
178 $$ = createFunction($2,$3);
183 : function_attributes
184 | function_attributes function_attribute { $$ = mergeSpec($1,$2,"function_attribute"); }
189 $$ = newLink(SPECIFIER) ;
190 FUNC_REGBANK($$) = (int) floatFromVal($2);
192 | REENTRANT { $$ = newLink (SPECIFIER);
195 | CRITICAL { $$ = newLink (SPECIFIER);
196 FUNC_ISCRITICAL($$) = 1;
198 | NAKED { $$ = newLink (SPECIFIER);
201 | JAVANATIVE { $$ = newLink (SPECIFIER);
202 FUNC_ISJAVANATIVE($$)=1;
204 | OVERLAY { $$ = newLink (SPECIFIER);
205 FUNC_ISOVERLAY($$)=1;
207 | NONBANKED {$$ = newLink (SPECIFIER);
208 FUNC_NONBANKED($$) = 1;
209 if (FUNC_BANKED($$)) {
210 werror(W_BANKED_WITH_NONBANKED);
213 | BANKED {$$ = newLink (SPECIFIER);
215 if (FUNC_NONBANKED($$)) {
216 werror(W_BANKED_WITH_NONBANKED);
219 werror(W_BANKED_WITH_STATIC);
224 $$ = newLink (SPECIFIER) ;
225 FUNC_INTNO($$) = $1 ;
232 | declaration_list compound_statement
234 werror(E_OLD_STYLE,($1 ? $1->name: "")) ;
240 : identifier { $$ = newAst_VALUE(symbolVal($1)); }
241 | CONSTANT { $$ = newAst_VALUE($1); }
243 | '(' expr ')' { $$ = $2 ; }
247 : STRING_LITERAL { $$ = newAst_VALUE($1); }
252 | postfix_expr '[' expr ']' { $$ = newNode ('[', $1, $3) ; }
253 | postfix_expr '(' ')' { $$ = newNode (CALL,$1,NULL);
254 $$->left->funcName = 1;}
255 | postfix_expr '(' argument_expr_list ')'
257 $$ = newNode (CALL,$1,$3) ; $$->left->funcName = 1;
259 | postfix_expr '.' identifier
261 $3 = newSymbol($3->name,NestLevel);
263 $$ = newNode(PTR_OP,newNode('&',$1,NULL),newAst_VALUE(symbolVal($3)));
264 /* $$ = newNode('.',$1,newAst(EX_VALUE,symbolVal($3))) ; */
266 | postfix_expr PTR_OP identifier
268 $3 = newSymbol($3->name,NestLevel);
270 $$ = newNode(PTR_OP,$1,newAst_VALUE(symbolVal($3)));
272 | postfix_expr INC_OP
273 { $$ = newNode(INC_OP,$1,NULL);}
274 | postfix_expr DEC_OP
275 { $$ = newNode(DEC_OP,$1,NULL); }
280 | assignment_expr ',' argument_expr_list { $$ = newNode(PARAM,$1,$3); }
285 | INC_OP unary_expr { $$ = newNode(INC_OP,NULL,$2); }
286 | DEC_OP unary_expr { $$ = newNode(DEC_OP,NULL,$2); }
287 | unary_operator cast_expr { $$ = newNode($1,$2,NULL) ; }
288 | SIZEOF unary_expr { $$ = newNode(SIZEOF,NULL,$2); }
289 | SIZEOF '(' type_name ')' { $$ = newAst_VALUE(sizeofOp($3)); }
290 | TYPEOF unary_expr { $$ = newNode(TYPEOF,NULL,$2); }
304 | '(' type_name ')' cast_expr { $$ = newNode(CAST,newAst_LINK($2),$4); }
309 | multiplicative_expr '*' cast_expr { $$ = newNode('*',$1,$3);}
310 | multiplicative_expr '/' cast_expr { $$ = newNode('/',$1,$3);}
311 | multiplicative_expr '%' cast_expr { $$ = newNode('%',$1,$3);}
315 : multiplicative_expr
316 | additive_expr '+' multiplicative_expr { $$=newNode('+',$1,$3);}
317 | additive_expr '-' multiplicative_expr { $$=newNode('-',$1,$3);}
322 | shift_expr LEFT_OP additive_expr { $$ = newNode(LEFT_OP,$1,$3); }
323 | shift_expr RIGHT_OP additive_expr { $$ = newNode(RIGHT_OP,$1,$3); }
328 | relational_expr '<' shift_expr {
330 newNode('!',newNode(GE_OP,$1,$3),NULL) :
331 newNode('<', $1,$3));
333 | relational_expr '>' shift_expr {
335 newNode('!',newNode(LE_OP,$1,$3),NULL) :
338 | relational_expr LE_OP shift_expr {
340 newNode('!', newNode('>', $1 , $3 ), NULL) :
341 newNode(LE_OP,$1,$3));
343 | relational_expr GE_OP shift_expr {
345 newNode('!', newNode('<', $1 , $3 ), NULL) :
346 newNode(GE_OP,$1,$3));
352 | equality_expr EQ_OP relational_expr {
354 newNode('!',newNode(NE_OP,$1,$3),NULL) :
355 newNode(EQ_OP,$1,$3));
357 | equality_expr NE_OP relational_expr {
359 newNode('!', newNode(EQ_OP,$1,$3), NULL) :
360 newNode(NE_OP,$1,$3));
366 | and_expr '&' equality_expr { $$ = newNode('&',$1,$3);}
371 | exclusive_or_expr '^' and_expr { $$ = newNode('^',$1,$3);}
376 | inclusive_or_expr '|' exclusive_or_expr { $$ = newNode('|',$1,$3);}
381 | logical_and_expr AND_OP { seqPointNo++;} inclusive_or_expr
382 { $$ = newNode(AND_OP,$1,$4);}
387 | logical_or_expr OR_OP { seqPointNo++;} logical_and_expr
388 { $$ = newNode(OR_OP,$1,$4); }
393 | logical_or_expr '?' { seqPointNo++;} logical_or_expr ':' conditional_expr
395 $$ = newNode(':',$4,$6) ;
396 $$ = newNode('?',$1,$$) ;
402 | unary_expr assignment_operator assignment_expr
407 $$ = newNode($2,$1,$3);
410 $$ = newNode('=',removePostIncDecOps(copyAst($1)),
411 newNode('*',removePreIncDecOps(copyAst($1)),$3));
414 $$ = newNode('=',removePostIncDecOps(copyAst($1)),
415 newNode('/',removePreIncDecOps(copyAst($1)),$3));
418 $$ = newNode('=',removePostIncDecOps(copyAst($1)),
419 newNode('%',removePreIncDecOps(copyAst($1)),$3));
422 $$ = newNode('=',removePostIncDecOps(copyAst($1)),
423 newNode('+',removePreIncDecOps(copyAst($1)),$3));
426 $$ = newNode('=',removePostIncDecOps(copyAst($1)),
427 newNode('-',removePreIncDecOps(copyAst($1)),$3));
430 $$ = newNode('=',removePostIncDecOps(copyAst($1)),
431 newNode(LEFT_OP,removePreIncDecOps(copyAst($1)),$3));
434 $$ = newNode('=',removePostIncDecOps(copyAst($1)),
435 newNode(RIGHT_OP,removePreIncDecOps(copyAst($1)),$3));
438 $$ = newNode('=',removePostIncDecOps(copyAst($1)),
439 newNode('&',removePreIncDecOps(copyAst($1)),$3));
442 $$ = newNode('=',removePostIncDecOps(copyAst($1)),
443 newNode('^',removePreIncDecOps(copyAst($1)),$3));
446 /* $$ = newNode('=',$1,newNode('|',removeIncDecOps(copyAst($1)),$3)); */
447 $$ = newNode('=',removePostIncDecOps(copyAst($1)),
448 newNode('|',removePreIncDecOps(copyAst($1)),$3));
473 | expr ',' { seqPointNo++;} assignment_expr { $$ = newNode(',',$1,$4);}
481 : declaration_specifiers ';'
484 werror(W_USELESS_DECL);
488 | declaration_specifiers init_declarator_list ';'
490 /* add the specifier list to the id */
493 for (sym1 = sym = reverseSyms($2);sym != NULL;sym = sym->next) {
494 sym_link *lnk = copyLinkChain($1);
495 /* do the pointer stuff */
496 pointerTypes(sym->type,lnk);
497 addDecl (sym,0,lnk) ;
505 declaration_specifiers
506 : storage_class_specifier { $$ = $1; }
507 | storage_class_specifier declaration_specifiers {
508 /* if the decl $2 is not a specifier */
509 /* find the spec and replace it */
512 while (lnk && !IS_SPEC(lnk->next))
514 lnk->next = mergeSpec($1,lnk->next, "storage_class_specifier declaration_specifiers - skipped");
518 $$ = mergeSpec($1,$2, "storage_class_specifier declaration_specifiers");
520 | type_specifier { $$ = $1; }
521 | type_specifier declaration_specifiers {
522 /* if the decl $2 is not a specifier */
523 /* find the spec and replace it */
526 while (lnk && !IS_SPEC(lnk->next))
528 lnk->next = mergeSpec($1,lnk->next, "type_specifier declaration_specifiers - skipped");
532 $$ = mergeSpec($1,$2, "type_specifier declaration_specifiers");
538 | init_declarator_list ',' init_declarator { $3->next = $1 ; $$ = $3;}
542 : declarator { $1->ival = NULL ; }
543 | declarator '=' initializer { $1->ival = $3 ; }
547 storage_class_specifier
549 $$ = newLink (SPECIFIER) ;
550 SPEC_TYPEDEF($$) = 1 ;
553 $$ = newLink(SPECIFIER);
557 $$ = newLink (SPECIFIER);
561 $$ = newLink (SPECIFIER) ;
562 SPEC_SCLS($$) = S_AUTO ;
565 $$ = newLink (SPECIFIER);
566 SPEC_SCLS($$) = S_REGISTER ;
571 : INTERRUPT { $$ = INTNO_UNSPEC ; }
573 { int intno = (int) floatFromVal($2);
574 if ((intno >= 0) && (intno <= INTNO_MAX))
578 werror(E_INT_BAD_INTNO, intno);
586 | type_specifier2 AT constant_expr
588 /* add this to the storage class specifier */
589 SPEC_ABSA($1) = 1; /* set the absolute addr flag */
590 /* now get the abs addr from value */
591 SPEC_ADDR($1) = (int) floatFromVal(constExprValue($3,TRUE)) ;
597 $$=newLink(SPECIFIER);
598 SPEC_NOUN($$) = V_CHAR ;
599 ignoreTypedefType = 1;
602 $$=newLink(SPECIFIER);
603 $$->select.s._short = 1 ;
604 ignoreTypedefType = 1;
607 $$=newLink(SPECIFIER);
608 SPEC_NOUN($$) = V_INT ;
609 ignoreTypedefType = 1;
612 $$=newLink(SPECIFIER);
614 ignoreTypedefType = 1;
617 $$=newLink(SPECIFIER);
618 $$->select.s._signed = 1;
619 ignoreTypedefType = 1;
622 $$=newLink(SPECIFIER);
624 ignoreTypedefType = 1;
627 $$=newLink(SPECIFIER);
628 SPEC_NOUN($$) = V_VOID ;
629 ignoreTypedefType = 1;
632 $$=newLink(SPECIFIER);
636 $$=newLink(SPECIFIER);
637 SPEC_VOLATILE($$) = 1 ;
640 $$=newLink(SPECIFIER);
641 SPEC_NOUN($$) = V_FLOAT;
642 ignoreTypedefType = 1;
645 $$ = newLink (SPECIFIER);
646 SPEC_SCLS($$) = S_XDATA ;
649 $$ = newLink (SPECIFIER) ;
650 SPEC_SCLS($$) = S_CODE ;
653 $$ = newLink (SPECIFIER) ;
654 SPEC_SCLS($$) = S_EEPROM ;
657 $$ = newLink (SPECIFIER);
658 SPEC_SCLS($$) = S_DATA ;
661 $$ = newLink (SPECIFIER);
662 SPEC_SCLS($$) = S_IDATA ;
665 $$ = newLink (SPECIFIER);
666 SPEC_SCLS($$) = S_PDATA ;
669 $$=newLink(SPECIFIER);
670 SPEC_NOUN($$) = V_BIT ;
671 SPEC_SCLS($$) = S_BIT ;
674 ignoreTypedefType = 1;
677 | struct_or_union_specifier {
680 ignoreTypedefType = 1;
685 ignoreTypedefType = 1;
692 sym = findSym(TypedefTab,NULL,$1) ;
693 $$ = p = copyLinkChain(sym->type);
694 SPEC_TYPEDEF(getSpec(p)) = 0;
695 ignoreTypedefType = 1;
702 $$ = newLink(SPECIFIER) ;
703 SPEC_NOUN($$) = V_SBIT;
704 SPEC_SCLS($$) = S_SBIT;
707 ignoreTypedefType = 1;
714 $$ = newLink(SPECIFIER) ;
715 FUNC_REGBANK($$) = 0;
716 SPEC_NOUN($$) = V_CHAR;
717 SPEC_SCLS($$) = S_SFR ;
719 ignoreTypedefType = 1;
722 $$ = newLink(SPECIFIER) ;
723 FUNC_REGBANK($$) = 1;
724 SPEC_NOUN($$) = V_CHAR;
725 SPEC_SCLS($$) = S_SFR ;
727 ignoreTypedefType = 1;
731 struct_or_union_specifier
732 : struct_or_union opt_stag
741 werror(E_BAD_TAG, $2->tag, $1==STRUCT ? "struct" : "union");
745 '{' struct_declaration_list '}'
750 // check for errors in structure members
751 for (sym=$5; sym; sym=sym->next) {
752 if (IS_ABSOLUTE(sym->etype)) {
753 werrorfl(sym->fileDef, sym->lineDef, E_NOT_ALLOWED, "'at'");
754 SPEC_ABSA(sym->etype) = 0;
756 if (IS_SPEC(sym->etype) && SPEC_SCLS(sym->etype)) {
757 werrorfl(sym->fileDef, sym->lineDef, E_NOT_ALLOWED, "storage class");
758 printTypeChainRaw (sym->type,NULL);
759 SPEC_SCLS(sym->etype) = 0;
761 for (dsym=sym->next; dsym; dsym=dsym->next) {
762 if (*dsym->name && strcmp(sym->name, dsym->name)==0) {
763 werrorfl(sym->fileDef, sym->lineDef, E_DUPLICATE_MEMBER,
764 $1==STRUCT ? "struct" : "union", sym->name);
765 werrorfl(dsym->fileDef, dsym->lineDef, E_PREVIOUS_DEF);
770 /* Create a structdef */
772 sdef->fields = reverseSyms($5) ; /* link the fields */
773 sdef->size = compStructSize($1,sdef); /* update size of */
774 promoteAnonStructs ($1, sdef);
776 /* Create the specifier */
777 $$ = newLink (SPECIFIER) ;
778 SPEC_NOUN($$) = V_STRUCT;
779 SPEC_STRUCT($$)= sdef ;
781 | struct_or_union stag
783 $$ = newLink(SPECIFIER) ;
784 SPEC_NOUN($$) = V_STRUCT;
785 SPEC_STRUCT($$) = $2;
794 werror(E_BAD_TAG, $2->tag, $1==STRUCT ? "struct" : "union");
800 : STRUCT { $$ = STRUCT ; }
801 | UNION { $$ = UNION ; }
806 | { /* synthesize a name add to structtable */
807 $$ = newStruct(genSymName(NestLevel)) ;
808 $$->level = NestLevel ;
809 addSym (StructTab, $$, $$->tag,$$->level,currBlockno, 0);
813 : identifier { /* add name to structure table */
814 $$ = findSymWithBlock (StructTab,$1,currBlockno);
816 $$ = newStruct($1->name) ;
817 $$->level = NestLevel ;
818 addSym (StructTab, $$, $$->tag,$$->level,currBlockno,0);
823 struct_declaration_list
825 | struct_declaration_list struct_declaration
829 /* go to the end of the chain */
830 while (sym->next) sym=sym->next;
838 : type_specifier_list struct_declarator_list ';'
840 /* add this type to all the symbols */
842 for ( sym = $2 ; sym != NULL ; sym = sym->next ) {
843 sym_link *btype = copyLinkChain($1);
845 /* make the symbol one level up */
848 pointerTypes(sym->type,btype);
851 sym->etype = getSpec(sym->type);
854 addDecl (sym,0,btype);
855 /* make sure the type is complete and sane */
856 checkTypeSanity(sym->etype, sym->name);
858 ignoreTypedefType = 0;
863 struct_declarator_list
865 | struct_declarator_list ',' struct_declarator
874 | ':' constant_expr {
876 $$ = newSymbol (genSymName(NestLevel),NestLevel) ;
877 bitsize= (int) floatFromVal(constExprValue($2,TRUE));
878 if (bitsize > (port->s.int_size * 8)) {
879 bitsize = port->s.int_size * 8;
880 werror(E_BITFLD_SIZE, bitsize);
883 bitsize = BITVAR_PAD;
884 $$->bitVar = bitsize;
886 | declarator ':' constant_expr
889 bitsize= (int) floatFromVal(constExprValue($3,TRUE));
890 if (bitsize > (port->s.int_size * 8)) {
891 bitsize = port->s.int_size * 8;
892 werror(E_BITFLD_SIZE, bitsize);
895 $$ = newSymbol (genSymName(NestLevel),NestLevel) ;
896 $$->bitVar = BITVAR_PAD;
897 werror(W_BITFLD_NAMED);
900 $1->bitVar = bitsize;
902 | { $$ = newSymbol ("", NestLevel) ; }
907 : ENUM '{' enumerator_list '}' {
908 $$ = newEnumType ($3); //copyLinkChain(cenum->type);
909 SPEC_SCLS(getSpec($$)) = 0;
912 | ENUM identifier '{' enumerator_list '}' {
916 csym=findSym(enumTab,$2,$2->name);
917 if ((csym && csym->level == $2->level))
919 werrorfl($2->fileDef, $2->lineDef, E_DUPLICATE_TYPEDEF,csym->name);
920 werrorfl(csym->fileDef, csym->lineDef, E_PREVIOUS_DEF);
923 enumtype = newEnumType ($4); //copyLinkChain(cenum->type);
924 SPEC_SCLS(getSpec(enumtype)) = 0;
927 /* add this to the enumerator table */
929 addSym ( enumTab,$2,$2->name,$2->level,$2->block, 0);
930 $$ = copyLinkChain(enumtype);
935 /* check the enumerator table */
936 if ((csym = findSym(enumTab,$2,$2->name)))
937 $$ = copyLinkChain(csym->type);
939 $$ = newLink(SPECIFIER) ;
940 SPEC_NOUN($$) = V_INT ;
947 | enumerator_list ',' {
949 | enumerator_list ',' enumerator
953 for (dsym=$1; dsym; dsym=dsym->next)
955 if (strcmp($3->name, dsym->name)==0)
957 werrorfl($3->fileDef, $3->lineDef, E_DUPLICATE_MEMBER, "enum", $3->name);
958 werrorfl(dsym->fileDef, dsym->lineDef, E_PREVIOUS_DEF);
968 : identifier opt_assign_expr
970 /* make the symbol one level up */
972 $1->type = copyLinkChain($2->type);
973 $1->etype= getSpec($1->type);
974 SPEC_ENUM($1->etype) = 1;
976 // do this now, so we can use it for the next enums in the list
982 : '=' constant_expr {
985 val = constExprValue($2,TRUE);
986 if (!IS_INT(val->type) && !IS_CHAR(val->type))
988 werror(E_ENUM_NON_INTEGER);
989 SNPRINTF(lbuff, sizeof(lbuff),
990 "%d",(int) floatFromVal(val));
991 val = constVal(lbuff);
997 SNPRINTF(lbuff, sizeof(lbuff),
998 "%d",(int) floatFromVal(cenum)+1);
999 $$ = cenum = constVal(lbuff);
1002 SNPRINTF(lbuff, sizeof(lbuff),
1004 $$ = cenum = constVal(lbuff);
1010 : declarator3 { $$ = $1 ; }
1011 | pointer declarator3
1013 addDecl ($2,0,reverseLink($1));
1019 : declarator2_function_attributes { $$ = $1 ; }
1020 | declarator2 { $$ = $1 ; }
1024 : declarator2_function_attributes { $$ = $1; }
1025 | pointer declarator2_function_attributes
1027 addDecl ($2,0,reverseLink($1));
1032 declarator2_function_attributes
1033 : function_declarator2 { $$ = $1 ; }
1034 | function_declarator2 function_attribute {
1035 // copy the functionAttributes (not the args and hasVargs !!)
1038 sym_link *funcType=$1->type;
1040 while (funcType && !IS_FUNC(funcType))
1041 funcType = funcType->next;
1044 werror (E_FUNC_ATTR);
1047 args=FUNC_ARGS(funcType);
1048 hasVargs=FUNC_HASVARARGS(funcType);
1050 memcpy (&funcType->funcAttrs, &$2->funcAttrs,
1051 sizeof($2->funcAttrs));
1053 FUNC_ARGS(funcType)=args;
1054 FUNC_HASVARARGS(funcType)=hasVargs;
1057 memset (&$2->funcAttrs, 0,
1058 sizeof($2->funcAttrs));
1067 | '(' declarator ')' { $$ = $2; }
1068 | declarator3 '[' ']'
1072 p = newLink (DECLARATOR);
1073 DCL_TYPE(p) = ARRAY ;
1077 | declarator3 '[' constant_expr ']'
1082 tval = constExprValue($3,TRUE);
1083 /* if it is not a constant then Error */
1084 p = newLink (DECLARATOR);
1085 DCL_TYPE(p) = ARRAY ;
1086 if ( !tval || (SPEC_SCLS(tval->etype) != S_LITERAL)) {
1087 werror(E_CONST_EXPECTED) ;
1088 /* Assume a single item array to limit the cascade */
1089 /* of additional errors. */
1093 DCL_ELEM(p) = (int) floatFromVal(tval) ;
1099 function_declarator2
1100 : declarator2 '(' ')' { addDecl ($1,FUNCTION,NULL) ; }
1101 | declarator2 '(' { NestLevel++ ; currBlockno++; }
1102 parameter_type_list ')'
1106 addDecl ($1,FUNCTION,NULL) ;
1108 funcType = $1->type;
1109 while (funcType && !IS_FUNC(funcType))
1110 funcType = funcType->next;
1114 FUNC_HASVARARGS(funcType) = IS_VARG($4);
1115 FUNC_ARGS(funcType) = reverseVal($4);
1117 /* nest level was incremented to take care of the parms */
1121 // if this was a pointer (to a function)
1122 if (!IS_FUNC($1->type))
1123 cleanUpLevel(SymbolTab,NestLevel+1);
1127 | declarator2 '(' parameter_identifier_list ')'
1129 werror(E_OLD_STYLE,$1->name) ;
1130 /* assume it returns an int */
1131 $1->type = $1->etype = newIntLink();
1137 : unqualified_pointer { $$ = $1 ;}
1138 | unqualified_pointer type_specifier_list
1143 DCL_PTR_CONST($1) = SPEC_CONST($2);
1144 DCL_PTR_VOLATILE($1) = SPEC_VOLATILE($2);
1147 werror (W_PTR_TYPE_INVALID);
1149 | unqualified_pointer pointer
1153 DCL_TYPE($2)=port->unqualified_pointer;
1155 | unqualified_pointer type_specifier_list pointer
1158 if (IS_SPEC($2) && DCL_TYPE($3) == UPOINTER) {
1159 DCL_PTR_CONST($1) = SPEC_CONST($2);
1160 DCL_PTR_VOLATILE($1) = SPEC_VOLATILE($2);
1161 switch (SPEC_SCLS($2)) {
1163 DCL_TYPE($3) = FPOINTER;
1166 DCL_TYPE($3) = IPOINTER ;
1169 DCL_TYPE($3) = PPOINTER ;
1172 DCL_TYPE($3) = POINTER ;
1175 DCL_TYPE($3) = CPOINTER ;
1178 DCL_TYPE($3) = EEPPOINTER;
1181 // this could be just "constant"
1182 // werror(W_PTR_TYPE_INVALID);
1187 werror (W_PTR_TYPE_INVALID);
1195 $$ = newLink(DECLARATOR);
1196 DCL_TYPE($$)=UPOINTER;
1202 //| type_specifier_list type_specifier { $$ = mergeSpec ($1,$2, "type_specifier_list"); }
1203 | type_specifier_list type_specifier {
1204 /* if the decl $2 is not a specifier */
1205 /* find the spec and replace it */
1206 if ( !IS_SPEC($2)) {
1207 sym_link *lnk = $2 ;
1208 while (lnk && !IS_SPEC(lnk->next))
1210 lnk->next = mergeSpec($1,lnk->next, "type_specifier_list type_specifier skipped");
1214 $$ = mergeSpec($1,$2, "type_specifier_list type_specifier");
1218 parameter_identifier_list
1220 | identifier_list ',' ELIPSIS
1225 | identifier_list ',' identifier
1234 | parameter_list ',' VAR_ARGS { $1->vArgs = 1;}
1238 : parameter_declaration
1239 | parameter_list ',' parameter_declaration
1246 parameter_declaration
1247 : type_specifier_list declarator
1250 pointerTypes($2->type,$1);
1252 for (loop=$2;loop;loop->_isparm=1,loop=loop->next);
1255 ignoreTypedefType = 0;
1260 $$->etype = getSpec($$->type);
1261 ignoreTypedefType = 0;
1266 : type_specifier_list { $$ = $1; ignoreTypedefType = 0;}
1267 | type_specifier_list abstract_declarator
1269 /* go to the end of the list */
1271 pointerTypes($2,$1);
1272 for ( p = $2 ; p && p->next ; p=p->next);
1274 werror(E_SYNTAX_ERROR, yytext);
1279 ignoreTypedefType = 0;
1284 : pointer { $$ = reverseLink($1); }
1285 | abstract_declarator2
1286 | pointer abstract_declarator2 { $1 = reverseLink($1); $1->next = $2 ; $$ = $1;
1287 if (IS_PTR($1) && IS_FUNC($2))
1288 DCL_TYPE($1) = CPOINTER;
1292 abstract_declarator2
1293 : '(' abstract_declarator ')' { $$ = $2 ; }
1295 $$ = newLink (DECLARATOR);
1296 DCL_TYPE($$) = ARRAY ;
1299 | '[' constant_expr ']' {
1301 $$ = newLink (DECLARATOR);
1302 DCL_TYPE($$) = ARRAY ;
1303 DCL_ELEM($$) = (int) floatFromVal(val = constExprValue($2,TRUE));
1305 | abstract_declarator2 '[' ']' {
1306 $$ = newLink (DECLARATOR);
1307 DCL_TYPE($$) = ARRAY ;
1311 | abstract_declarator2 '[' constant_expr ']'
1314 $$ = newLink (DECLARATOR);
1315 DCL_TYPE($$) = ARRAY ;
1316 DCL_ELEM($$) = (int) floatFromVal(val = constExprValue($3,TRUE));
1319 | '(' ')' { $$ = NULL;}
1320 | '(' parameter_type_list ')' { $$ = NULL;}
1321 | abstract_declarator2 '(' ')' {
1322 // $1 must be a pointer to a function
1323 sym_link *p=newLink(DECLARATOR);
1324 DCL_TYPE(p) = FUNCTION;
1326 // ((void (code *) ()) 0) ()
1327 $1=newLink(DECLARATOR);
1328 DCL_TYPE($1)=CPOINTER;
1333 | abstract_declarator2 '(' { NestLevel++ ; currBlockno++; } parameter_type_list ')' {
1334 sym_link *p=newLink(DECLARATOR);
1335 DCL_TYPE(p) = FUNCTION;
1337 FUNC_HASVARARGS(p) = IS_VARG($4);
1338 FUNC_ARGS(p) = reverseVal($4);
1340 /* nest level was incremented to take care of the parms */
1346 // remove the symbol args (if any)
1347 cleanUpLevel(SymbolTab,NestLevel+1);
1352 : assignment_expr { $$ = newiList(INIT_NODE,$1); }
1353 | '{' initializer_list '}' { $$ = newiList(INIT_DEEP,revinit($2)); }
1354 | '{' initializer_list ',' '}' { $$ = newiList(INIT_DEEP,revinit($2)); }
1359 | initializer_list ',' initializer { $3->next = $1; $$ = $3; }
1364 | compound_statement
1365 | expression_statement
1366 | selection_statement
1367 | iteration_statement
1369 | critical_statement
1373 ex = newNode(INLINEASM,NULL,NULL);
1374 ex->values.inlineasm = strdup($1);
1383 STACK_PUSH(continueStack,NULL);
1384 STACK_PUSH(breakStack,NULL);
1390 : critical statement {
1391 STACK_POP(breakStack);
1392 STACK_POP(continueStack);
1394 $$ = newNode(CRITICAL,$2,NULL);
1399 // : identifier ':' statement { $$ = createLabel($1,$3); }
1400 : identifier ':' { $$ = createLabel($1,NULL); }
1401 | CASE constant_expr ':' statement
1403 if (STACK_EMPTY(swStk))
1404 $$ = createCase(NULL,$2,$4);
1406 $$ = createCase(STACK_PEEK(swStk),$2,$4);
1408 | DEFAULT { $<asts>$ = newNode(DEFAULT,NULL,NULL); } ':' statement
1410 if (STACK_EMPTY(swStk))
1411 $$ = createDefault(NULL,$<asts>2,$4);
1413 $$ = createDefault(STACK_PEEK(swStk),$<asts>2,$4);
1419 STACK_PUSH(blockNum,currBlockno);
1420 currBlockno = ++blockNo ;
1421 ignoreTypedefType = 0;
1425 end_block : '}' { currBlockno = STACK_POP(blockNum); }
1429 : start_block end_block { $$ = createBlock(NULL,NULL); }
1430 | start_block statement_list end_block { $$ = createBlock(NULL,$2) ; }
1432 declaration_list { addSymChain($2); }
1433 end_block { $$ = createBlock($2,NULL) ; }
1435 declaration_list { addSymChain ($2); }
1437 end_block {$$ = createBlock($2,$4) ; }
1438 | error ';' { $$ = NULL ; }
1444 /* if this is typedef declare it immediately */
1445 if ( $1 && IS_TYPEDEF($1->etype)) {
1446 allocVariables ($1);
1451 ignoreTypedefType = 0;
1454 | declaration_list declaration
1458 /* if this is a typedef */
1459 if ($2 && IS_TYPEDEF($2->etype)) {
1460 allocVariables ($2);
1464 /* get to the end of the previous decl */
1474 ignoreTypedefType = 0;
1480 | statement_list statement { $$ = newNode(NULLOP,$1,$2) ;}
1483 expression_statement
1485 | expr ';' { $$ = $1; seqPointNo++;}
1489 : ELSE statement { $$ = $2 ; }
1495 : IF '(' expr ')' { seqPointNo++;} statement else_statement
1498 $$ = createIf ($3, $6, $7 );
1501 | SWITCH '(' expr ')' {
1503 static int swLabel = 0 ;
1506 /* create a node for expression */
1507 ex = newNode(SWITCH,$3,NULL);
1508 STACK_PUSH(swStk,ex); /* save it in the stack */
1509 ex->values.switchVals.swNum = swLabel ;
1511 /* now create the label */
1512 SNPRINTF(lbuff, sizeof(lbuff),
1513 "_swBrk_%d",swLabel++);
1514 $<sym>$ = newSymbol(lbuff,NestLevel);
1515 /* put label in the break stack */
1516 STACK_PUSH(breakStack,$<sym>$);
1519 /* get back the switch form the stack */
1520 $$ = STACK_POP(swStk) ;
1521 $$->right = newNode (NULLOP,$6,createLabel($<sym>5,NULL));
1522 STACK_POP(breakStack);
1526 while : WHILE { /* create and push the continue , break & body labels */
1527 static int Lblnum = 0 ;
1529 SNPRINTF (lbuff, sizeof(lbuff), "_whilecontinue_%d",Lblnum);
1530 STACK_PUSH(continueStack,newSymbol(lbuff,NestLevel));
1532 SNPRINTF (lbuff, sizeof(lbuff), "_whilebreak_%d",Lblnum);
1533 STACK_PUSH(breakStack,newSymbol(lbuff,NestLevel));
1535 SNPRINTF (lbuff, sizeof(lbuff), "_whilebody_%d",Lblnum++);
1536 $$ = newSymbol(lbuff,NestLevel);
1540 do : DO { /* create and push the continue , break & body Labels */
1541 static int Lblnum = 0 ;
1544 SNPRINTF(lbuff, sizeof(lbuff), "_docontinue_%d",Lblnum);
1545 STACK_PUSH(continueStack,newSymbol(lbuff,NestLevel));
1547 SNPRINTF(lbuff, sizeof(lbuff), "_dobreak_%d",Lblnum);
1548 STACK_PUSH(breakStack,newSymbol(lbuff,NestLevel));
1550 SNPRINTF(lbuff, sizeof(lbuff), "_dobody_%d",Lblnum++);
1551 $$ = newSymbol (lbuff,NestLevel);
1555 for : FOR { /* create & push continue, break & body labels */
1556 static int Lblnum = 0 ;
1559 SNPRINTF(lbuff, sizeof(lbuff), "_forcontinue_%d",Lblnum);
1560 STACK_PUSH(continueStack,newSymbol(lbuff,NestLevel));
1562 SNPRINTF(lbuff, sizeof(lbuff), "_forbreak_%d",Lblnum);
1563 STACK_PUSH(breakStack,newSymbol(lbuff,NestLevel));
1565 SNPRINTF(lbuff, sizeof(lbuff), "_forbody_%d",Lblnum);
1566 $$ = newSymbol(lbuff,NestLevel);
1568 SNPRINTF(lbuff, sizeof(lbuff), "_forcond_%d",Lblnum++);
1569 STACK_PUSH(forStack,newSymbol(lbuff,NestLevel));
1574 : while '(' expr ')' { seqPointNo++;} statement
1577 $$ = createWhile ( $1, STACK_POP(continueStack),
1578 STACK_POP(breakStack), $3, $6 );
1579 $$->lineno = $1->lineDef ;
1582 | do statement WHILE '(' expr ')' ';'
1586 $$ = createDo ( $1 , STACK_POP(continueStack),
1587 STACK_POP(breakStack), $5, $2);
1588 $$->lineno = $1->lineDef ;
1591 | for '(' expr_opt ';' expr_opt ';' expr_opt ')' statement
1595 /* if break or continue statement present
1596 then create a general case loop */
1597 if (STACK_PEEK(continueStack)->isref ||
1598 STACK_PEEK(breakStack)->isref) {
1599 $$ = createFor ($1, STACK_POP(continueStack),
1600 STACK_POP(breakStack) ,
1601 STACK_POP(forStack) ,
1604 $$ = newNode(FOR,$9,NULL);
1605 AST_FOR($$,trueLabel) = $1;
1606 AST_FOR($$,continueLabel) = STACK_POP(continueStack);
1607 AST_FOR($$,falseLabel) = STACK_POP(breakStack);
1608 AST_FOR($$,condLabel) = STACK_POP(forStack) ;
1609 AST_FOR($$,initExpr) = $3;
1610 AST_FOR($$,condExpr) = $5;
1611 AST_FOR($$,loopExpr) = $7;
1619 : { $$ = NULL ; seqPointNo++; }
1620 | expr { $$ = $1 ; seqPointNo++; }
1624 : GOTO identifier ';' {
1626 $$ = newAst_VALUE(symbolVal($2));
1627 $$ = newNode(GOTO,$$,NULL);
1630 /* make sure continue is in context */
1631 if (STACK_EMPTY(continueStack) || STACK_PEEK(continueStack) == NULL) {
1632 werror(E_BREAK_CONTEXT);
1636 $$ = newAst_VALUE(symbolVal(STACK_PEEK(continueStack)));
1637 $$ = newNode(GOTO,$$,NULL);
1638 /* mark the continue label as referenced */
1639 STACK_PEEK(continueStack)->isref = 1;
1643 if (STACK_EMPTY(breakStack) || STACK_PEEK(breakStack) == NULL) {
1644 werror(E_BREAK_CONTEXT);
1647 $$ = newAst_VALUE(symbolVal(STACK_PEEK(breakStack)));
1648 $$ = newNode(GOTO,$$,NULL);
1649 STACK_PEEK(breakStack)->isref = 1;
1655 werror(E_INVALID_CRITICAL);
1658 $$ = newNode(RETURN,NULL,NULL);
1664 werror(E_INVALID_CRITICAL);
1667 $$ = newNode(RETURN,NULL,$2);
1673 : IDENTIFIER { $$ = newSymbol ($1,NestLevel) ; }