[BACK]Return to cgram.y CVS log [TXT][DIR] Up to [cvs.NetBSD.org] / src / usr.bin / xlint / lint1

Annotation of src/usr.bin/xlint/lint1/cgram.y, Revision 1.208

1.2       cgd         1: %{
1.208   ! rillig      2: /* $NetBSD: cgram.y,v 1.207 2021/03/30 14:25:28 rillig Exp $ */
1.2       cgd         3:
1.1       cgd         4: /*
1.9       cgd         5:  * Copyright (c) 1996 Christopher G. Demetriou.  All Rights Reserved.
1.1       cgd         6:  * Copyright (c) 1994, 1995 Jochen Pohl
                      7:  * All Rights Reserved.
                      8:  *
                      9:  * Redistribution and use in source and binary forms, with or without
                     10:  * modification, are permitted provided that the following conditions
                     11:  * are met:
                     12:  * 1. Redistributions of source code must retain the above copyright
                     13:  *    notice, this list of conditions and the following disclaimer.
                     14:  * 2. Redistributions in binary form must reproduce the above copyright
                     15:  *    notice, this list of conditions and the following disclaimer in the
                     16:  *    documentation and/or other materials provided with the distribution.
                     17:  * 3. All advertising materials mentioning features or use of this software
                     18:  *    must display the following acknowledgement:
                     19:  *      This product includes software developed by Jochen Pohl for
                     20:  *     The NetBSD Project.
                     21:  * 4. The name of the author may not be used to endorse or promote products
                     22:  *    derived from this software without specific prior written permission.
                     23:  *
                     24:  * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
                     25:  * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
                     26:  * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
                     27:  * IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
                     28:  * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
                     29:  * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
                     30:  * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
                     31:  * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
                     32:  * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
                     33:  * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
                     34:  */
                     35:
1.13      christos   36: #include <sys/cdefs.h>
1.23      tv         37: #if defined(__RCSID) && !defined(lint)
1.208   ! rillig     38: __RCSID("$NetBSD: cgram.y,v 1.207 2021/03/30 14:25:28 rillig Exp $");
1.1       cgd        39: #endif
                     40:
1.108     rillig     41: #include <limits.h>
1.1       cgd        42: #include <stdlib.h>
1.12      cjs        43: #include <string.h>
1.1       cgd        44:
                     45: #include "lint1.h"
                     46:
1.41      christos   47: extern char *yytext;
1.132     rillig     48:
1.1       cgd        49: /*
1.148     rillig     50:  * Contains the level of current declaration, used for symbol table entries.
                     51:  * 0 is the top-level, > 0 is inside a function body.
1.1       cgd        52:  */
1.171     rillig     53: int    block_level;
1.1       cgd        54:
                     55: /*
1.171     rillig     56:  * level for memory allocation. Normally the same as block_level.
1.49      wiz        57:  * An exception is the declaration of arguments in prototypes. Memory
1.1       cgd        58:  * for these can't be freed after the declaration, but symbols must
                     59:  * be removed from the symbol table after the declaration.
                     60:  */
1.171     rillig     61: int    mem_block_level;
1.1       cgd        62:
1.15      christos   63: /*
                     64:  * Save the no-warns state and restore it to avoid the problem where
                     65:  * if (expr) { stmt } / * NOLINT * / stmt;
                     66:  */
1.55      christos   67: static int olwarn = LWARN_BAD;
1.15      christos   68:
1.174     rillig     69: static void    cgram_declare(sym_t *, bool, sbuf_t *);
1.148     rillig     70: static void    ignore_up_to_rparen(void);
1.75      christos   71: static sym_t   *symbolrename(sym_t *, sbuf_t *);
                     72:
1.1       cgd        73:
1.15      christos   74: #ifdef DEBUG
1.148     rillig     75: static void
                     76: CLEAR_WARN_FLAGS(const char *file, size_t line)
1.15      christos   77: {
1.190     rillig     78:        printf("%s:%d: %s:%zu: clearing flags\n",
                     79:            curr_pos.p_file, curr_pos.p_line, file, line);
1.148     rillig     80:        clear_warn_flags();
1.55      christos   81:        olwarn = LWARN_BAD;
1.15      christos   82: }
                     83:
1.148     rillig     84: static void
                     85: SAVE_WARN_FLAGS(const char *file, size_t line)
1.15      christos   86: {
1.149     rillig     87:        lint_assert(olwarn == LWARN_BAD);
1.190     rillig     88:        printf("%s:%d: %s:%zu: saving flags %d\n",
                     89:            curr_pos.p_file, curr_pos.p_line, file, line, lwarn);
1.55      christos   90:        olwarn = lwarn;
1.15      christos   91: }
                     92:
1.148     rillig     93: static void
                     94: RESTORE_WARN_FLAGS(const char *file, size_t line)
1.15      christos   95: {
1.55      christos   96:        if (olwarn != LWARN_BAD) {
                     97:                lwarn = olwarn;
1.190     rillig     98:                printf("%s:%d: %s:%zu: restoring flags %d\n",
                     99:                    curr_pos.p_file, curr_pos.p_line, file, line, lwarn);
1.55      christos  100:                olwarn = LWARN_BAD;
1.15      christos  101:        } else
1.148     rillig    102:                CLEAR_WARN_FLAGS(file, line);
1.15      christos  103: }
1.117     rillig    104: #define cgram_debug(fmt, args...) printf("cgram_debug: " fmt "\n", ##args)
1.15      christos  105: #else
1.190     rillig    106: #define CLEAR_WARN_FLAGS(f, l) clear_warn_flags(), olwarn = LWARN_BAD
1.148     rillig    107: #define SAVE_WARN_FLAGS(f, l)  olwarn = lwarn
                    108: #define RESTORE_WARN_FLAGS(f, l) \
                    109:        (void)(olwarn == LWARN_BAD ? (clear_warn_flags(), 0) : (lwarn = olwarn))
1.176     rillig    110: #define cgram_debug(fmt, args...) do { } while (false)
1.15      christos  111: #endif
1.73      christos  112:
1.190     rillig    113: #define clear_warning_flags()  CLEAR_WARN_FLAGS(__FILE__, __LINE__)
                    114: #define save_warning_flags()   SAVE_WARN_FLAGS(__FILE__, __LINE__)
                    115: #define restore_warning_flags()        RESTORE_WARN_FLAGS(__FILE__, __LINE__)
1.187     rillig    116:
1.73      christos  117: /* unbind the anonymous struct members from the struct */
                    118: static void
                    119: anonymize(sym_t *s)
                    120: {
1.119     rillig    121:        for ( ; s; s = s->s_next)
1.73      christos  122:                s->s_styp = NULL;
                    123: }
1.1       cgd       124: %}
                    125:
1.199     christos  126: %expect 165
1.40      christos  127:
1.1       cgd       128: %union {
                    129:        val_t   *y_val;
                    130:        sbuf_t  *y_sb;
                    131:        sym_t   *y_sym;
                    132:        op_t    y_op;
                    133:        scl_t   y_scl;
                    134:        tspec_t y_tspec;
                    135:        tqual_t y_tqual;
                    136:        type_t  *y_type;
                    137:        tnode_t *y_tnode;
1.35      christos  138:        range_t y_range;
1.121     rillig    139:        strg_t  *y_string;
1.1       cgd       140:        pqinf_t *y_pqinf;
1.185     rillig    141:        int     y_seen_statement;
1.1       cgd       142: };
                    143:
1.126     rillig    144: %token                 T_LBRACE T_RBRACE T_LBRACK T_RBRACK T_LPAREN T_RPAREN
1.146     rillig    145: %token <y_op>          T_MEMBACC
1.150     rillig    146: %token <y_op>          T_UNARY
1.1       cgd       147: %token <y_op>          T_INCDEC
                    148: %token                 T_SIZEOF
1.94      christos  149: %token                 T_BUILTIN_OFFSETOF
1.58      christos  150: %token                 T_TYPEOF
                    151: %token                 T_EXTENSION
1.199     christos  152: %token                 T_ALIGNAS
1.44      christos  153: %token                 T_ALIGNOF
1.189     rillig    154: %token                 T_ASTERISK
1.150     rillig    155: %token <y_op>          T_MULTIPLICATIVE
                    156: %token <y_op>          T_ADDITIVE
                    157: %token <y_op>          T_SHIFT
                    158: %token <y_op>          T_RELATIONAL
                    159: %token <y_op>          T_EQUALITY
1.189     rillig    160: %token                 T_AMPER
1.191     rillig    161: %token                 T_BITXOR
1.189     rillig    162: %token                 T_BITOR
                    163: %token                 T_LOGAND
                    164: %token                 T_LOGOR
1.1       cgd       165: %token                 T_QUEST
                    166: %token                 T_COLON
1.189     rillig    167: %token                 T_ASSIGN
1.150     rillig    168: %token <y_op>          T_OPASSIGN
1.1       cgd       169: %token                 T_COMMA
                    170: %token                 T_SEMI
1.147     rillig    171: %token                 T_ELLIPSIS
1.41      christos  172: %token                 T_REAL
                    173: %token                 T_IMAG
1.81      christos  174: %token                 T_GENERIC
1.95      christos  175: %token                 T_NORETURN
1.1       cgd       176:
                    177: /* storage classes (extern, static, auto, register and typedef) */
                    178: %token <y_scl>         T_SCLASS
                    179:
1.152     rillig    180: /*
                    181:  * predefined type keywords (char, int, short, long, unsigned, signed,
                    182:  * float, double, void); see T_TYPENAME
                    183:  */
1.1       cgd       184: %token <y_tspec>       T_TYPE
                    185:
1.152     rillig    186: /* qualifiers (const, volatile, restrict, _Thread_local) */
1.1       cgd       187: %token <y_tqual>       T_QUAL
                    188:
                    189: /* struct or union */
1.152     rillig    190: %token <y_tspec>       T_STRUCT_OR_UNION
1.1       cgd       191:
                    192: /* remaining keywords */
1.153     rillig    193: %token                 T_ASM
                    194: %token                 T_BREAK
1.1       cgd       195: %token                 T_CASE
1.153     rillig    196: %token                 T_CONTINUE
1.1       cgd       197: %token                 T_DEFAULT
1.153     rillig    198: %token                 T_DO
1.1       cgd       199: %token                 T_ELSE
1.153     rillig    200: %token                 T_ENUM
1.1       cgd       201: %token                 T_FOR
                    202: %token                 T_GOTO
1.153     rillig    203: %token                 T_IF
                    204: %token                 T_PACKED
1.1       cgd       205: %token                 T_RETURN
1.153     rillig    206: %token                 T_SWITCH
1.11      cgd       207: %token                 T_SYMBOLRENAME
1.153     rillig    208: %token                 T_WHILE
1.45      christos  209: /* Type Attributes */
                    210: %token <y_type>                T_ATTRIBUTE
1.86      christos  211: %token <y_type>                T_AT_ALIAS
1.153     rillig    212: %token <y_type>                T_AT_ALIGNED
1.101     christos  213: %token <y_type>                T_AT_ALLOC_SIZE
1.85      christos  214: %token <y_type>                T_AT_ALWAYS_INLINE
1.89      christos  215: %token <y_type>                T_AT_BOUNDED
1.91      christos  216: %token <y_type>                T_AT_BUFFER
1.84      christos  217: %token <y_type>                T_AT_COLD
                    218: %token <y_type>                T_AT_CONSTRUCTOR
1.45      christos  219: %token <y_type>                T_AT_DEPRECATED
1.100     christos  220: %token <y_type>                T_AT_DESTRUCTOR
1.84      christos  221: %token <y_type>                T_AT_FORMAT
                    222: %token <y_type>                T_AT_FORMAT_ARG
1.102     christos  223: %token <y_type>                T_AT_FORMAT_GNU_PRINTF
1.84      christos  224: %token <y_type>                T_AT_FORMAT_PRINTF
                    225: %token <y_type>                T_AT_FORMAT_SCANF
