[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.409

1.2       cgd         1: %{
1.409   ! rillig      2: /* $NetBSD: cgram.y,v 1.408 2022/04/30 19:18:48 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.409   ! rillig     38: __RCSID("$NetBSD: cgram.y,v 1.408 2022/04/30 19:18:48 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.383     rillig     61: size_t 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.331     rillig     70: static void    read_until_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.354     rillig     78:        debug_step("%s:%zu: clearing flags", file, line);
1.148     rillig     79:        clear_warn_flags();
1.55      christos   80:        olwarn = LWARN_BAD;
1.15      christos   81: }
                     82:
1.148     rillig     83: static void
                     84: SAVE_WARN_FLAGS(const char *file, size_t line)
1.15      christos   85: {
1.149     rillig     86:        lint_assert(olwarn == LWARN_BAD);
1.354     rillig     87:        debug_step("%s:%zu: saving flags %d", file, line, lwarn);
1.55      christos   88:        olwarn = lwarn;
1.15      christos   89: }
                     90:
1.148     rillig     91: static void
                     92: RESTORE_WARN_FLAGS(const char *file, size_t line)
1.15      christos   93: {
1.55      christos   94:        if (olwarn != LWARN_BAD) {
                     95:                lwarn = olwarn;
1.354     rillig     96:                debug_step("%s:%zu: restoring flags %d", file, line, lwarn);
1.55      christos   97:                olwarn = LWARN_BAD;
1.15      christos   98:        } else
1.148     rillig     99:                CLEAR_WARN_FLAGS(file, line);
1.15      christos  100: }
                    101: #else
1.190     rillig    102: #define CLEAR_WARN_FLAGS(f, l) clear_warn_flags(), olwarn = LWARN_BAD
1.148     rillig    103: #define SAVE_WARN_FLAGS(f, l)  olwarn = lwarn
                    104: #define RESTORE_WARN_FLAGS(f, l) \
                    105:        (void)(olwarn == LWARN_BAD ? (clear_warn_flags(), 0) : (lwarn = olwarn))
1.15      christos  106: #endif
1.73      christos  107:
1.190     rillig    108: #define clear_warning_flags()  CLEAR_WARN_FLAGS(__FILE__, __LINE__)
                    109: #define save_warning_flags()   SAVE_WARN_FLAGS(__FILE__, __LINE__)
                    110: #define restore_warning_flags()        RESTORE_WARN_FLAGS(__FILE__, __LINE__)
1.187     rillig    111:
1.73      christos  112: /* unbind the anonymous struct members from the struct */
                    113: static void
                    114: anonymize(sym_t *s)
                    115: {
1.219     rillig    116:        for ( ; s != NULL; s = s->s_next)
1.391     rillig    117:                s->u.s_member.sm_sou_type = NULL;
1.73      christos  118: }
1.297     rillig    119:
1.407     rillig    120: #if YYDEBUG && (YYBYACC || YYBISON)
1.352     rillig    121: #define YYSTYPE_TOSTRING cgram_to_string
                    122: #endif
1.407     rillig    123: #if YYDEBUG && YYBISON
1.352     rillig    124: #define YYPRINT cgram_print
                    125: #endif
                    126:
1.1       cgd       127: %}
                    128:
1.404     rillig    129: %expect 129
1.40      christos  130:
1.1       cgd       131: %union {
                    132:        val_t   *y_val;
1.297     rillig    133:        sbuf_t  *y_name;
1.1       cgd       134:        sym_t   *y_sym;
                    135:        op_t    y_op;
                    136:        scl_t   y_scl;
                    137:        tspec_t y_tspec;
                    138:        tqual_t y_tqual;
                    139:        type_t  *y_type;
                    140:        tnode_t *y_tnode;
1.35      christos  141:        range_t y_range;
1.121     rillig    142:        strg_t  *y_string;
1.243     rillig    143:        qual_ptr *y_qual_ptr;
1.219     rillig    144:        bool    y_seen_statement;
1.253     rillig    145:        struct generic_association *y_generic;
1.364     rillig    146:        struct array_size y_array_size;
1.370     rillig    147:        bool    y_in_system_header;
1.1       cgd       148: };
                    149:
1.126     rillig    150: %token                 T_LBRACE T_RBRACE T_LBRACK T_RBRACK T_LPAREN T_RPAREN
1.230     rillig    151: %token                 T_POINT T_ARROW
1.310     rillig    152: %token                 T_COMPLEMENT T_LOGNOT
1.1       cgd       153: %token <y_op>          T_INCDEC
                    154: %token                 T_SIZEOF
1.94      christos  155: %token                 T_BUILTIN_OFFSETOF
1.58      christos  156: %token                 T_TYPEOF
                    157: %token                 T_EXTENSION
1.199     christos  158: %token                 T_ALIGNAS
1.44      christos  159: %token                 T_ALIGNOF
1.189     rillig    160: %token                 T_ASTERISK
1.150     rillig    161: %token <y_op>          T_MULTIPLICATIVE
                    162: %token <y_op>          T_ADDITIVE
                    163: %token <y_op>          T_SHIFT
                    164: %token <y_op>          T_RELATIONAL
                    165: %token <y_op>          T_EQUALITY
1.189     rillig    166: %token                 T_AMPER
1.191     rillig    167: %token                 T_BITXOR
1.189     rillig    168: %token                 T_BITOR
                    169: %token                 T_LOGAND
                    170: %token                 T_LOGOR
1.1       cgd       171: %token                 T_QUEST
                    172: %token                 T_COLON
1.189     rillig    173: %token                 T_ASSIGN
1.150     rillig    174: %token <y_op>          T_OPASSIGN
1.1       cgd       175: %token                 T_COMMA
                    176: %token                 T_SEMI
1.147     rillig    177: %token                 T_ELLIPSIS
1.41      christos  178: %token                 T_REAL
                    179: %token                 T_IMAG
1.81      christos  180: %token                 T_GENERIC
1.95      christos  181: %token                 T_NORETURN
1.1       cgd       182:
                    183: /* storage classes (extern, static, auto, register and typedef) */
                    184: %token <y_scl>         T_SCLASS
                    185:
1.152     rillig    186: /*
                    187:  * predefined type keywords (char, int, short, long, unsigned, signed,
1.326     rillig    188:  * float, double, void); see T_TYPENAME for types from typedef
1.152     rillig    189:  */
1.1       cgd       190: %token <y_tspec>       T_TYPE
                    191:
1.152     rillig    192: /* qualifiers (const, volatile, restrict, _Thread_local) */
1.1       cgd       193: %token <y_tqual>       T_QUAL
                    194:
                    195: /* struct or union */
1.152     rillig    196: %token <y_tspec>       T_STRUCT_OR_UNION
1.1       cgd       197:
                    198: /* remaining keywords */
1.153     rillig    199: %token                 T_ASM
                    200: %token                 T_BREAK
1.1       cgd       201: %token                 T_CASE
1.153     rillig    202: %token                 T_CONTINUE
1.1       cgd       203: %token                 T_DEFAULT
1.153     rillig    204: %token                 T_DO
1.1       cgd       205: %token                 T_ELSE
1.153     rillig    206: %token                 T_ENUM
1.1       cgd       207: %token                 T_FOR
                    208: %token                 T_GOTO
1.153     rillig    209: %token                 T_IF
                    210: %token                 T_PACKED
1.1       cgd       211: %token                 T_RETURN
1.153     rillig    212: %token                 T_SWITCH
1.11      cgd       213: %token                 T_SYMBOLRENAME
1.153     rillig    214: %token                 T_WHILE
1.365     christos  215: %token                 T_STATIC_ASSERT
1.266     rillig    216:
                    217: %token                 T_ATTRIBUTE
                    218: %token                 T_AT_ALIAS
                    219: %token                 T_AT_ALIGNED
                    220: %token                 T_AT_ALLOC_SIZE
                    221: %token                 T_AT_ALWAYS_INLINE
                    222: %token                 T_AT_BOUNDED
                    223: %token                 T_AT_BUFFER
                    224: %token                 T_AT_COLD
                    225: %token                 T_AT_COMMON
                    226: %token                 T_AT_CONSTRUCTOR
                    227: %token                 T_AT_DEPRECATED
                    228: %token                 T_AT_DESTRUCTOR
1.374     christos  229: %token                 T_AT_DISABLE_SANITIZER_INSTRUMENTATION
1.266     rillig    230: %token                 T_AT_FALLTHROUGH
                    231: %token                 T_AT_FORMAT
                    232: %token                 T_AT_FORMAT_ARG
                    233: %token                 T_AT_FORMAT_GNU_PRINTF
                    234: %token                 T_AT_FORMAT_PRINTF
                    235: %token                 T_AT_FORMAT_SCANF
                    236: %token                 T_AT_FORMAT_STRFMON
                    237: %token                 T_AT_FORMAT_STRFTIME
                    238: %token                 T_AT_FORMAT_SYSLOG
                    239: %token                 T_AT_GNU_INLINE
1.313     rillig    240: %token                 T_AT_HOT
1.266     rillig    241: %token                 T_AT_MALLOC
                    242: %token                 T_AT_MAY_ALIAS
                    243: %token                 T_AT_MINBYTES
                    244: %token                 T_AT_MODE
1.374     christos  245: %token                 T_AT_NO_SANITIZE
                    246: %token                 T_AT_NO_SANITIZE_THREAD
1.266     rillig    247: %token                 T_AT_NOINLINE
                    248: %token                 T_AT_NONNULL
                    249: %token                 T_AT_NONSTRING
                    250: %token                 T_AT_NORETURN
                    251: %token                 T_AT_NOTHROW
                    252: %token                 T_AT_NO_INSTRUMENT_FUNCTION
                    253: %token                 T_AT_OPTIMIZE
1.378     christos  254: %token                 T_AT_OPTNONE
1.266     rillig    255: %token                 T_AT_PACKED
                    256: %token                 T_AT_PCS
                    257: %token                 T_AT_PURE
1.358     rillig    258: %token                 T_AT_REGPARM
1.356     christos  259: %token                 T_AT_RETURNS_NONNULL
1.266     rillig    260: %token                 T_AT_RETURNS_TWICE
                    261: %token                 T_AT_SECTION
                    262: %token                 T_AT_SENTINEL
                    263: %token                 T_AT_STRING
1.371     christos  264: %token                 T_AT_TARGET
1.266     rillig    265: %token                 T_AT_TLS_MODEL
                    266: %token                 T_AT_TUNION
                    267: %token                 T_AT_UNUSED
                    268: %token                 T_AT_USED
                    269: %token                 T_AT_VISIBILITY
                    270: %token                 T_AT_WARN_UNUSED_RESULT
                    271: %token                 T_AT_WEAK
1.1       cgd       272:
1.312     rillig    273: %left  T_THEN
                    274: %left  T_ELSE
1.1       cgd       275: %right T_QUEST T_COLON
                    276: %left  T_LOGOR
                    277: %left  T_LOGAND
1.150     rillig    278: %left  T_BITOR
1.191     rillig    279: %left  T_BITXOR
1.145     rillig    280: %left  T_AMPER
1.150     rillig    281: %left  T_EQUALITY
                    282: %left  T_RELATIONAL
                    283: %left  T_SHIFT
                    284: %left  T_ADDITIVE
                    285: %left  T_ASTERISK T_MULTIPLICATIVE
1.1       cgd       286:
1.297     rillig    287: %token <y_name>        T_NAME
                    288: %token <y_name>        T_TYPENAME
1.1       cgd       289: %token <y_val>         T_CON
1.121     rillig    290: %token <y_string>      T_STRING
1.1       cgd       291:
1.320     rillig    292: %type  <y_sym>         identifier_sym
                    293: %type  <y_name>        identifier
                    294: %type  <y_string>      string
                    295:
1.307     rillig    296: %type  <y_tnode>       primary_expression
1.320     rillig    297: %type  <y_tnode>       generic_selection
                    298: %type  <y_generic>     generic_assoc_list
                    299: %type  <y_generic>     generic_association
1.307     rillig    300: %type  <y_tnode>       postfix_expression
1.320     rillig    301: %type  <y_tnode>       gcc_statement_expr_list
                    302: %type  <y_tnode>       gcc_statement_expr_item
                    303: %type  <y_op>          point_or_arrow
1.316     rillig    304: %type  <y_tnode>       argument_expression_list
1.308     rillig    305: %type  <y_tnode>       unary_expression
1.316     rillig    306: %type  <y_tnode>       cast_expression
1.325     rillig    307: %type  <y_tnode>       conditional_expression
                    308: %type  <y_tnode>       assignment_expression
1.322     rillig    309: %type  <y_tnode>       expression_opt
                    310: %type  <y_tnode>       expression
1.320     rillig    311: %type  <y_tnode>       constant_expr
1.307     rillig    312:
1.320     rillig    313: %type  <y_type>        begin_type_typespec
1.300     rillig    314: %type  <y_type>        type_specifier
                    315: %type  <y_type>        notype_type_specifier
                    316: %type  <y_type>        struct_or_union_specifier
                    317: %type  <y_tspec>       struct_or_union
1.306     rillig    318: %type  <y_sym>         braced_struct_declaration_list
                    319: %type  <y_sym>         struct_declaration_list_with_rbrace
1.300     rillig    320: %type  <y_sym>         struct_declaration_list
1.1       cgd       321: %type  <y_sym>         struct_declaration
1.324     rillig    322: %type  <y_sym>         notype_struct_declarators
                    323: %type  <y_sym>         type_struct_declarators
                    324: %type  <y_sym>         notype_struct_declarator
                    325: %type  <y_sym>         type_struct_declarator
1.320     rillig    326: %type  <y_type>        enum_specifier
1.306     rillig    327: %type  <y_sym>         enum_declaration
                    328: %type  <y_sym>         enums_with_opt_comma
1.259     rillig    329: %type  <y_sym>         enumerator_list
1.1       cgd       330: %type  <y_sym>         enumerator
1.320     rillig    331: %type  <y_qual_ptr>    type_qualifier
                    332: %type  <y_qual_ptr>    pointer
                    333: %type  <y_qual_ptr>    asterisk
                    334: %type  <y_qual_ptr>    type_qualifier_list_opt
                    335: %type  <y_qual_ptr>    type_qualifier_list
1.324     rillig    336: %type  <y_sym>         notype_declarator
                    337: %type  <y_sym>         type_declarator
                    338: %type  <y_sym>         notype_direct_declarator
                    339: %type  <y_sym>         type_direct_declarator
                    340: %type  <y_sym>         type_param_declarator
                    341: %type  <y_sym>         notype_param_declarator
                    342: %type  <y_sym>         direct_param_declarator
                    343: %type  <y_sym>         direct_notype_param_declarator
1.320     rillig    344: %type  <y_sym>         param_list
1.364     rillig    345: %type  <y_array_size>  array_size_opt
1.320     rillig    346: %type  <y_tnode>       array_size
1.1       cgd       347: %type  <y_sym>         identifier_list
1.320     rillig    348: %type  <y_type>        type_name
                    349: %type  <y_sym>         abstract_declaration
1.246     rillig    350: %type  <y_sym>         abstract_declarator
                    351: %type  <y_sym>         direct_abstract_declarator
1.320     rillig    352: %type  <y_sym>         abstract_decl_param_list
1.1       cgd       353: %type  <y_sym>         vararg_parameter_type_list
                    354: %type  <y_sym>         parameter_type_list
                    355: %type  <y_sym>         parameter_declaration
1.320     rillig    356: %type  <y_range>       range
1.297     rillig    357: %type  <y_name>        asm_or_symbolrename_opt
1.320     rillig    358:
1.185     rillig    359: %type  <y_seen_statement> block_item_list
                    360: %type  <y_seen_statement> block_item
1.320     rillig    361: %type  <y_tnode>       do_while_expr
1.324     rillig    362: %type  <y_sym>         func_declarator
1.370     rillig    363: %type  <y_in_system_header> sys
1.1       cgd       364:
1.352     rillig    365: %{
1.407     rillig    366: #if YYDEBUG && YYBISON
1.372     rillig    367: static inline void cgram_print(FILE *, int, YYSTYPE);
1.352     rillig    368: #endif
                    369: %}
                    370:
1.1       cgd       371: %%
                    372:
                    373: program:
                    374:          /* empty */ {
                    375:                if (sflag) {
                    376:                        /* empty translation unit */
                    377:                        error(272);
1.409   ! rillig    378:                } else if (allow_c90) {
1.1       cgd       379:                        /* empty translation unit */
                    380:                        warning(272);
                    381:                }
                    382:          }
                    383:        | translation_unit
                    384:        ;
                    385:
1.319     rillig    386: identifier_sym:                        /* helper for struct/union/enum */
                    387:          identifier {
                    388:                $$ = getsym($1);
                    389:          }
                    390:        ;
                    391:
1.321     rillig    392: /* K&R ???, C90 ???, C99 6.4.2.1, C11 ??? */
1.319     rillig    393: identifier:
                    394:          T_NAME {
1.357     rillig    395:                debug_step("cgram: name '%s'", $1->sb_name);
1.319     rillig    396:                $$ = $1;
                    397:          }
                    398:        | T_TYPENAME {
1.357     rillig    399:                debug_step("cgram: typename '%s'", $1->sb_name);
1.319     rillig    400:                $$ = $1;
                    401:          }
                    402:        ;
                    403:
                    404: /* see C99 6.4.5, string literals are joined by 5.1.1.2 */
                    405: string:
                    406:          T_STRING
1.386     rillig    407:        | string T_STRING {
1.409   ! rillig    408:                if (!allow_c90) {
1.319     rillig    409:                        /* concatenated strings are illegal in traditional C */
                    410:                        warning(219);
                    411:                }
                    412:                $$ = cat_strings($1, $2);
                    413:          }
                    414:        ;
                    415:
1.321     rillig    416: /* K&R 7.1, C90 ???, C99 6.5.1, C11 6.5.1 */
1.319     rillig    417: primary_expression:
                    418:          T_NAME {
1.402     rillig    419:                bool sys_name, sys_next;
1.369     rillig    420:                sys_name = in_system_header;
1.319     rillig    421:                if (yychar < 0)
                    422:                        yychar = yylex();
1.369     rillig    423:                sys_next = in_system_header;
                    424:                in_system_header = sys_name;
1.375     rillig    425:                $$ = build_name(getsym($1), yychar == T_LPAREN);
1.369     rillig    426:                in_system_header = sys_next;
1.319     rillig    427:          }
                    428:        | T_CON {
1.330     rillig    429:                $$ = build_constant(gettyp($1->v_tspec), $1);
1.319     rillig    430:          }
                    431:        | string {
1.330     rillig    432:                $$ = build_string($1);
1.319     rillig    433:          }
1.322     rillig    434:        | T_LPAREN expression T_RPAREN {
1.319     rillig    435:                if ($2 != NULL)
                    436:                        $2->tn_parenthesized = true;
                    437:                $$ = $2;
                    438:          }
                    439:        | generic_selection
                    440:        /* GCC primary-expression, see c_parser_postfix_expression */
                    441:        | T_BUILTIN_OFFSETOF T_LPAREN type_name T_COMMA identifier T_RPAREN {
                    442:                symtyp = FMEMBER;
                    443:                $$ = build_offsetof($3, getsym($5));
                    444:          }
                    445:        ;
                    446:
1.321     rillig    447: /* K&R ---, C90 ---, C99 ---, C11 6.5.1.1 */
1.319     rillig    448: generic_selection:
                    449:          T_GENERIC T_LPAREN assignment_expression T_COMMA
                    450:            generic_assoc_list T_RPAREN {
1.361     rillig    451:                /* generic selection requires C11 or later */
                    452:                c11ism(345);
1.319     rillig    453:                $$ = build_generic_selection($3, $5);
                    454:          }
                    455:        ;
                    456:
1.321     rillig    457: /* K&R ---, C90 ---, C99 ---, C11 6.5.1.1 */
1.319     rillig    458: generic_assoc_list:
                    459:          generic_association
                    460:        | generic_assoc_list T_COMMA generic_association {
                    461:                $3->ga_prev = $1;
                    462:                $$ = $3;
                    463:          }
                    464:        ;
                    465:
1.321     rillig    466: /* K&R ---, C90 ---, C99 ---, C11 6.5.1.1 */
1.319     rillig    467: generic_association:
                    468:          type_name T_COLON assignment_expression {
1.383     rillig    469:                $$ = block_zero_alloc(sizeof(*$$));
1.319     rillig    470:                $$->ga_arg = $1;
                    471:                $$->ga_result = $3;
                    472:          }
                    473:        | T_DEFAULT T_COLON assignment_expression {
1.383     rillig    474:                $$ = block_zero_alloc(sizeof(*$$));
1.319     rillig    475:                $$->ga_arg = NULL;
                    476:                $$->ga_result = $3;
                    477:          }
1.1       cgd       478:        ;
                    479:
1.321     rillig    480: /* K&R 7.1, C90 ???, C99 6.5.2, C11 6.5.2 */
1.319     rillig    481: postfix_expression:
                    482:          primary_expression
1.370     rillig    483:        | postfix_expression T_LBRACK sys expression T_RBRACK {
                    484:                $$ = build_unary(INDIR, $3, build_binary($1, PLUS, $3, $4));
1.319     rillig    485:          }
1.370     rillig    486:        | postfix_expression T_LPAREN sys T_RPAREN {
                    487:                $$ = build_function_call($1, $3, NULL);
1.319     rillig    488:          }
1.370     rillig    489:        | postfix_expression T_LPAREN sys argument_expression_list T_RPAREN {
                    490:                $$ = build_function_call($1, $3, $4);
1.319     rillig    491:          }
1.370     rillig    492:        | postfix_expression point_or_arrow sys T_NAME {
                    493:                $$ = build_member_access($1, $2, $3, $4);
1.319     rillig    494:          }
1.370     rillig    495:        | postfix_expression T_INCDEC sys {
                    496:                $$ = build_unary($2 == INC ? INCAFT : DECAFT, $3, $1);
1.319     rillig    497:          }
                    498:        | T_LPAREN type_name T_RPAREN { /* C99 6.5.2.5 "Compound literals" */
                    499:                sym_t *tmp = mktempsym($2);
                    500:                begin_initialization(tmp);
                    501:                cgram_declare(tmp, true, NULL);
                    502:          } init_lbrace initializer_list comma_opt init_rbrace {
1.408     rillig    503:                if (!allow_c99)
1.385     rillig    504:                         /* compound literals are a C99/GCC extension */
1.319     rillig    505:                         gnuism(319);
1.375     rillig    506:                $$ = build_name(*current_initsym(), false);
1.319     rillig    507:                end_initialization();
1.1       cgd       508:          }
1.381     rillig    509:        | T_LPAREN compound_statement_lbrace {
                    510:                begin_statement_expr();
                    511:          } gcc_statement_expr_list {
                    512:                do_statement_expr($4);
1.319     rillig    513:          } compound_statement_rbrace T_RPAREN {
1.380     rillig    514:                $$ = end_statement_expr();
1.1       cgd       515:          }
                    516:        ;
                    517:
1.319     rillig    518: comma_opt:                     /* helper for 'postfix_expression' */
                    519:          /* empty */
                    520:        | T_COMMA
                    521:        ;
                    522:
1.193     rillig    523: /*
1.319     rillig    524:  * The inner part of a GCC statement-expression of the form ({ ... }).
1.193     rillig    525:  *
1.319     rillig    526:  * https://gcc.gnu.org/onlinedocs/gcc/Statement-Exprs.html
1.193     rillig    527:  */
1.319     rillig    528: gcc_statement_expr_list:
                    529:          gcc_statement_expr_item
                    530:        | gcc_statement_expr_list gcc_statement_expr_item {
                    531:                $$ = $2;
                    532:          }
                    533:        ;
                    534:
                    535: gcc_statement_expr_item:
1.326     rillig    536:          declaration_or_error {
1.319     rillig    537:                clear_warning_flags();
                    538:                $$ = NULL;
                    539:          }
                    540:        | non_expr_statement {
1.383     rillig    541:                $$ = expr_alloc_tnode();
1.319     rillig    542:                $$->tn_type = gettyp(VOID);
                    543:          }
1.322     rillig    544:        | expression T_SEMI {
1.319     rillig    545:                if ($1 == NULL) {       /* in case of syntax errors */
1.383     rillig    546:                        $$ = expr_alloc_tnode();
1.319     rillig    547:                        $$->tn_type = gettyp(VOID);
                    548:                } else {
                    549:                        /* XXX: do that only on the last name */
                    550:                        if ($1->tn_op == NAME)
                    551:                                $1->tn_sym->s_used = true;
                    552:                        expr($1, false, false, false, false);
                    553:                        seen_fallthrough = false;
1.334     rillig    554:                        $$ = $1;
1.319     rillig    555:                }
                    556:          }
                    557:        ;
                    558:
                    559: point_or_arrow:                        /* helper for 'postfix_expression' */
                    560:          T_POINT {
                    561:                symtyp = FMEMBER;
                    562:                $$ = POINT;
                    563:          }
                    564:        | T_ARROW {
                    565:                symtyp = FMEMBER;
                    566:                $$ = ARROW;
                    567:          }
                    568:        ;
                    569:
1.321     rillig    570: /* K&R 7.1, C90 ???, C99 6.5.2, C11 6.5.2 */
1.319     rillig    571: argument_expression_list:
1.325     rillig    572:          assignment_expression {
1.330     rillig    573:                $$ = build_function_argument(NULL, $1);
1.319     rillig    574:          }
1.325     rillig    575:        | argument_expression_list T_COMMA assignment_expression {
1.330     rillig    576:                $$ = build_function_argument($1, $3);
1.319     rillig    577:          }
                    578:        ;
                    579:
1.321     rillig    580: /* K&R 7.2, C90 ???, C99 6.5.3, C11 6.5.3 */
1.319     rillig    581: unary_expression:
                    582:          postfix_expression
1.370     rillig    583:        | T_INCDEC sys unary_expression {
                    584:                $$ = build_unary($1 == INC ? INCBEF : DECBEF, $2, $3);
1.319     rillig    585:          }
1.370     rillig    586:        | T_AMPER sys cast_expression {
                    587:                $$ = build_unary(ADDR, $2, $3);
1.319     rillig    588:          }
1.370     rillig    589:        | T_ASTERISK sys cast_expression {
                    590:                $$ = build_unary(INDIR, $2, $3);
1.319     rillig    591:          }
1.370     rillig    592:        | T_ADDITIVE sys cast_expression {
1.409   ! rillig    593:                if (!allow_c90 && $1 == PLUS) {
1.319     rillig    594:                        /* unary + is illegal in traditional C */
                    595:                        warning(100);
1.1       cgd       596:                }
1.370     rillig    597:                $$ = build_unary($1 == PLUS ? UPLUS : UMINUS, $2, $3);
1.319     rillig    598:          }
1.370     rillig    599:        | T_COMPLEMENT sys cast_expression {
                    600:                $$ = build_unary(COMPL, $2, $3);
1.319     rillig    601:          }
1.370     rillig    602:        | T_LOGNOT sys cast_expression {
                    603:                $$ = build_unary(NOT, $2, $3);
1.319     rillig    604:          }
1.370     rillig    605:        | T_REAL sys cast_expression {  /* GCC c_parser_unary_expression */
                    606:                $$ = build_unary(REAL, $2, $3);
1.319     rillig    607:          }
1.370     rillig    608:        | T_IMAG sys cast_expression {  /* GCC c_parser_unary_expression */
                    609:                $$ = build_unary(IMAG, $2, $3);
1.319     rillig    610:          }
                    611:        | T_EXTENSION cast_expression { /* GCC c_parser_unary_expression */
                    612:                $$ = $2;
                    613:          }
                    614:        | T_SIZEOF unary_expression {
                    615:                $$ = $2 == NULL ? NULL : build_sizeof($2->tn_type);
                    616:                if ($$ != NULL)
1.338     rillig    617:                        check_expr_misc($2,
                    618:                            false, false, false, false, false, true);
1.319     rillig    619:          }
                    620:        | T_SIZEOF T_LPAREN type_name T_RPAREN {
                    621:                $$ = build_sizeof($3);
                    622:          }
1.321     rillig    623:        /* K&R ---, C90 ---, C99 ---, C11 6.5.3 */
1.319     rillig    624:        | T_ALIGNOF T_LPAREN type_name T_RPAREN {
1.334     rillig    625:                /* TODO: c11ism */
1.319     rillig    626:                $$ = build_alignof($3);
                    627:          }
                    628:        ;
                    629:
                    630: /* The rule 'unary_operator' is inlined into unary_expression. */
                    631:
1.321     rillig    632: /* K&R 7.2, C90 ???, C99 6.5.4, C11 6.5.4 */
1.319     rillig    633: cast_expression:
                    634:          unary_expression
                    635:        | T_LPAREN type_name T_RPAREN cast_expression {
                    636:                $$ = cast($4, $2);
                    637:          }
                    638:        ;
                    639:
1.322     rillig    640: expression_opt:
1.319     rillig    641:          /* empty */ {
                    642:                $$ = NULL;
                    643:          }
1.322     rillig    644:        | expression
1.319     rillig    645:        ;
                    646:
1.325     rillig    647: /* 'conditional_expression' also implements 'multiplicative_expression'. */
                    648: /* 'conditional_expression' also implements 'additive_expression'. */
                    649: /* 'conditional_expression' also implements 'shift_expression'. */
                    650: /* 'conditional_expression' also implements 'relational_expression'. */
                    651: /* 'conditional_expression' also implements 'equality_expression'. */
                    652: /* 'conditional_expression' also implements 'AND_expression'. */
                    653: /* 'conditional_expression' also implements 'exclusive_OR_expression'. */
                    654: /* 'conditional_expression' also implements 'inclusive_OR_expression'. */
                    655: /* 'conditional_expression' also implements 'logical_AND_expression'. */
                    656: /* 'conditional_expression' also implements 'logical_OR_expression'. */
                    657: /* K&R ???, C90 ???, C99 6.5.5 to 6.5.15, C11 6.5.5 to 6.5.15 */
                    658: conditional_expression:
1.343     rillig    659:          cast_expression
1.370     rillig    660:        | conditional_expression T_ASTERISK sys conditional_expression {
                    661:                $$ = build_binary($1, MULT, $3, $4);
1.319     rillig    662:          }
1.370     rillig    663:        | conditional_expression T_MULTIPLICATIVE sys conditional_expression {
                    664:                $$ = build_binary($1, $2, $3, $4);
1.319     rillig    665:          }
1.370     rillig    666:        | conditional_expression T_ADDITIVE sys conditional_expression {
                    667:                $$ = build_binary($1, $2, $3, $4);
1.319     rillig    668:          }
1.370     rillig    669:        | conditional_expression T_SHIFT sys conditional_expression {
                    670:                $$ = build_binary($1, $2, $3, $4);
1.319     rillig    671:          }
1.370     rillig    672:        | conditional_expression T_RELATIONAL sys conditional_expression {
                    673:                $$ = build_binary($1, $2, $3, $4);
1.319     rillig    674:          }
1.370     rillig    675:        | conditional_expression T_EQUALITY sys conditional_expression {
                    676:                $$ = build_binary($1, $2, $3, $4);
1.1       cgd       677:          }
1.370     rillig    678:        | conditional_expression T_AMPER sys conditional_expression {
                    679:                $$ = build_binary($1, BITAND, $3, $4);
1.1       cgd       680:          }
1.370     rillig    681:        | conditional_expression T_BITXOR sys conditional_expression {
                    682:                $$ = build_binary($1, BITXOR, $3, $4);
1.306     rillig    683:          }
1.370     rillig    684:        | conditional_expression T_BITOR sys conditional_expression {
                    685:                $$ = build_binary($1, BITOR, $3, $4);
1.306     rillig    686:          }
1.370     rillig    687:        | conditional_expression T_LOGAND sys conditional_expression {
                    688:                $$ = build_binary($1, LOGAND, $3, $4);
1.1       cgd       689:          }
1.370     rillig    690:        | conditional_expression T_LOGOR sys conditional_expression {
                    691:                $$ = build_binary($1, LOGOR, $3, $4);
1.1       cgd       692:          }
1.370     rillig    693:        | conditional_expression T_QUEST sys
                    694:            expression T_COLON sys conditional_expression {
                    695:                $$ = build_binary($1, QUEST, $3,
                    696:                    build_binary($4, COLON, $6, $7));
1.1       cgd       697:          }
1.343     rillig    698:        ;
1.325     rillig    699:
                    700: /* K&R ???, C90 ???, C99 6.5.16, C11 6.5.16 */
                    701: assignment_expression:
                    702:          conditional_expression
1.370     rillig    703:        | unary_expression T_ASSIGN sys assignment_expression {
                    704:                $$ = build_binary($1, ASSIGN, $3, $4);
1.1       cgd       705:          }
1.370     rillig    706:        | unary_expression T_OPASSIGN sys assignment_expression {
                    707:                $$ = build_binary($1, $2, $3, $4);
1.1       cgd       708:          }
1.325     rillig    709:        ;
                    710:
                    711: /* K&R ???, C90 ???, C99 6.5.17, C11 6.5.17 */
                    712: expression:
                    713:          assignment_expression
1.370     rillig    714:        | expression T_COMMA sys assignment_expression {
                    715:                $$ = build_binary($1, COMMA, $3, $4);
1.1       cgd       716:          }
                    717:        ;
                    718:
1.319     rillig    719: constant_expr_list_opt:                /* helper for gcc_attribute */
1.1       cgd       720:          /* empty */
1.319     rillig    721:        | constant_expr_list
1.1       cgd       722:        ;
                    723:
1.319     rillig    724: constant_expr_list:            /* helper for gcc_attribute */
                    725:          constant_expr
                    726:        | constant_expr_list T_COMMA constant_expr
1.1       cgd       727:        ;
                    728:
1.319     rillig    729: constant_expr:                 /* C99 6.6 */
1.325     rillig    730:          conditional_expression
1.1       cgd       731:        ;
                    732:
1.326     rillig    733: declaration_or_error:
                    734:          declaration
                    735:        | error T_SEMI
                    736:        ;
                    737:
1.193     rillig    738: declaration:                   /* C99 6.7 */
1.306     rillig    739:          begin_type_declmods end_type T_SEMI {
1.3       jpo       740:                if (dcs->d_scl == TYPEDEF) {
1.1       cgd       741:                        /* typedef declares no type name */
                    742:                        warning(72);
                    743:                } else {
                    744:                        /* empty declaration */
                    745:                        warning(2);
                    746:                }
                    747:          }
1.401     rillig    748:        | begin_type_declmods end_type notype_init_declarators T_SEMI {
                    749:                if (dcs->d_scl == TYPEDEF) {
                    750:                        /* syntax error '%s' */
                    751:                        error(249, "missing base type for typedef");
                    752:                } else {
                    753:                        /* old style declaration; add 'int' */
                    754:                        error(1);
                    755:                }
                    756:          }
1.306     rillig    757:        | begin_type_declaration_specifiers end_type T_SEMI {
1.3       jpo       758:                if (dcs->d_scl == TYPEDEF) {
1.1       cgd       759:                        /* typedef declares no type name */
                    760:                        warning(72);
1.195     rillig    761:                } else if (!dcs->d_nonempty_decl) {
1.1       cgd       762:                        /* empty declaration */
                    763:                        warning(2);
                    764:                }
                    765:          }
1.324     rillig    766:        | begin_type_declaration_specifiers end_type
                    767:            type_init_declarators T_SEMI
1.365     christos  768:        | static_assert_declaration
1.1       cgd       769:        ;
                    770:
1.306     rillig    771: begin_type_declaration_specifiers:     /* see C99 6.7 */
                    772:          begin_type_typespec {
                    773:                add_type($1);
                    774:          }
                    775:        | begin_type_declmods type_specifier {
                    776:                add_type($2);
                    777:          }
                    778:        | type_attribute begin_type_declaration_specifiers
                    779:        | begin_type_declaration_specifiers declmod
                    780:        | begin_type_declaration_specifiers notype_type_specifier {
                    781:                add_type($2);
                    782:          }
1.1       cgd       783:        ;
                    784:
1.319     rillig    785: begin_type_declmods:           /* see C99 6.7 */
1.306     rillig    786:          begin_type T_QUAL {
                    787:                add_qualifier($2);
                    788:          }
                    789:        | begin_type T_SCLASS {
                    790:                add_storage_class($2);
1.1       cgd       791:          }
1.306     rillig    792:        | begin_type_declmods declmod
1.1       cgd       793:        ;
                    794:
1.333     rillig    795: begin_type_specifier_qualifier_list:   /* see C11 6.7.2.1 */
1.344     rillig    796:          begin_type_specifier_qualifier_list_postfix
                    797:        | type_attribute_list begin_type_specifier_qualifier_list_postfix
                    798:        ;
                    799:
                    800: begin_type_specifier_qualifier_list_postfix:
1.319     rillig    801:          begin_type_typespec {
                    802:                add_type($1);
                    803:          }
1.333     rillig    804:        | begin_type_qualifier_list type_specifier {
1.319     rillig    805:                add_type($2);
                    806:          }
1.344     rillig    807:        | begin_type_specifier_qualifier_list_postfix T_QUAL {
1.319     rillig    808:                add_qualifier($2);
1.306     rillig    809:          }
1.344     rillig    810:        | begin_type_specifier_qualifier_list_postfix notype_type_specifier {
1.319     rillig    811:                add_type($2);
1.299     rillig    812:          }
1.344     rillig    813:        | begin_type_specifier_qualifier_list_postfix type_attribute
1.299     rillig    814:        ;
                    815:
1.306     rillig    816: begin_type_typespec:
                    817:          begin_type notype_type_specifier {
                    818:                $$ = $2;
                    819:          }
1.406     rillig    820:        | begin_type T_TYPENAME {
                    821:                $$ = getsym($2)->s_type;
1.306     rillig    822:          }
1.302     rillig    823:        ;
                    824:
1.333     rillig    825: begin_type_qualifier_list:
1.319     rillig    826:          begin_type T_QUAL {
                    827:                add_qualifier($2);
                    828:          }
1.333     rillig    829:        | begin_type_qualifier_list T_QUAL {
1.319     rillig    830:                add_qualifier($2);
                    831:          }
                    832:        ;
                    833:
                    834: declmod:
                    835:          T_QUAL {
                    836:                add_qualifier($1);
                    837:          }
                    838:        | T_SCLASS {
                    839:                add_storage_class($1);
                    840:          }
                    841:        | type_attribute_list
                    842:        ;
                    843:
1.398     rillig    844: type_attribute_list_opt:
                    845:          /* empty */
                    846:        | type_attribute_list
                    847:        ;
                    848:
1.302     rillig    849: type_attribute_list:
                    850:          type_attribute
                    851:        | type_attribute_list type_attribute
                    852:        ;
                    853:
                    854: type_attribute_opt:
                    855:          /* empty */
                    856:        | type_attribute
                    857:        ;
                    858:
                    859: type_attribute:                        /* See C11 6.7 declaration-specifiers */
1.339     rillig    860:          gcc_attribute
1.351     rillig    861:        | T_ALIGNAS T_LPAREN type_specifier T_RPAREN    /* C11 6.7.5 */
                    862:        | T_ALIGNAS T_LPAREN constant_expr T_RPAREN     /* C11 6.7.5 */
1.302     rillig    863:        | T_PACKED {
                    864:                addpacked();
                    865:          }
                    866:        | T_NORETURN
                    867:        ;
                    868:
1.319     rillig    869: begin_type:
                    870:          /* empty */ {
                    871:                begin_type();
                    872:          }
                    873:        ;
                    874:
                    875: end_type:
                    876:          /* empty */ {
                    877:                end_type();
                    878:          }
                    879:        ;
                    880:
1.300     rillig    881: type_specifier:                        /* C99 6.7.2 */
                    882:          notype_type_specifier
1.1       cgd       883:        | T_TYPENAME {
                    884:                $$ = getsym($1)->s_type;
                    885:          }
                    886:        ;
                    887:
1.319     rillig    888: notype_type_specifier:         /* see C99 6.7.2 */
1.1       cgd       889:          T_TYPE {
                    890:                $$ = gettyp($1);
                    891:          }
1.337     rillig    892:        | T_TYPEOF T_LPAREN expression T_RPAREN {       /* GCC extension */
1.394     rillig    893:                $$ = block_dup_type($3->tn_type);
                    894:                $$->t_typeof = true;
1.58      christos  895:          }
1.300     rillig    896:        | struct_or_union_specifier {
1.202     rillig    897:                end_declaration_level();
1.1       cgd       898:                $$ = $1;
                    899:          }
1.300     rillig    900:        | enum_specifier {
1.202     rillig    901:                end_declaration_level();
1.1       cgd       902:                $$ = $1;
                    903:          }
                    904:        ;
                    905:
1.300     rillig    906: struct_or_union_specifier:     /* C99 6.7.2.1 */
1.301     rillig    907:          struct_or_union identifier_sym {
1.1       cgd       908:                /*
                    909:                 * STDC requires that "struct a;" always introduces
                    910:                 * a new tag if "a" is not declared at current level
                    911:                 *
1.110     rillig    912:                 * yychar is valid because otherwise the parser would not
                    913:                 * have been able to decide if it must shift or reduce
1.1       cgd       914:                 */
1.183     rillig    915:                $$ = mktag($2, $1, false, yychar == T_SEMI);
1.1       cgd       916:          }
1.306     rillig    917:        | struct_or_union identifier_sym {
1.183     rillig    918:                dcs->d_tagtyp = mktag($2, $1, true, false);
1.306     rillig    919:          } braced_struct_declaration_list {
                    920:                $$ = complete_tag_struct_or_union(dcs->d_tagtyp, $4);
                    921:          }
                    922:        | struct_or_union {
                    923:                dcs->d_tagtyp = mktag(NULL, $1, true, false);
                    924:          } braced_struct_declaration_list {
                    925:                $$ = complete_tag_struct_or_union(dcs->d_tagtyp, $3);
1.1       cgd       926:          }
1.300     rillig    927:        | struct_or_union error {
1.1       cgd       928:                symtyp = FVFT;
                    929:                $$ = gettyp(INT);
                    930:          }
                    931:        ;
                    932:
1.300     rillig    933: struct_or_union:               /* C99 6.7.2.1 */
1.343     rillig    934:          T_STRUCT_OR_UNION {
1.1       cgd       935:                symtyp = FTAG;
1.393     rillig    936:                begin_declaration_level($1 == STRUCT ? DK_MOS : DK_MOU);
1.392     rillig    937:                dcs->d_offset_in_bits = 0;
1.250     rillig    938:                dcs->d_sou_align_in_bits = CHAR_SIZE;
1.306     rillig    939:                $$ = $1;
                    940:          }
1.343     rillig    941:        | struct_or_union type_attribute
1.306     rillig    942:        ;
                    943:
1.319     rillig    944: braced_struct_declaration_list:        /* see C99 6.7.2.1 */
1.306     rillig    945:          struct_declaration_lbrace struct_declaration_list_with_rbrace {
                    946:                $$ = $2;
                    947:          }
1.1       cgd       948:        ;
                    949:
1.319     rillig    950: struct_declaration_lbrace:     /* see C99 6.7.2.1 */
1.306     rillig    951:          T_LBRACE {
                    952:                symtyp = FVFT;
1.269     rillig    953:          }
1.306     rillig    954:        ;
                    955:
1.319     rillig    956: struct_declaration_list_with_rbrace:   /* see C99 6.7.2.1 */
1.328     rillig    957:          struct_declaration_list T_RBRACE
1.306     rillig    958:        | T_RBRACE {
1.328     rillig    959:                /* XXX: This is not allowed by any C standard. */
1.306     rillig    960:                $$ = NULL;
                    961:          }
1.1       cgd       962:        ;
                    963:
1.319     rillig    964: struct_declaration_list:       /* C99 6.7.2.1 */
1.300     rillig    965:          struct_declaration
1.328     rillig    966:        | struct_declaration_list struct_declaration {
                    967:                $$ = lnklst($1, $2);
1.1       cgd       968:          }
                    969:        ;
                    970:
1.319     rillig    971: struct_declaration:            /* C99 6.7.2.1 */
1.333     rillig    972:          begin_type_qualifier_list end_type {
1.334     rillig    973:                /* ^^ There is no check for the missing type-specifier. */
1.1       cgd       974:                /* too late, i know, but getsym() compensates it */
1.120     rillig    975:                symtyp = FMEMBER;
1.328     rillig    976:          } notype_struct_declarators type_attribute_opt T_SEMI {
1.1       cgd       977:                symtyp = FVFT;
1.306     rillig    978:                $$ = $4;
1.1       cgd       979:          }
1.333     rillig    980:        | begin_type_specifier_qualifier_list end_type {
1.120     rillig    981:                symtyp = FMEMBER;
1.328     rillig    982:          } type_struct_declarators type_attribute_opt T_SEMI {
1.1       cgd       983:                symtyp = FVFT;
1.306     rillig    984:                $$ = $4;
1.1       cgd       985:          }
1.333     rillig    986:        | begin_type_qualifier_list end_type type_attribute_opt T_SEMI {
1.288     rillig    987:                /* syntax error '%s' */
                    988:                error(249, "member without type");
                    989:                $$ = NULL;
1.1       cgd       990:          }
1.338     rillig    991:        | begin_type_specifier_qualifier_list end_type type_attribute_opt
                    992:            T_SEMI {
1.74      christos  993:                symtyp = FVFT;
1.397     rillig    994:                if (!allow_c11 && !allow_gcc)
1.385     rillig    995:                        /* anonymous struct/union members is a C11 feature */
1.73      christos  996:                        warning(49);
1.228     rillig    997:                if (is_struct_or_union(dcs->d_type->t_tspec)) {
                    998:                        $$ = dcs->d_type->t_str->sou_first_member;
                    999:                        /* add all the members of the anonymous struct/union */
                   1000:                        anonymize($$);
                   1001:                } else {
                   1002:                        /* syntax error '%s' */
                   1003:                        error(249, "unnamed member");
1.232     rillig   1004:                        $$ = NULL;
1.228     rillig   1005:                }
1.1       cgd      1006:          }
1.367     rillig   1007:        | static_assert_declaration {
                   1008:                $$ = NULL;
                   1009:          }
1.328     rillig   1010:        | error T_SEMI {
1.1       cgd      1011:                symtyp = FVFT;
                   1012:                $$ = NULL;
                   1013:          }
                   1014:        ;
                   1015:
1.324     rillig   1016: notype_struct_declarators:
                   1017:          notype_struct_declarator {
1.111     rillig   1018:                $$ = declarator_1_struct_union($1);
1.1       cgd      1019:          }
1.324     rillig   1020:        | notype_struct_declarators {
1.120     rillig   1021:                symtyp = FMEMBER;
1.324     rillig   1022:          } T_COMMA type_struct_declarator {
1.111     rillig   1023:                $$ = lnklst($1, declarator_1_struct_union($4));
1.1       cgd      1024:          }
                   1025:        ;
                   1026:
1.324     rillig   1027: type_struct_declarators:
                   1028:          type_struct_declarator {
1.111     rillig   1029:                $$ = declarator_1_struct_union($1);
1.1       cgd      1030:          }
1.324     rillig   1031:        | type_struct_declarators {
1.120     rillig   1032:                symtyp = FMEMBER;
1.324     rillig   1033:          } T_COMMA type_struct_declarator {
1.111     rillig   1034:                $$ = lnklst($1, declarator_1_struct_union($4));
1.1       cgd      1035:          }
                   1036:        ;
                   1037:
1.324     rillig   1038: notype_struct_declarator:
                   1039:          notype_declarator
1.338     rillig   1040:        | notype_declarator T_COLON constant_expr {     /* C99 6.7.2.1 */
1.175     rillig   1041:                $$ = bitfield($1, to_int_constant($3, true));
1.1       cgd      1042:          }
                   1043:        | {
                   1044:                symtyp = FVFT;
1.168     rillig   1045:          } T_COLON constant_expr {                     /* C99 6.7.2.1 */
1.175     rillig   1046:                $$ = bitfield(NULL, to_int_constant($3, true));
1.1       cgd      1047:          }
                   1048:        ;
                   1049:
1.324     rillig   1050: type_struct_declarator:
                   1051:          type_declarator
                   1052:        | type_declarator T_COLON constant_expr {
1.175     rillig   1053:                $$ = bitfield($1, to_int_constant($3, true));
1.1       cgd      1054:          }
                   1055:        | {
                   1056:                symtyp = FVFT;
1.168     rillig   1057:          } T_COLON constant_expr {
1.175     rillig   1058:                $$ = bitfield(NULL, to_int_constant($3, true));
1.1       cgd      1059:          }
                   1060:        ;
                   1061:
1.395     rillig   1062: /* K&R ---, C90 6.5.2.2, C99 6.7.2.2, C11 6.7.2.2 */
1.319     rillig   1063: enum_specifier:                        /* C99 6.7.2.2 */
1.341     rillig   1064:          enum gcc_attribute_list_opt identifier_sym {
                   1065:                $$ = mktag($3, ENUM, false, false);
1.1       cgd      1066:          }
1.341     rillig   1067:        | enum gcc_attribute_list_opt identifier_sym {
                   1068:                dcs->d_tagtyp = mktag($3, ENUM, true, false);
                   1069:          } enum_declaration /*gcc_attribute_list_opt*/ {
                   1070:                $$ = complete_tag_enum(dcs->d_tagtyp, $5);
1.306     rillig   1071:          }
1.341     rillig   1072:        | enum gcc_attribute_list_opt {
1.306     rillig   1073:                dcs->d_tagtyp = mktag(NULL, ENUM, true, false);
1.341     rillig   1074:          } enum_declaration /*gcc_attribute_list_opt*/ {
                   1075:                $$ = complete_tag_enum(dcs->d_tagtyp, $4);
1.1       cgd      1076:          }
                   1077:        | enum error {
                   1078:                symtyp = FVFT;
                   1079:                $$ = gettyp(INT);
                   1080:          }
                   1081:        ;
                   1082:
1.319     rillig   1083: enum:                          /* helper for C99 6.7.2.2 */
1.1       cgd      1084:          T_ENUM {
                   1085:                symtyp = FTAG;
1.393     rillig   1086:                begin_declaration_level(DK_ENUM_CONST);
1.1       cgd      1087:          }
                   1088:        ;
                   1089:
1.319     rillig   1090: enum_declaration:              /* helper for C99 6.7.2.2 */
1.306     rillig   1091:          enum_decl_lbrace enums_with_opt_comma T_RBRACE {
                   1092:                $$ = $2;
1.259     rillig   1093:          }
1.306     rillig   1094:        ;
                   1095:
1.319     rillig   1096: enum_decl_lbrace:              /* helper for C99 6.7.2.2 */
1.306     rillig   1097:          T_LBRACE {
                   1098:                symtyp = FVFT;
                   1099:                enumval = 0;
1.259     rillig   1100:          }
                   1101:        ;
                   1102:
1.319     rillig   1103: enums_with_opt_comma:          /* helper for C99 6.7.2.2 */
1.306     rillig   1104:          enumerator_list
                   1105:        | enumerator_list T_COMMA {
1.408     rillig   1106:                if (!allow_c99 && !allow_trad) {
1.123     rillig   1107:                        /* trailing ',' prohibited in enum declaration */
1.1       cgd      1108:                        error(54);
                   1109:                } else {
1.319     rillig   1110:                        /* trailing ',' prohibited in enum declaration */
                   1111:                        c99ism(54);
                   1112:                }
                   1113:                $$ = $1;
                   1114:          }
                   1115:        ;
                   1116:
                   1117: enumerator_list:               /* C99 6.7.2.2 */
                   1118:          enumerator
                   1119:        | enumerator_list T_COMMA enumerator {
                   1120:                $$ = lnklst($1, $3);
                   1121:          }
                   1122:        | error {
                   1123:                $$ = NULL;
                   1124:          }
                   1125:        ;
                   1126:
                   1127: enumerator:                    /* C99 6.7.2.2 */
1.342     rillig   1128:          identifier_sym gcc_attribute_list_opt {
1.319     rillig   1129:                $$ = enumeration_constant($1, enumval, true);
                   1130:          }
1.342     rillig   1131:        | identifier_sym gcc_attribute_list_opt T_ASSIGN constant_expr {
                   1132:                $$ = enumeration_constant($1, to_int_constant($4, true),
1.338     rillig   1133:                    false);
1.319     rillig   1134:          }
                   1135:        ;
                   1136:
                   1137: type_qualifier:                        /* C99 6.7.3 */
                   1138:          T_QUAL {
                   1139:                $$ = xcalloc(1, sizeof(*$$));
1.332     rillig   1140:                if ($1 == CONST)
1.319     rillig   1141:                        $$->p_const = true;
1.332     rillig   1142:                if ($1 == VOLATILE)
1.319     rillig   1143:                        $$->p_volatile = true;
                   1144:          }
                   1145:        ;
                   1146:
                   1147: pointer:                       /* C99 6.7.5 */
                   1148:          asterisk type_qualifier_list_opt {
                   1149:                $$ = merge_qualified_pointer($1, $2);
                   1150:          }
                   1151:        | asterisk type_qualifier_list_opt pointer {
                   1152:                $$ = merge_qualified_pointer($1, $2);
                   1153:                $$ = merge_qualified_pointer($$, $3);
1.306     rillig   1154:          }
                   1155:        ;
                   1156:
1.319     rillig   1157: asterisk:                      /* helper for 'pointer' */
                   1158:          T_ASTERISK {
                   1159:                $$ = xcalloc(1, sizeof(*$$));
                   1160:                $$->p_pointer = true;
1.306     rillig   1161:          }
1.319     rillig   1162:        ;
                   1163:
                   1164: type_qualifier_list_opt:       /* see C99 6.7.5 */
                   1165:          /* empty */ {
1.306     rillig   1166:                $$ = NULL;
1.1       cgd      1167:          }
1.319     rillig   1168:        | type_qualifier_list
1.1       cgd      1169:        ;
                   1170:
1.319     rillig   1171: type_qualifier_list:           /* C99 6.7.5 */
                   1172:          type_qualifier
                   1173:        | type_qualifier_list type_qualifier {
                   1174:                $$ = merge_qualified_pointer($1, $2);
1.1       cgd      1175:          }
                   1176:        ;
                   1177:
1.256     rillig   1178: /*
1.350     rillig   1179:  * For an explanation of 'notype' in the following rules, see
                   1180:  * https://www.gnu.org/software/bison/manual/bison.html#Semantic-Tokens.
1.256     rillig   1181:  */
                   1182:
1.324     rillig   1183: notype_init_declarators:
                   1184:          notype_init_declarator
                   1185:        | notype_init_declarators T_COMMA type_init_declarator
1.1       cgd      1186:        ;
                   1187:
1.324     rillig   1188: type_init_declarators:
                   1189:          type_init_declarator
                   1190:        | type_init_declarators T_COMMA type_init_declarator
1.1       cgd      1191:        ;
                   1192:
1.324     rillig   1193: notype_init_declarator:
                   1194:          notype_declarator asm_or_symbolrename_opt {
1.174     rillig   1195:                cgram_declare($1, false, $2);
1.111     rillig   1196:                check_size($1);
1.1       cgd      1197:          }
1.324     rillig   1198:        | notype_declarator asm_or_symbolrename_opt {
1.198     rillig   1199:                begin_initialization($1);
1.174     rillig   1200:                cgram_declare($1, true, $2);
1.198     rillig   1201:          } T_ASSIGN initializer {
1.111     rillig   1202:                check_size($1);
1.198     rillig   1203:                end_initialization();
1.1       cgd      1204:          }
                   1205:        ;
                   1206:
1.324     rillig   1207: type_init_declarator:
                   1208:          type_declarator asm_or_symbolrename_opt {
1.174     rillig   1209:                cgram_declare($1, false, $2);
1.111     rillig   1210:                check_size($1);
1.1       cgd      1211:          }
1.324     rillig   1212:        | type_declarator asm_or_symbolrename_opt {
1.198     rillig   1213:                begin_initialization($1);
1.174     rillig   1214:                cgram_declare($1, true, $2);
1.198     rillig   1215:          } T_ASSIGN initializer {
1.111     rillig   1216:                check_size($1);
1.198     rillig   1217:                end_initialization();
1.1       cgd      1218:          }
                   1219:        ;
                   1220:
1.324     rillig   1221: notype_declarator:
                   1222:          notype_direct_declarator
                   1223:        | pointer notype_direct_declarator {
1.306     rillig   1224:                $$ = add_pointer($2, $1);
1.1       cgd      1225:          }
                   1226:        ;
                   1227:
1.324     rillig   1228: type_declarator:
                   1229:          type_direct_declarator
                   1230:        | pointer type_direct_declarator {
1.306     rillig   1231:                $$ = add_pointer($2, $1);
1.239     rillig   1232:          }
                   1233:        ;
                   1234:
1.324     rillig   1235: notype_direct_declarator:
1.398     rillig   1236:          type_attribute_list_opt T_NAME {
                   1237:                $$ = declarator_name(getsym($2));
1.1       cgd      1238:          }
1.398     rillig   1239:        | type_attribute_list_opt T_LPAREN type_declarator T_RPAREN {
                   1240:                $$ = $3;
1.306     rillig   1241:          }
1.364     rillig   1242:        | notype_direct_declarator T_LBRACK array_size_opt T_RBRACK {
                   1243:                $$ = add_array($1, $3.has_dim, $3.dim);
1.1       cgd      1244:          }
1.324     rillig   1245:        | notype_direct_declarator param_list asm_or_symbolrename_opt {
1.111     rillig   1246:                $$ = add_function(symbolrename($1, $3), $2);
1.202     rillig   1247:                end_declaration_level();
1.171     rillig   1248:                block_level--;
1.1       cgd      1249:          }
1.324     rillig   1250:        | notype_direct_declarator type_attribute
1.1       cgd      1251:        ;
                   1252:
1.324     rillig   1253: type_direct_declarator:
1.399     rillig   1254:          type_attribute_list_opt identifier {
                   1255:                $$ = declarator_name(getsym($2));
1.1       cgd      1256:          }
1.399     rillig   1257:        | type_attribute_list_opt T_LPAREN type_declarator T_RPAREN {
                   1258:                $$ = $3;
1.306     rillig   1259:          }
1.364     rillig   1260:        | type_direct_declarator T_LBRACK array_size_opt T_RBRACK {
                   1261:                $$ = add_array($1, $3.has_dim, $3.dim);
1.1       cgd      1262:          }
1.324     rillig   1263:        | type_direct_declarator param_list asm_or_symbolrename_opt {
1.111     rillig   1264:                $$ = add_function(symbolrename($1, $3), $2);
1.202     rillig   1265:                end_declaration_level();
1.171     rillig   1266:                block_level--;
1.1       cgd      1267:          }
1.324     rillig   1268:        | type_direct_declarator type_attribute
1.1       cgd      1269:        ;
                   1270:
                   1271: /*
1.338     rillig   1272:  * The two distinct rules type_param_declarator and notype_param_declarator
                   1273:  * avoid a conflict in argument lists. A typename enclosed in parentheses is
                   1274:  * always treated as a typename, not an argument name. For example, after
1.257     rillig   1275:  * "typedef double a;", the declaration "f(int (a));" is interpreted as
                   1276:  * "f(int (double));", not "f(int a);".
1.1       cgd      1277:  */
1.324     rillig   1278: type_param_declarator:
                   1279:          direct_param_declarator
                   1280:        | pointer direct_param_declarator {
1.111     rillig   1281:                $$ = add_pointer($2, $1);
1.1       cgd      1282:          }
                   1283:        ;
                   1284:
1.324     rillig   1285: notype_param_declarator:
                   1286:          direct_notype_param_declarator
                   1287:        | pointer direct_notype_param_declarator {
1.319     rillig   1288:                $$ = add_pointer($2, $1);
1.257     rillig   1289:          }
                   1290:        ;
                   1291:
1.324     rillig   1292: direct_param_declarator:
1.306     rillig   1293:          identifier type_attribute_list {
                   1294:                $$ = declarator_name(getsym($1));
                   1295:          }
                   1296:        | identifier {
1.111     rillig   1297:                $$ = declarator_name(getsym($1));
1.1       cgd      1298:          }
1.324     rillig   1299:        | T_LPAREN notype_param_declarator T_RPAREN {
1.1       cgd      1300:                $$ = $2;
                   1301:          }
1.364     rillig   1302:        | direct_param_declarator T_LBRACK array_size_opt T_RBRACK
1.355     rillig   1303:            gcc_attribute_list_opt {
1.364     rillig   1304:                $$ = add_array($1, $3.has_dim, $3.dim);
1.1       cgd      1305:          }
1.324     rillig   1306:        | direct_param_declarator param_list asm_or_symbolrename_opt {
1.111     rillig   1307:                $$ = add_function(symbolrename($1, $3), $2);
1.202     rillig   1308:                end_declaration_level();
1.171     rillig   1309:                block_level--;
1.1       cgd      1310:          }
                   1311:        ;
                   1312:
1.324     rillig   1313: direct_notype_param_declarator:
1.306     rillig   1314:          identifier {
1.111     rillig   1315:                $$ = declarator_name(getsym($1));
1.1       cgd      1316:          }
1.324     rillig   1317:        | T_LPAREN notype_param_declarator T_RPAREN {
1.1       cgd      1318:                $$ = $2;
                   1319:          }
1.364     rillig   1320:        | direct_notype_param_declarator T_LBRACK array_size_opt T_RBRACK {
                   1321:                $$ = add_array($1, $3.has_dim, $3.dim);
1.1       cgd      1322:          }
1.324     rillig   1323:        | direct_notype_param_declarator param_list asm_or_symbolrename_opt {
1.111     rillig   1324:                $$ = add_function(symbolrename($1, $3), $2);
1.202     rillig   1325:                end_declaration_level();
1.171     rillig   1326:                block_level--;
1.1       cgd      1327:          }
                   1328:        ;
                   1329:
1.319     rillig   1330: param_list:
                   1331:          id_list_lparen identifier_list T_RPAREN {
                   1332:                $$ = $2;
1.1       cgd      1333:          }
1.319     rillig   1334:        | abstract_decl_param_list
                   1335:        ;
                   1336:
                   1337: id_list_lparen:
                   1338:          T_LPAREN {
                   1339:                block_level++;
1.393     rillig   1340:                begin_declaration_level(DK_PROTO_ARG);
1.1       cgd      1341:          }
                   1342:        ;
                   1343:
1.364     rillig   1344: array_size_opt:
                   1345:          /* empty */ {
                   1346:                $$.has_dim = false;
                   1347:                $$.dim = 0;
                   1348:          }
                   1349:        | T_ASTERISK {
                   1350:                /* since C99; variable length array of unspecified size */
                   1351:                $$.has_dim = false; /* TODO: maybe change to true */
                   1352:                $$.dim = 0;     /* just as a placeholder */
                   1353:          }
                   1354:        | array_size {
                   1355:                $$.has_dim = true;
1.373     christos 1356:                $$.dim = $1 == NULL ? 0 : to_int_constant($1, false);
1.364     rillig   1357:          }
                   1358:        ;
                   1359:
1.319     rillig   1360: array_size:
                   1361:          type_qualifier_list_opt T_SCLASS constant_expr {
                   1362:                /* C11 6.7.6.3p7 */
                   1363:                if ($2 != STATIC)
                   1364:                        yyerror("Bad attribute");
                   1365:                /* static array size is a C11 extension */
                   1366:                c11ism(343);
                   1367:                $$ = $3;
1.1       cgd      1368:          }
1.373     christos 1369:        | T_QUAL {
1.376     rillig   1370:                /* C11 6.7.6.2 */
1.373     christos 1371:                if ($1 != RESTRICT)
                   1372:                        yyerror("Bad attribute");
                   1373:                $$ = NULL;
1.376     rillig   1374:          }
1.319     rillig   1375:        | constant_expr
1.1       cgd      1376:        ;
                   1377:
1.319     rillig   1378: identifier_list:               /* C99 6.7.5 */
                   1379:          T_NAME {
                   1380:                $$ = old_style_function_name(getsym($1));
                   1381:          }
                   1382:        | identifier_list T_COMMA T_NAME {
                   1383:                $$ = lnklst($1, old_style_function_name(getsym($3)));
1.245     rillig   1384:          }
1.319     rillig   1385:        | identifier_list error
1.245     rillig   1386:        ;
                   1387:
1.319     rillig   1388: /* XXX: C99 requires an additional specifier-qualifier-list. */
                   1389: type_name:                     /* C99 6.7.6 */
                   1390:          {
1.393     rillig   1391:                begin_declaration_level(DK_ABSTRACT);
1.319     rillig   1392:          } abstract_declaration {
                   1393:                end_declaration_level();
                   1394:                $$ = $2->s_type;
1.1       cgd      1395:          }
                   1396:        ;
                   1397:
1.340     rillig   1398: abstract_declaration:          /* specific to lint */
1.346     rillig   1399:          begin_type_qualifier_list end_type {
                   1400:                $$ = declare_1_abstract(abstract_name());
                   1401:          }
                   1402:        | begin_type_specifier_qualifier_list end_type {
                   1403:                $$ = declare_1_abstract(abstract_name());
                   1404:          }
                   1405:        | begin_type_qualifier_list end_type abstract_declarator {
1.345     rillig   1406:                $$ = declare_1_abstract($3);
1.319     rillig   1407:          }
1.346     rillig   1408:        | begin_type_specifier_qualifier_list end_type abstract_declarator {
1.319     rillig   1409:                $$ = declare_1_abstract($3);
                   1410:          }
1.345     rillig   1411:        ;
                   1412:
1.340     rillig   1413: /* K&R 8.7, C90 ???, C99 6.7.6, C11 6.7.7 */
                   1414: /* In K&R, abstract-declarator could be empty and was still simpler. */
                   1415: abstract_declarator:
1.346     rillig   1416:          pointer {
                   1417:                $$ = add_pointer(abstract_name(), $1);
1.319     rillig   1418:          }
                   1419:        | direct_abstract_declarator
1.346     rillig   1420:        | pointer direct_abstract_declarator {
                   1421:                $$ = add_pointer($2, $1);
1.319     rillig   1422:          }
1.396     rillig   1423:        | type_attribute_list direct_abstract_declarator {
                   1424:                $$ = $2;
                   1425:          }
                   1426:        | pointer type_attribute_list direct_abstract_declarator {
                   1427:                $$ = add_pointer($3, $1);
                   1428:          }
1.260     rillig   1429:        ;
                   1430:
1.340     rillig   1431: /* K&R ---, C90 ???, C99 6.7.6, C11 6.7.7 */
                   1432: direct_abstract_declarator:
1.362     rillig   1433:        /* TODO: sort rules according to C99 */
1.319     rillig   1434:          T_LPAREN abstract_declarator T_RPAREN {
                   1435:                $$ = $2;
                   1436:          }
1.364     rillig   1437:        | T_LBRACK array_size_opt T_RBRACK {
                   1438:                $$ = add_array(abstract_name(), $2.has_dim, $2.dim);
1.319     rillig   1439:          }
1.364     rillig   1440:        | direct_abstract_declarator T_LBRACK array_size_opt T_RBRACK {
                   1441:                $$ = add_array($1, $3.has_dim, $3.dim);
1.1       cgd      1442:          }
1.319     rillig   1443:        | abstract_decl_param_list asm_or_symbolrename_opt {
                   1444:                $$ = add_function(symbolrename(abstract_name(), $2), $1);
                   1445:                end_declaration_level();
                   1446:                block_level--;
1.1       cgd      1447:          }
1.338     rillig   1448:        | direct_abstract_declarator abstract_decl_param_list
                   1449:            asm_or_symbolrename_opt {
1.319     rillig   1450:                $$ = add_function(symbolrename($1, $3), $2);
                   1451:                end_declaration_level();
                   1452:                block_level--;
1.1       cgd      1453:          }
1.319     rillig   1454:        | direct_abstract_declarator type_attribute_list
1.1       cgd      1455:        ;
                   1456:
1.340     rillig   1457: abstract_decl_param_list:      /* specific to lint */
1.241     rillig   1458:          abstract_decl_lparen T_RPAREN type_attribute_opt {
1.1       cgd      1459:                $$ = NULL;
                   1460:          }
1.338     rillig   1461:        | abstract_decl_lparen vararg_parameter_type_list T_RPAREN
                   1462:            type_attribute_opt {
1.140     rillig   1463:                dcs->d_proto = true;
1.1       cgd      1464:                $$ = $2;
                   1465:          }
1.241     rillig   1466:        | abstract_decl_lparen error T_RPAREN type_attribute_opt {
1.1       cgd      1467:                $$ = NULL;
                   1468:          }
                   1469:        ;
                   1470:
1.340     rillig   1471: abstract_decl_lparen:          /* specific to lint */
1.126     rillig   1472:          T_LPAREN {
1.171     rillig   1473:                block_level++;
1.393     rillig   1474:                begin_declaration_level(DK_PROTO_ARG);
1.1       cgd      1475:          }
                   1476:        ;
                   1477:
1.340     rillig   1478: vararg_parameter_type_list:    /* specific to lint */
1.240     rillig   1479:          parameter_type_list
1.147     rillig   1480:        | parameter_type_list T_COMMA T_ELLIPSIS {
1.140     rillig   1481:                dcs->d_vararg = true;
1.1       cgd      1482:                $$ = $1;
                   1483:          }
1.147     rillig   1484:        | T_ELLIPSIS {
1.1       cgd      1485:                if (sflag) {
1.123     rillig   1486:                        /* ANSI C requires formal parameter before '...' */
1.1       cgd      1487:                        error(84);
1.409   ! rillig   1488:                } else if (allow_c90) {
1.123     rillig   1489:                        /* ANSI C requires formal parameter before '...' */
1.1       cgd      1490:                        warning(84);
                   1491:                }
1.140     rillig   1492:                dcs->d_vararg = true;
1.1       cgd      1493:                $$ = NULL;
                   1494:          }
                   1495:        ;
                   1496:
1.319     rillig   1497: /* XXX: C99 6.7.5 defines the same name, but it looks different. */
1.1       cgd      1498: parameter_type_list:
1.240     rillig   1499:          parameter_declaration
1.11      cgd      1500:        | parameter_type_list T_COMMA parameter_declaration {
1.1       cgd      1501:                $$ = lnklst($1, $3);
                   1502:          }
                   1503:        ;
                   1504:
1.258     rillig   1505: /* XXX: C99 6.7.5 defines the same name, but it looks completely different. */
1.1       cgd      1506: parameter_declaration:
1.306     rillig   1507:          begin_type_declmods end_type {
1.334     rillig   1508:                /* ^^ There is no check for the missing type-specifier. */
1.183     rillig   1509:                $$ = declare_argument(abstract_name(), false);
1.1       cgd      1510:          }
1.306     rillig   1511:        | begin_type_declaration_specifiers end_type {
1.183     rillig   1512:                $$ = declare_argument(abstract_name(), false);
1.1       cgd      1513:          }
1.324     rillig   1514:        | begin_type_declmods end_type notype_param_declarator {
1.334     rillig   1515:                /* ^^ There is no check for the missing type-specifier. */
1.306     rillig   1516:                $$ = declare_argument($3, false);
1.1       cgd      1517:          }
1.306     rillig   1518:        /*
1.324     rillig   1519:         * type_param_declarator is needed because of following conflict:
1.306     rillig   1520:         * "typedef int a; f(int (a));" could be parsed as
                   1521:         * "function with argument a of type int", or
                   1522:         * "function with an abstract argument of type function".
                   1523:         * This grammar realizes the second case.
                   1524:         */
1.324     rillig   1525:        | begin_type_declaration_specifiers end_type type_param_declarator {
1.306     rillig   1526:                $$ = declare_argument($3, false);
1.1       cgd      1527:          }
1.306     rillig   1528:        | begin_type_declmods end_type abstract_declarator {
1.334     rillig   1529:                /* ^^ There is no check for the missing type-specifier. */
1.306     rillig   1530:                $$ = declare_argument($3, false);
1.1       cgd      1531:          }
1.306     rillig   1532:        | begin_type_declaration_specifiers end_type abstract_declarator {
                   1533:                $$ = declare_argument($3, false);
1.1       cgd      1534:          }
                   1535:        ;
                   1536:
1.179     rillig   1537: initializer:                   /* C99 6.7.8 "Initialization" */
1.325     rillig   1538:          assignment_expression {
1.207     rillig   1539:                init_expr($1);
1.1       cgd      1540:          }
1.178     rillig   1541:        | init_lbrace init_rbrace {
                   1542:                /* XXX: Empty braces are not covered by C99 6.7.8. */
                   1543:          }
1.182     rillig   1544:        | init_lbrace initializer_list comma_opt init_rbrace
1.334     rillig   1545:          /* XXX: What is this error handling for? */
1.1       cgd      1546:        | error
                   1547:        ;
                   1548:
1.179     rillig   1549: initializer_list:              /* C99 6.7.8 "Initialization" */
1.192     rillig   1550:          initializer_list_item
1.180     rillig   1551:        | initializer_list T_COMMA initializer_list_item
                   1552:        ;
                   1553:
1.319     rillig   1554: initializer_list_item:         /* helper */
1.180     rillig   1555:          designation initializer
                   1556:        | initializer
1.1       cgd      1557:        ;
                   1558:
1.239     rillig   1559: designation:                   /* C99 6.7.8 "Initialization" */
1.377     rillig   1560:          begin_designation designator_list T_ASSIGN
1.239     rillig   1561:        | identifier T_COLON {
                   1562:                /* GCC style struct or union member name in initializer */
                   1563:                gnuism(315);
1.377     rillig   1564:                begin_designation();
1.239     rillig   1565:                add_designator_member($1);
1.35      christos 1566:          }
1.239     rillig   1567:        ;
                   1568:
1.377     rillig   1569: begin_designation:             /* lint-specific helper */
                   1570:          /* empty */ {
                   1571:                begin_designation();
                   1572:          }
                   1573:        ;
                   1574:
1.239     rillig   1575: designator_list:               /* C99 6.7.8 "Initialization" */
                   1576:          designator
                   1577:        | designator_list designator
1.35      christos 1578:        ;
                   1579:
1.167     rillig   1580: designator:                    /* C99 6.7.8 "Initialization" */
1.71      christos 1581:          T_LBRACK range T_RBRACK {
1.408     rillig   1582:                if (!allow_c99)
1.385     rillig   1583:                        /* array initializer with designators is a C99 ... */
1.34      yamt     1584:                        warning(321);
1.408     rillig   1585:                add_designator_subscript($2);
1.34      yamt     1586:          }
1.230     rillig   1587:        | T_POINT identifier {
1.408     rillig   1588:                if (!allow_c99)
1.127     rillig   1589:                        /* struct or union member name in initializer is ... */
1.26      christos 1590:                        warning(313);
1.205     rillig   1591:                add_designator_member($2);
1.26      christos 1592:          }
1.71      christos 1593:        ;
                   1594:
1.365     christos 1595: static_assert_declaration:
1.366     christos 1596:          T_STATIC_ASSERT T_LPAREN constant_expr T_COMMA T_STRING T_RPAREN T_SEMI /* C11 */
                   1597:        | T_STATIC_ASSERT T_LPAREN constant_expr T_RPAREN T_SEMI /* C23 */
1.402     rillig   1598:        ;
1.365     christos 1599:
1.239     rillig   1600: range:
                   1601:          constant_expr {
                   1602:                $$.lo = to_int_constant($1, true);
                   1603:                $$.hi = $$.lo;
                   1604:          }
                   1605:        | constant_expr T_ELLIPSIS constant_expr {
                   1606:                $$.lo = to_int_constant($1, true);
                   1607:                $$.hi = to_int_constant($3, true);
1.251     rillig   1608:                /* initialization with '[a...b]' is a GCC extension */
1.239     rillig   1609:                gnuism(340);
1.26      christos 1610:          }
                   1611:        ;
                   1612:
1.319     rillig   1613: init_lbrace:                   /* helper */
1.1       cgd      1614:          T_LBRACE {
1.114     rillig   1615:                init_lbrace();
1.1       cgd      1616:          }
                   1617:        ;
                   1618:
1.319     rillig   1619: init_rbrace:                   /* helper */
1.1       cgd      1620:          T_RBRACE {
1.114     rillig   1621:                init_rbrace();
1.1       cgd      1622:          }
                   1623:        ;
                   1624:
1.319     rillig   1625: asm_or_symbolrename_opt:       /* GCC extensions */
                   1626:          /* empty */ {
                   1627:                $$ = NULL;
1.1       cgd      1628:          }
1.339     rillig   1629:        | T_ASM T_LPAREN T_STRING T_RPAREN gcc_attribute_list_opt {
1.319     rillig   1630:                freeyyv(&$3, T_STRING);
                   1631:                $$ = NULL;
1.1       cgd      1632:          }
1.339     rillig   1633:        | T_SYMBOLRENAME T_LPAREN T_NAME T_RPAREN gcc_attribute_list_opt {
1.319     rillig   1634:                $$ = $3;
1.1       cgd      1635:          }
                   1636:        ;
                   1637:
1.319     rillig   1638: statement:                     /* C99 6.8 */
                   1639:          expression_statement
                   1640:        | non_expr_statement
1.256     rillig   1641:        ;
                   1642:
1.319     rillig   1643: non_expr_statement:            /* helper for C99 6.8 */
1.405     rillig   1644:          gcc_attribute /* ((__fallthrough__)) */ T_SEMI
1.212     christos 1645:        | labeled_statement
1.133     rillig   1646:        | compound_statement
                   1647:        | selection_statement
                   1648:        | iteration_statement
                   1649:        | jump_statement {
1.188     rillig   1650:                seen_fallthrough = false;
1.1       cgd      1651:          }
1.133     rillig   1652:        | asm_statement
1.212     christos 1653:        ;
1.32      christos 1654:
1.134     rillig   1655: labeled_statement:             /* C99 6.8.1 */
1.404     rillig   1656:          label gcc_attribute_list_opt statement
1.1       cgd      1657:        ;
                   1658:
                   1659: label:
1.53      christos 1660:          T_NAME T_COLON {
1.120     rillig   1661:                symtyp = FLABEL;
1.125     rillig   1662:                named_label(getsym($1));
1.1       cgd      1663:          }
1.168     rillig   1664:        | T_CASE constant_expr T_COLON {
1.125     rillig   1665:                case_label($2);
1.188     rillig   1666:                seen_fallthrough = true;
1.130     rillig   1667:          }
1.168     rillig   1668:        | T_CASE constant_expr T_ELLIPSIS constant_expr T_COLON {
1.40      christos 1669:                /* XXX: We don't fill all cases */
1.125     rillig   1670:                case_label($2);
1.188     rillig   1671:                seen_fallthrough = true;
1.130     rillig   1672:          }
1.1       cgd      1673:        | T_DEFAULT T_COLON {
1.125     rillig   1674:                default_label();
1.188     rillig   1675:                seen_fallthrough = true;
1.1       cgd      1676:          }
                   1677:        ;
                   1678:
1.134     rillig   1679: compound_statement:            /* C99 6.8.2 */
1.306     rillig   1680:          compound_statement_lbrace compound_statement_rbrace
                   1681:        | compound_statement_lbrace block_item_list compound_statement_rbrace
1.1       cgd      1682:        ;
                   1683:
1.133     rillig   1684: compound_statement_lbrace:
1.1       cgd      1685:          T_LBRACE {
1.171     rillig   1686:                block_level++;
                   1687:                mem_block_level++;
1.393     rillig   1688:                begin_declaration_level(DK_AUTO);
1.1       cgd      1689:          }
                   1690:        ;
                   1691:
1.133     rillig   1692: compound_statement_rbrace:
1.1       cgd      1693:          T_RBRACE {
1.202     rillig   1694:                end_declaration_level();
1.383     rillig   1695:                level_free_all(mem_block_level);
1.171     rillig   1696:                mem_block_level--;
                   1697:                block_level--;
1.188     rillig   1698:                seen_fallthrough = false;
1.1       cgd      1699:          }
                   1700:        ;
                   1701:
1.300     rillig   1702: block_item_list:               /* C99 6.8.2 */
1.185     rillig   1703:          block_item
                   1704:        | block_item_list block_item {
1.408     rillig   1705:                if ($1 && !$2)
1.185     rillig   1706:                        /* declarations after statements is a C99 feature */
                   1707:                        c99ism(327);
1.234     rillig   1708:                $$ = $1 || $2;
1.254     rillig   1709:          }
1.185     rillig   1710:        ;
                   1711:
1.300     rillig   1712: block_item:                    /* C99 6.8.2 */
1.326     rillig   1713:          declaration_or_error {
1.300     rillig   1714:                $$ = false;
1.187     rillig   1715:                restore_warning_flags();
1.185     rillig   1716:          }
1.300     rillig   1717:        | statement {
                   1718:                $$ = true;
1.187     rillig   1719:                restore_warning_flags();
1.7       jpo      1720:          }
1.1       cgd      1721:        ;
                   1722:
1.270     rillig   1723: expression_statement:          /* C99 6.8.3 */
1.322     rillig   1724:          expression T_SEMI {
1.160     rillig   1725:                expr($1, false, false, false, false);
1.188     rillig   1726:                seen_fallthrough = false;
1.1       cgd      1727:          }
                   1728:        | T_SEMI {
1.379     rillig   1729:                check_statement_reachable();
1.188     rillig   1730:                seen_fallthrough = false;
1.1       cgd      1731:          }
                   1732:        ;
                   1733:
1.134     rillig   1734: selection_statement:           /* C99 6.8.4 */
1.312     rillig   1735:          if_without_else %prec T_THEN {
1.187     rillig   1736:                save_warning_flags();
1.1       cgd      1737:                if2();
1.183     rillig   1738:                if3(false);
1.1       cgd      1739:          }
                   1740:        | if_without_else T_ELSE {
1.187     rillig   1741:                save_warning_flags();
1.1       cgd      1742:                if2();
1.133     rillig   1743:          } statement {
1.187     rillig   1744:                clear_warning_flags();
1.183     rillig   1745:                if3(true);
1.1       cgd      1746:          }
                   1747:        | if_without_else T_ELSE error {
1.187     rillig   1748:                clear_warning_flags();
1.183     rillig   1749:                if3(false);
1.1       cgd      1750:          }
1.133     rillig   1751:        | switch_expr statement {
1.187     rillig   1752:                clear_warning_flags();
1.1       cgd      1753:                switch2();
                   1754:          }
                   1755:        | switch_expr error {
1.187     rillig   1756:                clear_warning_flags();
1.1       cgd      1757:                switch2();
                   1758:          }
                   1759:        ;
                   1760:
1.270     rillig   1761: if_without_else:               /* see C99 6.8.4 */
1.133     rillig   1762:          if_expr statement
1.1       cgd      1763:        | if_expr error
                   1764:        ;
                   1765:
1.270     rillig   1766: if_expr:                       /* see C99 6.8.4 */
1.322     rillig   1767:          T_IF T_LPAREN expression T_RPAREN {
1.1       cgd      1768:                if1($3);
1.187     rillig   1769:                clear_warning_flags();
1.1       cgd      1770:          }
                   1771:        ;
                   1772:
1.270     rillig   1773: switch_expr:                   /* see C99 6.8.4 */
1.322     rillig   1774:          T_SWITCH T_LPAREN expression T_RPAREN {
1.1       cgd      1775:                switch1($3);
1.187     rillig   1776:                clear_warning_flags();
1.1       cgd      1777:          }
                   1778:        ;
                   1779:
1.134     rillig   1780: iteration_statement:           /* C99 6.8.5 */
1.306     rillig   1781:          while_expr statement {
1.187     rillig   1782:                clear_warning_flags();
1.306     rillig   1783:                while2();
                   1784:          }
                   1785:        | while_expr error {
1.187     rillig   1786:                clear_warning_flags();
1.1       cgd      1787:                while2();
                   1788:          }
1.306     rillig   1789:        | do_statement do_while_expr {
                   1790:                do2($2);
1.188     rillig   1791:                seen_fallthrough = false;
1.1       cgd      1792:          }
                   1793:        | do error {
1.187     rillig   1794:                clear_warning_flags();
1.1       cgd      1795:                do2(NULL);
                   1796:          }
1.306     rillig   1797:        | for_exprs statement {
                   1798:                clear_warning_flags();
                   1799:                for2();
                   1800:                end_declaration_level();
                   1801:                block_level--;
                   1802:          }
                   1803:        | for_exprs error {
1.187     rillig   1804:                clear_warning_flags();
1.1       cgd      1805:                for2();
1.202     rillig   1806:                end_declaration_level();
1.171     rillig   1807:                block_level--;
1.1       cgd      1808:          }
                   1809:        ;
                   1810:
1.319     rillig   1811: while_expr:                    /* see C99 6.8.5 */
1.322     rillig   1812:          T_WHILE T_LPAREN expression T_RPAREN {
1.306     rillig   1813:                while1($3);
                   1814:                clear_warning_flags();
                   1815:          }
1.1       cgd      1816:        ;
                   1817:
1.319     rillig   1818: do_statement:                  /* see C99 6.8.5 */
                   1819:          do statement {
                   1820:                clear_warning_flags();
                   1821:          }
                   1822:        ;
                   1823:
1.270     rillig   1824: do:                            /* see C99 6.8.5 */
1.1       cgd      1825:          T_DO {
                   1826:                do1();
                   1827:          }
                   1828:        ;
                   1829:
1.319     rillig   1830: do_while_expr:                 /* see C99 6.8.5 */
1.322     rillig   1831:          T_WHILE T_LPAREN expression T_RPAREN T_SEMI {
1.306     rillig   1832:                $$ = $3;
                   1833:          }
                   1834:        ;
                   1835:
1.270     rillig   1836: for_start:                     /* see C99 6.8.5 */
1.126     rillig   1837:          T_FOR T_LPAREN {
1.393     rillig   1838:                begin_declaration_level(DK_AUTO);
1.171     rillig   1839:                block_level++;
1.66      christos 1840:          }
                   1841:        ;
1.254     rillig   1842:
1.270     rillig   1843: for_exprs:                     /* see C99 6.8.5 */
1.322     rillig   1844:          for_start
                   1845:            begin_type_declaration_specifiers end_type
1.324     rillig   1846:            notype_init_declarators T_SEMI
1.388     rillig   1847:            expression_opt T_SEMI
                   1848:            expression_opt T_RPAREN {
1.127     rillig   1849:                /* variable declaration in for loop */
1.43      christos 1850:                c99ism(325);
1.306     rillig   1851:                for1(NULL, $6, $8);
1.187     rillig   1852:                clear_warning_flags();
1.43      christos 1853:            }
1.388     rillig   1854:        | for_start
                   1855:            expression_opt T_SEMI
                   1856:            expression_opt T_SEMI
                   1857:            expression_opt T_RPAREN {
1.66      christos 1858:                for1($2, $4, $6);
1.187     rillig   1859:                clear_warning_flags();
1.1       cgd      1860:          }
                   1861:        ;
                   1862:
1.319     rillig   1863: jump_statement:                        /* C99 6.8.6 */
                   1864:          goto identifier T_SEMI {
                   1865:                do_goto(getsym($2));
1.1       cgd      1866:          }
1.319     rillig   1867:        | goto error T_SEMI {
                   1868:                symtyp = FVFT;
1.1       cgd      1869:          }
1.319     rillig   1870:        | T_CONTINUE T_SEMI {
                   1871:                do_continue();
1.1       cgd      1872:          }
1.319     rillig   1873:        | T_BREAK T_SEMI {
                   1874:                do_break();
1.1       cgd      1875:          }
1.370     rillig   1876:        | T_RETURN sys T_SEMI {
                   1877:                do_return($2, NULL);
1.310     rillig   1878:          }
1.370     rillig   1879:        | T_RETURN sys expression T_SEMI {
                   1880:                do_return($2, $3);
1.308     rillig   1881:          }
1.319     rillig   1882:        ;
                   1883:
                   1884: goto:                          /* see C99 6.8.6 */
                   1885:          T_GOTO {
                   1886:                symtyp = FLABEL;
1.315     rillig   1887:          }
1.319     rillig   1888:        ;
                   1889:
                   1890: asm_statement:                 /* GCC extension */
                   1891:          T_ASM T_LPAREN read_until_rparen T_SEMI {
                   1892:                setasm();
1.315     rillig   1893:          }
1.319     rillig   1894:        | T_ASM T_QUAL T_LPAREN read_until_rparen T_SEMI {
                   1895:                setasm();
1.315     rillig   1896:          }
1.319     rillig   1897:        | T_ASM error
                   1898:        ;
                   1899:
                   1900: read_until_rparen:             /* helper for 'asm_statement' */
                   1901:          /* empty */ {
1.331     rillig   1902:                read_until_rparen();
1.315     rillig   1903:          }
1.308     rillig   1904:        ;
                   1905:
1.319     rillig   1906: translation_unit:              /* C99 6.9 */
                   1907:          external_declaration
                   1908:        | translation_unit external_declaration
                   1909:        ;
                   1910:
                   1911: external_declaration:          /* C99 6.9 */
1.335     rillig   1912:          function_definition {
1.319     rillig   1913:                global_clean_up_decl(false);
                   1914:                clear_warning_flags();
                   1915:          }
                   1916:        | top_level_declaration {
                   1917:                global_clean_up_decl(false);
                   1918:                clear_warning_flags();
1.1       cgd      1919:          }
1.335     rillig   1920:        | asm_statement         /* GCC extension */
                   1921:        | T_SEMI {              /* GCC extension */
                   1922:                if (sflag) {
                   1923:                        /* empty declaration */
                   1924:                        error(0);
1.409   ! rillig   1925:                } else if (allow_c90) {
1.335     rillig   1926:                        /* empty declaration */
                   1927:                        warning(0);
                   1928:                }
                   1929:          }
1.1       cgd      1930:        ;
                   1931:
1.226     rillig   1932: /*
1.319     rillig   1933:  * On the top level, lint allows several forms of declarations that it doesn't
                   1934:  * allow in functions.  For example, a single ';' is an empty declaration and
                   1935:  * is supported by some compilers, but in a function it would be an empty
                   1936:  * statement, not a declaration.  This makes a difference in C90 mode, where
                   1937:  * a statement must not be followed by a declaration.
1.226     rillig   1938:  *
1.319     rillig   1939:  * See 'declaration' for all other declarations.
1.226     rillig   1940:  */
1.319     rillig   1941: top_level_declaration:         /* C99 6.9 calls this 'declaration' */
1.335     rillig   1942:          begin_type end_type notype_init_declarators T_SEMI {
1.319     rillig   1943:                if (sflag) {
                   1944:                        /* old style declaration; add 'int' */
                   1945:                        error(1);
1.409   ! rillig   1946:                } else if (allow_c90) {
1.319     rillig   1947:                        /* old style declaration; add 'int' */
                   1948:                        warning(1);
                   1949:                }
1.226     rillig   1950:          }
1.327     rillig   1951:        | declaration
1.319     rillig   1952:        | error T_SEMI {
                   1953:                global_clean_up();
                   1954:          }
                   1955:        | error T_RBRACE {
                   1956:                global_clean_up();
                   1957:          }
1.226     rillig   1958:        ;
                   1959:
1.319     rillig   1960: function_definition:           /* C99 6.9.1 */
1.324     rillig   1961:          func_declarator {
1.319     rillig   1962:                if ($1->s_type->t_tspec != FUNC) {
                   1963:                        /* syntax error '%s' */
                   1964:                        error(249, yytext);
                   1965:                        YYERROR;
                   1966:                }
                   1967:                if ($1->s_type->t_typedef) {
                   1968:                        /* ()-less function definition */
                   1969:                        error(64);
                   1970:                        YYERROR;
                   1971:                }
                   1972:                funcdef($1);
                   1973:                block_level++;
1.393     rillig   1974:                begin_declaration_level(DK_OLD_STYLE_ARG);
1.319     rillig   1975:                if (lwarn == LWARN_NONE)
                   1976:                        $1->s_used = true;
                   1977:          } arg_declaration_list_opt {
                   1978:                end_declaration_level();
                   1979:                block_level--;
                   1980:                check_func_lint_directives();
                   1981:                check_func_old_style_arguments();
                   1982:                begin_control_statement(CS_FUNCTION_BODY);
                   1983:          } compound_statement {
                   1984:                funcend();
                   1985:                end_control_statement(CS_FUNCTION_BODY);
1.1       cgd      1986:          }
                   1987:        ;
                   1988:
1.324     rillig   1989: func_declarator:
                   1990:          begin_type end_type notype_declarator {
1.402     rillig   1991:                if (!allow_trad) {
                   1992:                        /* old style declaration; add 'int' */
                   1993:                        error(1);
                   1994:                }
1.319     rillig   1995:                $$ = $3;
                   1996:          }
1.324     rillig   1997:        | begin_type_declmods end_type notype_declarator {
1.402     rillig   1998:                if (!allow_trad) {
                   1999:                        /* old style declaration; add 'int' */
                   2000:                        error(1);
                   2001:                }
1.319     rillig   2002:                $$ = $3;
1.1       cgd      2003:          }
1.324     rillig   2004:        | begin_type_declaration_specifiers end_type type_declarator {
1.319     rillig   2005:                $$ = $3;
1.1       cgd      2006:          }
                   2007:        ;
                   2008:
1.319     rillig   2009: arg_declaration_list_opt:      /* C99 6.9.1p13 example 1 */
                   2010:          /* empty */
                   2011:        | arg_declaration_list
1.1       cgd      2012:        ;
                   2013:
1.319     rillig   2014: arg_declaration_list:          /* C99 6.9.1p13 example 1 */
                   2015:          arg_declaration
                   2016:        | arg_declaration_list arg_declaration
                   2017:        /* XXX or better "arg_declaration error" ? */
                   2018:        | error
1.301     rillig   2019:        ;
                   2020:
1.319     rillig   2021: /*
                   2022:  * "arg_declaration" is separated from "declaration" because it
                   2023:  * needs other error handling.
                   2024:  */
                   2025: arg_declaration:
                   2026:          begin_type_declmods end_type T_SEMI {
                   2027:                /* empty declaration */
                   2028:                warning(2);
                   2029:          }
1.324     rillig   2030:        | begin_type_declmods end_type notype_init_declarators T_SEMI
1.319     rillig   2031:        | begin_type_declaration_specifiers end_type T_SEMI {
                   2032:                if (!dcs->d_nonempty_decl) {
                   2033:                        /* empty declaration */
                   2034:                        warning(2);
                   2035:                } else {
                   2036:                        /* '%s' declared in argument declaration list */
                   2037:                        warning(3, type_name(dcs->d_type));
                   2038:                }
1.1       cgd      2039:          }
1.324     rillig   2040:        | begin_type_declaration_specifiers end_type
                   2041:            type_init_declarators T_SEMI {
1.319     rillig   2042:                if (dcs->d_nonempty_decl) {
                   2043:                        /* '%s' declared in argument declaration list */
                   2044:                        warning(3, type_name(dcs->d_type));
                   2045:                }
1.1       cgd      2046:          }
1.319     rillig   2047:        | begin_type_declmods error
                   2048:        | begin_type_declaration_specifiers error
1.180     rillig   2049:        ;
1.254     rillig   2050:
1.339     rillig   2051: gcc_attribute_list_opt:
                   2052:          /* empty */
                   2053:        | gcc_attribute_list
                   2054:        ;
                   2055:
                   2056: gcc_attribute_list:
                   2057:          gcc_attribute
                   2058:        | gcc_attribute_list gcc_attribute
                   2059:        ;
                   2060:
                   2061: gcc_attribute:
                   2062:          T_ATTRIBUTE T_LPAREN T_LPAREN {
1.368     rillig   2063:            in_gcc_attribute = true;
1.339     rillig   2064:          } gcc_attribute_spec_list {
1.368     rillig   2065:            in_gcc_attribute = false;
1.339     rillig   2066:          } T_RPAREN T_RPAREN
                   2067:        ;
                   2068:
1.261     rillig   2069: gcc_attribute_spec_list:
                   2070:          gcc_attribute_spec
                   2071:        | gcc_attribute_spec_list T_COMMA gcc_attribute_spec
1.260     rillig   2072:        ;
                   2073:
1.261     rillig   2074: gcc_attribute_spec:
1.260     rillig   2075:          /* empty */
                   2076:        | T_AT_ALWAYS_INLINE
                   2077:        | T_AT_ALIAS T_LPAREN string T_RPAREN
                   2078:        | T_AT_ALIGNED T_LPAREN constant_expr T_RPAREN
                   2079:        | T_AT_ALIGNED
                   2080:        | T_AT_ALLOC_SIZE T_LPAREN constant_expr T_COMMA constant_expr T_RPAREN
                   2081:        | T_AT_ALLOC_SIZE T_LPAREN constant_expr T_RPAREN
1.261     rillig   2082:        | T_AT_BOUNDED T_LPAREN gcc_attribute_bounded
1.260     rillig   2083:          T_COMMA constant_expr T_COMMA constant_expr T_RPAREN
                   2084:        | T_AT_COLD
                   2085:        | T_AT_COMMON
                   2086:        | T_AT_CONSTRUCTOR T_LPAREN constant_expr T_RPAREN
                   2087:        | T_AT_CONSTRUCTOR
                   2088:        | T_AT_DEPRECATED T_LPAREN string T_RPAREN
                   2089:        | T_AT_DEPRECATED
                   2090:        | T_AT_DESTRUCTOR T_LPAREN constant_expr T_RPAREN
                   2091:        | T_AT_DESTRUCTOR
1.374     christos 2092:        | T_AT_DISABLE_SANITIZER_INSTRUMENTATION
1.260     rillig   2093:        | T_AT_FALLTHROUGH {
                   2094:                fallthru(1);
                   2095:          }
1.261     rillig   2096:        | T_AT_FORMAT T_LPAREN gcc_attribute_format T_COMMA
1.260     rillig   2097:            constant_expr T_COMMA constant_expr T_RPAREN
                   2098:        | T_AT_FORMAT_ARG T_LPAREN constant_expr T_RPAREN
                   2099:        | T_AT_GNU_INLINE
1.313     rillig   2100:        | T_AT_HOT
1.260     rillig   2101:        | T_AT_MALLOC
                   2102:        | T_AT_MAY_ALIAS
                   2103:        | T_AT_MODE T_LPAREN T_NAME T_RPAREN
1.374     christos 2104:        | T_AT_NO_SANITIZE T_LPAREN T_NAME T_RPAREN
                   2105:        | T_AT_NO_SANITIZE_THREAD
1.260     rillig   2106:        | T_AT_NOINLINE
                   2107:        | T_AT_NONNULL T_LPAREN constant_expr_list_opt T_RPAREN
                   2108:        | T_AT_NONNULL
                   2109:        | T_AT_NONSTRING
                   2110:        | T_AT_NORETURN
                   2111:        | T_AT_NOTHROW
                   2112:        | T_AT_NO_INSTRUMENT_FUNCTION
                   2113:        | T_AT_OPTIMIZE T_LPAREN string T_RPAREN
1.378     christos 2114:        | T_AT_OPTNONE
1.260     rillig   2115:        | T_AT_PACKED {
                   2116:                addpacked();
                   2117:          }
                   2118:        | T_AT_PCS T_LPAREN string T_RPAREN
                   2119:        | T_AT_PURE
1.358     rillig   2120:        | T_AT_REGPARM T_LPAREN constant_expr T_RPAREN
1.356     christos 2121:        | T_AT_RETURNS_NONNULL
1.260     rillig   2122:        | T_AT_RETURNS_TWICE
                   2123:        | T_AT_SECTION T_LPAREN string T_RPAREN
                   2124:        | T_AT_SENTINEL T_LPAREN constant_expr T_RPAREN
                   2125:        | T_AT_SENTINEL
1.371     christos 2126:        | T_AT_TARGET T_LPAREN string T_RPAREN
1.260     rillig   2127:        | T_AT_TLS_MODEL T_LPAREN string T_RPAREN
                   2128:        | T_AT_TUNION
                   2129:        | T_AT_UNUSED {
                   2130:                add_attr_used();
                   2131:          }
                   2132:        | T_AT_USED {
                   2133:                add_attr_used();
                   2134:          }
                   2135:        | T_AT_VISIBILITY T_LPAREN constant_expr T_RPAREN
                   2136:        | T_AT_WARN_UNUSED_RESULT
                   2137:        | T_AT_WEAK
                   2138:        | T_QUAL {
                   2139:                if ($1 != CONST)
                   2140:                        yyerror("Bad attribute");
                   2141:          }
                   2142:        ;
                   2143:
1.261     rillig   2144: gcc_attribute_bounded:
1.260     rillig   2145:          T_AT_MINBYTES
                   2146:        | T_AT_STRING
                   2147:        | T_AT_BUFFER
                   2148:        ;
                   2149:
1.261     rillig   2150: gcc_attribute_format:
1.260     rillig   2151:          T_AT_FORMAT_GNU_PRINTF
                   2152:        | T_AT_FORMAT_PRINTF
                   2153:        | T_AT_FORMAT_SCANF
                   2154:        | T_AT_FORMAT_STRFMON
                   2155:        | T_AT_FORMAT_STRFTIME
                   2156:        | T_AT_FORMAT_SYSLOG
                   2157:        ;
                   2158:
1.370     rillig   2159: sys:
                   2160:          /* empty */ {
                   2161:                $$ = in_system_header;
                   2162:          }
                   2163:        ;
                   2164:
1.1       cgd      2165: %%
                   2166:
                   2167: /* ARGSUSED */
                   2168: int
1.42      dholland 2169: yyerror(const char *msg)
1.1       cgd      2170: {
1.127     rillig   2171:        /* syntax error '%s' */
1.41      christos 2172:        error(249, yytext);
1.1       cgd      2173:        if (++sytxerr >= 5)
                   2174:                norecover();
1.112     rillig   2175:        return 0;
1.1       cgd      2176: }
                   2177:
1.407     rillig   2178: #if YYDEBUG && (YYBYACC || YYBISON)
1.352     rillig   2179: static const char *
                   2180: cgram_to_string(int token, YYSTYPE val)
                   2181: {
                   2182:
                   2183:        switch (token) {
                   2184:        case T_INCDEC:
                   2185:        case T_MULTIPLICATIVE:
                   2186:        case T_ADDITIVE:
                   2187:        case T_SHIFT:
                   2188:        case T_RELATIONAL:
                   2189:        case T_EQUALITY:
                   2190:        case T_OPASSIGN:
                   2191:                return modtab[val.y_op].m_name;
                   2192:        case T_SCLASS:
                   2193:                return scl_name(val.y_scl);
                   2194:        case T_TYPE:
                   2195:        case T_STRUCT_OR_UNION:
                   2196:                return tspec_name(val.y_tspec);
                   2197:        case T_QUAL:
1.387     rillig   2198:                return tqual_name(val.y_tqual);
1.352     rillig   2199:        case T_NAME:
                   2200:                return val.y_name->sb_name;
                   2201:        default:
                   2202:                return "<none>";
                   2203:        }
                   2204: }
                   2205: #endif
                   2206:
1.407     rillig   2207: #if YYDEBUG && YYBISON
1.372     rillig   2208: static inline void
1.352     rillig   2209: cgram_print(FILE *output, int token, YYSTYPE val)
                   2210: {
1.359     rillig   2211:        (void)fprintf(output, "%s", cgram_to_string(token, val));
1.352     rillig   2212: }
                   2213: #endif
                   2214:
1.1       cgd      2215: static void
1.174     rillig   2216: cgram_declare(sym_t *decl, bool initflg, sbuf_t *renaming)
1.1       cgd      2217: {
1.174     rillig   2218:        declare(decl, initflg, renaming);
                   2219:        if (renaming != NULL)
                   2220:                freeyyv(&renaming, T_NAME);
1.6       jpo      2221: }
                   2222:
                   2223: /*
                   2224:  * Discard all input tokens up to and including the next
                   2225:  * unmatched right paren
                   2226:  */
1.22      thorpej  2227: static void
1.331     rillig   2228: read_until_rparen(void)
1.6       jpo      2229: {
                   2230:        int     level;
                   2231:
                   2232:        if (yychar < 0)
                   2233:                yychar = yylex();
                   2234:        freeyyv(&yylval, yychar);
                   2235:
                   2236:        level = 1;
1.126     rillig   2237:        while (yychar != T_RPAREN || --level > 0) {
                   2238:                if (yychar == T_LPAREN) {
1.6       jpo      2239:                        level++;
                   2240:                } else if (yychar <= 0) {
                   2241:                        break;
                   2242:                }
                   2243:                freeyyv(&yylval, yychar = yylex());
                   2244:        }
                   2245:
                   2246:        yyclearin;
1.1       cgd      2247: }
1.75      christos 2248:
                   2249: static sym_t *
                   2250: symbolrename(sym_t *s, sbuf_t *sb)
                   2251: {
1.219     rillig   2252:        if (sb != NULL)
1.75      christos 2253:                s->s_rename = sb->sb_name;
                   2254:        return s;
                   2255: }

CVSweb <webmaster@jp.NetBSD.org>