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

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

CVSweb <webmaster@jp.NetBSD.org>