1.90      christos  226: %token <y_type>                T_AT_FORMAT_STRFMON
1.84      christos  227: %token <y_type>                T_AT_FORMAT_STRFTIME
1.96      christos  228: %token <y_type>                T_AT_FORMAT_SYSLOG
1.77      christos  229: %token <y_type>                T_AT_GNU_INLINE
1.101     christos  230: %token <y_type>                T_AT_MALLOC
1.45      christos  231: %token <y_type>                T_AT_MAY_ALIAS
1.89      christos  232: %token <y_type>                T_AT_MINBYTES
1.84      christos  233: %token <y_type>                T_AT_MODE
1.97      christos  234: %token <y_type>                T_AT_NOINLINE
1.90      christos  235: %token <y_type>                T_AT_NONNULL
1.84      christos  236: %token <y_type>                T_AT_NORETURN
1.101     christos  237: %token <y_type>                T_AT_NOTHROW
1.84      christos  238: %token <y_type>                T_AT_NO_INSTRUMENT_FUNCTION
1.105     christos  239: %token <y_type>                T_AT_OPTIMIZE
1.45      christos  240: %token <y_type>                T_AT_PACKED
1.92      christos  241: %token <y_type>                T_AT_PCS
1.61      christos  242: %token <y_type>                T_AT_PURE
1.84      christos  243: %token <y_type>                T_AT_RETURNS_TWICE
                    244: %token <y_type>                T_AT_SECTION
                    245: %token <y_type>                T_AT_SENTINEL
1.89      christos  246: %token <y_type>                T_AT_STRING
1.104     christos  247: %token <y_type>                T_AT_TLS_MODEL
1.45      christos  248: %token <y_type>                T_AT_TUNION
                    249: %token <y_type>                T_AT_UNUSED
1.84      christos  250: %token <y_type>                T_AT_USED
                    251: %token <y_type>                T_AT_VISIBILITY
1.99      christos  252: %token <y_type>                T_AT_WARN_UNUSED_RESULT
1.76      christos  253: %token <y_type>                T_AT_WEAK
1.1       cgd       254:
                    255: %left  T_COMMA
1.150     rillig    256: %right T_ASSIGN T_OPASSIGN
1.1       cgd       257: %right T_QUEST T_COLON
                    258: %left  T_LOGOR
                    259: %left  T_LOGAND
1.150     rillig    260: %left  T_BITOR
1.191     rillig    261: %left  T_BITXOR
1.145     rillig    262: %left  T_AMPER
1.150     rillig    263: %left  T_EQUALITY
                    264: %left  T_RELATIONAL
                    265: %left  T_SHIFT
                    266: %left  T_ADDITIVE
                    267: %left  T_ASTERISK T_MULTIPLICATIVE
1.192     rillig    268: %right T_UNARY T_INCDEC T_SIZEOF T_REAL T_IMAG
1.146     rillig    269: %left  T_LPAREN T_LBRACK T_MEMBACC
1.1       cgd       270:
                    271: %token <y_sb>          T_NAME
                    272: %token <y_sb>          T_TYPENAME
                    273: %token <y_val>         T_CON
1.121     rillig    274: %token <y_string>      T_STRING
1.1       cgd       275:
                    276: %type  <y_sym>         func_decl
                    277: %type  <y_sym>         notype_decl
                    278: %type  <y_sym>         type_decl
                    279: %type  <y_type>        typespec
                    280: %type  <y_type>        clrtyp_typespec
                    281: %type  <y_type>        notype_typespec
                    282: %type  <y_type>        struct_spec
                    283: %type  <y_type>        enum_spec
1.45      christos  284: %type  <y_type>        type_attribute
1.1       cgd       285: %type  <y_sym>         struct_tag
                    286: %type  <y_sym>         enum_tag
                    287: %type  <y_tspec>       struct
                    288: %type  <y_sym>         struct_declaration
                    289: %type  <y_sb>          identifier
                    290: %type  <y_sym>         member_declaration_list_with_rbrace
                    291: %type  <y_sym>         member_declaration_list
                    292: %type  <y_sym>         member_declaration
                    293: %type  <y_sym>         notype_member_decls
                    294: %type  <y_sym>         type_member_decls
                    295: %type  <y_sym>         notype_member_decl
                    296: %type  <y_sym>         type_member_decl
1.168     rillig    297: %type  <y_tnode>       constant_expr
1.1       cgd       298: %type  <y_sym>         enum_declaration
                    299: %type  <y_sym>         enums_with_opt_comma
                    300: %type  <y_sym>         enums
                    301: %type  <y_sym>         enumerator
1.135     rillig    302: %type  <y_sym>         enumeration_constant
1.1       cgd       303: %type  <y_sym>         notype_direct_decl
                    304: %type  <y_sym>         type_direct_decl
                    305: %type  <y_pqinf>       pointer
                    306: %type  <y_pqinf>       asterisk
                    307: %type  <y_sym>         param_decl
                    308: %type  <y_sym>         param_list
1.155     rillig    309: %type  <y_sym>         abstract_decl_param_list
1.1       cgd       310: %type  <y_sym>         direct_param_decl
                    311: %type  <y_sym>         notype_param_decl
                    312: %type  <y_sym>         direct_notype_param_decl
                    313: %type  <y_pqinf>       type_qualifier_list
                    314: %type  <y_pqinf>       type_qualifier
                    315: %type  <y_sym>         identifier_list
1.155     rillig    316: %type  <y_sym>         abstract_decl
                    317: %type  <y_sym>         direct_abstract_decl
1.1       cgd       318: %type  <y_sym>         vararg_parameter_type_list
                    319: %type  <y_sym>         parameter_type_list
                    320: %type  <y_sym>         parameter_declaration
                    321: %type  <y_tnode>       expr
1.133     rillig    322: %type  <y_tnode>       expr_statement_val
                    323: %type  <y_tnode>       expr_statement_list
1.1       cgd       324: %type  <y_tnode>       term
1.81      christos  325: %type  <y_tnode>       generic_expr
1.1       cgd       326: %type  <y_tnode>       func_arg_list
                    327: %type  <y_op>          point_or_arrow
                    328: %type  <y_type>        type_name
                    329: %type  <y_sym>         abstract_declaration
                    330: %type  <y_tnode>       do_while_expr
                    331: %type  <y_tnode>       opt_expr
1.121     rillig    332: %type  <y_string>      string
                    333: %type  <y_string>      string2
1.11      cgd       334: %type  <y_sb>          opt_asm_or_symbolrename
1.35      christos  335: %type  <y_range>       range
1.185     rillig    336: %type  <y_seen_statement> block_item_list
                    337: %type  <y_seen_statement> block_item
1.1       cgd       338:
                    339:
                    340: %%
                    341:
                    342: program:
                    343:          /* empty */ {
                    344:                if (sflag) {
                    345:                        /* empty translation unit */
                    346:                        error(272);
                    347:                } else if (!tflag) {
                    348:                        /* empty translation unit */
                    349:                        warning(272);
                    350:                }
                    351:          }
                    352:        | translation_unit
                    353:        ;
                    354:
1.134     rillig    355: translation_unit:              /* C99 6.9 */
                    356:          external_declaration
                    357:        | translation_unit external_declaration
1.1       cgd       358:        ;
                    359:
1.134     rillig    360: external_declaration:          /* C99 6.9 */
1.133     rillig    361:          asm_statement
1.134     rillig    362:        | function_definition {
1.183     rillig    363:                global_clean_up_decl(false);
1.187     rillig    364:                clear_warning_flags();
1.1       cgd       365:          }
1.193     rillig    366:        | top_level_declaration {
1.183     rillig    367:                global_clean_up_decl(false);
1.187     rillig    368:                clear_warning_flags();
1.1       cgd       369:          }
                    370:        ;
                    371:
1.193     rillig    372: /*
                    373:  * On the top level, lint allows several forms of declarations that it doesn't
                    374:  * allow in functions.  For example, a single ';' is an empty declaration and
                    375:  * is supported by some compilers, but in a function it would be an empty
                    376:  * statement, not a declaration.  This makes a difference in C90 mode, where
                    377:  * a statement must not be followed by a declaration.
                    378:  *
                    379:  * See 'declaration' for all other declarations.
                    380:  */
                    381: top_level_declaration:         /* C99 6.9 calls this 'declaration' */
1.1       cgd       382:          T_SEMI {
                    383:                if (sflag) {
1.123     rillig    384:                        /* empty declaration */
1.1       cgd       385:                        error(0);
                    386:                } else if (!tflag) {
1.123     rillig    387:                        /* empty declaration */
1.1       cgd       388:                        warning(0);
                    389:                }
                    390:          }
                    391:        | clrtyp deftyp notype_init_decls T_SEMI {
                    392:                if (sflag) {
1.159     rillig    393:                        /* old style declaration; add 'int' */
1.1       cgd       394:                        error(1);
                    395:                } else if (!tflag) {
1.159     rillig    396:                        /* old style declaration; add 'int' */
1.1       cgd       397:                        warning(1);
                    398:                }
                    399:          }
                    400:        | declmods deftyp T_SEMI {
1.3       jpo       401:                if (dcs->d_scl == TYPEDEF) {
1.1       cgd       402:                        /* typedef declares no type name */
                    403:                        warning(72);
                    404:                } else {
                    405:                        /* empty declaration */
                    406:                        warning(2);
                    407:                }
                    408:          }
                    409:        | declmods deftyp notype_init_decls T_SEMI
1.194     rillig    410:        | declaration_specifiers deftyp T_SEMI {
1.3       jpo       411:                if (dcs->d_scl == TYPEDEF) {
1.1       cgd       412:                        /* typedef declares no type name */
                    413:                        warning(72);
1.195     rillig    414:                } else if (!dcs->d_nonempty_decl) {
1.1       cgd       415:                        /* empty declaration */
                    416:                        warning(2);
                    417:                }
                    418:          }
1.194     rillig    419:        | declaration_specifiers deftyp type_init_decls T_SEMI
1.1       cgd       420:        | error T_SEMI {
1.114     rillig    421:                global_clean_up();
1.1       cgd       422:          }
                    423:        | error T_RBRACE {
1.114     rillig    424:                global_clean_up();
1.1       cgd       425:          }
                    426:        ;
                    427:
1.134     rillig    428: function_definition:           /* C99 6.9.1 */
1.1       cgd       429:          func_decl {
                    430:                if ($1->s_type->t_tspec != FUNC) {
1.123     rillig    431:                        /* syntax error '%s' */
1.41      christos  432:                        error(249, yytext);
1.1       cgd       433:                        YYERROR;
                    434:                }
                    435:                if ($1->s_type->t_typedef) {
                    436:                        /* ()-less function definition */
                    437:                        error(64);
                    438:                        YYERROR;
                    439:                }
                    440:                funcdef($1);
1.171     rillig    441:                block_level++;
1.202     rillig    442:                begin_declaration_level(ARG);
1.55      christos  443:                if (lwarn == LWARN_NONE)
1.140     rillig    444:                        $1->s_used = true;
1.134     rillig    445:          } arg_declaration_list_opt {
1.202     rillig    446:                end_declaration_level();
1.171     rillig    447:                block_level--;
1.122     rillig    448:                check_func_lint_directives();
                    449:                check_func_old_style_arguments();
1.203     rillig    450:                begin_control_statement(CS_FUNCTION_BODY);
1.133     rillig    451:          } compound_statement {
1.1       cgd       452:                funcend();
1.203     rillig    453:                end_control_statement(CS_FUNCTION_BODY);
1.1       cgd       454:          }
                    455:        ;
                    456:
                    457: func_decl:
                    458:          clrtyp deftyp notype_decl {
                    459:                $$ = $3;
                    460:          }
                    461:        | declmods deftyp notype_decl {
                    462:                $$ = $3;
                    463:          }
1.194     rillig    464:        | declaration_specifiers deftyp type_decl {
1.1       cgd       465:                $$ = $3;
                    466:          }
                    467:        ;
                    468:
1.193     rillig    469: arg_declaration_list_opt:      /* C99 6.9.1p13 example 1 */
1.1       cgd       470:          /* empty */
                    471:        | arg_declaration_list
                    472:        ;
                    473:
1.193     rillig    474: arg_declaration_list:          /* C99 6.9.1p13 example 1 */
1.1       cgd       475:          arg_declaration
                    476:        | arg_declaration_list arg_declaration
                    477:        /* XXX or better "arg_declaration error" ? */
                    478:        | error
                    479:        ;
                    480:
                    481: /*
                    482:  * "arg_declaration" is separated from "declaration" because it
                    483:  * needs other error handling.
                    484:  */
                    485: arg_declaration:
                    486:          declmods deftyp T_SEMI {
                    487:                /* empty declaration */
                    488:                warning(2);
                    489:          }
                    490:        | declmods deftyp notype_init_decls T_SEMI
