3e084fcdabb4fa38fc326e721c33bab532d8faf9
[fw/sdcc] / src / SDCC.y
1 /*-----------------------------------------------------------------------
2
3   SDCC.y - parser definition file for sdcc :
4           Written By : Sandeep Dutta . sandeep.dutta@usa.net (1997)
5
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
9    later version.
10    
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.
15    
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.
19    
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 -------------------------------------------------------------------------*/
24 %{
25 #include <stdio.h>
26 #include <stdarg.h> 
27 #include <string.h>
28 #include "SDCCglobl.h"
29 #include "SDCCsymt.h"
30 #include "SDCChasht.h"
31 #include "SDCCval.h"
32 #include "SDCCmem.h"
33 #include "SDCCast.h"
34 #include "port.h"
35 #include "newalloc.h"
36 #include "SDCCerr.h"
37 #include "SDCCutil.h"
38
39 extern int yyerror (char *);
40 extern FILE     *yyin;
41 int NestLevel = 0 ;     /* current NestLevel       */
42 int stackPtr  = 1 ;     /* stack pointer           */
43 int xstackPtr = 0 ;     /* xstack pointer          */
44 int reentrant = 0 ; 
45 int blockNo   = 0 ;     /* sequential block number  */
46 int currBlockno=0 ;
47 int inCritical= 0 ;
48 int seqPointNo= 1 ;     /* sequence point number */
49 int ignoreTypedefType=0;
50 extern int yylex();
51 int yyparse(void);
52 extern int noLineno ;
53 char lbuff[1024];      /* local buffer */
54
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)
61
62 value *cenum = NULL  ;  /* current enumeration  type chain*/
63 bool uselessDecl = TRUE;
64
65 #define YYDEBUG 1
66
67 %}
68 %expect 6
69
70 %union {
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            */
80 }
81
82 %token <yychar> IDENTIFIER TYPE_NAME
83 %token <val>   CONSTANT   STRING_LITERAL
84 %token SIZEOF TYPEOF 
85 %token PTR_OP INC_OP DEC_OP LEFT_OP RIGHT_OP LE_OP GE_OP EQ_OP NE_OP
86 %token AND_OP OR_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 SFR16 SFR32
91 %token AT SBIT REENTRANT USING  XDATA DATA IDATA PDATA VAR_ARGS CRITICAL
92 %token NONBANKED BANKED SHADOWREGS WPARAM
93 %token CHAR SHORT INT LONG SIGNED UNSIGNED FLOAT DOUBLE CONST VOLATILE VOID BIT
94 %token STRUCT UNION ENUM ELIPSIS RANGE FAR
95 %token CASE DEFAULT IF ELSE SWITCH WHILE DO FOR GOTO CONTINUE BREAK RETURN
96 %token NAKED JAVANATIVE OVERLAY
97 %token <yyinline> INLINEASM
98 %token IFX ADDRESS_OF GET_VALUE_AT_ADDRESS SPIL UNSPIL GETHBIT
99 %token BITWISEAND UNARYMINUS IPUSH IPOP PCALL  ENDFUNCTION JUMPTABLE
100 %token RRC RLC 
101 %token CAST CALL PARAM NULLOP BLOCK LABEL RECEIVE SEND ARRAYINIT
102 %token DUMMY_READ_VOLATILE ENDCRITICAL SWAP INLINE RESTRICT
103
104 %type <yyint>  Interrupt_storage
105 %type <sym> identifier  declarator  declarator2 declarator3 enumerator_list enumerator
106 %type <sym> struct_declarator function_declarator function_declarator2
107 %type <sym> struct_declarator_list  struct_declaration   struct_declaration_list
108 %type <sym> declaration init_declarator_list init_declarator
109 %type <sym> declaration_list identifier_list parameter_identifier_list
110 %type <sym> declarator2_function_attributes while do for critical
111 %type <lnk> pointer type_specifier_list type_specifier type_name
112 %type <lnk> storage_class_specifier struct_or_union_specifier
113 %type <lnk> declaration_specifiers sfr_reg_bit sfr_attributes type_specifier2
114 %type <lnk> function_attribute function_attributes enum_specifier
115 %type <lnk> abstract_declarator abstract_declarator2 unqualified_pointer
116 %type <val> parameter_type_list parameter_list parameter_declaration opt_assign_expr
117 %type <sdef> stag opt_stag
118 %type <asts> primary_expr
119 %type <asts> postfix_expr unary_expr cast_expr multiplicative_expr
120 %type <asts> additive_expr shift_expr relational_expr equality_expr
121 %type <asts> and_expr exclusive_or_expr inclusive_or_expr logical_or_expr
122 %type <asts> logical_and_expr conditional_expr assignment_expr constant_expr
123 %type <asts> expr argument_expr_list function_definition expr_opt
124 %type <asts> statement_list statement labeled_statement compound_statement
125 %type <asts> expression_statement selection_statement iteration_statement
126 %type <asts> jump_statement function_body else_statement string_literal
127 %type <asts> critical_statement
128 %type <ilist> initializer initializer_list
129 %type <yyint> unary_operator  assignment_operator struct_or_union
130
131 %start file
132
133 %%
134
135 file
136    : external_definition       
137    | file external_definition
138    ;
139
140 external_definition
141    : function_definition     { 
142                                blockNo=0;
143                              }
144    | declaration             { 
145                                ignoreTypedefType = 0;
146                                if ($1 && $1->type
147                                 && IS_FUNC($1->type))
148                                {
149                                    /* The only legal storage classes for 
150                                     * a function prototype (declaration)
151                                     * are extern and static. extern is the
152                                     * default. Thus, if this function isn't
153                                     * explicitly marked static, mark it
154                                     * extern.
155                                     */
156                                    if ($1->etype 
157                                     && IS_SPEC($1->etype)
158                                     && !SPEC_STAT($1->etype))
159                                    {
160                                         SPEC_EXTR($1->etype) = 1;
161                                    }
162                                }
163                                addSymChain (&$1);
164                                allocVariables ($1) ;
165                                cleanUpLevel (SymbolTab,1);
166                              }
167    ;
168
169 function_definition
170    : function_declarator function_body  {   /* function type not specified */
171                                    /* assume it to be 'int'       */
172                                    addDecl($1,0,newIntLink());
173                                    $$ = createFunction($1,$2); 
174                                } 
175    | declaration_specifiers function_declarator function_body  
176                                 {   
177                                     pointerTypes($2->type,copyLinkChain($1));
178                                     addDecl($2,0,$1); 
179                                     $$ = createFunction($2,$3);   
180                                 }
181    ;
182
183 function_attribute
184    : function_attributes
185    | function_attributes function_attribute { $$ = mergeSpec($1,$2,"function_attribute"); }
186    ;
187
188 function_attributes
189    :  USING CONSTANT {
190                         $$ = newLink(SPECIFIER) ;
191                         FUNC_REGBANK($$) = (int) floatFromVal($2);
192                      }
193    |  REENTRANT      {  $$ = newLink (SPECIFIER);
194                         FUNC_ISREENT($$)=1;
195                      }
196    |  CRITICAL       {  $$ = newLink (SPECIFIER);
197                         FUNC_ISCRITICAL($$) = 1;
198                      }
199    |  NAKED          {  $$ = newLink (SPECIFIER);
200                         FUNC_ISNAKED($$)=1;
201                      }
202    |  JAVANATIVE     {  $$ = newLink (SPECIFIER);
203                         FUNC_ISJAVANATIVE($$)=1;
204                      }
205    |  OVERLAY        {  $$ = newLink (SPECIFIER);
206                         FUNC_ISOVERLAY($$)=1;
207                      }
208    |  NONBANKED      {$$ = newLink (SPECIFIER);
209                         FUNC_NONBANKED($$) = 1;
210                         if (FUNC_BANKED($$)) {
211                             werror(W_BANKED_WITH_NONBANKED);
212                         }
213                      }
214    |  SHADOWREGS     {$$ = newLink (SPECIFIER);
215                         FUNC_ISSHADOWREGS($$) = 1;
216                      }
217    |  WPARAM         {$$ = newLink (SPECIFIER);
218                         FUNC_ISWPARAM($$) = 1;
219                      }
220    |  BANKED         {$$ = newLink (SPECIFIER);
221                         FUNC_BANKED($$) = 1;
222                         if (FUNC_NONBANKED($$)) {
223                             werror(W_BANKED_WITH_NONBANKED);
224                         }
225                         if (SPEC_STAT($$)) {
226                             werror(W_BANKED_WITH_STATIC);
227                         }
228                      }
229    |  Interrupt_storage
230                      {
231                         $$ = newLink (SPECIFIER) ;
232                         FUNC_INTNO($$) = $1 ;
233                         FUNC_ISISR($$) = 1;
234                      }
235    ;
236
237 function_body
238    : compound_statement                   
239    | declaration_list compound_statement
240          {
241             werror(E_OLD_STYLE,($1 ? $1->name: "")) ;
242             exit(1);
243          }
244    ;
245
246 primary_expr
247    : identifier      {  $$ = newAst_VALUE(symbolVal($1));  }
248    | CONSTANT        {  $$ = newAst_VALUE($1);  }
249    | string_literal  
250    | '(' expr ')'    {  $$ = $2 ;                   }
251    ;
252          
253 string_literal
254     : STRING_LITERAL                    { $$ = newAst_VALUE($1); }
255     ;
256
257 postfix_expr
258    : primary_expr
259    | postfix_expr '[' expr ']'          { $$ = newNode  ('[', $1, $3) ; }
260    | postfix_expr '(' ')'               { $$ = newNode  (CALL,$1,NULL); 
261                                           $$->left->funcName = 1;}
262    | postfix_expr '(' argument_expr_list ')'
263           {        
264             $$ = newNode  (CALL,$1,$3) ; $$->left->funcName = 1;
265           }
266    | postfix_expr '.' { ignoreTypedefType = 1; } identifier       
267                       {    
268                         ignoreTypedefType = 0;
269                         $4 = newSymbol($4->name,NestLevel);
270                         $4->implicit = 1;
271                         $$ = newNode(PTR_OP,newNode('&',$1,NULL),newAst_VALUE(symbolVal($4)));
272 /*                      $$ = newNode('.',$1,newAst(EX_VALUE,symbolVal($4))) ;                   */
273                       }
274    | postfix_expr PTR_OP { ignoreTypedefType = 1; } identifier    
275                       { 
276                         ignoreTypedefType = 0;
277                         $4 = newSymbol($4->name,NestLevel);
278                         $4->implicit = 1;                       
279                         $$ = newNode(PTR_OP,$1,newAst_VALUE(symbolVal($4)));
280                       }
281    | postfix_expr INC_OP   
282                       { $$ = newNode(INC_OP,$1,NULL);}
283    | postfix_expr DEC_OP
284                       { $$ = newNode(DEC_OP,$1,NULL); }
285    ;
286
287 argument_expr_list
288    : assignment_expr 
289    | assignment_expr ',' argument_expr_list { $$ = newNode(PARAM,$1,$3); }
290    ;
291
292 unary_expr
293    : postfix_expr
294    | INC_OP unary_expr        { $$ = newNode(INC_OP,NULL,$2);  }
295    | DEC_OP unary_expr        { $$ = newNode(DEC_OP,NULL,$2);  }
296    | unary_operator cast_expr { $$ = newNode($1,$2,NULL)    ;  }
297    | SIZEOF unary_expr        { $$ = newNode(SIZEOF,NULL,$2);  }
298    | SIZEOF '(' type_name ')' { $$ = newAst_VALUE(sizeofOp($3)); }
299    | TYPEOF unary_expr        { $$ = newNode(TYPEOF,NULL,$2);  }
300    ;
301               
302 unary_operator
303    : '&'    { $$ = '&' ;}
304    | '*'    { $$ = '*' ;}
305    | '+'    { $$ = '+' ;}
306    | '-'    { $$ = '-' ;}
307    | '~'    { $$ = '~' ;}
308    | '!'    { $$ = '!' ;}
309    ;
310
311 cast_expr
312    : unary_expr
313    | '(' type_name ')' cast_expr { $$ = newNode(CAST,newAst_LINK($2),$4); }
314    ;
315
316 multiplicative_expr
317    : cast_expr
318    | multiplicative_expr '*' cast_expr { $$ = newNode('*',$1,$3);}
319    | multiplicative_expr '/' cast_expr { $$ = newNode('/',$1,$3);}
320    | multiplicative_expr '%' cast_expr { $$ = newNode('%',$1,$3);}
321    ;
322
323 additive_expr
324    : multiplicative_expr
325    | additive_expr '+' multiplicative_expr { $$=newNode('+',$1,$3);}
326    | additive_expr '-' multiplicative_expr { $$=newNode('-',$1,$3);}
327    ;
328
329 shift_expr
330    : additive_expr
331    | shift_expr LEFT_OP additive_expr  { $$ = newNode(LEFT_OP,$1,$3); }
332    | shift_expr RIGHT_OP additive_expr { $$ = newNode(RIGHT_OP,$1,$3); }
333    ;
334
335 relational_expr
336    : shift_expr
337    | relational_expr '<' shift_expr    { 
338         $$ = (port->lt_nge ? 
339               newNode('!',newNode(GE_OP,$1,$3),NULL) :
340               newNode('<', $1,$3));
341    }
342    | relational_expr '>' shift_expr    { 
343            $$ = (port->gt_nle ? 
344                  newNode('!',newNode(LE_OP,$1,$3),NULL) :
345                  newNode('>',$1,$3));
346    }
347    | relational_expr LE_OP shift_expr  { 
348            $$ = (port->le_ngt ? 
349                  newNode('!', newNode('>', $1 , $3 ), NULL) :
350                  newNode(LE_OP,$1,$3));
351    }
352    | relational_expr GE_OP shift_expr  { 
353            $$ = (port->ge_nlt ? 
354                  newNode('!', newNode('<', $1 , $3 ), NULL) :
355                  newNode(GE_OP,$1,$3));
356    }
357    ;
358
359 equality_expr
360    : relational_expr
361    | equality_expr EQ_OP relational_expr  { 
362     $$ = (port->eq_nne ? 
363           newNode('!',newNode(NE_OP,$1,$3),NULL) : 
364           newNode(EQ_OP,$1,$3));
365    }
366    | equality_expr NE_OP relational_expr { 
367        $$ = (port->ne_neq ? 
368              newNode('!', newNode(EQ_OP,$1,$3), NULL) : 
369              newNode(NE_OP,$1,$3));
370    }       
371    ;
372
373 and_expr
374    : equality_expr
375    | and_expr '&' equality_expr  { $$ = newNode('&',$1,$3);}
376    ;
377
378 exclusive_or_expr
379    : and_expr
380    | exclusive_or_expr '^' and_expr { $$ = newNode('^',$1,$3);}
381    ;
382
383 inclusive_or_expr
384    : exclusive_or_expr
385    | inclusive_or_expr '|' exclusive_or_expr { $$ = newNode('|',$1,$3);}
386    ;
387
388 logical_and_expr
389    : inclusive_or_expr
390    | logical_and_expr AND_OP { seqPointNo++;} inclusive_or_expr 
391                                  { $$ = newNode(AND_OP,$1,$4);}
392    ;
393
394 logical_or_expr
395    : logical_and_expr
396    | logical_or_expr OR_OP { seqPointNo++;} logical_and_expr  
397                                  { $$ = newNode(OR_OP,$1,$4); }
398    ;
399
400 conditional_expr
401    : logical_or_expr
402    | logical_or_expr '?' { seqPointNo++;} logical_or_expr ':' conditional_expr  
403                      {
404                         $$ = newNode(':',$4,$6) ;
405                         $$ = newNode('?',$1,$$) ;
406                      }                        
407    ;
408
409 assignment_expr
410    : conditional_expr
411    | cast_expr assignment_operator assignment_expr   
412                      { 
413                                  
414                              switch ($2) {
415                              case '=':
416                                      $$ = newNode($2,$1,$3);
417                                      break;
418                              case MUL_ASSIGN:
419                                      $$ = newNode('=',removePostIncDecOps(copyAst($1)),
420                                                       newNode('*',removePreIncDecOps(copyAst($1)),$3));
421                                      break;
422                              case DIV_ASSIGN:
423                                      $$ = newNode('=',removePostIncDecOps(copyAst($1)),
424                                                       newNode('/',removePreIncDecOps(copyAst($1)),$3));
425                                      break;
426                              case MOD_ASSIGN:
427                                      $$ = newNode('=',removePostIncDecOps(copyAst($1)),
428                                                       newNode('%',removePreIncDecOps(copyAst($1)),$3));
429                                      break;
430                              case ADD_ASSIGN:
431                                      $$ = newNode('=',removePostIncDecOps(copyAst($1)),
432                                                       newNode('+',removePreIncDecOps(copyAst($1)),$3));
433                                      break;
434                              case SUB_ASSIGN:
435                                      $$ = newNode('=',removePostIncDecOps(copyAst($1)),
436                                                       newNode('-',removePreIncDecOps(copyAst($1)),$3));
437                                      break;
438                              case LEFT_ASSIGN:
439                                      $$ = newNode('=',removePostIncDecOps(copyAst($1)),
440                                                       newNode(LEFT_OP,removePreIncDecOps(copyAst($1)),$3));
441                                      break;
442                              case RIGHT_ASSIGN:
443                                      $$ = newNode('=',removePostIncDecOps(copyAst($1)),
444                                                       newNode(RIGHT_OP,removePreIncDecOps(copyAst($1)),$3));
445                                      break;
446                              case AND_ASSIGN:
447                                      $$ = newNode('=',removePostIncDecOps(copyAst($1)),
448                                                       newNode('&',removePreIncDecOps(copyAst($1)),$3));
449                                      break;
450                              case XOR_ASSIGN:
451                                      $$ = newNode('=',removePostIncDecOps(copyAst($1)),
452                                                       newNode('^',removePreIncDecOps(copyAst($1)),$3));
453                                      break;
454                              case OR_ASSIGN:
455                                      /* $$ = newNode('=',$1,newNode('|',removeIncDecOps(copyAst($1)),$3)); */
456                                      $$ = newNode('=',removePostIncDecOps(copyAst($1)),
457                                                       newNode('|',removePreIncDecOps(copyAst($1)),$3));
458                                      break;
459                              default :
460                                      $$ = NULL;
461                              }
462                                      
463                      }
464 ;
465
466 assignment_operator
467    : '='             { $$ = '=' ;}
468    | MUL_ASSIGN
469    | DIV_ASSIGN
470    | MOD_ASSIGN
471    | ADD_ASSIGN
472    | SUB_ASSIGN
473    | LEFT_ASSIGN
474    | RIGHT_ASSIGN
475    | AND_ASSIGN
476    | XOR_ASSIGN
477    | OR_ASSIGN
478    ;
479
480 expr
481    : assignment_expr
482    | expr ',' { seqPointNo++;} assignment_expr { $$ = newNode(',',$1,$4);}
483    ;
484
485 constant_expr
486    : conditional_expr 
487    ;
488
489 declaration
490    : declaration_specifiers ';'
491       {
492          if (uselessDecl)
493            werror(W_USELESS_DECL);
494          uselessDecl = TRUE;
495          $$ = NULL ;
496       }
497    | declaration_specifiers init_declarator_list ';'
498       {
499          /* add the specifier list to the id */
500          symbol *sym , *sym1;
501
502          for (sym1 = sym = reverseSyms($2);sym != NULL;sym = sym->next) {
503              sym_link *lnk = copyLinkChain($1);
504              /* do the pointer stuff */
505              pointerTypes(sym->type,lnk);
506              addDecl (sym,0,lnk) ;
507          }
508         
509          uselessDecl = TRUE;
510          $$ = sym1 ;
511       }
512    ;
513
514 declaration_specifiers
515    : storage_class_specifier                                            { $$ = $1; }
516    | storage_class_specifier declaration_specifiers { 
517      /* if the decl $2 is not a specifier */
518      /* find the spec and replace it      */
519      if ( !IS_SPEC($2)) {
520        sym_link *lnk = $2 ;
521        while (lnk && !IS_SPEC(lnk->next))
522          lnk = lnk->next;
523        lnk->next = mergeSpec($1,lnk->next, "storage_class_specifier declaration_specifiers - skipped");
524        $$ = $2 ;
525      }
526      else
527        $$ = mergeSpec($1,$2, "storage_class_specifier declaration_specifiers");
528    }
529    | type_specifier                                 { $$ = $1; }
530    | type_specifier declaration_specifiers          { 
531      /* if the decl $2 is not a specifier */
532      /* find the spec and replace it      */
533      if ( !IS_SPEC($2)) {
534        sym_link *lnk = $2 ;
535        while (lnk && !IS_SPEC(lnk->next))
536          lnk = lnk->next;
537        lnk->next = mergeSpec($1,lnk->next, "type_specifier declaration_specifiers - skipped");
538        $$ = $2 ;
539      }
540      else
541        $$ = mergeSpec($1,$2, "type_specifier declaration_specifiers");
542    }
543    ;
544
545 init_declarator_list
546    : init_declarator
547    | init_declarator_list ',' init_declarator      { $3->next = $1 ; $$ = $3;}
548    ;
549
550 init_declarator
551    : declarator                  { $1->ival = NULL ; }
552    | declarator '=' initializer  { $1->ival = $3   ; }
553    ;
554
555
556 storage_class_specifier
557    : TYPEDEF   {
558                   $$ = newLink (SPECIFIER) ;
559                   SPEC_TYPEDEF($$) = 1 ;
560                }
561    | EXTERN    {
562                   $$ = newLink(SPECIFIER);
563                   SPEC_EXTR($$) = 1 ;
564                }
565    | STATIC    {
566                   $$ = newLink (SPECIFIER);
567                   SPEC_STAT($$) = 1 ;
568                }
569    | AUTO      {
570                   $$ = newLink (SPECIFIER) ;
571                   SPEC_SCLS($$) = S_AUTO  ;
572                }
573    | REGISTER  {
574                   $$ = newLink (SPECIFIER);
575                   SPEC_SCLS($$) = S_REGISTER ;
576                }
577    ;
578
579 Interrupt_storage
580    : INTERRUPT { $$ = INTNO_UNSPEC ; }
581    | INTERRUPT CONSTANT
582         { int intno = (int) floatFromVal($2);
583           if ((intno >= 0) && (intno <= INTNO_MAX))
584             $$ = intno;
585           else
586             {
587               werror(E_INT_BAD_INTNO, intno);
588               $$ = INTNO_UNSPEC;
589             }
590         }
591    ;
592
593 type_specifier
594    : type_specifier2
595    | type_specifier2 AT constant_expr
596         {
597            /* add this to the storage class specifier  */
598            SPEC_ABSA($1) = 1;   /* set the absolute addr flag */
599            /* now get the abs addr from value */
600            SPEC_ADDR($1) = (int) floatFromVal(constExprValue($3,TRUE)) ;
601         }
602    ;
603
604 type_specifier2
605    : CHAR   {
606                $$=newLink(SPECIFIER);
607                SPEC_NOUN($$) = V_CHAR  ;
608                ignoreTypedefType = 1;
609             }
610    | SHORT  {
611                $$=newLink(SPECIFIER);
612                $$->select.s._short = 1 ;
613                ignoreTypedefType = 1;
614             }
615    | INT    {
616                $$=newLink(SPECIFIER);
617                SPEC_NOUN($$) = V_INT   ;
618                ignoreTypedefType = 1;
619             }
620    | LONG   {
621                $$=newLink(SPECIFIER);
622                SPEC_LONG($$) = 1       ;
623                ignoreTypedefType = 1;
624             }
625    | SIGNED {
626                $$=newLink(SPECIFIER);
627                $$->select.s._signed = 1;
628                ignoreTypedefType = 1;
629             }
630    | UNSIGNED  {
631                $$=newLink(SPECIFIER);
632                SPEC_USIGN($$) = 1      ;
633                ignoreTypedefType = 1;
634             }
635    | VOID   {
636                $$=newLink(SPECIFIER);
637                SPEC_NOUN($$) = V_VOID  ;
638                ignoreTypedefType = 1;
639             }
640    | CONST  {
641                $$=newLink(SPECIFIER);
642                SPEC_CONST($$) = 1;
643             }
644    | VOLATILE  {
645                $$=newLink(SPECIFIER);
646                SPEC_VOLATILE($$) = 1 ;
647             }
648    | FLOAT  {
649                $$=newLink(SPECIFIER);
650                SPEC_NOUN($$) = V_FLOAT;
651                ignoreTypedefType = 1;
652             }
653    | XDATA     {
654                   $$ = newLink (SPECIFIER);
655                   SPEC_SCLS($$) = S_XDATA  ;
656                }
657    | CODE      {
658                   $$ = newLink (SPECIFIER) ;
659                   SPEC_SCLS($$) = S_CODE ;                 
660                }
661    | EEPROM      {
662                   $$ = newLink (SPECIFIER) ;
663                   SPEC_SCLS($$) = S_EEPROM ;
664                }
665    | DATA      {
666                   $$ = newLink (SPECIFIER);
667                   SPEC_SCLS($$) = S_DATA   ;
668                }
669    | IDATA     {
670                   $$ = newLink (SPECIFIER);
671                   SPEC_SCLS($$) = S_IDATA  ;
672                }
673    | PDATA     { 
674                   $$ = newLink (SPECIFIER);
675                   SPEC_SCLS($$) = S_PDATA  ;
676                }
677    | BIT    {
678                $$=newLink(SPECIFIER);
679                SPEC_NOUN($$) = V_BIT   ;
680                SPEC_SCLS($$) = S_BIT   ;
681                SPEC_BLEN($$) = 1;
682                SPEC_BSTR($$) = 0;
683                ignoreTypedefType = 1;
684             }
685
686    | struct_or_union_specifier  {
687                                    uselessDecl = FALSE;
688                                    $$ = $1 ;
689                                    ignoreTypedefType = 1;
690                                 }
691    | enum_specifier     {                           
692                            cenum = NULL ;
693                            uselessDecl = FALSE;
694                            ignoreTypedefType = 1;
695                            $$ = $1 ;                              
696                         }
697    | TYPE_NAME    
698          {
699             symbol *sym;
700             sym_link   *p  ;
701             sym = findSym(TypedefTab,NULL,$1) ;
702             $$ = p = copyLinkChain(sym->type);
703             SPEC_TYPEDEF(getSpec(p)) = 0;
704             ignoreTypedefType = 1;
705          }
706    | sfr_reg_bit
707    ;
708
709 sfr_reg_bit
710    :  SBIT  {
711                $$ = newLink(SPECIFIER) ;
712                SPEC_NOUN($$) = V_SBIT;
713                SPEC_SCLS($$) = S_SBIT;
714                SPEC_BLEN($$) = 1;
715                SPEC_BSTR($$) = 0;
716                ignoreTypedefType = 1;
717             }
718    |  sfr_attributes
719    ;
720
721 sfr_attributes
722    : SFR    {
723                $$ = newLink(SPECIFIER) ;
724                FUNC_REGBANK($$) = 0;
725                SPEC_NOUN($$)    = V_CHAR;
726                SPEC_SCLS($$)    = S_SFR ;
727                SPEC_USIGN($$)   = 1 ;
728                ignoreTypedefType = 1;
729             }
730    | SFR BANKED {
731                $$ = newLink(SPECIFIER) ;
732                FUNC_REGBANK($$) = 1;
733                SPEC_NOUN($$)    = V_CHAR;
734                SPEC_SCLS($$)    = S_SFR ;
735                SPEC_USIGN($$)   = 1 ;
736                ignoreTypedefType = 1;
737             }
738    ;
739
740 sfr_attributes
741    : SFR16  {
742                $$ = newLink(SPECIFIER) ;
743                FUNC_REGBANK($$) = 0;
744                SPEC_NOUN($$)    = V_INT;
745                SPEC_SCLS($$)    = S_SFR;
746                SPEC_USIGN($$)   = 1 ;
747                ignoreTypedefType = 1;
748             }
749    ;
750
751 sfr_attributes
752    : SFR32  {
753                $$ = newLink(SPECIFIER) ;
754                FUNC_REGBANK($$) = 0;
755                SPEC_NOUN($$)    = V_INT;
756                SPEC_SCLS($$)    = S_SFR;
757                SPEC_LONG($$)    = 1;
758                SPEC_USIGN($$)   = 1;
759                ignoreTypedefType = 1;
760             }
761    ;
762
763 struct_or_union_specifier
764    : struct_or_union opt_stag
765         {
766            if (!$2->type)
767              {
768                $2->type = $1;
769              }
770            else
771              {
772                if ($2->type != $1)
773                  werror(E_BAD_TAG, $2->tag, $1==STRUCT ? "struct" : "union");
774              }
775
776         }
777            '{' struct_declaration_list '}'
778         {
779            structdef *sdef ;
780            symbol *sym, *dsym;
781
782            // check for errors in structure members
783            for (sym=$5; sym; sym=sym->next) {
784              if (IS_ABSOLUTE(sym->etype)) {
785                werrorfl(sym->fileDef, sym->lineDef, E_NOT_ALLOWED, "'at'");
786                SPEC_ABSA(sym->etype) = 0;
787              }
788              if (IS_SPEC(sym->etype) && SPEC_SCLS(sym->etype)) {
789                werrorfl(sym->fileDef, sym->lineDef, E_NOT_ALLOWED, "storage class");
790                printTypeChainRaw (sym->type,NULL);
791                SPEC_SCLS(sym->etype) = 0;
792              }
793              for (dsym=sym->next; dsym; dsym=dsym->next) {
794                if (*dsym->name && strcmp(sym->name, dsym->name)==0) {
795                  werrorfl(sym->fileDef, sym->lineDef, E_DUPLICATE_MEMBER, 
796                         $1==STRUCT ? "struct" : "union", sym->name);
797                  werrorfl(dsym->fileDef, dsym->lineDef, E_PREVIOUS_DEF);
798                }
799              }
800            }
801
802            /* Create a structdef   */      
803            sdef = $2 ;
804            sdef->fields   = reverseSyms($5) ;   /* link the fields */
805            sdef->size  = compStructSize($1,sdef);   /* update size of  */
806            promoteAnonStructs ($1, sdef);
807            
808            /* Create the specifier */
809            $$ = newLink (SPECIFIER) ;
810            SPEC_NOUN($$) = V_STRUCT;
811            SPEC_STRUCT($$)= sdef ;
812         }
813    | struct_or_union stag
814          {
815             $$ = newLink(SPECIFIER) ;
816             SPEC_NOUN($$) = V_STRUCT;
817             SPEC_STRUCT($$) = $2;
818
819            if (!$2->type)
820              {
821                $2->type = $1;
822              }
823            else
824              {
825                if ($2->type != $1)
826                  werror(E_BAD_TAG, $2->tag, $1==STRUCT ? "struct" : "union");
827              }
828          }
829    ;
830
831 struct_or_union
832    : STRUCT          { $$ = STRUCT ; }
833    | UNION           { $$ = UNION  ; }
834    ;
835
836 opt_stag
837 : stag
838 |  {  /* synthesize a name add to structtable */
839      $$ = newStruct(genSymName(NestLevel)) ;
840      $$->level = NestLevel ;
841      addSym (StructTab, $$, $$->tag,$$->level,currBlockno, 0);
842 };
843
844 stag
845 :  identifier  {  /* add name to structure table */
846      $$ = findSymWithBlock (StructTab,$1,currBlockno);
847      if (! $$ ) {
848        $$ = newStruct($1->name) ;
849        $$->level = NestLevel ;
850        addSym (StructTab, $$, $$->tag,$$->level,currBlockno,0);
851      }
852 };
853
854
855 struct_declaration_list
856    : struct_declaration
857    | struct_declaration_list struct_declaration
858        {
859            symbol *sym=$2;
860
861            /* go to the end of the chain */
862            while (sym->next) sym=sym->next;
863            sym->next = $1 ;
864          
865            $$ = $2;
866        }
867    ;
868
869 struct_declaration
870    : type_specifier_list struct_declarator_list ';'
871        {
872            /* add this type to all the symbols */
873            symbol *sym ;
874            for ( sym = $2 ; sym != NULL ; sym = sym->next ) {
875                sym_link *btype = copyLinkChain($1);
876                
877                /* make the symbol one level up */
878                sym->level-- ;
879
880                pointerTypes(sym->type,btype);
881                if (!sym->type) {
882                    sym->type = btype;
883                    sym->etype = getSpec(sym->type);
884                }
885                else
886                  addDecl (sym,0,btype);
887                /* make sure the type is complete and sane */
888                checkTypeSanity(sym->etype, sym->name);
889            }
890            ignoreTypedefType = 0;
891            $$ = $2;
892        }
893    ;
894
895 struct_declarator_list
896    : struct_declarator
897    | struct_declarator_list ',' struct_declarator
898        {
899            $3->next  = $1 ;
900            $$ = $3 ;
901        }
902    ;
903
904 struct_declarator
905    : declarator 
906    | ':' constant_expr  {
907                            int bitsize;
908                            $$ = newSymbol (genSymName(NestLevel),NestLevel) ; 
909                            bitsize= (int) floatFromVal(constExprValue($2,TRUE));
910                            if (bitsize > (port->s.int_size * 8)) {
911                              bitsize = port->s.int_size * 8;
912                              werror(E_BITFLD_SIZE, bitsize);
913                            }
914                            if (!bitsize)
915                              bitsize = BITVAR_PAD;
916                            $$->bitVar = bitsize;
917                         }                        
918    | declarator ':' constant_expr 
919                         {
920                           int bitsize;
921                           bitsize= (int) floatFromVal(constExprValue($3,TRUE));
922                           if (bitsize > (port->s.int_size * 8)) {
923                             bitsize = port->s.int_size * 8;
924                             werror(E_BITFLD_SIZE, bitsize);
925                           }
926                           if (!bitsize) {
927                             $$ = newSymbol (genSymName(NestLevel),NestLevel) ; 
928                             $$->bitVar = BITVAR_PAD;
929                             werror(W_BITFLD_NAMED);
930                           }
931                           else
932                             $1->bitVar = bitsize;
933                         }
934    | { $$ = newSymbol ("", NestLevel) ; }
935    
936    ;
937
938 enum_specifier
939    : ENUM            '{' enumerator_list '}' {
940            $$ = newEnumType ($3);       //copyLinkChain(cenum->type);
941            SPEC_SCLS(getSpec($$)) = 0;
942          }
943
944    | ENUM identifier '{' enumerator_list '}' {
945      symbol *csym ;
946      sym_link *enumtype;
947
948      csym=findSym(enumTab,$2,$2->name);
949      if ((csym && csym->level == $2->level))
950        {
951          werrorfl($2->fileDef, $2->lineDef, E_DUPLICATE_TYPEDEF,csym->name);
952          werrorfl(csym->fileDef, csym->lineDef, E_PREVIOUS_DEF);
953        }
954      
955      enumtype = newEnumType ($4);       //copyLinkChain(cenum->type);
956      SPEC_SCLS(getSpec(enumtype)) = 0;
957      $2->type = enumtype;
958      
959      /* add this to the enumerator table */
960      if (!csym)
961        addSym ( enumTab,$2,$2->name,$2->level,$2->block, 0);
962      $$ = copyLinkChain(enumtype);
963    }
964    | ENUM identifier                         {
965      symbol *csym ;
966      
967      /* check the enumerator table */
968      if ((csym = findSym(enumTab,$2,$2->name)))
969        $$ = copyLinkChain(csym->type);
970      else  {
971        $$ = newLink(SPECIFIER) ;
972        SPEC_NOUN($$) = V_INT   ;
973      }
974    }
975    ;
976
977 enumerator_list
978    : enumerator
979    | enumerator_list ',' {
980                          }
981    | enumerator_list ',' enumerator
982      {
983        symbol *dsym;
984        
985        for (dsym=$1; dsym; dsym=dsym->next)
986          {
987            if (strcmp($3->name, dsym->name)==0)
988              {
989                werrorfl($3->fileDef, $3->lineDef, E_DUPLICATE_MEMBER, "enum", $3->name);
990                werrorfl(dsym->fileDef, dsym->lineDef, E_PREVIOUS_DEF);
991              }
992          }
993        
994        $3->next = $1 ;
995        $$ = $3  ;
996      }
997    ;
998
999 enumerator
1000    : identifier opt_assign_expr  
1001      {
1002        /* make the symbol one level up */
1003        $1->level-- ;
1004        $1->type = copyLinkChain($2->type); 
1005        $1->etype= getSpec($1->type);
1006        SPEC_ENUM($1->etype) = 1;
1007        $$ = $1 ;
1008        // do this now, so we can use it for the next enums in the list
1009        addSymChain(&$1);
1010      }
1011    ;
1012
1013 opt_assign_expr
1014    :  '='   constant_expr  {
1015                               value *val ;
1016
1017                               val = constExprValue($2,TRUE);
1018                               if (!IS_INT(val->type) && !IS_CHAR(val->type))
1019                                 {
1020                                   werror(E_ENUM_NON_INTEGER);
1021                                   SNPRINTF(lbuff, sizeof(lbuff), 
1022                                           "%d",(int) floatFromVal(val));
1023                                   val = constVal(lbuff);
1024                                 }
1025                               $$ = cenum = val ;
1026                            }                           
1027    |                       {                              
1028                               if (cenum)  {
1029                                  SNPRINTF(lbuff, sizeof(lbuff), 
1030                                           "%d",(int) floatFromVal(cenum)+1);
1031                                  $$ = cenum = constVal(lbuff);
1032                               }
1033                               else {
1034                                  SNPRINTF(lbuff, sizeof(lbuff), 
1035                                           "%d",0);
1036                                  $$ = cenum = constVal(lbuff);
1037                               }   
1038                            }
1039    ;
1040
1041 declarator
1042    : declarator3                        { $$ = $1 ; } 
1043    | pointer declarator3
1044          {
1045              addDecl ($2,0,reverseLink($1));
1046              $$ = $2 ;
1047          }
1048    ;
1049
1050 declarator3
1051    : declarator2_function_attributes    { $$ = $1 ; }
1052    | declarator2                        { $$ = $1 ; }
1053    ;
1054
1055 function_declarator
1056    : declarator2_function_attributes    { $$ = $1; }
1057    | pointer declarator2_function_attributes
1058          {
1059              addDecl ($2,0,reverseLink($1));
1060              $$ = $2 ;
1061          }
1062    ;
1063    
1064 declarator2_function_attributes
1065    : function_declarator2                 { $$ = $1 ; } 
1066    | function_declarator2 function_attribute  { 
1067            // copy the functionAttributes (not the args and hasVargs !!)
1068            struct value *args;
1069            unsigned hasVargs;
1070            sym_link *funcType=$1->type;
1071
1072            while (funcType && !IS_FUNC(funcType))
1073              funcType = funcType->next;
1074            
1075            if (!funcType)
1076              werror (E_FUNC_ATTR);
1077            else
1078              {
1079                args=FUNC_ARGS(funcType);
1080                hasVargs=FUNC_HASVARARGS(funcType);
1081
1082                memcpy (&funcType->funcAttrs, &$2->funcAttrs, 
1083                    sizeof($2->funcAttrs));
1084
1085                FUNC_ARGS(funcType)=args;
1086                FUNC_HASVARARGS(funcType)=hasVargs;
1087
1088                // just to be sure
1089                memset (&$2->funcAttrs, 0,
1090                    sizeof($2->funcAttrs));
1091            
1092                addDecl ($1,0,$2); 
1093              }
1094    }     
1095    ;
1096
1097 declarator2
1098    : identifier
1099    | '(' declarator ')'     { $$ = $2; }
1100    | declarator3 '[' ']'
1101          {
1102             sym_link   *p;
1103
1104             p = newLink (DECLARATOR);
1105             DCL_TYPE(p) = ARRAY ;
1106             DCL_ELEM(p) = 0     ;
1107             addDecl($1,0,p);
1108          }
1109    | declarator3 '[' constant_expr ']'
1110          {
1111             sym_link   *p ;
1112                         value *tval;
1113                         
1114             tval = constExprValue($3,TRUE);
1115             /* if it is not a constant then Error  */
1116             p = newLink (DECLARATOR);
1117             DCL_TYPE(p) = ARRAY ;
1118             if ( !tval || (SPEC_SCLS(tval->etype) != S_LITERAL)) {
1119                werror(E_CONST_EXPECTED) ;
1120                /* Assume a single item array to limit the cascade */
1121                /* of additional errors. */
1122                DCL_ELEM(p) = 1;
1123             }
1124             else {
1125                DCL_ELEM(p) = (int) floatFromVal(tval) ;
1126             }                           
1127             addDecl($1,0,p);
1128          }
1129    ;
1130
1131 function_declarator2
1132    : declarator2 '('  ')'       {  addDecl ($1,FUNCTION,NULL) ;   }
1133    | declarator2 '('            { NestLevel++ ; currBlockno++;  }
1134                      parameter_type_list ')'
1135          {
1136              sym_link *funcType;
1137            
1138              addDecl ($1,FUNCTION,NULL) ;
1139
1140              funcType = $1->type;
1141              while (funcType && !IS_FUNC(funcType))
1142                funcType = funcType->next;
1143            
1144              assert (funcType);
1145              
1146              FUNC_HASVARARGS(funcType) = IS_VARG($4);
1147              FUNC_ARGS(funcType) = reverseVal($4);
1148              
1149              /* nest level was incremented to take care of the parms  */
1150              NestLevel-- ;
1151              currBlockno--;
1152
1153              // if this was a pointer (to a function)
1154              if (!IS_FUNC($1->type))
1155                cleanUpLevel(SymbolTab,NestLevel+1);
1156              
1157              $$ = $1;
1158          }
1159    | declarator2 '(' parameter_identifier_list ')'
1160          {         
1161            werror(E_OLD_STYLE,$1->name) ;         
1162            /* assume it returns an int */
1163            $1->type = $1->etype = newIntLink();
1164            $$ = $1 ;
1165          }
1166    ;
1167    
1168 pointer
1169    : unqualified_pointer { $$ = $1 ;}
1170    | unqualified_pointer type_specifier_list   
1171          {
1172              $$ = $1  ;
1173              if (IS_SPEC($2)) {
1174                  DCL_TSPEC($1) = $2;
1175                  DCL_PTR_CONST($1) = SPEC_CONST($2);
1176                  DCL_PTR_VOLATILE($1) = SPEC_VOLATILE($2);
1177              }
1178              else
1179                  werror (W_PTR_TYPE_INVALID);
1180          }
1181    | unqualified_pointer pointer         
1182          {
1183              $$ = $1 ;          
1184              $$->next = $2 ;
1185              DCL_TYPE($2)=port->unqualified_pointer;
1186          }
1187    | unqualified_pointer type_specifier_list pointer
1188          {
1189              $$ = $1 ;               
1190              if (IS_SPEC($2) && DCL_TYPE($3) == UPOINTER) {
1191                  DCL_PTR_CONST($1) = SPEC_CONST($2);
1192                  DCL_PTR_VOLATILE($1) = SPEC_VOLATILE($2);
1193                  switch (SPEC_SCLS($2)) {
1194                  case S_XDATA:
1195                      DCL_TYPE($3) = FPOINTER;
1196                      break;
1197                  case S_IDATA:
1198                      DCL_TYPE($3) = IPOINTER ;
1199                      break;
1200                  case S_PDATA:
1201                      DCL_TYPE($3) = PPOINTER ;
1202                      break;
1203                  case S_DATA:
1204                      DCL_TYPE($3) = POINTER ;
1205                      break;
1206                  case S_CODE:
1207                      DCL_TYPE($3) = CPOINTER ;
1208                      break;
1209                  case S_EEPROM:
1210                      DCL_TYPE($3) = EEPPOINTER;
1211                      break;
1212                  default:
1213                    // this could be just "constant" 
1214                    // werror(W_PTR_TYPE_INVALID);
1215                      ;
1216                  }
1217              }
1218              else 
1219                  werror (W_PTR_TYPE_INVALID);
1220              $$->next = $3 ;
1221          }
1222    ;
1223
1224 unqualified_pointer
1225    :  '*'   
1226       {
1227         $$ = newLink(DECLARATOR);
1228         DCL_TYPE($$)=UPOINTER;
1229       }
1230    ;
1231
1232 type_specifier_list
1233    : type_specifier
1234    //| type_specifier_list type_specifier         {  $$ = mergeSpec ($1,$2, "type_specifier_list"); }
1235    | type_specifier_list type_specifier {
1236      /* if the decl $2 is not a specifier */
1237      /* find the spec and replace it      */
1238      if ( !IS_SPEC($2)) {
1239        sym_link *lnk = $2 ;
1240        while (lnk && !IS_SPEC(lnk->next))
1241          lnk = lnk->next;
1242        lnk->next = mergeSpec($1,lnk->next, "type_specifier_list type_specifier skipped");
1243        $$ = $2 ;
1244      }
1245      else
1246        $$ = mergeSpec($1,$2, "type_specifier_list type_specifier");
1247    }
1248    ;
1249
1250 parameter_identifier_list
1251    : identifier_list
1252    | identifier_list ',' ELIPSIS
1253    ;
1254
1255 identifier_list
1256    : identifier
1257    | identifier_list ',' identifier         
1258          {            
1259            $3->next = $1;
1260            $$ = $3 ;
1261          }
1262    ;
1263
1264 parameter_type_list
1265         : parameter_list
1266         | parameter_list ',' VAR_ARGS { $1->vArgs = 1;}
1267         ;
1268
1269 parameter_list
1270    : parameter_declaration
1271    | parameter_list ',' parameter_declaration
1272          {
1273             $3->next = $1 ;
1274             $$ = $3 ;
1275          }
1276    ;
1277
1278 parameter_declaration
1279    : type_specifier_list declarator 
1280                {        
1281                   symbol *loop ;
1282                   pointerTypes($2->type,$1);
1283                   addDecl ($2,0,$1);              
1284                   for (loop=$2;loop;loop->_isparm=1,loop=loop->next);
1285                   addSymChain (&$2);
1286                   $$ = symbolVal($2);
1287                   ignoreTypedefType = 0;
1288                }
1289    | type_name { 
1290                   $$ = newValue() ; 
1291                   $$->type = $1;
1292                   $$->etype = getSpec($$->type);
1293                   ignoreTypedefType = 0;
1294                }
1295    ;
1296
1297 type_name
1298    : type_specifier_list  { $$ = $1; ignoreTypedefType = 0;}
1299    | type_specifier_list abstract_declarator 
1300                {
1301                  /* go to the end of the list */
1302                  sym_link *p;
1303                  pointerTypes($2,$1);
1304                  for ( p = $2 ; p && p->next ; p=p->next);
1305                  if (!p) {
1306                    werror(E_SYNTAX_ERROR, yytext);
1307                  } else {
1308                    p->next = $1 ;
1309                  }
1310                  $$ = $2 ;
1311                  ignoreTypedefType = 0;
1312                }   
1313    ;
1314
1315 abstract_declarator
1316    : pointer { $$ = reverseLink($1); }
1317    | abstract_declarator2
1318    | pointer abstract_declarator2   { $1 = reverseLink($1); $1->next = $2 ; $$ = $1;
1319           if (IS_PTR($1) && IS_FUNC($2))
1320             DCL_TYPE($1) = CPOINTER;
1321         } 
1322    ;
1323
1324 abstract_declarator2
1325    : '(' abstract_declarator ')'    { $$ = $2 ; }
1326    | '[' ']'                        {             
1327                                        $$ = newLink (DECLARATOR);
1328                                        DCL_TYPE($$) = ARRAY ;
1329                                        DCL_ELEM($$) = 0     ;
1330                                     }
1331    | '[' constant_expr ']'          { 
1332                                        value *val ;
1333                                        $$ = newLink (DECLARATOR);
1334                                        DCL_TYPE($$) = ARRAY ;
1335                                        DCL_ELEM($$) = (int) floatFromVal(val = constExprValue($2,TRUE));
1336                                     }
1337    | abstract_declarator2 '[' ']'   {
1338                                        $$ = newLink (DECLARATOR);
1339                                        DCL_TYPE($$) = ARRAY ;
1340                                        DCL_ELEM($$) = 0     ;
1341                                        $$->next = $1 ;
1342                                     }
1343    | abstract_declarator2 '[' constant_expr ']'
1344                                     {
1345                                        value *val ;
1346                                        $$ = newLink (DECLARATOR);
1347                                        DCL_TYPE($$) = ARRAY ;
1348                                        DCL_ELEM($$) = (int) floatFromVal(val = constExprValue($3,TRUE));
1349                                        $$->next = $1 ;
1350                                     }
1351    | '(' ')'                        { $$ = NULL;}
1352    | '(' parameter_type_list ')'    { $$ = NULL;}   
1353    | abstract_declarator2 '(' ')' {
1354      // $1 must be a pointer to a function
1355      sym_link *p=newLink(DECLARATOR);
1356      DCL_TYPE(p) = FUNCTION;
1357      if (!$1) {
1358        // ((void (code *) ()) 0) ()
1359        $1=newLink(DECLARATOR);
1360        DCL_TYPE($1)=CPOINTER;
1361        $$ = $1;
1362      }
1363      $1->next=p;
1364    }
1365    | abstract_declarator2 '(' { NestLevel++ ; currBlockno++; } parameter_type_list ')' {
1366        sym_link *p=newLink(DECLARATOR);
1367        DCL_TYPE(p) = FUNCTION;
1368            
1369        FUNC_HASVARARGS(p) = IS_VARG($4);
1370        FUNC_ARGS(p) = reverseVal($4);
1371              
1372        /* nest level was incremented to take care of the parms  */
1373        NestLevel-- ;
1374        currBlockno--;
1375        p->next = $1;
1376        $$ = p;
1377
1378        // remove the symbol args (if any)
1379        cleanUpLevel(SymbolTab,NestLevel+1);
1380    }
1381    ;
1382
1383 initializer
1384    : assignment_expr                { $$ = newiList(INIT_NODE,$1); }
1385    | '{'  initializer_list '}'      { $$ = newiList(INIT_DEEP,revinit($2)); }
1386    | '{'  initializer_list ',' '}'  { $$ = newiList(INIT_DEEP,revinit($2)); }
1387    ;
1388
1389 initializer_list
1390    : initializer
1391    | initializer_list ',' initializer  {  $3->next = $1; $$ = $3; }
1392    ;
1393
1394 statement
1395    : labeled_statement
1396    | compound_statement
1397    | expression_statement
1398    | selection_statement
1399    | iteration_statement
1400    | jump_statement
1401    | critical_statement
1402    | INLINEASM  ';'      {
1403                             ast *ex;
1404                             seqPointNo++;
1405                             ex = newNode(INLINEASM,NULL,NULL);
1406                             ex->values.inlineasm = strdup($1);
1407                             seqPointNo++;
1408                             $$ = ex;
1409                          } 
1410    ;
1411
1412 critical
1413    : CRITICAL   {
1414                    inCritical++;
1415                    STACK_PUSH(continueStack,NULL);
1416                    STACK_PUSH(breakStack,NULL);
1417                    $$ = NULL;
1418                 }
1419    ;
1420    
1421 critical_statement
1422    : critical statement  {
1423                    STACK_POP(breakStack);
1424                    STACK_POP(continueStack);
1425                    inCritical--;
1426                    $$ = newNode(CRITICAL,$2,NULL);
1427                 }
1428    ;
1429       
1430 labeled_statement
1431 //   : identifier ':' statement          {  $$ = createLabel($1,$3);  }   
1432    : identifier ':'                    {  $$ = createLabel($1,NULL);
1433                                           $1->isitmp = 0;  }   
1434    | CASE constant_expr ':'
1435      {
1436        if (STACK_EMPTY(swStk))
1437          $$ = createCase(NULL,$2,NULL);
1438        else
1439          $$ = createCase(STACK_PEEK(swStk),$2,NULL);
1440      }
1441    | DEFAULT { $<asts>$ = newNode(DEFAULT,NULL,NULL); } ':'
1442      {
1443        if (STACK_EMPTY(swStk))
1444          $$ = createDefault(NULL,$<asts>2,NULL);
1445        else
1446          $$ = createDefault(STACK_PEEK(swStk),$<asts>2,NULL);
1447      }
1448    ;
1449
1450 start_block : '{'
1451               {
1452                 STACK_PUSH(blockNum,currBlockno);
1453                 currBlockno = ++blockNo ;
1454                 ignoreTypedefType = 0;
1455               }
1456             ;
1457
1458 end_block   : '}'     { currBlockno = STACK_POP(blockNum); }           
1459             ;
1460
1461 compound_statement
1462    : start_block end_block                    { $$ = createBlock(NULL,NULL); }
1463    | start_block statement_list end_block     { $$ = createBlock(NULL,$2) ;  }
1464    | start_block 
1465           declaration_list                    { addSymChain(&$2); }
1466      end_block                                { $$ = createBlock($2,NULL) ;  }
1467    | start_block 
1468           declaration_list                    {  addSymChain (&$2); }
1469           statement_list   
1470      end_block                                {$$ = createBlock($2,$4)   ;  }
1471    | error ';'                                { $$ = NULL ; }
1472    ;
1473
1474 declaration_list
1475    : declaration        
1476      {
1477        /* if this is typedef declare it immediately */
1478        if ( $1 && IS_TYPEDEF($1->etype)) {
1479          allocVariables ($1);
1480          $$ = NULL ;
1481        }
1482        else
1483          $$ = $1 ;
1484        ignoreTypedefType = 0;
1485      }
1486
1487    | declaration_list declaration
1488      {
1489        symbol   *sym;
1490        
1491        /* if this is a typedef */
1492        if ($2 && IS_TYPEDEF($2->etype)) {
1493          allocVariables ($2);
1494          $$ = $1 ;
1495        }
1496        else {
1497                                 /* get to the end of the previous decl */
1498          if ( $1 ) {
1499            $$ = sym = $1 ;
1500            while (sym->next)
1501              sym = sym->next ;
1502            sym->next = $2;
1503          } 
1504          else
1505            $$ = $2 ;
1506        }
1507        ignoreTypedefType = 0;
1508      }
1509    ;
1510
1511 statement_list
1512    : statement
1513    | statement_list statement          {  $$ = newNode(NULLOP,$1,$2) ;}
1514    ;
1515
1516 expression_statement
1517    : ';'                { $$ = NULL;}
1518    | expr ';'           { $$ = $1; seqPointNo++;} 
1519    ;
1520
1521 else_statement
1522    :  ELSE  statement   { $$ = $2  ; }
1523    |                    { $$ = NULL;}
1524    ;
1525
1526   
1527 selection_statement
1528    : IF '(' expr ')' { seqPointNo++;} statement else_statement
1529                            {
1530                               noLineno++ ;
1531                               $$ = createIf ($3, $6, $7 );
1532                               noLineno--;
1533                            }
1534    | SWITCH '(' expr ')'   { 
1535                               ast *ex ;                              
1536                               static   int swLabel = 0 ;
1537
1538                               seqPointNo++;
1539                               /* create a node for expression  */
1540                               ex = newNode(SWITCH,$3,NULL);
1541                               STACK_PUSH(swStk,ex);   /* save it in the stack */
1542                               ex->values.switchVals.swNum = swLabel ;
1543                                  
1544                               /* now create the label */
1545                               SNPRINTF(lbuff, sizeof(lbuff), 
1546                                        "_swBrk_%d",swLabel++);
1547                               $<sym>$  =  newSymbol(lbuff,NestLevel);
1548                               /* put label in the break stack  */
1549                               STACK_PUSH(breakStack,$<sym>$);   
1550                            }
1551      statement             {  
1552                               /* get back the switch form the stack  */
1553                               $$ = STACK_POP(swStk)  ;
1554                               $$->right = newNode (NULLOP,$6,createLabel($<sym>5,NULL));
1555                               STACK_POP(breakStack);   
1556                            }
1557         ;
1558
1559 while : WHILE  {  /* create and push the continue , break & body labels */
1560                   static int Lblnum = 0 ;
1561                   /* continue */
1562                   SNPRINTF (lbuff, sizeof(lbuff), "_whilecontinue_%d",Lblnum);
1563                   STACK_PUSH(continueStack,newSymbol(lbuff,NestLevel));
1564                   /* break */
1565                   SNPRINTF (lbuff, sizeof(lbuff), "_whilebreak_%d",Lblnum);
1566                   STACK_PUSH(breakStack,newSymbol(lbuff,NestLevel));
1567                   /* body */
1568                   SNPRINTF (lbuff, sizeof(lbuff), "_whilebody_%d",Lblnum++);
1569                   $$ = newSymbol(lbuff,NestLevel);
1570                }
1571    ;
1572
1573 do : DO {  /* create and push the continue , break & body Labels */
1574            static int Lblnum = 0 ;
1575
1576            /* continue */
1577            SNPRINTF(lbuff, sizeof(lbuff), "_docontinue_%d",Lblnum);
1578            STACK_PUSH(continueStack,newSymbol(lbuff,NestLevel));
1579            /* break */
1580            SNPRINTF(lbuff, sizeof(lbuff), "_dobreak_%d",Lblnum);
1581            STACK_PUSH(breakStack,newSymbol(lbuff,NestLevel));
1582            /* do body */
1583            SNPRINTF(lbuff, sizeof(lbuff), "_dobody_%d",Lblnum++);
1584            $$ = newSymbol (lbuff,NestLevel);       
1585         }
1586    ;
1587
1588 for : FOR { /* create & push continue, break & body labels */
1589             static int Lblnum = 0 ;
1590          
1591             /* continue */
1592             SNPRINTF(lbuff, sizeof(lbuff), "_forcontinue_%d",Lblnum);
1593             STACK_PUSH(continueStack,newSymbol(lbuff,NestLevel));
1594             /* break    */
1595             SNPRINTF(lbuff, sizeof(lbuff), "_forbreak_%d",Lblnum);
1596             STACK_PUSH(breakStack,newSymbol(lbuff,NestLevel));
1597             /* body */
1598             SNPRINTF(lbuff, sizeof(lbuff), "_forbody_%d",Lblnum);
1599             $$ = newSymbol(lbuff,NestLevel);
1600             /* condition */
1601             SNPRINTF(lbuff, sizeof(lbuff), "_forcond_%d",Lblnum++);
1602             STACK_PUSH(forStack,newSymbol(lbuff,NestLevel));
1603           }
1604    ;
1605
1606 iteration_statement  
1607    : while '(' expr ')' { seqPointNo++;}  statement 
1608                          { 
1609                            noLineno++ ;
1610                            $$ = createWhile ( $1, STACK_POP(continueStack),
1611                                               STACK_POP(breakStack), $3, $6 ); 
1612                            $$->lineno = $1->lineDef ;
1613                            noLineno-- ;
1614                          }
1615    | do statement   WHILE '(' expr ')' ';' 
1616                         { 
1617                           seqPointNo++; 
1618                           noLineno++ ; 
1619                           $$ = createDo ( $1 , STACK_POP(continueStack), 
1620                                           STACK_POP(breakStack), $5, $2);
1621                           $$->lineno = $1->lineDef ;
1622                           noLineno-- ;
1623                         }                                                 
1624    | for '(' expr_opt   ';' expr_opt ';' expr_opt ')'  statement   
1625                         {
1626                           noLineno++ ;  
1627                           
1628                           /* if break or continue statement present
1629                              then create a general case loop */
1630                           if (STACK_PEEK(continueStack)->isref ||
1631                               STACK_PEEK(breakStack)->isref) {
1632                               $$ = createFor ($1, STACK_POP(continueStack),
1633                                               STACK_POP(breakStack) ,
1634                                               STACK_POP(forStack)   ,
1635                                               $3 , $5 , $7, $9 );
1636                           } else {
1637                               $$ = newNode(FOR,$9,NULL);
1638                               AST_FOR($$,trueLabel) = $1;
1639                               AST_FOR($$,continueLabel) =  STACK_POP(continueStack);
1640                               AST_FOR($$,falseLabel) = STACK_POP(breakStack);
1641                               AST_FOR($$,condLabel)  = STACK_POP(forStack)  ;
1642                               AST_FOR($$,initExpr)   = $3;
1643                               AST_FOR($$,condExpr)   = $5;
1644                               AST_FOR($$,loopExpr)   = $7;
1645                           }
1646                           
1647                           noLineno-- ;
1648                         }
1649 ;
1650
1651 expr_opt
1652         :                       { $$ = NULL ; seqPointNo++; }
1653         |       expr            { $$ = $1 ; seqPointNo++; }
1654         ;
1655
1656 jump_statement          
1657    : GOTO identifier ';'   { 
1658                               $2->islbl = 1;
1659                               $$ = newAst_VALUE(symbolVal($2)); 
1660                               $$ = newNode(GOTO,$$,NULL);
1661                            }
1662    | CONTINUE ';'          {  
1663        /* make sure continue is in context */
1664        if (STACK_EMPTY(continueStack) || STACK_PEEK(continueStack) == NULL) {
1665            werror(E_BREAK_CONTEXT);
1666            $$ = NULL;
1667        }
1668        else {
1669            $$ = newAst_VALUE(symbolVal(STACK_PEEK(continueStack)));      
1670            $$ = newNode(GOTO,$$,NULL);
1671            /* mark the continue label as referenced */
1672            STACK_PEEK(continueStack)->isref = 1;
1673        }
1674    }
1675    | BREAK ';'             { 
1676        if (STACK_EMPTY(breakStack) || STACK_PEEK(breakStack) == NULL) {
1677            werror(E_BREAK_CONTEXT);
1678            $$ = NULL;
1679        } else {
1680            $$ = newAst_VALUE(symbolVal(STACK_PEEK(breakStack)));
1681            $$ = newNode(GOTO,$$,NULL);
1682            STACK_PEEK(breakStack)->isref = 1;
1683        }
1684    }
1685    | RETURN ';'            {
1686        seqPointNo++;
1687        if (inCritical) {
1688            werror(E_INVALID_CRITICAL);
1689            $$ = NULL;
1690        } else {
1691            $$ = newNode(RETURN,NULL,NULL);
1692        }
1693    }
1694    | RETURN expr ';'       {
1695        seqPointNo++;
1696        if (inCritical) {
1697            werror(E_INVALID_CRITICAL);
1698            $$ = NULL;
1699        } else {
1700            $$ = newNode(RETURN,NULL,$2);
1701        }
1702    }
1703    ;
1704
1705 identifier
1706    : IDENTIFIER   { $$ = newSymbol ($1,NestLevel) ; }
1707    ;
1708 %%
1709