1.194     rillig    491:        | declaration_specifiers deftyp T_SEMI {
1.195     rillig    492:                if (!dcs->d_nonempty_decl) {
1.1       cgd       493:                        /* empty declaration */
                    494:                        warning(2);
                    495:                } else {
1.158     rillig    496:                        /* '%s' declared in argument declaration list */
                    497:                        warning(3, type_name(dcs->d_type));
1.1       cgd       498:                }
                    499:          }
1.194     rillig    500:        | declaration_specifiers deftyp type_init_decls T_SEMI {
1.195     rillig    501:                if (dcs->d_nonempty_decl) {
1.158     rillig    502:                        /* '%s' declared in argument declaration list */
                    503:                        warning(3, type_name(dcs->d_type));
1.1       cgd       504:                }
                    505:          }
                    506:        | declmods error
1.194     rillig    507:        | declaration_specifiers error
1.1       cgd       508:        ;
                    509:
1.193     rillig    510: declaration:                   /* C99 6.7 */
1.1       cgd       511:          declmods deftyp T_SEMI {
1.3       jpo       512:                if (dcs->d_scl == TYPEDEF) {
1.1       cgd       513:                        /* typedef declares no type name */
                    514:                        warning(72);
                    515:                } else {
                    516:                        /* empty declaration */
                    517:                        warning(2);
                    518:                }
                    519:          }
                    520:        | declmods deftyp notype_init_decls T_SEMI
1.194     rillig    521:        | declaration_specifiers deftyp T_SEMI {
1.3       jpo       522:                if (dcs->d_scl == TYPEDEF) {
1.1       cgd       523:                        /* typedef declares no type name */
                    524:                        warning(72);
1.195     rillig    525:                } else if (!dcs->d_nonempty_decl) {
1.1       cgd       526:                        /* empty declaration */
                    527:                        warning(2);
                    528:                }
                    529:          }
1.194     rillig    530:        | declaration_specifiers deftyp type_init_decls T_SEMI
1.1       cgd       531:        | error T_SEMI
                    532:        ;
                    533:
1.61      christos  534: type_attribute_format_type:
1.102     christos  535:          T_AT_FORMAT_GNU_PRINTF
                    536:        | T_AT_FORMAT_PRINTF
1.61      christos  537:        | T_AT_FORMAT_SCANF
1.84      christos  538:        | T_AT_FORMAT_STRFMON
1.61      christos  539:        | T_AT_FORMAT_STRFTIME
1.96      christos  540:        | T_AT_FORMAT_SYSLOG
1.61      christos  541:        ;
                    542:
1.91      christos  543: type_attribute_bounded_type:
                    544:          T_AT_MINBYTES
                    545:        | T_AT_STRING
                    546:        | T_AT_BUFFER
                    547:        ;
                    548:
1.98      christos  549:
1.45      christos  550: type_attribute_spec:
1.109     rillig    551:          /* empty */
1.126     rillig    552:        | T_AT_DEPRECATED T_LPAREN string T_RPAREN
1.91      christos  553:        | T_AT_DEPRECATED
1.168     rillig    554:        | T_AT_ALIGNED T_LPAREN constant_expr T_RPAREN
                    555:        | T_AT_ALLOC_SIZE T_LPAREN constant_expr T_COMMA constant_expr T_RPAREN
                    556:        | T_AT_ALLOC_SIZE T_LPAREN constant_expr T_RPAREN
1.126     rillig    557:        | T_AT_BOUNDED T_LPAREN type_attribute_bounded_type
1.168     rillig    558:          T_COMMA constant_expr T_COMMA constant_expr T_RPAREN
                    559:        | T_AT_SENTINEL T_LPAREN constant_expr T_RPAREN
1.106     christos  560:        | T_AT_SENTINEL
1.168     rillig    561:        | T_AT_FORMAT_ARG T_LPAREN constant_expr T_RPAREN
                    562:        | T_AT_NONNULL T_LPAREN constant_expr T_RPAREN
1.126     rillig    563:        | T_AT_MODE T_LPAREN T_NAME T_RPAREN
                    564:        | T_AT_ALIAS T_LPAREN string T_RPAREN
                    565:        | T_AT_OPTIMIZE T_LPAREN string T_RPAREN
                    566:        | T_AT_PCS T_LPAREN string T_RPAREN
                    567:        | T_AT_SECTION T_LPAREN string T_RPAREN
                    568:        | T_AT_TLS_MODEL T_LPAREN string T_RPAREN
1.109     rillig    569:        | T_AT_ALIGNED
                    570:        | T_AT_CONSTRUCTOR
                    571:        | T_AT_DESTRUCTOR
1.101     christos  572:        | T_AT_MALLOC
1.45      christos  573:        | T_AT_MAY_ALIAS
1.84      christos  574:        | T_AT_NO_INSTRUMENT_FUNCTION
1.97      christos  575:        | T_AT_NOINLINE
1.61      christos  576:        | T_AT_NORETURN
1.101     christos  577:        | T_AT_NOTHROW
1.65      christos  578:        | T_AT_COLD
                    579:        | T_AT_RETURNS_TWICE
1.45      christos  580:        | T_AT_PACKED {
                    581:                addpacked();
1.130     rillig    582:          }
1.61      christos  583:        | T_AT_PURE
1.45      christos  584:        | T_AT_TUNION
1.77      christos  585:        | T_AT_GNU_INLINE
1.85      christos  586:        | T_AT_ALWAYS_INLINE
1.126     rillig    587:        | T_AT_FORMAT T_LPAREN type_attribute_format_type T_COMMA
1.168     rillig    588:            constant_expr T_COMMA constant_expr T_RPAREN
1.84      christos  589:        | T_AT_USED {
1.114     rillig    590:                add_attr_used();
1.130     rillig    591:          }
1.82      christos  592:        | T_AT_UNUSED {
1.114     rillig    593:                add_attr_used();
1.130     rillig    594:          }
1.99      christos  595:        | T_AT_WARN_UNUSED_RESULT
1.76      christos  596:        | T_AT_WEAK
1.168     rillig    597:        | T_AT_VISIBILITY T_LPAREN constant_expr T_RPAREN
1.62      christos  598:        | T_QUAL {
1.109     rillig    599:                if ($1 != CONST)
1.62      christos  600:                        yyerror("Bad attribute");
1.130     rillig    601:          }
1.45      christos  602:        ;
                    603:
1.84      christos  604: type_attribute_spec_list:
                    605:          type_attribute_spec
                    606:        | type_attribute_spec_list T_COMMA type_attribute_spec
                    607:        ;
                    608:
1.199     christos  609: align_as:
                    610:          typespec
                    611:        | constant_expr
                    612:        ;
                    613:
1.45      christos  614: type_attribute:
1.126     rillig    615:          T_ATTRIBUTE T_LPAREN T_LPAREN {
1.140     rillig    616:            attron = true;
1.130     rillig    617:          } type_attribute_spec_list {
1.140     rillig    618:            attron = false;
1.130     rillig    619:          } T_RPAREN T_RPAREN
1.199     christos  620:        | T_ALIGNAS T_LPAREN align_as T_RPAREN {
                    621:          }
1.45      christos  622:        | T_PACKED {
                    623:                addpacked();
1.130     rillig    624:          }
1.95      christos  625:        | T_NORETURN {
1.130     rillig    626:          }
1.45      christos  627:        ;
                    628:
1.87      christos  629: type_attribute_list:
                    630:          type_attribute
                    631:        | type_attribute_list type_attribute
                    632:        ;
                    633:
1.1       cgd       634: clrtyp:
1.110     rillig    635:          /* empty */ {
1.1       cgd       636:                clrtyp();
                    637:          }
                    638:        ;
                    639:
                    640: deftyp:
                    641:          /* empty */ {
                    642:                deftyp();
                    643:          }
                    644:        ;
                    645:
1.194     rillig    646: declaration_specifiers:                /* C99 6.7 */
1.1       cgd       647:          clrtyp_typespec {
1.114     rillig    648:                add_type($1);
1.1       cgd       649:          }
                    650:        | declmods typespec {
1.114     rillig    651:                add_type($2);
1.1       cgd       652:          }
1.194     rillig    653:        | type_attribute declaration_specifiers
                    654:        | declaration_specifiers declmod
                    655:        | declaration_specifiers notype_typespec {
1.114     rillig    656:                add_type($2);
1.1       cgd       657:          }
                    658:        ;
                    659:
                    660: declmods:
                    661:          clrtyp T_QUAL {
1.114     rillig    662:                add_qualifier($2);
1.1       cgd       663:          }
                    664:        | clrtyp T_SCLASS {
1.114     rillig    665:                add_storage_class($2);
1.1       cgd       666:          }
                    667:        | declmods declmod
                    668:        ;
                    669:
                    670: declmod:
                    671:          T_QUAL {
1.114     rillig    672:                add_qualifier($1);
1.1       cgd       673:          }
                    674:        | T_SCLASS {
1.114     rillig    675:                add_storage_class($1);
1.1       cgd       676:          }
1.87      christos  677:        | type_attribute_list
1.1       cgd       678:        ;
                    679:
                    680: clrtyp_typespec:
                    681:          clrtyp notype_typespec {
                    682:                $$ = $2;
                    683:          }
                    684:        | T_TYPENAME clrtyp {
                    685:                $$ = getsym($1)->s_type;
                    686:          }
                    687:        ;
                    688:
                    689: typespec:
                    690:          notype_typespec {
                    691:                $$ = $1;
                    692:          }
                    693:        | T_TYPENAME {
                    694:                $$ = getsym($1)->s_type;
                    695:          }
                    696:        ;
                    697:
                    698: notype_typespec:
                    699:          T_TYPE {
                    700:                $$ = gettyp($1);
                    701:          }
1.60      christos  702:        | T_TYPEOF term {
                    703:                $$ = $2->tn_type;
1.58      christos  704:          }
1.1       cgd       705:        | struct_spec {
1.202     rillig    706:                end_declaration_level();
1.1       cgd       707:                $$ = $1;
                    708:          }
                    709:        | enum_spec {
1.202     rillig    710:                end_declaration_level();
1.1       cgd       711:                $$ = $1;
                    712:          }
                    713:        ;
                    714:
                    715: struct_spec:
                    716:          struct struct_tag {
                    717:                /*
                    718:                 * STDC requires that "struct a;" always introduces
                    719:                 * a new tag if "a" is not declared at current level
                    720:                 *
1.110     rillig    721:                 * yychar is valid because otherwise the parser would not
                    722:                 * have been able to decide if it must shift or reduce
1.1       cgd       723:                 */
1.183     rillig    724:                $$ = mktag($2, $1, false, yychar == T_SEMI);
1.1       cgd       725:          }
                    726:        | struct struct_tag {
1.183     rillig    727:                dcs->d_tagtyp = mktag($2, $1, true, false);
1.1       cgd       728:          } struct_declaration {
1.116     rillig    729:                $$ = complete_tag_struct_or_union(dcs->d_tagtyp, $4);
1.1       cgd       730:          }
                    731:        | struct {
1.183     rillig    732:                dcs->d_tagtyp = mktag(NULL, $1, true, false);
1.1       cgd       733:          } struct_declaration {
1.116     rillig    734:                $$ = complete_tag_struct_or_union(dcs->d_tagtyp, $3);
1.1       cgd       735:          }
                    736:        | struct error {
                    737:                symtyp = FVFT;
                    738:                $$ = gettyp(INT);
                    739:          }
                    740:        ;
                    741:
                    742: struct:
1.46      christos  743:          struct type_attribute
1.152     rillig    744:        | T_STRUCT_OR_UNION {
1.1       cgd       745:                symtyp = FTAG;
1.202     rillig    746:                begin_declaration_level($1 == STRUCT ? MOS : MOU);
1.3       jpo       747:                dcs->d_offset = 0;
1.136     rillig    748:                dcs->d_stralign = CHAR_SIZE;
1.1       cgd       749:                $$ = $1;
                    750:          }
                    751:        ;
                    752:
                    753: struct_tag:
                    754:          identifier {
                    755:                $$ = getsym($1);
                    756:          }
                    757:        ;
                    758:
                    759: struct_declaration:
                    760:          struct_decl_lbrace member_declaration_list_with_rbrace {
                    761:                $$ = $2;
                    762:          }
                    763:        ;
                    764:
                    765: struct_decl_lbrace:
                    766:          T_LBRACE {
                    767:                symtyp = FVFT;
                    768:          }
                    769:        ;
                    770:
                    771: member_declaration_list_with_rbrace:
                    772:          member_declaration_list T_SEMI T_RBRACE {
                    773:                $$ = $1;
                    774:          }
                    775:        | member_declaration_list T_RBRACE {
                    776:                if (sflag) {
1.123     rillig    777:                        /* syntax req. ';' after last struct/union member */
1.1       cgd       778:                        error(66);
                    779:                } else {
1.123     rillig    780:                        /* syntax req. ';' after last struct/union member */
1.1       cgd       781:                        warning(66);
                    782:                }
                    783:                $$ = $1;
                    784:          }
                    785:        | T_RBRACE {
                    786:                $$ = NULL;
                    787:          }
                    788:        ;
                    789:
1.83      christos  790: opt_type_attribute:
1.91      christos  791:          /* empty */
1.83      christos  792:        | type_attribute
                    793:        ;
                    794:
1.1       cgd       795: member_declaration_list:
                    796:          member_declaration {
                    797:                $$ = $1;
                    798:          }
                    799:        | member_declaration_list T_SEMI member_declaration {
                    800:                $$ = lnklst($1, $3);
                    801:          }
                    802:        ;
                    803:
                    804: member_declaration:
                    805:          noclass_declmods deftyp {
                    806:                /* too late, i know, but getsym() compensates it */
1.120     rillig    807:                symtyp = FMEMBER;
1.83      christos  808:          } notype_member_decls opt_type_attribute {
1.1       cgd       809:                symtyp = FVFT;
                    810:                $$ = $4;
                    811:          }
                    812:        | noclass_declspecs deftyp {
1.120     rillig    813:                symtyp = FMEMBER;
1.83      christos  814:          } type_member_decls opt_type_attribute {
1.1       cgd       815:                symtyp = FVFT;
                    816:                $$ = $4;
                    817:          }
1.83      christos  818:        | noclass_declmods deftyp opt_type_attribute {
1.74      christos  819:                symtyp = FVFT;
1.1       cgd       820:                /* struct or union member must be named */
1.73      christos  821:                if (!Sflag)
1.127     rillig    822:                        /* anonymous struct/union members is a C9X feature */
1.73      christos  823:                        warning(49);
                    824:                /* add all the members of the anonymous struct/union */
1.161     rillig    825:                $$ = dcs->d_type->t_str->sou_first_member;
1.73      christos  826:                anonymize($$);
1.1       cgd       827:          }
1.83      christos  828:        | noclass_declspecs deftyp opt_type_attribute {
1.74      christos  829:                symtyp = FVFT;
1.1       cgd       830:                /* struct or union member must be named */
1.73      christos  831:                if (!Sflag)
1.127     rillig    832:                        /* anonymous struct/union members is a C9X feature */
1.73      christos  833:                        warning(49);
1.161     rillig    834:                $$ = dcs->d_type->t_str->sou_first_member;
1.73      christos  835:                /* add all the members of the anonymous struct/union */
                    836:                anonymize($$);
1.1       cgd       837:          }
                    838:        | error {
                    839:                symtyp = FVFT;
                    840:                $$ = NULL;
                    841:          }
                    842:        ;
                    843:
                    844: noclass_declspecs:
                    845:          clrtyp_typespec {
1.114     rillig    846:                add_type($1);
1.1       cgd       847:          }
1.63      christos  848:        | type_attribute noclass_declspecs
1.1       cgd       849:        | noclass_declmods typespec {
1.114     rillig    850:                add_type($2);
1.1       cgd       851:          }
                    852:        | noclass_declspecs T_QUAL {
1.114     rillig    853:                add_qualifier($2);
1.1       cgd       854:          }
                    855:        | noclass_declspecs notype_typespec {
1.114     rillig    856:                add_type($2);
1.1       cgd       857:          }
1.48      christos  858:        | noclass_declspecs type_attribute
1.1       cgd       859:        ;
                    860:
                    861: noclass_declmods:
                    862:          clrtyp T_QUAL {
1.114     rillig    863:                add_qualifier($2);
1.1       cgd       864:          }
                    865:        | noclass_declmods T_QUAL {
1.114     rillig    866:                add_qualifier($2);
1.1       cgd       867:          }
                    868:        ;
                    869:
                    870: notype_member_decls:
                    871:          notype_member_decl {
1.111     rillig    872:                $$ = declarator_1_struct_union($1);
1.1       cgd       873:          }
                    874:        | notype_member_decls {
1.120     rillig    875:                symtyp = FMEMBER;
1.1       cgd       876:          } T_COMMA type_member_decl {
1.111     rillig    877:                $$ = lnklst($1, declarator_1_struct_union($4));
1.1       cgd       878:          }
                    879:        ;
                    880:
                    881: type_member_decls:
                    882:          type_member_decl {
1.111     rillig    883:                $$ = declarator_1_struct_union($1);
1.1       cgd       884:          }
                    885:        | type_member_decls {
1.120     rillig    886:                symtyp = FMEMBER;
1.1       cgd       887:          } T_COMMA type_member_decl {
1.111     rillig    888:                $$ = lnklst($1, declarator_1_struct_union($4));
1.1       cgd       889:          }
                    890:        ;
                    891:
                    892: notype_member_decl:
                    893:          notype_decl {
                    894:                $$ = $1;
                    895:          }
1.168     rillig    896:        | notype_decl T_COLON constant_expr {           /* C99 6.7.2.1 */
1.175     rillig    897:                $$ = bitfield($1, to_int_constant($3, true));
1.1       cgd       898:          }
                    899:        | {
                    900:                symtyp = FVFT;
1.168     rillig    901:          } T_COLON constant_expr {                     /* C99 6.7.2.1 */
1.175     rillig    902:                $$ = bitfield(NULL, to_int_constant($3, true));
1.1       cgd       903:          }
                    904:        ;
                    905:
                    906: type_member_decl:
                    907:          type_decl {
                    908:                $$ = $1;
                    909:          }
1.168     rillig    910:        | type_decl T_COLON constant_expr {
1.175     rillig    911:                $$ = bitfield($1, to_int_constant($3, true));
1.1       cgd       912:          }
                    913:        | {
                    914:                symtyp = FVFT;
1.168     rillig    915:          } T_COLON constant_expr {
1.175     rillig    916:                $$ = bitfield(NULL, to_int_constant($3, true));
1.1       cgd       917:          }
                    918:        ;
                    919:
                    920: enum_spec:
                    921:          enum enum_tag {
1.183     rillig    922:                $$ = mktag($2, ENUM, false, false);
1.1       cgd       923:          }
                    924:        | enum enum_tag {
1.183     rillig    925:                dcs->d_tagtyp = mktag($2, ENUM, true, false);
1.1       cgd       926:          } enum_declaration {
1.116     rillig    927:                $$ = complete_tag_enum(dcs->d_tagtyp, $4);
1.1       cgd       928:          }
                    929:        | enum {
1.183     rillig    930:                dcs->d_tagtyp = mktag(NULL, ENUM, true, false);
1.1       cgd       931:          } enum_declaration {
1.116     rillig    932:                $$ = complete_tag_enum(dcs->d_tagtyp, $3);
1.1       cgd       933:          }
                    934:        | enum error {
                    935:                symtyp = FVFT;
                    936:                $$ = gettyp(INT);
                    937:          }
                    938:        ;
                    939:
                    940: enum:
                    941:          T_ENUM {
                    942:                symtyp = FTAG;
1.202     rillig    943:                begin_declaration_level(CTCONST);
1.1       cgd       944:          }
                    945:        ;
                    946:
                    947: enum_tag:
                    948:          identifier {
                    949:                $$ = getsym($1);
                    950:          }
                    951:        ;
                    952:
                    953: enum_declaration:
                    954:          enum_decl_lbrace enums_with_opt_comma T_RBRACE {
                    955:                $$ = $2;
                    956:          }
                    957:        ;
                    958:
                    959: enum_decl_lbrace:
                    960:          T_LBRACE {
                    961:                symtyp = FVFT;
                    962:                enumval = 0;
                    963:          }
                    964:        ;
                    965:
                    966: enums_with_opt_comma:
                    967:          enums {
                    968:                $$ = $1;
                    969:          }
                    970:        | enums T_COMMA {
                    971:                if (sflag) {
1.123     rillig    972:                        /* trailing ',' prohibited in enum declaration */
1.1       cgd       973:                        error(54);
                    974:                } else {
1.123     rillig    975:                        /* trailing ',' prohibited in enum declaration */
1.51      njoly     976:                        c99ism(54);
1.1       cgd       977:                }
                    978:                $$ = $1;
                    979:          }
                    980:        ;
                    981:
                    982: enums:
                    983:          enumerator {
                    984:                $$ = $1;
                    985:          }
                    986:        | enums T_COMMA enumerator {
                    987:                $$ = lnklst($1, $3);
                    988:          }
                    989:        | error {
                    990:                $$ = NULL;
                    991:          }
                    992:        ;
                    993:
                    994: enumerator:
1.135     rillig    995:          enumeration_constant {
1.183     rillig    996:                $$ = enumeration_constant($1, enumval, true);
1.1       cgd       997:          }
1.168     rillig    998:        | enumeration_constant T_ASSIGN constant_expr {
1.183     rillig    999:                $$ = enumeration_constant($1, to_int_constant($3, true), false);
1.1       cgd      1000:          }
                   1001:        ;
                   1002:
1.135     rillig   1003: enumeration_constant:          /* C99 6.4.4.3 */
1.1       cgd      1004:          identifier {
                   1005:                $$ = getsym($1);
                   1006:          }
                   1007:        ;
                   1008:
                   1009:
                   1010: notype_init_decls:
                   1011:          notype_init_decl
                   1012:        | notype_init_decls T_COMMA type_init_decl
                   1013:        ;
                   1014:
                   1015: type_init_decls:
                   1016:          type_init_decl
                   1017:        | type_init_decls T_COMMA type_init_decl
                   1018:        ;
                   1019:
                   1020: notype_init_decl:
1.110     rillig   1021:          notype_decl opt_asm_or_symbolrename {
1.174     rillig   1022:                cgram_declare($1, false, $2);
1.111     rillig   1023:                check_size($1);
1.1       cgd      1024:          }
1.11      cgd      1025:        | notype_decl opt_asm_or_symbolrename {
1.198     rillig   1026:                begin_initialization($1);
1.174     rillig   1027:                cgram_declare($1, true, $2);
1.198     rillig   1028:          } T_ASSIGN initializer {
1.111     rillig   1029:                check_size($1);
1.198     rillig   1030:                end_initialization();
1.1       cgd      1031:          }
                   1032:        ;
                   1033:
                   1034: type_init_decl:
1.110     rillig   1035:          type_decl opt_asm_or_symbolrename {
1.174     rillig   1036:                cgram_declare($1, false, $2);
1.111     rillig   1037:                check_size($1);
1.1       cgd      1038:          }
1.11      cgd      1039:        | type_decl opt_asm_or_symbolrename {
1.198     rillig   1040:                begin_initialization($1);
1.174     rillig   1041:                cgram_declare($1, true, $2);
1.198     rillig   1042:          } T_ASSIGN initializer {
1.111     rillig   1043:                check_size($1);
1.198     rillig   1044:                end_initialization();
1.1       cgd      1045:          }
                   1046:        ;
                   1047:
                   1048: notype_decl:
                   1049:          notype_direct_decl {
                   1050:                $$ = $1;
                   1051:          }
                   1052:        | pointer notype_direct_decl {
1.111     rillig   1053:                $$ = add_pointer($2, $1);
1.1       cgd      1054:          }
                   1055:        ;
                   1056:
                   1057: notype_direct_decl:
                   1058:          T_NAME {
1.111     rillig   1059:                $$ = declarator_name(getsym($1));
1.1       cgd      1060:          }
1.126     rillig   1061:        | T_LPAREN type_decl T_RPAREN {
1.1       cgd      1062:                $$ = $2;
                   1063:          }
1.63      christos 1064:        | type_attribute notype_direct_decl {
                   1065:                $$ = $2;
1.130     rillig   1066:          }
1.1       cgd      1067:        | notype_direct_decl T_LBRACK T_RBRACK {
1.183     rillig   1068:                $$ = add_array($1, false, 0);
1.1       cgd      1069:          }
1.168     rillig   1070:        | notype_direct_decl T_LBRACK constant_expr T_RBRACK {
1.183     rillig   1071:                $$ = add_array($1, true, to_int_constant($3, false));
1.1       cgd      1072:          }
1.64      christos 1073:        | notype_direct_decl param_list opt_asm_or_symbolrename {
1.111     rillig   1074:                $$ = add_function(symbolrename($1, $3), $2);
1.202     rillig   1075:                end_declaration_level();
1.171     rillig   1076:                block_level--;
1.1       cgd      1077:          }
1.87      christos 1078:        | notype_direct_decl type_attribute_list
1.1       cgd      1079:        ;
                   1080:
                   1081: type_decl:
                   1082:          type_direct_decl {
                   1083:                $$ = $1;
                   1084:          }
                   1085:        | pointer type_direct_decl {
1.111     rillig   1086:                $$ = add_pointer($2, $1);
1.1       cgd      1087:          }
                   1088:        ;
                   1089:
                   1090: type_direct_decl:
                   1091:          identifier {
1.111     rillig   1092:                $$ = declarator_name(getsym($1));
1.1       cgd      1093:          }
1.126     rillig   1094:        | T_LPAREN type_decl T_RPAREN {
1.1       cgd      1095:                $$ = $2;
                   1096:          }
1.63      christos 1097:        | type_attribute type_direct_decl {
                   1098:                $$ = $2;
1.130     rillig   1099:          }
1.1       cgd      1100:        | type_direct_decl T_LBRACK T_RBRACK {
1.183     rillig   1101:                $$ = add_array($1, false, 0);
1.1       cgd      1102:          }
1.168     rillig   1103:        | type_direct_decl T_LBRACK constant_expr T_RBRACK {
1.183     rillig   1104:                $$ = add_array($1, true, to_int_constant($3, false));
1.1       cgd      1105:          }
1.64      christos 1106:        | type_direct_decl param_list opt_asm_or_symbolrename {
1.111     rillig   1107:                $$ = add_function(symbolrename($1, $3), $2);
1.202     rillig   1108:                end_declaration_level();
1.171     rillig   1109:                block_level--;
1.1       cgd      1110:          }
1.87      christos 1111:        | type_direct_decl type_attribute_list
1.1       cgd      1112:        ;
                   1113:
                   1114: /*
                   1115:  * param_decl and notype_param_decl exist to avoid a conflict in
                   1116:  * argument lists. A typename enclosed in parens should always be
                   1117:  * treated as a typename, not an argument.
                   1118:  * "typedef int a; f(int (a));" is  "typedef int a; f(int foo(a));"
                   1119:  *                             not "typedef int a; f(int a);"
                   1120:  */
                   1121: param_decl:
                   1122:          direct_param_decl {
                   1123:                $$ = $1;
                   1124:          }
                   1125:        | pointer direct_param_decl {
1.111     rillig   1126:                $$ = add_pointer($2, $1);
1.1       cgd      1127:          }
                   1128:        ;
                   1129:
                   1130: direct_param_decl:
1.87      christos 1131:          identifier type_attribute_list {
1.111     rillig   1132:                $$ = declarator_name(getsym($1));
1.78      christos 1133:          }
                   1134:        | identifier {
1.111     rillig   1135:                $$ = declarator_name(getsym($1));
1.1       cgd      1136:          }
1.126     rillig   1137:        | T_LPAREN notype_param_decl T_RPAREN {
1.1       cgd      1138:                $$ = $2;
                   1139:          }
                   1140:        | direct_param_decl T_LBRACK T_RBRACK {
1.183     rillig   1141:                $$ = add_array($1, false, 0);
1.1       cgd      1142:          }
1.168     rillig   1143:        | direct_param_decl T_LBRACK constant_expr T_RBRACK {
1.183     rillig   1144:                $$ = add_array($1, true, to_int_constant($3, false));
1.1       cgd      1145:          }
1.64      christos 1146:        | direct_param_decl param_list opt_asm_or_symbolrename {
1.111     rillig   1147:                $$ = add_function(symbolrename($1, $3), $2);
1.202     rillig   1148:                end_declaration_level();
1.171     rillig   1149:                block_level--;
1.1       cgd      1150:          }
                   1151:        ;
                   1152:
                   1153: notype_param_decl:
                   1154:          direct_notype_param_decl {
                   1155:                $$ = $1;
                   1156:          }
                   1157:        | pointer direct_notype_param_decl {
1.111     rillig   1158:                $$ = add_pointer($2, $1);
1.1       cgd      1159:          }
                   1160:        ;
                   1161:
                   1162: direct_notype_param_decl:
1.68      christos 1163:          identifier {
1.111     rillig   1164:                $$ = declarator_name(getsym($1));
1.1       cgd      1165:          }
1.126     rillig   1166:        | T_LPAREN notype_param_decl T_RPAREN {
1.1       cgd      1167:                $$ = $2;
                   1168:          }
                   1169:        | direct_notype_param_decl T_LBRACK T_RBRACK {
1.183     rillig   1170:                $$ = add_array($1, false, 0);
1.1       cgd      1171:          }
1.168     rillig   1172:        | direct_notype_param_decl T_LBRACK constant_expr T_RBRACK {
1.183     rillig   1173:                $$ = add_array($1, true, to_int_constant($3, false));
1.1       cgd      1174:          }
1.64      christos 1175:        | direct_notype_param_decl param_list opt_asm_or_symbolrename {
1.111     rillig   1176:                $$ = add_function(symbolrename($1, $3), $2);
1.202     rillig   1177:                end_declaration_level();
1.171     rillig   1178:                block_level--;
1.1       cgd      1179:          }
                   1180:        ;
                   1181:
                   1182: pointer:
                   1183:          asterisk {
                   1184:                $$ = $1;
                   1185:          }
                   1186:        | asterisk type_qualifier_list {
1.111     rillig   1187:                $$ = merge_pointers_and_qualifiers($1, $2);
1.1       cgd      1188:          }
                   1189:        | asterisk pointer {
1.111     rillig   1190:                $$ = merge_pointers_and_qualifiers($1, $2);
1.1       cgd      1191:          }
                   1192:        | asterisk type_qualifier_list pointer {
1.118     rillig   1193:                $$ = merge_pointers_and_qualifiers($1, $2);
                   1194:                $$ = merge_pointers_and_qualifiers($$, $3);
1.1       cgd      1195:          }
                   1196:        ;
                   1197:
                   1198: asterisk:
1.132     rillig   1199:          T_ASTERISK {
1.204     rillig   1200:                $$ = xcalloc(1, sizeof *$$);
1.1       cgd      1201:                $$->p_pcnt = 1;
                   1202:          }
                   1203:        ;
                   1204:
                   1205: type_qualifier_list:
                   1206:          type_qualifier {
                   1207:                $$ = $1;
                   1208:          }
                   1209:        | type_qualifier_list type_qualifier {
1.111     rillig   1210:                $$ = merge_pointers_and_qualifiers($1, $2);
1.1       cgd      1211:          }
                   1212:        ;
                   1213:
                   1214: type_qualifier:
                   1215:          T_QUAL {
1.204     rillig   1216:                $$ = xcalloc(1, sizeof *$$);
1.5       jpo      1217:                if ($1 == CONST) {
1.140     rillig   1218:                        $$->p_const = true;
1.151     rillig   1219:                } else if ($1 == VOLATILE) {
                   1220:                        $$->p_volatile = true;
1.1       cgd      1221:                } else {
1.151     rillig   1222:                        lint_assert($1 == RESTRICT || $1 == THREAD);
1.1       cgd      1223:                }
                   1224:          }
                   1225:        ;
                   1226:
                   1227: param_list:
1.170     rillig   1228:          id_list_lparen identifier_list T_RPAREN {
1.1       cgd      1229:                $$ = $2;
                   1230:          }
1.155     rillig   1231:        | abstract_decl_param_list {
1.1       cgd      1232:                $$ = $1;
                   1233:          }
                   1234:        ;
                   1235:
1.170     rillig   1236: id_list_lparen:
1.126     rillig   1237:          T_LPAREN {
1.171     rillig   1238:                block_level++;
1.202     rillig   1239:                begin_declaration_level(PROTO_ARG);
1.1       cgd      1240:          }
                   1241:        ;
                   1242:
                   1243: identifier_list:
                   1244:          T_NAME {
1.111     rillig   1245:                $$ = old_style_function_name(getsym($1));
1.1       cgd      1246:          }
                   1247:        | identifier_list T_COMMA T_NAME {
1.111     rillig   1248:                $$ = lnklst($1, old_style_function_name(getsym($3)));
1.1       cgd      1249:          }
                   1250:        | identifier_list error {
                   1251:                $$ = $1;
                   1252:          }
                   1253:        ;
                   1254:
1.155     rillig   1255: abstract_decl_param_list:
1.170     rillig   1256:          abstract_decl_lparen T_RPAREN {
1.1       cgd      1257:                $$ = NULL;
                   1258:          }
1.170     rillig   1259:        | abstract_decl_lparen vararg_parameter_type_list T_RPAREN {
1.140     rillig   1260:                dcs->d_proto = true;
1.1       cgd      1261:                $$ = $2;
                   1262:          }
1.170     rillig   1263:        | abstract_decl_lparen error T_RPAREN {
1.1       cgd      1264:                $$ = NULL;
                   1265:          }
                   1266:        ;
                   1267:
1.170     rillig   1268: abstract_decl_lparen:
1.126     rillig   1269:          T_LPAREN {
1.171     rillig   1270:                block_level++;
1.202     rillig   1271:                begin_declaration_level(PROTO_ARG);
1.1       cgd      1272:          }
                   1273:        ;
                   1274:
                   1275: vararg_parameter_type_list:
                   1276:          parameter_type_list {
                   1277:                $$ = $1;
                   1278:          }
1.147     rillig   1279:        | parameter_type_list T_COMMA T_ELLIPSIS {
1.140     rillig   1280:                dcs->d_vararg = true;
1.1       cgd      1281:                $$ = $1;
                   1282:          }
1.147     rillig   1283:        | T_ELLIPSIS {
1.1       cgd      1284:                if (sflag) {
1.123     rillig   1285:                        /* ANSI C requires formal parameter before '...' */
1.1       cgd      1286:                        error(84);
                   1287:                } else if (!tflag) {
1.123     rillig   1288:                        /* ANSI C requires formal parameter before '...' */
1.1       cgd      1289:                        warning(84);
                   1290:                }
1.140     rillig   1291:                dcs->d_vararg = true;
1.1       cgd      1292:                $$ = NULL;
                   1293:          }
                   1294:        ;
                   1295:
                   1296: parameter_type_list:
1.11      cgd      1297:          parameter_declaration {
1.1       cgd      1298:                $$ = $1;
                   1299:          }
1.11      cgd      1300:        | parameter_type_list T_COMMA parameter_declaration {
1.1       cgd      1301:                $$ = lnklst($1, $3);
                   1302:          }
                   1303:        ;
                   1304:
                   1305: parameter_declaration:
                   1306:          declmods deftyp {
1.183     rillig   1307:                $$ = declare_argument(abstract_name(), false);
1.1       cgd      1308:          }
1.194     rillig   1309:        | declaration_specifiers deftyp {
1.183     rillig   1310:                $$ = declare_argument(abstract_name(), false);
1.1       cgd      1311:          }
                   1312:        | declmods deftyp notype_param_decl {
1.183     rillig   1313:                $$ = declare_argument($3, false);
1.1       cgd      1314:          }
                   1315:        /*
                   1316:         * param_decl is needed because of following conflict:
                   1317:         * "typedef int a; f(int (a));" could be parsed as
                   1318:         * "function with argument a of type int", or
                   1319:         * "function with an abstract argument of type function".
                   1320:         * This grammar realizes the second case.
                   1321:         */
1.194     rillig   1322:        | declaration_specifiers deftyp param_decl {
1.183     rillig   1323:                $$ = declare_argument($3, false);
1.1       cgd      1324:          }
1.155     rillig   1325:        | declmods deftyp abstract_decl {
1.183     rillig   1326:                $$ = declare_argument($3, false);
1.1       cgd      1327:          }
1.194     rillig   1328:        | declaration_specifiers deftyp abstract_decl {
1.183     rillig   1329:                $$ = declare_argument($3, false);
1.1       cgd      1330:          }
                   1331:        ;
                   1332:
1.11      cgd      1333: opt_asm_or_symbolrename:               /* expect only one */
                   1334:          /* empty */ {
                   1335:                $$ = NULL;
                   1336:          }
1.126     rillig   1337:        | T_ASM T_LPAREN T_STRING T_RPAREN {
1.6       jpo      1338:                freeyyv(&$3, T_STRING);
1.11      cgd      1339:                $$ = NULL;
                   1340:          }
1.126     rillig   1341:        | T_SYMBOLRENAME T_LPAREN T_NAME T_RPAREN {
1.11      cgd      1342:                $$ = $3;
1.6       jpo      1343:          }
                   1344:        ;
                   1345:
1.179     rillig   1346: initializer:                   /* C99 6.7.8 "Initialization" */
1.79      dholland 1347:          expr                          %prec T_COMMA {
1.207     rillig   1348:                init_expr($1);
1.1       cgd      1349:          }
1.178     rillig   1350:        | init_lbrace init_rbrace {
                   1351:                /* XXX: Empty braces are not covered by C99 6.7.8. */
                   1352:          }
1.182     rillig   1353:        | init_lbrace initializer_list comma_opt init_rbrace
1.1       cgd      1354:        | error
                   1355:        ;
                   1356:
1.179     rillig   1357: initializer_list:              /* C99 6.7.8 "Initialization" */
1.192     rillig   1358:          initializer_list_item
1.180     rillig   1359:        | initializer_list T_COMMA initializer_list_item
                   1360:        ;
                   1361:
                   1362: initializer_list_item:
                   1363:          designation initializer
                   1364:        | initializer
1.1       cgd      1365:        ;
                   1366:
1.35      christos 1367: range:
1.168     rillig   1368:          constant_expr {
1.175     rillig   1369:                $$.lo = to_int_constant($1, true);
1.165     rillig   1370:                $$.hi = $$.lo;
1.35      christos 1371:          }
1.168     rillig   1372:        | constant_expr T_ELLIPSIS constant_expr {
1.175     rillig   1373:                $$.lo = to_int_constant($1, true);
                   1374:                $$.hi = to_int_constant($3, true);
1.166     rillig   1375:                /* initialization with '[a...b]' is a GNU extension */
                   1376:                gnuism(340);
1.35      christos 1377:          }
                   1378:        ;
                   1379:
1.167     rillig   1380: designator:                    /* C99 6.7.8 "Initialization" */
1.71      christos 1381:          T_LBRACK range T_RBRACK {
1.205     rillig   1382:                add_designator_subscript($2);
1.34      yamt     1383:                if (!Sflag)
1.127     rillig   1384:                        /* array initializer with des.s is a C9X feature */
1.34      yamt     1385:                        warning(321);
                   1386:          }
1.71      christos 1387:        | point identifier {
1.26      christos 1388:                if (!Sflag)
1.127     rillig   1389:                        /* struct or union member name in initializer is ... */
1.26      christos 1390:                        warning(313);
1.205     rillig   1391:                add_designator_member($2);
1.26      christos 1392:          }
1.71      christos 1393:        ;
                   1394:
1.167     rillig   1395: designator_list:               /* C99 6.7.8 "Initialization" */
                   1396:          designator
                   1397:        | designator_list designator
1.71      christos 1398:        ;
                   1399:
1.179     rillig   1400: designation:                   /* C99 6.7.8 "Initialization" */
1.167     rillig   1401:          designator_list T_ASSIGN
1.37      christos 1402:        | identifier T_COLON {
1.127     rillig   1403:                /* GCC style struct or union member name in initializer */
1.26      christos 1404:                gnuism(315);
1.205     rillig   1405:                add_designator_member($1);
1.26      christos 1406:          }
                   1407:        ;
                   1408:
1.1       cgd      1409: init_lbrace:
                   1410:          T_LBRACE {
1.114     rillig   1411:                init_lbrace();
1.1       cgd      1412:          }
                   1413:        ;
                   1414:
                   1415: init_rbrace:
                   1416:          T_RBRACE {
1.114     rillig   1417:                init_rbrace();
1.1       cgd      1418:          }
                   1419:        ;
                   1420:
                   1421: type_name:
1.110     rillig   1422:          {
1.202     rillig   1423:                begin_declaration_level(ABSTRACT);
1.1       cgd      1424:          } abstract_declaration {
1.202     rillig   1425:                end_declaration_level();
1.1       cgd      1426:                $$ = $2->s_type;
                   1427:          }
                   1428:        ;
                   1429:
                   1430: abstract_declaration:
                   1431:          noclass_declmods deftyp {
1.111     rillig   1432:                $$ = declare_1_abstract(abstract_name());
1.1       cgd      1433:          }
                   1434:        | noclass_declspecs deftyp {
1.111     rillig   1435:                $$ = declare_1_abstract(abstract_name());
1.1       cgd      1436:          }
1.155     rillig   1437:        | noclass_declmods deftyp abstract_decl {
1.111     rillig   1438:                $$ = declare_1_abstract($3);
1.1       cgd      1439:          }
1.155     rillig   1440:        | noclass_declspecs deftyp abstract_decl {
1.111     rillig   1441:                $$ = declare_1_abstract($3);
1.1       cgd      1442:          }
                   1443:        ;
                   1444:
1.155     rillig   1445: abstract_decl:
1.1       cgd      1446:          pointer {
1.111     rillig   1447:                $$ = add_pointer(abstract_name(), $1);
1.1       cgd      1448:          }
1.155     rillig   1449:        | direct_abstract_decl {
1.1       cgd      1450:                $$ = $1;
                   1451:          }
1.155     rillig   1452:        | pointer direct_abstract_decl {
1.111     rillig   1453:                $$ = add_pointer($2, $1);
1.1       cgd      1454:          }
1.94      christos 1455:        | T_TYPEOF term {
                   1456:                $$ = mktempsym($2->tn_type);
                   1457:          }
1.1       cgd      1458:        ;
                   1459:
1.155     rillig   1460: direct_abstract_decl:
                   1461:          T_LPAREN abstract_decl T_RPAREN {
1.1       cgd      1462:                $$ = $2;
                   1463:          }
                   1464:        | T_LBRACK T_RBRACK {
1.183     rillig   1465:                $$ = add_array(abstract_name(), false, 0);
1.1       cgd      1466:          }
1.168     rillig   1467:        | T_LBRACK constant_expr T_RBRACK {
1.183     rillig   1468:                $$ = add_array(abstract_name(), true, to_int_constant($2, false));
1.1       cgd      1469:          }
1.155     rillig   1470:        | type_attribute direct_abstract_decl {
1.63      christos 1471:                $$ = $2;
1.130     rillig   1472:          }
1.155     rillig   1473:        | direct_abstract_decl T_LBRACK T_RBRACK {
1.183     rillig   1474:                $$ = add_array($1, false, 0);
1.1       cgd      1475:          }
1.168     rillig   1476:        | direct_abstract_decl T_LBRACK constant_expr T_RBRACK {
1.183     rillig   1477:                $$ = add_array($1, true, to_int_constant($3, false));
1.1       cgd      1478:          }
1.155     rillig   1479:        | abstract_decl_param_list opt_asm_or_symbolrename {
1.111     rillig   1480:                $$ = add_function(symbolrename(abstract_name(), $2), $1);
1.202     rillig   1481:                end_declaration_level();
1.171     rillig   1482:                block_level--;
1.1       cgd      1483:          }
1.155     rillig   1484:        | direct_abstract_decl abstract_decl_param_list opt_asm_or_symbolrename {
1.111     rillig   1485:                $$ = add_function(symbolrename($1, $3), $2);
1.202     rillig   1486:                end_declaration_level();
1.171     rillig   1487:                block_level--;
1.1       cgd      1488:          }
1.155     rillig   1489:        | direct_abstract_decl type_attribute_list
1.1       cgd      1490:        ;
                   1491:
1.133     rillig   1492: non_expr_statement:
                   1493:          labeled_statement
                   1494:        | compound_statement
                   1495:        | selection_statement
                   1496:        | iteration_statement
                   1497:        | jump_statement {
1.188     rillig   1498:                seen_fallthrough = false;
1.1       cgd      1499:          }
1.133     rillig   1500:        | asm_statement
1.32      christos 1501:
1.134     rillig   1502: statement:                     /* C99 6.8 */
1.133     rillig   1503:          expr_statement
                   1504:        | non_expr_statement
1.1       cgd      1505:        ;
                   1506:
1.134     rillig   1507: labeled_statement:             /* C99 6.8.1 */
1.133     rillig   1508:          label statement
1.1       cgd      1509:        ;
                   1510:
                   1511: label:
1.53      christos 1512:          T_NAME T_COLON {
1.120     rillig   1513:                symtyp = FLABEL;
1.125     rillig   1514:                named_label(getsym($1));
1.1       cgd      1515:          }
1.168     rillig   1516:        | T_CASE constant_expr T_COLON {
1.125     rillig   1517:                case_label($2);
1.188     rillig   1518:                seen_fallthrough = true;
1.130     rillig   1519:          }
1.168     rillig   1520:        | T_CASE constant_expr T_ELLIPSIS constant_expr T_COLON {
1.40      christos 1521:                /* XXX: We don't fill all cases */
1.125     rillig   1522:                case_label($2);
1.188     rillig   1523:                seen_fallthrough = true;
1.130     rillig   1524:          }
1.1       cgd      1525:        | T_DEFAULT T_COLON {
1.125     rillig   1526:                default_label();
1.188     rillig   1527:                seen_fallthrough = true;
1.1       cgd      1528:          }
                   1529:        ;
                   1530:
1.134     rillig   1531: compound_statement:            /* C99 6.8.2 */
1.133     rillig   1532:          compound_statement_lbrace compound_statement_rbrace
1.186     rillig   1533:        | compound_statement_lbrace block_item_list compound_statement_rbrace
1.1       cgd      1534:        ;
                   1535:
1.133     rillig   1536: compound_statement_lbrace:
1.1       cgd      1537:          T_LBRACE {
1.171     rillig   1538:                block_level++;
                   1539:                mem_block_level++;
1.202     rillig   1540:                begin_declaration_level(AUTO);
1.1       cgd      1541:          }
                   1542:        ;
                   1543:
1.133     rillig   1544: compound_statement_rbrace:
1.1       cgd      1545:          T_RBRACE {
1.202     rillig   1546:                end_declaration_level();
1.1       cgd      1547:                freeblk();
1.171     rillig   1548:                mem_block_level--;
                   1549:                block_level--;
1.188     rillig   1550:                seen_fallthrough = false;
1.1       cgd      1551:          }
                   1552:        ;
                   1553:
1.185     rillig   1554: block_item_list:
                   1555:          block_item
                   1556:        | block_item_list block_item {
                   1557:                if (!Sflag && $1 && !$2)
                   1558:                        /* declarations after statements is a C99 feature */
                   1559:                        c99ism(327);
                   1560:        }
                   1561:        ;
                   1562:
                   1563: block_item:
                   1564:          statement {
                   1565:                $$ = true;
1.187     rillig   1566:                restore_warning_flags();
1.185     rillig   1567:          }
                   1568:        | declaration {
                   1569:                $$ = false;
1.187     rillig   1570:                restore_warning_flags();
1.7       jpo      1571:          }
1.1       cgd      1572:        ;
                   1573:
1.133     rillig   1574: expr_statement:
1.1       cgd      1575:          expr T_SEMI {
1.160     rillig   1576:                expr($1, false, false, false, false);
1.188     rillig   1577:                seen_fallthrough = false;
1.1       cgd      1578:          }
                   1579:        | T_SEMI {
1.188     rillig   1580:                seen_fallthrough = false;
1.1       cgd      1581:          }
                   1582:        ;
                   1583:
1.30      christos 1584: /*
1.109     rillig   1585:  * The following two productions are used to implement
1.32      christos 1586:  * ({ [[decl-list] stmt-list] }).
                   1587:  * XXX: This is not well tested.
1.30      christos 1588:  */
1.133     rillig   1589: expr_statement_val:
1.29      christos 1590:          expr T_SEMI {
                   1591:                /* XXX: We should really do that only on the last name */
                   1592:                if ($1->tn_op == NAME)
1.140     rillig   1593:                        $1->tn_sym->s_used = true;
1.29      christos 1594:                $$ = $1;
1.160     rillig   1595:                expr($1, false, false, false, false);
1.188     rillig   1596:                seen_fallthrough = false;
1.29      christos 1597:          }
1.133     rillig   1598:        | non_expr_statement {
1.208   ! rillig   1599:                $$ = expr_zalloc_tnode();
1.33      christos 1600:                $$->tn_type = gettyp(VOID);
1.130     rillig   1601:          }
1.29      christos 1602:        ;
                   1603:
1.133     rillig   1604: expr_statement_list:
                   1605:          expr_statement_val
                   1606:        | expr_statement_list expr_statement_val {
1.32      christos 1607:                $$ = $2;
1.130     rillig   1608:          }
1.29      christos 1609:        ;
                   1610:
1.134     rillig   1611: selection_statement:           /* C99 6.8.4 */
1.1       cgd      1612:          if_without_else {
1.187     rillig   1613:                save_warning_flags();
1.1       cgd      1614:                if2();
1.183     rillig   1615:                if3(false);
1.1       cgd      1616:          }
                   1617:        | if_without_else T_ELSE {
1.187     rillig   1618:                save_warning_flags();
1.1       cgd      1619:                if2();
1.133     rillig   1620:          } statement {
1.187     rillig   1621:                clear_warning_flags();
1.183     rillig   1622:                if3(true);
1.1       cgd      1623:          }
                   1624:        | if_without_else T_ELSE error {
1.187     rillig   1625:                clear_warning_flags();
1.183     rillig   1626:                if3(false);
1.1       cgd      1627:          }
1.133     rillig   1628:        | switch_expr statement {
1.187     rillig   1629:                clear_warning_flags();
1.1       cgd      1630:                switch2();
                   1631:          }
                   1632:        | switch_expr error {
1.187     rillig   1633:                clear_warning_flags();
1.1       cgd      1634:                switch2();
                   1635:          }
                   1636:        ;
                   1637:
                   1638: if_without_else:
1.133     rillig   1639:          if_expr statement
1.1       cgd      1640:        | if_expr error
                   1641:        ;
                   1642:
                   1643: if_expr:
1.126     rillig   1644:          T_IF T_LPAREN expr T_RPAREN {
1.1       cgd      1645:                if1($3);
1.187     rillig   1646:                clear_warning_flags();
1.1       cgd      1647:          }
                   1648:        ;
                   1649:
                   1650: switch_expr:
1.126     rillig   1651:          T_SWITCH T_LPAREN expr T_RPAREN {
1.1       cgd      1652:                switch1($3);
1.187     rillig   1653:                clear_warning_flags();
1.1       cgd      1654:          }
                   1655:        ;
                   1656:
1.81      christos 1657: association:
                   1658:          type_name T_COLON expr
1.109     rillig   1659:        | T_DEFAULT T_COLON expr
1.81      christos 1660:        ;
                   1661:
                   1662: association_list:
                   1663:          association
                   1664:        | association_list T_COMMA association
                   1665:        ;
                   1666:
                   1667: generic_expr:
1.126     rillig   1668:          T_GENERIC T_LPAREN expr T_COMMA association_list T_RPAREN {
1.81      christos 1669:                $$ = $3;
                   1670:          }
                   1671:        ;
                   1672:
1.133     rillig   1673: do_statement:
                   1674:          do statement {
1.187     rillig   1675:                clear_warning_flags();
1.14      christos 1676:          }
                   1677:        ;
                   1678:
1.134     rillig   1679: iteration_statement:           /* C99 6.8.5 */
1.133     rillig   1680:          while_expr statement {
1.187     rillig   1681:                clear_warning_flags();
1.1       cgd      1682:                while2();
                   1683:          }
                   1684:        | while_expr error {
1.187     rillig   1685:                clear_warning_flags();
1.1       cgd      1686:                while2();
                   1687:          }
1.133     rillig   1688:        | do_statement do_while_expr {
1.14      christos 1689:                do2($2);
1.188     rillig   1690:                seen_fallthrough = false;
1.1       cgd      1691:          }
                   1692:        | do error {
1.187     rillig   1693:                clear_warning_flags();
1.1       cgd      1694:                do2(NULL);
                   1695:          }
1.133     rillig   1696:        | for_exprs statement {
1.187     rillig   1697:                clear_warning_flags();
1.1       cgd      1698:                for2();
1.202     rillig   1699:                end_declaration_level();
1.171     rillig   1700:                block_level--;
1.1       cgd      1701:          }
                   1702:        | for_exprs error {
1.187     rillig   1703:                clear_warning_flags();
1.1       cgd      1704:                for2();
1.202     rillig   1705:                end_declaration_level();
1.171     rillig   1706:                block_level--;
1.1       cgd      1707:          }
                   1708:        ;
                   1709:
                   1710: while_expr:
1.126     rillig   1711:          T_WHILE T_LPAREN expr T_RPAREN {
1.1       cgd      1712:                while1($3);
1.187     rillig   1713:                clear_warning_flags();
1.1       cgd      1714:          }
                   1715:        ;
                   1716:
                   1717: do:
                   1718:          T_DO {
                   1719:                do1();
                   1720:          }
                   1721:        ;
                   1722:
                   1723: do_while_expr:
1.126     rillig   1724:          T_WHILE T_LPAREN expr T_RPAREN T_SEMI {
1.1       cgd      1725:                $$ = $3;
                   1726:          }
                   1727:        ;
                   1728:
1.66      christos 1729: for_start:
1.126     rillig   1730:          T_FOR T_LPAREN {
1.202     rillig   1731:                begin_declaration_level(AUTO);
1.171     rillig   1732:                block_level++;
1.66      christos 1733:          }
                   1734:        ;
1.1       cgd      1735: for_exprs:
1.194     rillig   1736:          for_start declaration_specifiers deftyp notype_init_decls T_SEMI
                   1737:            opt_expr T_SEMI opt_expr T_RPAREN {
1.127     rillig   1738:                /* variable declaration in for loop */
1.43      christos 1739:                c99ism(325);
1.66      christos 1740:                for1(NULL, $6, $8);
1.187     rillig   1741:                clear_warning_flags();
1.43      christos 1742:            }
1.126     rillig   1743:          | for_start opt_expr T_SEMI opt_expr T_SEMI opt_expr T_RPAREN {
1.66      christos 1744:                for1($2, $4, $6);
1.187     rillig   1745:                clear_warning_flags();
1.1       cgd      1746:          }
                   1747:        ;
                   1748:
                   1749: opt_expr:
                   1750:          /* empty */ {
                   1751:                $$ = NULL;
                   1752:          }
                   1753:        | expr {
                   1754:                $$ = $1;
                   1755:          }
                   1756:        ;
                   1757:
1.134     rillig   1758: jump_statement:                        /* C99 6.8.6 */
1.1       cgd      1759:          goto identifier T_SEMI {
1.196     rillig   1760:                do_goto(getsym($2));
1.1       cgd      1761:          }
                   1762:        | goto error T_SEMI {
                   1763:                symtyp = FVFT;
                   1764:          }
                   1765:        | T_CONTINUE T_SEMI {
1.196     rillig   1766:                do_continue();
1.1       cgd      1767:          }
                   1768:        | T_BREAK T_SEMI {
1.196     rillig   1769:                do_break();
1.1       cgd      1770:          }
                   1771:        | T_RETURN T_SEMI {
1.196     rillig   1772:                do_return(NULL);
1.1       cgd      1773:          }
                   1774:        | T_RETURN expr T_SEMI {
1.196     rillig   1775:                do_return($2);
1.1       cgd      1776:          }
                   1777:        ;
                   1778:
                   1779: goto:
                   1780:          T_GOTO {
1.120     rillig   1781:                symtyp = FLABEL;
1.1       cgd      1782:          }
                   1783:        ;
                   1784:
1.133     rillig   1785: asm_statement:
1.170     rillig   1786:          T_ASM T_LPAREN read_until_rparen T_SEMI {
1.8       jpo      1787:                setasm();
                   1788:          }
1.170     rillig   1789:        | T_ASM T_QUAL T_LPAREN read_until_rparen T_SEMI {
1.8       jpo      1790:                setasm();
                   1791:          }
                   1792:        | T_ASM error
1.6       jpo      1793:        ;
                   1794:
1.170     rillig   1795: read_until_rparen:
1.6       jpo      1796:          /* empty */ {
1.148     rillig   1797:                ignore_up_to_rparen();
1.6       jpo      1798:          }
                   1799:        ;
                   1800:
1.1       cgd      1801: declaration_list:
1.7       jpo      1802:          declaration {
1.187     rillig   1803:                clear_warning_flags();
1.7       jpo      1804:          }
                   1805:        | declaration_list declaration {
1.187     rillig   1806:                clear_warning_flags();
1.7       jpo      1807:          }
1.1       cgd      1808:        ;
                   1809:
1.169     rillig   1810: constant_expr:                 /* C99 6.6 */
                   1811:          expr                          %prec T_ASSIGN {
1.1       cgd      1812:                  $$ = $1;
                   1813:          }
                   1814:        ;
                   1815:
                   1816: expr:
1.132     rillig   1817:          expr T_ASTERISK expr {
1.1       cgd      1818:                $$ = build(MULT, $1, $3);
                   1819:          }
1.150     rillig   1820:        | expr T_MULTIPLICATIVE expr {
1.1       cgd      1821:                $$ = build($2, $1, $3);
                   1822:          }
1.150     rillig   1823:        | expr T_ADDITIVE expr {
1.1       cgd      1824:                $$ = build($2, $1, $3);
                   1825:          }
1.150     rillig   1826:        | expr T_SHIFT expr {
1.1       cgd      1827:                $$ = build($2, $1, $3);
                   1828:          }
1.150     rillig   1829:        | expr T_RELATIONAL expr {
1.1       cgd      1830:                $$ = build($2, $1, $3);
                   1831:          }
1.150     rillig   1832:        | expr T_EQUALITY expr {
1.1       cgd      1833:                $$ = build($2, $1, $3);
                   1834:          }
1.145     rillig   1835:        | expr T_AMPER expr {
1.144     rillig   1836:                $$ = build(BITAND, $1, $3);
1.1       cgd      1837:          }
1.191     rillig   1838:        | expr T_BITXOR expr {
1.144     rillig   1839:                $$ = build(BITXOR, $1, $3);
1.1       cgd      1840:          }
1.150     rillig   1841:        | expr T_BITOR expr {
1.144     rillig   1842:                $$ = build(BITOR, $1, $3);
1.1       cgd      1843:          }
                   1844:        | expr T_LOGAND expr {
                   1845:                $$ = build(LOGAND, $1, $3);
                   1846:          }
                   1847:        | expr T_LOGOR expr {
                   1848:                $$ = build(LOGOR, $1, $3);
                   1849:          }
                   1850:        | expr T_QUEST expr T_COLON expr {
                   1851:                $$ = build(QUEST, $1, build(COLON, $3, $5));
                   1852:          }
                   1853:        | expr T_ASSIGN expr {
                   1854:                $$ = build(ASSIGN, $1, $3);
                   1855:          }
1.150     rillig   1856:        | expr T_OPASSIGN expr {
1.1       cgd      1857:                $$ = build($2, $1, $3);
                   1858:          }
                   1859:        | expr T_COMMA expr {
                   1860:                $$ = build(COMMA, $1, $3);
                   1861:          }
                   1862:        | term {
                   1863:                $$ = $1;
                   1864:          }
1.81      christos 1865:        | generic_expr {
                   1866:                $$ = $1;
                   1867:          }
1.1       cgd      1868:        ;
                   1869:
                   1870: term:
                   1871:          T_NAME {
1.21      wiz      1872:                /* XXX really necessary? */
1.1       cgd      1873:                if (yychar < 0)
                   1874:                        yychar = yylex();
1.128     rillig   1875:                $$ = new_name_node(getsym($1), yychar);
1.1       cgd      1876:          }
                   1877:        | string {
1.128     rillig   1878:                $$ = new_string_node($1);
1.1       cgd      1879:          }
                   1880:        | T_CON {
1.128     rillig   1881:                $$ = new_constant_node(gettyp($1->v_tspec), $1);
1.1       cgd      1882:          }
1.126     rillig   1883:        | T_LPAREN expr T_RPAREN {
1.1       cgd      1884:                if ($2 != NULL)
1.140     rillig   1885:                        $2->tn_parenthesized = true;
1.1       cgd      1886:                $$ = $2;
                   1887:          }
1.133     rillig   1888:        | T_LPAREN compound_statement_lbrace declaration_list
                   1889:            expr_statement_list {
1.171     rillig   1890:                block_level--;
                   1891:                mem_block_level--;
1.198     rillig   1892:                begin_initialization(mktempsym(duptyp($4->tn_type)));
1.171     rillig   1893:                mem_block_level++;
                   1894:                block_level++;
1.127     rillig   1895:                /* ({ }) is a GCC extension */
1.29      christos 1896:                gnuism(320);
1.133     rillig   1897:         } compound_statement_rbrace T_RPAREN {
1.197     rillig   1898:                $$ = new_name_node(*current_initsym(), 0);
1.198     rillig   1899:                end_initialization();
1.130     rillig   1900:         }
1.133     rillig   1901:        | T_LPAREN compound_statement_lbrace expr_statement_list {
1.171     rillig   1902:                block_level--;
                   1903:                mem_block_level--;
1.198     rillig   1904:                begin_initialization(mktempsym($3->tn_type));
1.171     rillig   1905:                mem_block_level++;
                   1906:                block_level++;
1.127     rillig   1907:                /* ({ }) is a GCC extension */
1.29      christos 1908:                gnuism(320);
1.133     rillig   1909:         } compound_statement_rbrace T_RPAREN {
1.197     rillig   1910:                $$ = new_name_node(*current_initsym(), 0);
1.198     rillig   1911:                end_initialization();
1.130     rillig   1912:         }
1.1       cgd      1913:        | term T_INCDEC {
                   1914:                $$ = build($2 == INC ? INCAFT : DECAFT, $1, NULL);
                   1915:          }
                   1916:        | T_INCDEC term {
                   1917:                $$ = build($1 == INC ? INCBEF : DECBEF, $2, NULL);
                   1918:          }
1.132     rillig   1919:        | T_ASTERISK term {
1.143     rillig   1920:                $$ = build(INDIR, $2, NULL);
1.1       cgd      1921:          }
1.145     rillig   1922:        | T_AMPER term {
1.142     rillig   1923:                $$ = build(ADDR, $2, NULL);
1.1       cgd      1924:          }
1.150     rillig   1925:        | T_UNARY term {
1.1       cgd      1926:                $$ = build($1, $2, NULL);
                   1927:          }
1.150     rillig   1928:        | T_ADDITIVE term {
1.1       cgd      1929:                if (tflag && $1 == PLUS) {
                   1930:                        /* unary + is illegal in traditional C */
                   1931:                        warning(100);
                   1932:                }
                   1933:                $$ = build($1 == PLUS ? UPLUS : UMINUS, $2, NULL);
                   1934:          }
                   1935:        | term T_LBRACK expr T_RBRACK {
1.143     rillig   1936:                $$ = build(INDIR, build(PLUS, $1, $3), NULL);
1.1       cgd      1937:          }
1.126     rillig   1938:        | term T_LPAREN T_RPAREN {
1.129     rillig   1939:                $$ = new_function_call_node($1, NULL);
1.1       cgd      1940:          }
1.126     rillig   1941:        | term T_LPAREN func_arg_list T_RPAREN {
1.129     rillig   1942:                $$ = new_function_call_node($1, $3);
1.1       cgd      1943:          }
                   1944:        | term point_or_arrow T_NAME {
                   1945:                if ($1 != NULL) {
                   1946:                        sym_t   *msym;
1.114     rillig   1947:                        /*
                   1948:                         * XXX struct_or_union_member should be integrated
                   1949:                         * in build()
                   1950:                         */
1.1       cgd      1951:                        if ($2 == ARROW) {
1.114     rillig   1952:                                /*
                   1953:                                 * must do this before struct_or_union_member
                   1954:                                 * is called
                   1955:                                 */
1.1       cgd      1956:                                $1 = cconv($1);
                   1957:                        }
1.114     rillig   1958:                        msym = struct_or_union_member($1, $2, getsym($3));
1.128     rillig   1959:                        $$ = build($2, $1, new_name_node(msym, 0));
1.1       cgd      1960:                } else {
                   1961:                        $$ = NULL;
                   1962:                }
                   1963:          }
1.41      christos 1964:        | T_REAL term {
                   1965:                $$ = build(REAL, $2, NULL);
                   1966:          }
                   1967:        | T_IMAG term {
                   1968:                $$ = build(IMAG, $2, NULL);
                   1969:          }
1.60      christos 1970:        | T_EXTENSION term {
                   1971:                $$ = $2;
                   1972:          }
1.126     rillig   1973:        | T_REAL T_LPAREN term T_RPAREN {
1.41      christos 1974:                $$ = build(REAL, $3, NULL);
                   1975:          }
1.126     rillig   1976:        | T_IMAG T_LPAREN term T_RPAREN {
1.41      christos 1977:                $$ = build(IMAG, $3, NULL);
                   1978:          }
1.192     rillig   1979:        | T_BUILTIN_OFFSETOF T_LPAREN type_name T_COMMA identifier T_RPAREN {
1.120     rillig   1980:                symtyp = FMEMBER;
1.114     rillig   1981:                $$ = build_offsetof($3, getsym($5));
1.94      christos 1982:          }
1.192     rillig   1983:        | T_SIZEOF term {
1.114     rillig   1984:                $$ = $2 == NULL ? NULL : build_sizeof($2->tn_type);
                   1985:                if ($$ != NULL)
1.183     rillig   1986:                        check_expr_misc($2, false, false, false, false, false, true);
1.1       cgd      1987:          }
1.126     rillig   1988:        | T_SIZEOF T_LPAREN type_name T_RPAREN          %prec T_SIZEOF {
1.114     rillig   1989:                $$ = build_sizeof($3);
1.1       cgd      1990:          }
1.192     rillig   1991:        | T_ALIGNOF T_LPAREN type_name T_RPAREN {
1.114     rillig   1992:                $$ = build_alignof($3);
1.44      christos 1993:          }
1.150     rillig   1994:        | T_LPAREN type_name T_RPAREN term              %prec T_UNARY {
1.1       cgd      1995:                $$ = cast($4, $2);
                   1996:          }
1.201     rillig   1997:        | T_LPAREN type_name T_RPAREN { /* C99 6.5.2.5 "Compound literals" */
1.28      christos 1998:                sym_t *tmp = mktempsym($2);
1.198     rillig   1999:                begin_initialization(tmp);
1.174     rillig   2000:                cgram_declare(tmp, true, NULL);
1.180     rillig   2001:          } init_lbrace initializer_list comma_opt init_rbrace {
1.28      christos 2002:                if (!Sflag)
1.127     rillig   2003:                         /* compound literals are a C9X/GCC extension */
                   2004:                         gnuism(319);
1.197     rillig   2005:                $$ = new_name_node(*current_initsym(), 0);
1.198     rillig   2006:                end_initialization();
1.28      christos 2007:          }
1.1       cgd      2008:        ;
                   2009:
                   2010: string:
                   2011:          T_STRING {
                   2012:                $$ = $1;
                   2013:          }
                   2014:        | T_STRING string2 {
1.114     rillig   2015:                $$ = cat_strings($1, $2);
1.1       cgd      2016:          }
                   2017:        ;
                   2018:
                   2019: string2:
1.110     rillig   2020:          T_STRING {
1.1       cgd      2021:                if (tflag) {
                   2022:                        /* concatenated strings are illegal in traditional C */
                   2023:                        warning(219);
                   2024:                }
                   2025:                $$ = $1;
                   2026:          }
                   2027:        | string2 T_STRING {
1.114     rillig   2028:                $$ = cat_strings($1, $2);
1.1       cgd      2029:          }
                   2030:        ;
                   2031:
                   2032: func_arg_list:
                   2033:          expr                                          %prec T_COMMA {
1.129     rillig   2034:                $$ = new_function_argument_node(NULL, $1);
1.1       cgd      2035:          }
                   2036:        | func_arg_list T_COMMA expr {
1.129     rillig   2037:                $$ = new_function_argument_node($1, $3);
1.1       cgd      2038:          }
                   2039:        ;
                   2040:
                   2041: point_or_arrow:
1.146     rillig   2042:          T_MEMBACC {
1.120     rillig   2043:                symtyp = FMEMBER;
1.1       cgd      2044:                $$ = $1;
1.26      christos 2045:          }
                   2046:        ;
                   2047:
                   2048: point:
1.146     rillig   2049:          T_MEMBACC {
1.50      christos 2050:                if ($1 != POINT) {
1.127     rillig   2051:                        /* syntax error '%s' */
1.41      christos 2052:                        error(249, yytext);
1.50      christos 2053:                }
1.1       cgd      2054:          }
                   2055:        ;
                   2056:
1.168     rillig   2057: identifier:                    /* C99 6.4.2.1 */
1.1       cgd      2058:          T_NAME {
                   2059:                $$ = $1;
1.117     rillig   2060:                cgram_debug("name '%s'", $$->sb_name);
1.1       cgd      2061:          }
                   2062:        | T_TYPENAME {
                   2063:                $$ = $1;
1.117     rillig   2064:                cgram_debug("typename '%s'", $$->sb_name);
1.1       cgd      2065:          }
                   2066:        ;
                   2067:
1.180     rillig   2068: comma_opt:
                   2069:          T_COMMA
                   2070:        | /* empty */
                   2071:        ;
1.1       cgd      2072: %%
                   2073:
                   2074: /* ARGSUSED */
                   2075: int
1.42      dholland 2076: yyerror(const char *msg)
1.1       cgd      2077: {
1.127     rillig   2078:        /* syntax error '%s' */
1.41      christos 2079:        error(249, yytext);
1.1       cgd      2080:        if (++sytxerr >= 5)
                   2081:                norecover();
1.112     rillig   2082:        return 0;
1.1       cgd      2083: }
                   2084:
                   2085: static void
1.174     rillig   2086: cgram_declare(sym_t *decl, bool initflg, sbuf_t *renaming)
1.1       cgd      2087: {
1.174     rillig   2088:        declare(decl, initflg, renaming);
                   2089:        if (renaming != NULL)
                   2090:                freeyyv(&renaming, T_NAME);
1.6       jpo      2091: }
                   2092:
                   2093: /*
                   2094:  * Discard all input tokens up to and including the next
                   2095:  * unmatched right paren
                   2096:  */
1.22      thorpej  2097: static void
1.148     rillig   2098: ignore_up_to_rparen(void)
1.6       jpo      2099: {
                   2100:        int     level;
                   2101:
                   2102:        if (yychar < 0)
                   2103:                yychar = yylex();
                   2104:        freeyyv(&yylval, yychar);
                   2105:
                   2106:        level = 1;
1.126     rillig   2107:        while (yychar != T_RPAREN || --level > 0) {
                   2108:                if (yychar == T_LPAREN) {
1.6       jpo      2109:                        level++;
                   2110:                } else if (yychar <= 0) {
                   2111:                        break;
                   2112:                }
                   2113:                freeyyv(&yylval, yychar = yylex());
                   2114:        }
                   2115:
                   2116:        yyclearin;
1.1       cgd      2117: }
1.75      christos 2118:
                   2119: static sym_t *
                   2120: symbolrename(sym_t *s, sbuf_t *sb)
                   2121: {
                   2122:        if (sb)
                   2123:                s->s_rename = sb->sb_name;
                   2124:        return s;
                   2125: }

CVSweb <webmaster@jp.NetBSD.org>