1%{
2/* $NetBSD: cgram.y,v 1.503 2024/05/12 09:07:41 rillig Exp $ */
3
4/*
5 * Copyright (c) 1996 Christopher G. Demetriou.  All Rights Reserved.
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
36#include <sys/cdefs.h>
37#if defined(__RCSID)
38__RCSID("$NetBSD: cgram.y,v 1.503 2024/05/12 09:07:41 rillig Exp $");
39#endif
40
41#include <limits.h>
42#include <stdlib.h>
43#include <string.h>
44
45#include "lint1.h"
46
47extern char *yytext;
48
49/*
50 * Contains the level of current declaration, used for symbol table entries.
51 * 0 is the top-level, > 0 is inside a function body.
52 */
53int block_level;
54
55/*
56 * level for memory allocation. Normally the same as block_level.
57 * An exception is the declaration of parameters in prototypes. Memory
58 * for these can't be freed after the declaration, but symbols must
59 * be removed from the symbol table after the declaration.
60 */
61size_t mem_block_level;
62
63/*
64 * Save the no-warns state and restore it to avoid the problem where
65 * if (expr) { stmt } / * NOLINT * / stmt;
66 */
67#define LWARN_NOTHING_SAVED (-3)
68static int saved_lwarn = LWARN_NOTHING_SAVED;
69
70static void cgram_declare(sym_t *, bool, sbuf_t *);
71static void read_until_rparen(void);
72static balanced_token_sequence read_balanced_token_sequence(void);
73static sym_t *symbolrename(sym_t *, sbuf_t *);
74
75
76/* ARGSUSED */
77static void
78clear_warning_flags_loc(const char *file, size_t line)
79{
80	debug_step("%s:%zu: clearing flags", file, line);
81	reset_suppressions();
82	saved_lwarn = LWARN_NOTHING_SAVED;
83}
84
85/* ARGSUSED */
86static void
87save_warning_flags_loc(const char *file, size_t line)
88{
89	debug_step("%s:%zu: saving flags %d", file, line, lwarn);
90	saved_lwarn = lwarn;
91}
92
93/* ARGSUSED */
94static void
95restore_warning_flags_loc(const char *file, size_t line)
96{
97	if (saved_lwarn != LWARN_NOTHING_SAVED) {
98		lwarn = saved_lwarn;
99		debug_step("%s:%zu: restoring flags %d", file, line, lwarn);
100	} else
101		clear_warning_flags_loc(file, line);
102}
103
104#define clear_warning_flags()	clear_warning_flags_loc(__FILE__, __LINE__)
105#define save_warning_flags()	save_warning_flags_loc(__FILE__, __LINE__)
106#define restore_warning_flags()	restore_warning_flags_loc(__FILE__, __LINE__)
107
108static bool
109is_either(const char *s, const char *a, const char *b)
110{
111	return strcmp(s, a) == 0 || strcmp(s, b) == 0;
112}
113
114static void
115attribute_list_add(attribute_list *list, attribute attr)
116{
117	if (list->len >= list->cap) {
118		attribute *old_attrs = list->attrs;
119		list->cap = 16 + 2 * list->cap;
120		list->attrs = block_zero_alloc(
121		    list->cap * sizeof(*list->attrs), "attribute[]");
122		if (list->len > 0)
123			memcpy(list->attrs, old_attrs,
124			    list->len * sizeof(*list->attrs));
125	}
126	list->attrs[list->len++] = attr;
127}
128
129static void
130attribute_list_add_all(attribute_list *dst, attribute_list src)
131{
132	for (size_t i = 0, n = src.len; i < n; i++)
133		attribute_list_add(dst, src.attrs[i]);
134}
135
136static attribute
137new_attribute(const sbuf_t *prefix, const sbuf_t *name,
138	      const balanced_token_sequence *arg)
139{
140	attribute attr = { .name = xstrdup(name->sb_name) };
141	if (prefix != NULL)
142		attr.prefix = xstrdup(prefix->sb_name);
143	if (arg != NULL) {
144		attr.arg = block_zero_alloc(sizeof(*attr.arg),
145		    "balanced_token_sequence");
146		*attr.arg = *arg;
147	}
148	return attr;
149}
150
151#if YYDEBUG && YYBYACC
152#define YYSTYPE_TOSTRING cgram_to_string
153#endif
154
155%}
156
157%expect 103
158
159%union {
160	val_t	*y_val;
161	sbuf_t	*y_name;
162	sym_t	*y_sym;
163	bool	y_inc;
164	op_t	y_op;
165	scl_t	y_scl;
166	tspec_t	y_tspec;
167	type_qualifiers y_type_qualifiers;
168	function_specifier y_function_specifier;
169	parameter_list y_parameter_list;
170	function_call *y_arguments;
171	type_t	*y_type;
172	tnode_t	*y_tnode;
173	range_t	y_range;
174	buffer	*y_string;
175	qual_ptr *y_qual_ptr;
176	bool	y_seen_statement;
177	struct generic_association *y_generic;
178	array_size y_array_size;
179	bool	y_in_system_header;
180	designation y_designation;
181	named_constant y_named_constant;
182	attribute y_attribute;
183	attribute_list y_attribute_list;
184	balanced_token_sequence y_tokens;
185};
186
187/* for Bison:
188%printer {
189	if (is_integer($$->v_tspec))
190		fprintf(yyo, "%lld", (long long)$$->u.integer);
191	else
192		fprintf(yyo, "%Lg", $$->u.floating);
193} <y_val>
194%printer { fprintf(yyo, "'%s'", $$ != NULL ? $$->sb_name : "<null>"); } <y_name>
195%printer {
196	bool indented = debug_push_indented(true);
197	debug_sym("", $$, "");
198	debug_pop_indented(indented);
199} <y_sym>
200%printer { fprintf(yyo, "%s", $$ ? "++" : "--"); } <y_inc>
201%printer { fprintf(yyo, "%s", op_name($$)); } <y_op>
202%printer { fprintf(yyo, "%s", scl_name($$)); } <y_scl>
203%printer { fprintf(yyo, "%s", tspec_name($$)); } <y_tspec>
204%printer { fprintf(yyo, "%s", type_qualifiers_string($$)); } <y_type_qualifiers>
205%printer {
206	fprintf(yyo, "%s", function_specifier_name($$));
207} <y_function_specifier>
208%printer {
209	size_t n = 0;
210	for (const sym_t *p = $$.first; p != NULL; p = p->s_next)
211		n++;
212	fprintf(yyo, "%zu parameter%s", n, n != 1 ? "s" : "");
213} <y_parameter_list>
214%printer { fprintf(yyo, "%s", type_name($$)); } <y_type>
215%printer {
216	if ($$ == NULL)
217		fprintf(yyo, "<null>");
218	else
219		fprintf(yyo, "%s '%s'",
220		    op_name($$->tn_op), type_name($$->tn_type));
221} <y_tnode>
222%printer { fprintf(yyo, "%zu to %zu", $$.lo, $$.hi); } <y_range>
223%printer { fprintf(yyo, "length %zu", $$->len); } <y_string>
224%printer {
225	fprintf(yyo, "%s *", type_qualifiers_string($$->qualifiers));
226} <y_qual_ptr>
227%printer { fprintf(yyo, "%s", $$ ? "yes" : "no"); } <y_seen_statement>
228%printer { fprintf(yyo, "%s", type_name($$->ga_arg)); } <y_generic>
229%printer { fprintf(yyo, "%d", $$.dim); } <y_array_size>
230%printer { fprintf(yyo, "%s", $$ ? "yes" : "no"); } <y_in_system_header>
231%printer {
232	if ($$.dn_len == 0)
233		fprintf(yyo, "(empty)");
234	for (size_t i = 0; i < $$.dn_len; i++) {
235		const designator *dr = $$.dn_items + i;
236		if (dr->dr_kind == DK_MEMBER)
237			fprintf(yyo, ".%s", dr->dr_member->s_name);
238		else if (dr->dr_kind == DK_SUBSCRIPT)
239			fprintf(yyo, "[%zu]", dr->dr_subscript);
240		else
241			fprintf(yyo, "<scalar>");
242	}
243} <y_designation>
244%printer { fprintf(yyo, "%s", named_constant_name($$)); } <y_named_constant>
245*/
246
247%token			T_LBRACE T_RBRACE T_LBRACK T_RBRACK T_LPAREN T_RPAREN
248%token			T_POINT T_ARROW
249%token			T_COMPLEMENT T_LOGNOT
250%token	<y_inc>		T_INCDEC
251%token			T_SIZEOF
252%token			T_BUILTIN_OFFSETOF
253%token			T_TYPEOF
254%token			T_EXTENSION
255%token			T_ALIGNAS
256%token			T_ALIGNOF
257%token			T_ASTERISK
258%token	<y_op>		T_MULTIPLICATIVE
259%token	<y_op>		T_ADDITIVE
260%token	<y_op>		T_SHIFT
261%token	<y_op>		T_RELATIONAL
262%token	<y_op>		T_EQUALITY
263%token			T_AMPER
264%token			T_BITXOR
265%token			T_BITOR
266%token			T_LOGAND
267%token			T_LOGOR
268%token			T_QUEST
269%token			T_COLON
270%token			T_ASSIGN
271%token	<y_op>		T_OPASSIGN
272%token			T_COMMA
273%token			T_SEMI
274%token			T_ELLIPSIS
275%token			T_DCOLON
276%token			T_REAL
277%token			T_IMAG
278%token			T_GENERIC
279
280/* storage classes (extern, static, auto, register and typedef) */
281%token	<y_scl>		T_SCLASS
282%token	<y_function_specifier> T_FUNCTION_SPECIFIER
283
284/*
285 * predefined type keywords (char, int, short, long, unsigned, signed,
286 * float, double, void); see T_TYPENAME for types from typedef
287 */
288%token	<y_tspec>	T_TYPE
289
290%token	<y_type_qualifiers>	T_QUAL
291%token	<y_type_qualifiers>	T_ATOMIC
292
293/* struct or union */
294%token	<y_tspec>	T_STRUCT_OR_UNION
295
296/* remaining keywords */
297%token			T_ASM
298%token			T_BREAK
299%token			T_CASE
300%token			T_CONTINUE
301%token			T_DEFAULT
302%token			T_DO
303%token			T_ELSE
304%token			T_ENUM
305%token			T_FOR
306%token			T_GOTO
307%token			T_IF
308%token			T_PACKED
309%token			T_RETURN
310%token			T_SWITCH
311%token			T_SYMBOLRENAME
312%token			T_WHILE
313%token			T_STATIC_ASSERT
314
315%token			T_ATTRIBUTE
316
317%left	T_THEN
318%left	T_ELSE
319%right	T_QUEST T_COLON
320%left	T_LOGOR
321%left	T_LOGAND
322%left	T_BITOR
323%left	T_BITXOR
324%left	T_AMPER
325%left	T_EQUALITY
326%left	T_RELATIONAL
327%left	T_SHIFT
328%left	T_ADDITIVE
329%left	T_ASTERISK T_MULTIPLICATIVE
330
331%token	<y_name>	T_NAME
332%token	<y_name>	T_TYPENAME
333%token	<y_val>		T_CON
334%token	<y_named_constant> T_NAMED_CONSTANT
335%token	<y_string>	T_STRING
336
337/* No type for program. */
338%type	<y_sym>		identifier_sym
339%type	<y_name>	identifier
340%type	<y_string>	string
341%type	<y_tnode>	primary_expression
342%type	<y_designation>	member_designator
343%type	<y_tnode>	generic_selection
344%type	<y_generic>	generic_assoc_list
345%type	<y_generic>	generic_association
346%type	<y_tnode>	postfix_expression
347%type	<y_tnode>	gcc_statement_expr_list
348%type	<y_tnode>	gcc_statement_expr_item
349%type	<y_op>		point_or_arrow
350%type	<y_arguments>	argument_expression_list
351%type	<y_scl>		storage_class_specifiers
352%type	<y_tnode>	unary_expression
353%type	<y_tnode>	cast_expression
354%type	<y_tnode>	expression_opt
355%type	<y_tnode>	conditional_expression
356%type	<y_tnode>	assignment_expression
357%type	<y_tnode>	expression
358%type	<y_tnode>	constant_expression
359/* No type for declaration_or_error. */
360/* No type for declaration. */
361/* No type for begin_type_declaration_specifiers. */
362/* No type for begin_type_declmods. */
363/* No type for begin_type_specifier_qualifier_list. */
364/* No type for begin_type_specifier_qualifier_list_postfix. */
365%type	<y_type>	begin_type_typespec
366/* No type for begin_type_qualifier_list. */
367/* No type for declmod. */
368/* No type for type_attribute_list_opt. */
369/* No type for type_attribute_list. */
370/* No type for type_attribute_opt. */
371/* No type for type_attribute. */
372/* No type for begin_type. */
373/* No type for end_type. */
374/* No type for notype_init_declarator_list. */
375/* No type for type_init_declarator_list. */
376/* No type for notype_init_declarator. */
377/* No type for type_init_declarator. */
378%type	<y_scl>		storage_class_specifier
379%type	<y_type>	type_type_specifier
380%type	<y_type>	notype_type_specifier
381%type	<y_type>	struct_or_union_specifier
382%type	<y_tspec>	struct_or_union
383%type	<y_sym>		braced_member_declaration_list
384%type	<y_sym>		member_declaration_list_with_rbrace
385%type	<y_sym>		member_declaration_list
386%type	<y_sym>		member_declaration
387%type	<y_sym>		notype_member_declarator_list
388%type	<y_sym>		type_member_declarator_list
389%type	<y_sym>		notype_member_declarator
390%type	<y_sym>		type_member_declarator
391%type	<y_type>	enum_specifier
392/* No type for enum. */
393%type	<y_sym>		enum_declaration
394%type	<y_sym>		enums_with_opt_comma
395%type	<y_sym>		enumerator_list
396%type	<y_sym>		enumerator
397%type	<y_type>	atomic_type_specifier
398/* No type for atomic. */
399%type	<y_type_qualifiers>	type_qualifier
400%type	<y_sym>		notype_declarator
401%type	<y_sym>		type_declarator
402%type	<y_sym>		notype_direct_declarator
403%type	<y_sym>		type_direct_declarator
404%type	<y_qual_ptr>	pointer
405%type	<y_type_qualifiers>	type_qualifier_list_opt
406%type	<y_type_qualifiers>	type_qualifier_list
407%type	<y_sym>		parameter_declaration
408%type	<y_sym>		type_param_declarator
409%type	<y_sym>		notype_param_declarator
410%type	<y_sym>		direct_param_declarator
411%type	<y_sym>		direct_notype_param_declarator
412%type	<y_parameter_list>	param_list
413%type	<y_array_size>	array_size_opt
414%type	<y_sym>		identifier_list
415%type	<y_type>	type_name
416%type	<y_sym>		abstract_declaration
417%type	<y_parameter_list>	abstract_decl_param_list
418/* No type for abstract_decl_lparen. */
419%type	<y_parameter_list>	vararg_parameter_type_list
420%type	<y_parameter_list>	parameter_type_list
421%type	<y_sym>		abstract_declarator
422%type	<y_sym>		direct_abstract_declarator
423/* No type for braced_initializer. */
424/* No type for initializer. */
425/* No type for initializer_list. */
426/* No type for designation. */
427/* No type for designator_list. */
428/* No type for designator. */
429/* No type for static_assert_declaration. */
430%type	<y_range>	range
431/* No type for init_lbrace. */
432/* No type for init_rbrace. */
433%type	<y_attribute_list>	attribute_specifier_sequence
434%type	<y_attribute_list>	attribute_specifier
435%type	<y_attribute_list>	attribute_list
436%type	<y_attribute>		attribute
437%type	<y_tokens>		attribute_argument_clause
438%type	<y_name>	asm_or_symbolrename_opt
439/* No type for statement. */
440/* No type for no_attr_statement. */
441/* No type for non_expr_statement. */
442/* No type for no_attr_non_expr_statement. */
443/* No type for label. */
444/* No type for labeled_statement. */
445/* No type for compound_statement. */
446/* No type for compound_statement_lbrace. */
447/* No type for compound_statement_rbrace. */
448%type	<y_seen_statement> block_item_list
449%type	<y_seen_statement> block_item
450/* No type for expression_statement. */
451/* No type for selection_statement. */
452/* No type for if_without_else. */
453/* No type for if_expr. */
454/* No type for switch_expr. */
455/* No type for iteration_statement. */
456/* No type for while_expr. */
457/* No type for do_statement. */
458/* No type for do. */
459/* No type for for_start. */
460/* No type for for_exprs. */
461/* No type for jump_statement. */
462/* No type for goto. */
463/* No type for asm_statement. */
464/* No type for read_until_rparen. */
465/* No type for translation_unit. */
466/* No type for external_declaration. */
467/* No type for top_level_declaration. */
468/* No type for function_definition. */
469%type	<y_sym>		func_declarator
470/* No type for arg_declaration_list_opt. */
471/* No type for arg_declaration_list. */
472/* No type for arg_declaration. */
473/* No type for gcc_attribute_specifier_list_opt. */
474/* No type for gcc_attribute_specifier_list. */
475/* No type for gcc_attribute_specifier. */
476/* No type for gcc_attribute_list. */
477/* No type for gcc_attribute. */
478%type	<y_in_system_header> sys
479
480%%
481
482program:
483	/* empty */ {
484		/* TODO: Make this an error in C99 mode as well. */
485		if (!allow_trad && !allow_c99)
486			/* empty translation unit */
487			error(272);
488		else if (allow_c90)
489			/* empty translation unit */
490			warning(272);
491	}
492|	translation_unit
493;
494
495identifier_sym:			/* helper for struct/union/enum */
496	identifier {
497		$$ = getsym($1);
498	}
499;
500
501/* K&R ???, C90 ???, C99 6.4.2.1, C11 ??? */
502identifier:
503	T_NAME {
504		debug_step("cgram: name '%s'", $1->sb_name);
505		$$ = $1;
506	}
507|	T_TYPENAME {
508		debug_step("cgram: typename '%s'", $1->sb_name);
509		$$ = $1;
510	}
511;
512
513/* see C99 6.4.5, string literals are joined by 5.1.1.2 */
514string:
515	T_STRING
516|	string T_STRING {
517		if (!allow_c90)
518			/* concatenated strings are illegal in traditional C */
519			warning(219);
520		$$ = cat_strings($1, $2);
521	}
522;
523
524/* K&R 7.1, C90 ???, C99 6.5.1, C11 6.5.1, C23 6.5.2 */
525primary_expression:
526	T_NAME {
527		bool sys_name, sys_next;
528		sys_name = in_system_header;
529		if (yychar < 0)
530			yychar = yylex();
531		sys_next = in_system_header;
532		in_system_header = sys_name;
533		$$ = build_name(getsym($1), yychar == T_LPAREN);
534		in_system_header = sys_next;
535	}
536|	T_CON {
537		$$ = build_constant(gettyp($1->v_tspec), $1);
538	}
539|	T_NAMED_CONSTANT {
540		if ($1 == NC_NULLPTR) {
541			tnode_t *zero = expr_alloc_tnode();
542			zero->tn_op = CON;
543			zero->tn_type = gettyp(INT);
544			zero->u.value.v_tspec = INT;
545
546			type_t *void_ptr = block_derive_type(gettyp(VOID), PTR);
547			$$ = convert(CVT, 0, void_ptr, zero);
548			$$->tn_sys = zero->tn_sys;
549		} else {
550			tnode_t *nc = expr_alloc_tnode();
551			nc->tn_op = CON;
552			nc->tn_type = gettyp(BOOL);
553			nc->u.value.v_tspec = BOOL;
554			nc->u.value.u.integer = $1 == NC_TRUE ? 1 : 0;
555			$$ = nc;
556		}
557	}
558|	string {
559		$$ = build_string($1);
560	}
561|	T_LPAREN expression T_RPAREN {
562		if ($2 != NULL)
563			$2->tn_parenthesized = true;
564		$$ = $2;
565	}
566|	generic_selection
567	/* GCC primary-expression, see c_parser_postfix_expression */
568|	T_BUILTIN_OFFSETOF T_LPAREN type_name T_COMMA {
569		set_sym_kind(SK_MEMBER);
570	} member_designator T_RPAREN {
571		$$ = build_offsetof($3, $6);
572	}
573;
574
575/* K&R ---, C90 ---, C99 7.17p3, C11 7.19p3, C23 7.21p4 */
576member_designator:
577	identifier {
578		$$ = (designation) { .dn_len = 0 };
579		designation_push(&$$, DK_MEMBER, getsym($1), 0);
580	}
581|	member_designator T_LBRACK range T_RBRACK {
582		$$ = $1;
583		designation_push(&$$, DK_SUBSCRIPT, NULL, $3.lo);
584	}
585|	member_designator T_POINT {
586		set_sym_kind(SK_MEMBER);
587	} identifier {
588		$$ = $1;
589		designation_push(&$$, DK_MEMBER, getsym($4), 0);
590	}
591;
592
593/* K&R ---, C90 ---, C99 ---, C11 6.5.1.1, C23 6.5.2.1 */
594generic_selection:
595	T_GENERIC T_LPAREN assignment_expression T_COMMA
596	    generic_assoc_list T_RPAREN {
597		/* generic selection requires C11 or later */
598		c11ism(345);
599		$$ = build_generic_selection($3, $5);
600	}
601;
602
603/* K&R ---, C90 ---, C99 ---, C11 6.5.1.1, C23 6.5.2.1 */
604generic_assoc_list:
605	generic_association
606|	generic_assoc_list T_COMMA generic_association {
607		$3->ga_prev = $1;
608		$$ = $3;
609	}
610;
611
612/* K&R ---, C90 ---, C99 ---, C11 6.5.1.1, C23 6.5.2.1 */
613generic_association:
614	type_name T_COLON assignment_expression {
615		$$ = block_zero_alloc(sizeof(*$$), "generic");
616		$$->ga_arg = $1;
617		$$->ga_result = $3;
618	}
619|	T_DEFAULT T_COLON assignment_expression {
620		$$ = block_zero_alloc(sizeof(*$$), "generic");
621		$$->ga_arg = NULL;
622		$$->ga_result = $3;
623	}
624;
625
626/* K&R 7.1, C90 ???, C99 6.5.2, C11 6.5.2, C23 6.5.3.1 */
627postfix_expression:
628	primary_expression
629|	postfix_expression T_LBRACK sys expression T_RBRACK {
630		$$ = build_unary(INDIR, $3, build_binary($1, PLUS, $3, $4));
631	}
632|	postfix_expression T_LPAREN sys T_RPAREN {
633		function_call *call =
634		    expr_zero_alloc(sizeof(*call), "function_call");
635		$$ = build_function_call($1, $3, call);
636	}
637|	postfix_expression T_LPAREN sys argument_expression_list T_RPAREN {
638		$$ = build_function_call($1, $3, $4);
639	}
640|	postfix_expression point_or_arrow sys T_NAME {
641		$$ = build_member_access($1, $2, $3, $4);
642	}
643|	postfix_expression T_INCDEC sys {
644		$$ = build_unary($2 ? INCAFT : DECAFT, $3, $1);
645	}
646	/* Rule 'compound_literal' from C99 6.5.2.5. */
647|	T_LPAREN type_name T_RPAREN {
648		sym_t *tmp = mktempsym($2);
649		begin_initialization(tmp);
650		cgram_declare(tmp, true, NULL);
651	} braced_initializer {
652		if (!allow_c99)
653			 /* compound literals are a C99/GCC extension */
654			 gnuism(319);
655		$$ = build_name(current_initsym(), false);
656		end_initialization();
657	}
658	/* Rule 'compound_literal' with storage classes from C23 6.5.3.6. */
659|	T_LPAREN storage_class_specifiers type_name T_RPAREN {
660		sym_t *tmp = mktempsym($3);
661		tmp->s_scl = $2;
662		begin_initialization(tmp);
663		cgram_declare(tmp, true, NULL);
664	} braced_initializer {
665		if (!allow_c99)
666			 /* compound literals are a C99/GCC extension */
667			 gnuism(319);
668		$$ = build_name(current_initsym(), false);
669		end_initialization();
670	}
671|	T_LPAREN compound_statement_lbrace {
672		begin_statement_expr();
673	} gcc_statement_expr_list {
674		do_statement_expr($4);
675	} compound_statement_rbrace T_RPAREN {
676		$$ = end_statement_expr();
677	}
678;
679
680/*
681 * The inner part of a GCC statement-expression of the form ({ ... }).
682 *
683 * https://gcc.gnu.org/onlinedocs/gcc/Statement-Exprs.html
684 */
685gcc_statement_expr_list:
686	gcc_statement_expr_item
687|	gcc_statement_expr_list gcc_statement_expr_item {
688		$$ = $2;
689	}
690;
691
692gcc_statement_expr_item:
693	declaration_or_error {
694		clear_warning_flags();
695		$$ = NULL;
696	}
697|	non_expr_statement {
698		$$ = expr_alloc_tnode();
699		$$->tn_type = gettyp(VOID);
700	}
701|	T_SEMI {
702		$$ = expr_alloc_tnode();
703		$$->tn_type = gettyp(VOID);
704	}
705|	expression T_SEMI {
706		if ($1 == NULL) {	/* in case of syntax errors */
707			$$ = expr_alloc_tnode();
708			$$->tn_type = gettyp(VOID);
709		} else {
710			/* XXX: do that only on the last name */
711			if ($1->tn_op == NAME)
712				$1->u.sym->s_used = true;
713			expr($1, false, false, false, false);
714			suppress_fallthrough = false;
715			$$ = $1;
716		}
717	}
718;
719
720point_or_arrow:			/* helper for 'postfix_expression' */
721	T_POINT {
722		set_sym_kind(SK_MEMBER);
723		$$ = POINT;
724	}
725|	T_ARROW {
726		set_sym_kind(SK_MEMBER);
727		$$ = ARROW;
728	}
729;
730
731/* K&R 7.1, C90 ???, C99 6.5.2, C11 6.5.2, C23 6.5.3.1 */
732argument_expression_list:
733	assignment_expression {
734		$$ = expr_zero_alloc(sizeof(*$$), "function_call");
735		add_function_argument($$, $1);
736	}
737|	argument_expression_list T_COMMA assignment_expression {
738		$$ = $1;
739		add_function_argument($1, $3);
740	}
741;
742
743
744/* C23 6.5.3.6 */
745/* The rule 'compound_literal' is inlined into 'postfix_expression'. */
746
747/* C23 6.5.3.6 */
748storage_class_specifiers:
749	storage_class_specifier
750|	storage_class_specifiers storage_class_specifier {
751		// TODO C23: maybe merge multiple storage class specifiers
752		$$ = $1;
753	}
754;
755
756/* K&R 7.2, C90 ???, C99 6.5.3, C11 6.5.3, C23 6.5.4 */
757unary_expression:
758	postfix_expression
759|	T_INCDEC sys unary_expression {
760		$$ = build_unary($1 ? INCBEF : DECBEF, $2, $3);
761	}
762|	T_AMPER sys cast_expression {
763		$$ = build_unary(ADDR, $2, $3);
764	}
765|	T_ASTERISK sys cast_expression {
766		$$ = build_unary(INDIR, $2, $3);
767	}
768|	T_ADDITIVE sys cast_expression {
769		if (!allow_c90 && $1 == PLUS)
770			/* unary '+' is illegal in traditional C */
771			warning(100);
772		$$ = build_unary($1 == PLUS ? UPLUS : UMINUS, $2, $3);
773	}
774|	T_COMPLEMENT sys cast_expression {
775		$$ = build_unary(COMPL, $2, $3);
776	}
777|	T_LOGNOT sys cast_expression {
778		$$ = build_unary(NOT, $2, $3);
779	}
780|	T_REAL sys cast_expression {	/* GCC c_parser_unary_expression */
781		$$ = build_unary(REAL, $2, $3);
782	}
783|	T_IMAG sys cast_expression {	/* GCC c_parser_unary_expression */
784		$$ = build_unary(IMAG, $2, $3);
785	}
786|	T_EXTENSION cast_expression {	/* GCC c_parser_unary_expression */
787		$$ = $2;
788	}
789|	T_SIZEOF unary_expression {
790		$$ = $2 == NULL ? NULL : build_sizeof($2->tn_type);
791		if ($$ != NULL)
792			check_expr_misc($2,
793			    false, false, false, false, false, true);
794	}
795|	T_SIZEOF T_LPAREN type_name T_RPAREN {
796		$$ = build_sizeof($3);
797	}
798|	T_ALIGNOF unary_expression {
799		/* non type argument to alignof is a GCC extension */
800		gnuism(349);
801		lint_assert($2 != NULL);
802		$$ = build_alignof($2->tn_type);
803	}
804	/* K&R ---, C90 ---, C99 ---, C11 6.5.3, C23 6.5.4.4 */
805|	T_ALIGNOF T_LPAREN type_name T_RPAREN {
806		/* TODO: c11ism */
807		$$ = build_alignof($3);
808	}
809;
810
811/* C23 6.5.4 */
812/* The rule 'unary_operator' is inlined into unary_expression. */
813
814/* K&R 7.2, C90 ???, C99 6.5.4, C11 6.5.4, C23 6.5.5 */
815cast_expression:
816	unary_expression
817|	T_LPAREN type_name T_RPAREN sys cast_expression {
818		$$ = cast($5, $4, $2);
819	}
820;
821
822expression_opt:
823	/* empty */ {
824		$$ = NULL;
825	}
826|	expression
827;
828
829/* 'conditional_expression' also implements 'multiplicative_expression'. */
830/* 'conditional_expression' also implements 'additive_expression'. */
831/* 'conditional_expression' also implements 'shift_expression'. */
832/* 'conditional_expression' also implements 'relational_expression'. */
833/* 'conditional_expression' also implements 'equality_expression'. */
834/* 'conditional_expression' also implements 'AND_expression'. */
835/* 'conditional_expression' also implements 'exclusive_OR_expression'. */
836/* 'conditional_expression' also implements 'inclusive_OR_expression'. */
837/* 'conditional_expression' also implements 'logical_AND_expression'. */
838/* 'conditional_expression' also implements 'logical_OR_expression'. */
839/* K&R ???, C90 ???, C99 6.5.5 to 6.5.15, C11 6.5.5 to 6.5.15, C23 6.5.6 to 6.5.16 */
840conditional_expression:
841	cast_expression
842|	conditional_expression T_ASTERISK sys conditional_expression {
843		$$ = build_binary($1, MULT, $3, $4);
844	}
845|	conditional_expression T_MULTIPLICATIVE sys conditional_expression {
846		$$ = build_binary($1, $2, $3, $4);
847	}
848|	conditional_expression T_ADDITIVE sys conditional_expression {
849		$$ = build_binary($1, $2, $3, $4);
850	}
851|	conditional_expression T_SHIFT sys conditional_expression {
852		$$ = build_binary($1, $2, $3, $4);
853	}
854|	conditional_expression T_RELATIONAL sys conditional_expression {
855		$$ = build_binary($1, $2, $3, $4);
856	}
857|	conditional_expression T_EQUALITY sys conditional_expression {
858		$$ = build_binary($1, $2, $3, $4);
859	}
860|	conditional_expression T_AMPER sys conditional_expression {
861		$$ = build_binary($1, BITAND, $3, $4);
862	}
863|	conditional_expression T_BITXOR sys conditional_expression {
864		$$ = build_binary($1, BITXOR, $3, $4);
865	}
866|	conditional_expression T_BITOR sys conditional_expression {
867		$$ = build_binary($1, BITOR, $3, $4);
868	}
869|	conditional_expression T_LOGAND sys conditional_expression {
870		$$ = build_binary($1, LOGAND, $3, $4);
871	}
872|	conditional_expression T_LOGOR sys conditional_expression {
873		$$ = build_binary($1, LOGOR, $3, $4);
874	}
875|	conditional_expression T_QUEST sys
876	    expression T_COLON sys conditional_expression {
877		$$ = build_binary($1, QUEST, $3,
878		    build_binary($4, COLON, $6, $7));
879	}
880;
881
882/* K&R ???, C90 ???, C99 6.5.16, C11 6.5.16, C23 6.5.17.1 */
883assignment_expression:
884	conditional_expression
885|	unary_expression T_ASSIGN sys assignment_expression {
886		$$ = build_binary($1, ASSIGN, $3, $4);
887	}
888|	unary_expression T_OPASSIGN sys assignment_expression {
889		$$ = build_binary($1, $2, $3, $4);
890	}
891;
892
893/* C23 6.5.17.1 */
894/* The rule 'assignment_operator' is inlined into 'assignment_expression'. */
895
896/* K&R ???, C90 ???, C99 6.5.17, C11 6.5.17, C23 6.5.18 */
897expression:
898	assignment_expression
899|	expression T_COMMA sys assignment_expression {
900		$$ = build_binary($1, COMMA, $3, $4);
901	}
902;
903
904/* K&R ???, C90 ???, C99 6.6, C11 ???, C23 6.6 */
905constant_expression:
906	conditional_expression
907;
908
909declaration_or_error:
910	declaration
911|	error T_SEMI
912;
913
914/* K&R ???, C90 ???, C99 6.7, C11 ???, C23 6.7.1 */
915declaration:
916	begin_type_declmods end_type T_SEMI {
917		if (dcs->d_scl == TYPEDEF)
918			/* typedef declares no type name */
919			warning(72);
920		else
921			/* empty declaration */
922			warning(2);
923	}
924|	begin_type_declmods end_type notype_init_declarator_list T_SEMI {
925		if (dcs->d_scl == TYPEDEF)
926			/* syntax error '%s' */
927			error(249, "missing base type for typedef");
928		else
929			/* old-style declaration; add 'int' */
930			error(1);
931	}
932|	begin_type_declaration_specifiers end_type T_SEMI {
933		if (dcs->d_scl == TYPEDEF)
934			/* typedef declares no type name */
935			warning(72);
936		else if (!dcs->d_nonempty_decl)
937			/* empty declaration */
938			warning(2);
939	}
940|	begin_type_declaration_specifiers end_type
941	    type_init_declarator_list T_SEMI
942|	static_assert_declaration
943;
944
945/* TODO: Implement 'declaration_specifiers' from C23 6.7.1. */
946
947begin_type_declaration_specifiers:	/* see C99 6.7, C23 6.7.1 */
948	begin_type_typespec {
949		dcs_add_type($1);
950	}
951|	begin_type_declmods type_type_specifier {
952		dcs_add_type($2);
953	}
954|	type_attribute begin_type_declaration_specifiers
955|	begin_type_declaration_specifiers declmod
956|	begin_type_declaration_specifiers notype_type_specifier {
957		dcs_add_type($2);
958	}
959;
960
961begin_type_declmods:		/* see C99 6.7 */
962	begin_type type_qualifier {
963		dcs_add_qualifiers($2);
964	}
965|	begin_type T_SCLASS {
966		dcs_add_storage_class($2);
967	}
968|	begin_type T_FUNCTION_SPECIFIER {
969		dcs_add_function_specifier($2);
970	}
971|	begin_type_declmods declmod
972;
973
974begin_type_specifier_qualifier_list:	/* see C11 6.7.2.1 */
975	begin_type_specifier_qualifier_list_postfix
976|	type_attribute_list begin_type_specifier_qualifier_list_postfix
977;
978
979begin_type_specifier_qualifier_list_postfix:
980	begin_type_typespec {
981		dcs_add_type($1);
982	}
983|	begin_type_qualifier_list type_type_specifier {
984		dcs_add_type($2);
985	}
986|	begin_type_specifier_qualifier_list_postfix type_qualifier {
987		dcs_add_qualifiers($2);
988	}
989|	begin_type_specifier_qualifier_list_postfix notype_type_specifier {
990		dcs_add_type($2);
991	}
992|	begin_type_specifier_qualifier_list_postfix type_attribute
993;
994
995begin_type_typespec:
996	begin_type notype_type_specifier {
997		$$ = $2;
998	}
999|	begin_type T_TYPENAME {
1000		$$ = getsym($2)->s_type;
1001	}
1002;
1003
1004begin_type_qualifier_list:
1005	begin_type type_qualifier {
1006		dcs_add_qualifiers($2);
1007	}
1008|	begin_type_qualifier_list type_qualifier {
1009		dcs_add_qualifiers($2);
1010	}
1011;
1012
1013declmod:
1014	type_qualifier {
1015		dcs_add_qualifiers($1);
1016	}
1017|	T_SCLASS {
1018		dcs_add_storage_class($1);
1019	}
1020|	T_FUNCTION_SPECIFIER {
1021		dcs_add_function_specifier($1);
1022	}
1023|	type_attribute_list
1024;
1025
1026type_attribute_list_opt:
1027	/* empty */
1028|	type_attribute_list
1029;
1030
1031type_attribute_list:
1032	type_attribute
1033|	type_attribute_list type_attribute
1034;
1035
1036type_attribute_opt:
1037	/* empty */
1038|	type_attribute
1039;
1040
1041type_attribute:			/* See C11 6.7 declaration-specifiers */
1042	gcc_attribute_specifier
1043|	T_ALIGNAS T_LPAREN type_type_specifier T_RPAREN {		/* C11 6.7.5 */
1044		dcs_add_alignas(build_sizeof($3));
1045	}
1046|	T_ALIGNAS T_LPAREN constant_expression T_RPAREN {	/* C11 6.7.5 */
1047		dcs_add_alignas($3);
1048	}
1049|	T_PACKED {
1050		dcs_add_packed();
1051	}
1052;
1053
1054begin_type:
1055	/* empty */ {
1056		dcs_begin_type();
1057	}
1058;
1059
1060end_type:
1061	/* empty */ {
1062		dcs_end_type();
1063	}
1064;
1065
1066/* TODO: Implement 'declaration_specifier' from C23 6.7.1. */
1067
1068/*
1069 * For an explanation of 'type' and 'notype' prefixes in the following rules,
1070 * see https://www.gnu.org/software/bison/manual/bison.html#Semantic-Tokens.
1071 */
1072
1073/* C23 6.7.1 */
1074/* The rule 'init_declarator_list' is split into the 'notype' and 'type' variants. */
1075
1076notype_init_declarator_list:
1077	notype_init_declarator
1078|	notype_init_declarator_list T_COMMA type_init_declarator
1079;
1080
1081type_init_declarator_list:
1082	type_init_declarator
1083|	type_init_declarator_list T_COMMA type_init_declarator
1084;
1085
1086/* C23 6.7.1 */
1087/* The rule 'init_declarator' is split into the 'notype' and 'type' variants. */
1088
1089notype_init_declarator:
1090	notype_declarator asm_or_symbolrename_opt {
1091		cgram_declare($1, false, $2);
1092		check_size($1);
1093	}
1094|	notype_declarator asm_or_symbolrename_opt {
1095		begin_initialization($1);
1096		cgram_declare($1, true, $2);
1097	} T_ASSIGN initializer {
1098		check_size($1);
1099		end_initialization();
1100	}
1101;
1102
1103type_init_declarator:
1104	type_declarator asm_or_symbolrename_opt {
1105		cgram_declare($1, false, $2);
1106		check_size($1);
1107	}
1108|	type_declarator asm_or_symbolrename_opt {
1109		begin_initialization($1);
1110		cgram_declare($1, true, $2);
1111	} T_ASSIGN initializer {
1112		check_size($1);
1113		end_initialization();
1114	}
1115;
1116
1117
1118/* TODO: Implement 'attribute_declaration' from C23 6.7.1. */
1119
1120/* K&R ???, C90 ???, C99 ???, C11 ???, C23 6.7.2 */
1121storage_class_specifier:
1122	T_SCLASS
1123;
1124
1125/* C99 6.7.2, C23 6.7.3.1 */
1126/* The rule 'type_specifier' is split into the 'notype' and 'type' variants. */
1127
1128type_type_specifier:
1129	notype_type_specifier
1130|	T_TYPENAME {
1131		$$ = getsym($1)->s_type;
1132	}
1133;
1134
1135notype_type_specifier:		/* see C99 6.7.2 */
1136	T_TYPE {
1137		$$ = gettyp($1);
1138	}
1139|	T_TYPEOF T_LPAREN expression T_RPAREN {	/* GCC extension */
1140		$$ = $3 != NULL ? block_dup_type($3->tn_type) : gettyp(INT);
1141		$$->t_typeof = true;
1142	}
1143|	atomic_type_specifier
1144|	struct_or_union_specifier {
1145		end_declaration_level();
1146		$$ = $1;
1147	}
1148|	enum_specifier {
1149		end_declaration_level();
1150		$$ = $1;
1151	}
1152;
1153
1154/* K&R ---, C90 ---, C99 6.7.2.1, C11 ???, C23 6.7.3.2 */
1155struct_or_union_specifier:
1156	struct_or_union identifier_sym {
1157		/*
1158		 * STDC requires that "struct a;" always introduces
1159		 * a new tag if "a" is not declared at current level
1160		 *
1161		 * yychar is valid because otherwise the parser would not
1162		 * have been able to decide if it must shift or reduce
1163		 */
1164		$$ = make_tag_type($2, $1, false, yychar == T_SEMI);
1165	}
1166|	struct_or_union identifier_sym {
1167		dcs->d_tag_type = make_tag_type($2, $1, true, false);
1168	} braced_member_declaration_list {
1169		$$ = complete_struct_or_union($4);
1170	}
1171|	struct_or_union {
1172		dcs->d_tag_type = make_tag_type(NULL, $1, true, false);
1173	} braced_member_declaration_list {
1174		$$ = complete_struct_or_union($3);
1175	}
1176|	struct_or_union error {
1177		set_sym_kind(SK_VCFT);
1178		$$ = gettyp(INT);
1179	}
1180;
1181
1182/* K&R ---, C90 ---, C99 6.7.2.1, C11 ???, C23 6.7.3.2 */
1183struct_or_union:
1184	T_STRUCT_OR_UNION {
1185		set_sym_kind(SK_TAG);
1186		begin_declaration_level($1 == STRUCT ? DLK_STRUCT : DLK_UNION);
1187		dcs->d_sou_size_in_bits = 0;
1188		dcs->d_sou_align = 1;
1189		$$ = $1;
1190	}
1191|	struct_or_union type_attribute
1192;
1193
1194braced_member_declaration_list:	/* see C99 6.7.2.1 */
1195	T_LBRACE {
1196		set_sym_kind(SK_VCFT);
1197	} member_declaration_list_with_rbrace {
1198		$$ = $3;
1199	}
1200;
1201
1202member_declaration_list_with_rbrace:	/* see C99 6.7.2.1 */
1203	member_declaration_list T_RBRACE
1204|	T_RBRACE {
1205		/* XXX: Allowed since C23. */
1206		$$ = NULL;
1207	}
1208;
1209
1210/* K&R ???, C90 ???, C99 6.7.2.1, C11 6.7.2.1, C23 6.7.3.2 */
1211/* Was named struct_declaration_list until C11. */
1212member_declaration_list:
1213	member_declaration
1214|	member_declaration_list member_declaration {
1215		$$ = concat_symbols($1, $2);
1216	}
1217;
1218
1219/* K&R ???, C90 ???, C99 6.7.2.1, C11 6.7.2.1, C23 6.7.3.2 */
1220/* Was named struct_declaration until C11. */
1221member_declaration:
1222	begin_type_qualifier_list end_type {
1223		/* ^^ There is no check for the missing type-specifier. */
1224		/* too late, i know, but getsym() compensates it */
1225		set_sym_kind(SK_MEMBER);
1226	} notype_member_declarator_list T_SEMI {
1227		set_sym_kind(SK_VCFT);
1228		$$ = $4;
1229	}
1230|	begin_type_specifier_qualifier_list end_type {
1231		set_sym_kind(SK_MEMBER);
1232	} type_member_declarator_list T_SEMI {
1233		set_sym_kind(SK_VCFT);
1234		$$ = $4;
1235	}
1236|	begin_type_qualifier_list end_type type_attribute_opt T_SEMI {
1237		/* syntax error '%s' */
1238		error(249, "member without type");
1239		$$ = NULL;
1240	}
1241|	begin_type_specifier_qualifier_list end_type type_attribute_opt
1242	    T_SEMI {
1243		set_sym_kind(SK_VCFT);
1244		if (!allow_c11 && !allow_gcc)
1245			/* anonymous struct/union members is a C11 feature */
1246			warning(49);
1247		if (is_struct_or_union(dcs->d_type->t_tspec))
1248			$$ = declare_unnamed_member();
1249		else {
1250			/* syntax error '%s' */
1251			error(249, "unnamed member");
1252			$$ = NULL;
1253		}
1254	}
1255|	static_assert_declaration {
1256		$$ = NULL;
1257	}
1258|	error T_SEMI {
1259		set_sym_kind(SK_VCFT);
1260		$$ = NULL;
1261	}
1262;
1263
1264/* TODO: Implement 'specifier_qualifier_list' from C23 6.7.3.2. */
1265
1266/* TODO: Implement 'type_specifier_qualifier' from C23 6.7.3.2. */
1267
1268/* C23 6.7.3.2 */
1269/* The rule 'member_declarator_list' is split into the 'type' and 'notype' variants. */
1270/* Was named struct_declarator_list until C11. */
1271
1272notype_member_declarator_list:
1273	notype_member_declarator {
1274		$$ = declare_member($1);
1275	}
1276|	notype_member_declarator_list {
1277		set_sym_kind(SK_MEMBER);
1278	} T_COMMA type_member_declarator {
1279		$$ = concat_symbols($1, declare_member($4));
1280	}
1281;
1282
1283type_member_declarator_list:
1284	type_member_declarator {
1285		$$ = declare_member($1);
1286	}
1287|	type_member_declarator_list {
1288		set_sym_kind(SK_MEMBER);
1289	} T_COMMA type_member_declarator {
1290		$$ = concat_symbols($1, declare_member($4));
1291	}
1292;
1293
1294/* C23 6.7.3.2 */
1295/* The rule 'member_declarator' is split into the 'type' and 'notype' variants. */
1296/* Was named struct_declarator until C11. */
1297
1298notype_member_declarator:
1299	notype_declarator
1300	/* C99 6.7.2.1 */
1301|	notype_declarator T_COLON constant_expression {
1302		$$ = set_bit_field_width($1, to_int_constant($3, true));
1303	}
1304	/* C99 6.7.2.1 */
1305|	{
1306		set_sym_kind(SK_VCFT);
1307	} T_COLON constant_expression {
1308		$$ = set_bit_field_width(NULL, to_int_constant($3, true));
1309	}
1310;
1311
1312type_member_declarator:
1313	type_declarator
1314|	type_declarator T_COLON constant_expression type_attribute_list_opt {
1315		$$ = set_bit_field_width($1, to_int_constant($3, true));
1316	}
1317|	{
1318		set_sym_kind(SK_VCFT);
1319	} T_COLON constant_expression type_attribute_list_opt {
1320		$$ = set_bit_field_width(NULL, to_int_constant($3, true));
1321	}
1322;
1323
1324/* K&R ---, C90 6.5.2.2, C99 6.7.2.2, C11 6.7.2.2, C23 6.7.3.5 */
1325enum_specifier:
1326	enum gcc_attribute_specifier_list_opt identifier_sym {
1327		$$ = make_tag_type($3, ENUM, false, false);
1328	}
1329|	enum gcc_attribute_specifier_list_opt identifier_sym {
1330		dcs->d_tag_type = make_tag_type($3, ENUM, true, false);
1331	} enum_declaration /*gcc_attribute_specifier_list_opt*/ {
1332		$$ = complete_enum($5);
1333	}
1334|	enum gcc_attribute_specifier_list_opt {
1335		dcs->d_tag_type = make_tag_type(NULL, ENUM, true, false);
1336	} enum_declaration /*gcc_attribute_specifier_list_opt*/ {
1337		$$ = complete_enum($4);
1338	}
1339|	enum error {
1340		set_sym_kind(SK_VCFT);
1341		$$ = gettyp(INT);
1342	}
1343;
1344
1345enum:				/* helper for C99 6.7.2.2 */
1346	T_ENUM {
1347		set_sym_kind(SK_TAG);
1348		begin_declaration_level(DLK_ENUM);
1349	}
1350;
1351
1352enum_declaration:		/* helper for C99 6.7.2.2 */
1353	T_LBRACE {
1354		set_sym_kind(SK_VCFT);
1355		enumval = 0;
1356	} enums_with_opt_comma T_RBRACE {
1357		$$ = $3;
1358	}
1359;
1360
1361enums_with_opt_comma:		/* helper for C99 6.7.2.2 */
1362	enumerator_list
1363|	enumerator_list T_COMMA {
1364		if (!allow_c99 && !allow_trad)
1365			/* trailing ',' in enum declaration requires C99 ... */
1366			error(54);
1367		else
1368			/* trailing ',' in enum declaration requires C99 ... */
1369			c99ism(54);
1370		$$ = $1;
1371	}
1372;
1373
1374/* C99 6.7.2.2, C23 6.7.3.3 */
1375enumerator_list:
1376	enumerator
1377|	enumerator_list T_COMMA enumerator {
1378		$$ = concat_symbols($1, $3);
1379	}
1380|	error {
1381		$$ = NULL;
1382	}
1383;
1384
1385/* C99 6.7.2.2, C23 6.7.3.3 */
1386enumerator:
1387	identifier_sym gcc_attribute_specifier_list_opt {
1388		$$ = enumeration_constant($1, enumval, true);
1389	}
1390|	identifier_sym gcc_attribute_specifier_list_opt
1391	    T_ASSIGN constant_expression {
1392		$$ = enumeration_constant($1, to_int_constant($4, true),
1393		    false);
1394	}
1395;
1396
1397/* TODO: Implement 'enum_type_specifier' from C23 6.7.3.3. */
1398
1399/* K&R ---, C90 ---, C99 ---, C11 6.7.2.4, C23 6.7.3.5 */
1400atomic_type_specifier:
1401	atomic T_LPAREN type_name T_RPAREN {
1402		$$ = $3;
1403	}
1404;
1405
1406atomic:				/* helper */
1407	T_ATOMIC {
1408		/* TODO: First fix c11ism, then use it here. */
1409		if (!allow_c11)
1410			/* '_Atomic' requires C11 or later */
1411			error(350);
1412	}
1413;
1414
1415/* TODO: Implement 'typeof_specifier' from C23 6.7.3.6. */
1416
1417/* TODO: Implement 'typeof_specifier_argument' from C23 6.7.3.6. */
1418
1419/* C99 6.7.3, C23 6.7.4.1 */
1420type_qualifier:
1421	T_QUAL
1422|	atomic {
1423		$$ = (type_qualifiers){ .tq_atomic = true };
1424	}
1425;
1426
1427/* TODO: Implement 'function_specifier' from C23 6.7.5. */
1428
1429/* TODO: Implement 'alignment_specifier' from C23 6.7.6. */
1430
1431/* C23 6.7.7.1 */
1432/* The rule 'declarator' is split into the 'notype' and 'type' variants. */
1433
1434notype_declarator:
1435	notype_direct_declarator
1436|	pointer notype_direct_declarator {
1437		$$ = add_pointer($2, $1);
1438	}
1439;
1440
1441type_declarator:
1442	type_direct_declarator
1443|	pointer type_direct_declarator {
1444		$$ = add_pointer($2, $1);
1445	}
1446;
1447
1448/* C23 6.7.7.1 */
1449/* The rule 'direct_declarator' is split into the 'notype' and 'type' variants. */
1450
1451notype_direct_declarator:
1452	type_attribute_list_opt T_NAME {
1453		$$ = declarator_name(getsym($2));
1454	}
1455|	type_attribute_list_opt T_LPAREN type_declarator T_RPAREN {
1456		$$ = $3;
1457	}
1458|	notype_direct_declarator T_LBRACK array_size_opt T_RBRACK {
1459		$$ = add_array($1, $3.has_dim, $3.dim);
1460	}
1461|	notype_direct_declarator param_list asm_or_symbolrename_opt {
1462		$$ = add_function(symbolrename($1, $3), $2);
1463		end_declaration_level();
1464		block_level--;
1465	}
1466|	notype_direct_declarator type_attribute
1467;
1468
1469type_direct_declarator:
1470	type_attribute_list_opt identifier {
1471		$$ = declarator_name(getsym($2));
1472	}
1473|	type_attribute_list_opt T_LPAREN type_declarator T_RPAREN {
1474		$$ = $3;
1475	}
1476|	type_direct_declarator T_LBRACK array_size_opt T_RBRACK {
1477		$$ = add_array($1, $3.has_dim, $3.dim);
1478	}
1479|	type_direct_declarator param_list asm_or_symbolrename_opt {
1480		$$ = add_function(symbolrename($1, $3), $2);
1481		end_declaration_level();
1482		block_level--;
1483	}
1484|	type_direct_declarator type_attribute
1485;
1486
1487
1488/* TODO: Implement 'array_declarator' from C23 6.7.7.1. */
1489
1490/* TODO: Implement 'function_declarator' from C23 6.7.7.1. */
1491
1492/* C99 6.7.5, C23 6.7.7.1 */
1493pointer:
1494	T_ASTERISK type_qualifier_list_opt {
1495		$$ = xcalloc(1, sizeof(*$$));
1496		add_type_qualifiers(&$$->qualifiers, $2);
1497	}
1498|	T_ASTERISK type_qualifier_list_opt pointer {
1499		$$ = xcalloc(1, sizeof(*$$));
1500		add_type_qualifiers(&$$->qualifiers, $2);
1501		$$ = append_qualified_pointer($$, $3);
1502	}
1503;
1504
1505/* see C99 6.7.5, C23 6.7.7.1 */
1506type_qualifier_list_opt:
1507	/* empty */ {
1508		$$ = (type_qualifiers){ .tq_const = false };
1509	}
1510|	type_qualifier_list
1511;
1512
1513/* C99 6.7.5 */
1514type_qualifier_list:
1515	type_qualifier
1516|	type_qualifier_list type_qualifier {
1517		$$ = $1;
1518		add_type_qualifiers(&$$, $2);
1519	}
1520;
1521
1522/* TODO: Implement 'parameter_type_list' from C23 6.7.7.1. */
1523
1524/* TODO: Implement 'parameter_list' from C23 6.7.7.1. */
1525
1526/* C23 6.7.7.1 */
1527/* XXX: C99 6.7.5 defines the same name, but it looks completely different. */
1528parameter_declaration:
1529	begin_type_declmods end_type {
1530		/* ^^ There is no check for the missing type-specifier. */
1531		$$ = declare_parameter(abstract_name(), false);
1532	}
1533|	begin_type_declaration_specifiers end_type {
1534		$$ = declare_parameter(abstract_name(), false);
1535	}
1536|	begin_type_declmods end_type notype_param_declarator {
1537		/* ^^ There is no check for the missing type-specifier. */
1538		$$ = declare_parameter($3, false);
1539	}
1540	/*
1541	 * type_param_declarator is needed because of following conflict:
1542	 * "typedef int a; f(int (a));" could be parsed as
1543	 * "function with argument a of type int", or
1544	 * "function with an unnamed (abstract) argument of type function".
1545	 * This grammar realizes the second case.
1546	 */
1547|	begin_type_declaration_specifiers end_type type_param_declarator {
1548		$$ = declare_parameter($3, false);
1549	}
1550|	begin_type_declmods end_type abstract_declarator {
1551		/* ^^ There is no check for the missing type-specifier. */
1552		$$ = declare_parameter($3, false);
1553	}
1554|	begin_type_declaration_specifiers end_type abstract_declarator {
1555		$$ = declare_parameter($3, false);
1556	}
1557;
1558
1559/*
1560 * The two distinct rules type_param_declarator and notype_param_declarator
1561 * avoid a conflict in parameter lists. A typename enclosed in parentheses is
1562 * always treated as a typename, not an argument name. For example, after
1563 * "typedef double a;", the declaration "f(int (a));" is interpreted as
1564 * "f(int (double));", not "f(int a);".
1565 */
1566type_param_declarator:
1567	direct_param_declarator
1568|	pointer direct_param_declarator {
1569		$$ = add_pointer($2, $1);
1570	}
1571;
1572
1573notype_param_declarator:
1574	direct_notype_param_declarator
1575|	pointer direct_notype_param_declarator {
1576		$$ = add_pointer($2, $1);
1577	}
1578;
1579
1580direct_param_declarator:
1581	identifier type_attribute_list {
1582		$$ = declarator_name(getsym($1));
1583	}
1584|	identifier {
1585		$$ = declarator_name(getsym($1));
1586	}
1587|	T_LPAREN notype_param_declarator T_RPAREN {
1588		$$ = $2;
1589	}
1590|	direct_param_declarator T_LBRACK array_size_opt T_RBRACK
1591	    gcc_attribute_specifier_list_opt {
1592		$$ = add_array($1, $3.has_dim, $3.dim);
1593	}
1594|	direct_param_declarator param_list asm_or_symbolrename_opt {
1595		$$ = add_function(symbolrename($1, $3), $2);
1596		end_declaration_level();
1597		block_level--;
1598	}
1599;
1600
1601direct_notype_param_declarator:
1602	identifier {
1603		$$ = declarator_name(getsym($1));
1604	}
1605|	T_LPAREN notype_param_declarator T_RPAREN {
1606		$$ = $2;
1607	}
1608|	direct_notype_param_declarator T_LBRACK array_size_opt T_RBRACK {
1609		$$ = add_array($1, $3.has_dim, $3.dim);
1610	}
1611|	direct_notype_param_declarator param_list asm_or_symbolrename_opt {
1612		$$ = add_function(symbolrename($1, $3), $2);
1613		end_declaration_level();
1614		block_level--;
1615	}
1616;
1617
1618param_list:
1619	T_LPAREN {
1620		block_level++;
1621		begin_declaration_level(DLK_PROTO_PARAMS);
1622	} identifier_list T_RPAREN {
1623		$$ = (parameter_list){ .first = $3 };
1624	}
1625|	abstract_decl_param_list
1626;
1627
1628array_size_opt:
1629	/* empty */ {
1630		$$.has_dim = false;
1631		$$.dim = 0;
1632	}
1633|	T_ASTERISK {
1634		/* since C99; variable length array of unspecified size */
1635		$$.has_dim = false; /* TODO: maybe change to true */
1636		$$.dim = 0;	/* just as a placeholder */
1637	}
1638|	type_qualifier_list_opt T_SCLASS constant_expression {
1639		/* C11 6.7.6.3p7 */
1640		if ($2 != STATIC)
1641			yyerror("Bad attribute");
1642		/* static array size requires C11 or later */
1643		c11ism(343);
1644		$$.has_dim = true;
1645		$$.dim = $3 == NULL ? 0 : to_int_constant($3, false);
1646	}
1647|	type_qualifier {
1648		/* C11 6.7.6.2 */
1649		if (!$1.tq_restrict)
1650			yyerror("Bad attribute");
1651		$$.has_dim = true;
1652		$$.dim = 0;
1653	}
1654|	constant_expression {
1655		$$.has_dim = true;
1656		$$.dim = $1 == NULL ? 0 : to_int_constant($1, false);
1657	}
1658;
1659
1660identifier_list:		/* C99 6.7.5 */
1661	T_NAME {
1662		$$ = old_style_function_parameter_name(getsym($1));
1663	}
1664|	identifier_list T_COMMA T_NAME {
1665		$$ = concat_symbols($1,
1666		    old_style_function_parameter_name(getsym($3)));
1667	}
1668|	identifier_list error
1669;
1670
1671/* C99 6.7.6, C23 6.7.8 */
1672/* XXX: C99 requires an additional specifier-qualifier-list. */
1673type_name:
1674	{
1675		begin_declaration_level(DLK_ABSTRACT);
1676	} abstract_declaration {
1677		end_declaration_level();
1678		$$ = $2->s_type;
1679	}
1680;
1681
1682abstract_declaration:		/* specific to lint */
1683	begin_type_qualifier_list end_type {
1684		$$ = declare_abstract_type(abstract_name());
1685	}
1686|	begin_type_specifier_qualifier_list end_type {
1687		$$ = declare_abstract_type(abstract_name());
1688	}
1689|	begin_type_qualifier_list end_type abstract_declarator {
1690		$$ = declare_abstract_type($3);
1691	}
1692|	begin_type_specifier_qualifier_list end_type abstract_declarator {
1693		$$ = declare_abstract_type($3);
1694	}
1695;
1696
1697abstract_decl_param_list:	/* specific to lint */
1698	abstract_decl_lparen T_RPAREN type_attribute_opt {
1699		$$ = (parameter_list){ .first = NULL };
1700	}
1701|	abstract_decl_lparen vararg_parameter_type_list T_RPAREN
1702	    type_attribute_opt {
1703		$$ = $2;
1704		$$.prototype = true;
1705	}
1706|	abstract_decl_lparen error T_RPAREN type_attribute_opt {
1707		$$ = (parameter_list){ .first = NULL };
1708	}
1709;
1710
1711abstract_decl_lparen:		/* specific to lint */
1712	T_LPAREN {
1713		block_level++;
1714		begin_declaration_level(DLK_PROTO_PARAMS);
1715	}
1716;
1717
1718vararg_parameter_type_list:	/* specific to lint */
1719	parameter_type_list
1720|	parameter_type_list T_COMMA T_ELLIPSIS {
1721		$$ = $1;
1722		$$.vararg = true;
1723	}
1724|	T_ELLIPSIS {
1725		/* TODO: C99 6.7.5 makes this an error as well. */
1726		if (!allow_trad && !allow_c99)
1727			/* C90 to C17 require formal parameter before '...' */
1728			error(84);
1729		else if (allow_c90)
1730			/* C90 to C17 require formal parameter before '...' */
1731			warning(84);
1732		$$ = (parameter_list){ .vararg = true };
1733	}
1734;
1735
1736/* XXX: C99 6.7.5 defines the same name, but it looks different. */
1737parameter_type_list:
1738	parameter_declaration {
1739		$$ = (parameter_list){ .first = $1 };
1740	}
1741|	parameter_type_list T_COMMA parameter_declaration {
1742		$$ = $1;
1743		$$.first = concat_symbols($1.first, $3);
1744	}
1745;
1746
1747/* K&R 8.7, C90 ???, C99 6.7.6, C11 6.7.7, C23 6.7.8 */
1748/* In K&R, abstract-declarator could be empty and was still simpler. */
1749abstract_declarator:
1750	pointer {
1751		$$ = add_pointer(abstract_name(), $1);
1752	}
1753|	direct_abstract_declarator
1754|	pointer direct_abstract_declarator {
1755		$$ = add_pointer($2, $1);
1756	}
1757|	type_attribute_list direct_abstract_declarator {
1758		$$ = $2;
1759	}
1760|	pointer type_attribute_list direct_abstract_declarator {
1761		$$ = add_pointer($3, $1);
1762	}
1763;
1764
1765/* K&R ---, C90 ???, C99 6.7.6, C11 6.7.7, C23 6.7.8 */
1766direct_abstract_declarator:
1767	/* TODO: sort rules according to C99 */
1768	T_LPAREN abstract_declarator T_RPAREN {
1769		$$ = $2;
1770	}
1771|	T_LBRACK array_size_opt T_RBRACK {
1772		$$ = add_array(abstract_name(), $2.has_dim, $2.dim);
1773	}
1774|	direct_abstract_declarator T_LBRACK array_size_opt T_RBRACK {
1775		$$ = add_array($1, $3.has_dim, $3.dim);
1776	}
1777|	abstract_decl_param_list asm_or_symbolrename_opt {
1778		sym_t *name = abstract_enclosing_name();
1779		$$ = add_function(symbolrename(name, $2), $1);
1780		end_declaration_level();
1781		block_level--;
1782	}
1783|	direct_abstract_declarator abstract_decl_param_list
1784	    asm_or_symbolrename_opt {
1785		$$ = add_function(symbolrename($1, $3), $2);
1786		end_declaration_level();
1787		block_level--;
1788	}
1789|	direct_abstract_declarator type_attribute_list
1790;
1791
1792/* TODO: Implement 'array_abstract_declarator' from C23 6.7.8. */
1793
1794/* TODO: Implement 'function_abstract_declarator' from C23 6.7.8. */
1795
1796/* TODO: Implement 'typedef_name' from C23 6.7.9. */
1797
1798/* C23 6.7.11 */
1799/* K&R ---, C90 ---, C99 6.7.8, C11 6.7.9, C23 6.7.10 */
1800braced_initializer:
1801	init_lbrace init_rbrace {
1802		/* empty initializer braces require C23 or later */
1803		c23ism(353);
1804	}
1805|	init_lbrace initializer_list init_rbrace
1806|	init_lbrace initializer_list T_COMMA init_rbrace
1807;
1808
1809/* C99 6.7.8, C23 6.7.11 */
1810initializer:
1811	assignment_expression {
1812		init_expr($1);
1813	}
1814|	init_lbrace init_rbrace {
1815		/* XXX: Empty braces are not covered by C99 6.7.8. */
1816	}
1817|	init_lbrace initializer_list init_rbrace
1818|	init_lbrace initializer_list T_COMMA init_rbrace
1819	/* XXX: What is this error handling for? */
1820|	error
1821;
1822
1823/* C99 6.7.8, C23 6.7.11 */
1824initializer_list:
1825	initializer
1826|	designation initializer
1827|	initializer_list T_COMMA initializer
1828|	initializer_list T_COMMA designation initializer
1829;
1830
1831/* C99 6.7.8, C23 6.7.11 */
1832designation:
1833	{
1834		begin_designation();
1835	} designator_list T_ASSIGN
1836|	identifier T_COLON {
1837		/* GCC style struct or union member name in initializer */
1838		gnuism(315);
1839		begin_designation();
1840		add_designator_member($1);
1841	}
1842;
1843
1844/* C99 6.7.8, C23 6.7.11 */
1845designator_list:
1846	designator
1847|	designator_list designator
1848;
1849
1850/* C99 6.7.8, C23 6.7.11 */
1851designator:
1852	T_LBRACK range T_RBRACK {
1853		if (!allow_c99)
1854			/* array initializer with designators is a C99 ... */
1855			warning(321);
1856		add_designator_subscript($2);
1857	}
1858|	T_POINT identifier {
1859		if (!allow_c99)
1860			/* struct or union member name in initializer is ... */
1861			warning(313);
1862		add_designator_member($2);
1863	}
1864;
1865
1866/* C23 6.7.12 */
1867static_assert_declaration:
1868	T_STATIC_ASSERT T_LPAREN constant_expression T_COMMA T_STRING
1869	    T_RPAREN T_SEMI {
1870		/* '_Static_assert' requires C11 or later */
1871		c11ism(354);
1872	}
1873|	T_STATIC_ASSERT T_LPAREN constant_expression T_RPAREN T_SEMI {
1874		/* '_Static_assert' without message requires C23 or later */
1875		c23ism(355);
1876	}
1877;
1878
1879range:
1880	constant_expression {
1881		$$.lo = to_int_constant($1, true);
1882		$$.hi = $$.lo;
1883	}
1884|	constant_expression T_ELLIPSIS constant_expression {
1885		$$.lo = to_int_constant($1, true);
1886		$$.hi = to_int_constant($3, true);
1887		/* initialization with '[a...b]' is a GCC extension */
1888		gnuism(340);
1889	}
1890;
1891
1892init_lbrace:			/* helper */
1893	T_LBRACE {
1894		init_lbrace();
1895	}
1896;
1897
1898init_rbrace:			/* helper */
1899	T_RBRACE {
1900		init_rbrace();
1901	}
1902;
1903
1904/* C23 6.7.13.2 */
1905attribute_specifier_sequence:
1906	attribute_specifier {
1907		$$ = (attribute_list) { NULL, 0, 0 };
1908		attribute_list_add_all(&$$, $1);
1909	}
1910|	attribute_specifier_sequence attribute_specifier {
1911		$$ = $1;
1912		attribute_list_add_all(&$$, $2);
1913	}
1914;
1915
1916/* C23 6.7.13.2 */
1917attribute_specifier:
1918	T_LBRACK T_LBRACK attribute_list T_RBRACK T_RBRACK {
1919		$$ = $3;
1920	}
1921;
1922
1923/* C23 6.7.13.2 */
1924attribute_list:
1925	/* empty */ {
1926		$$ = (attribute_list) { NULL, 0, 0 };
1927	}
1928|	attribute {
1929		$$ = (attribute_list) { NULL, 0, 0 };
1930		attribute_list_add(&$$, $1);
1931	}
1932|	attribute_list T_COMMA
1933|	attribute_list T_COMMA attribute {
1934		$$ = $1;
1935		attribute_list_add(&$$, $3);
1936	}
1937;
1938
1939/* C23 6.7.13.2 */
1940attribute:
1941	identifier {
1942		$$ = new_attribute(NULL, $1, NULL);
1943	}
1944|	identifier T_DCOLON identifier {
1945		$$ = new_attribute($1, $3, NULL);
1946	}
1947|	identifier attribute_argument_clause {
1948		$$ = new_attribute(NULL, $1, &$2);
1949	}
1950|	identifier T_DCOLON identifier attribute_argument_clause {
1951		$$ = new_attribute($1, $3, &$4);
1952	}
1953;
1954
1955/* The rule 'attribute_token' is inlined into 'attribute'. */
1956/* The rule 'standard_attribute' is inlined into 'attribute_token'. */
1957/* The rule 'attribute_prefixed_token' is inlined into 'attribute_token'. */
1958/* The rule 'attribute_prefix' is inlined into 'attribute_token'. */
1959
1960/* C23 6.7.13.2 */
1961attribute_argument_clause:
1962	T_LPAREN {
1963		$$ = read_balanced_token_sequence();
1964	}
1965;
1966
1967/* The rule 'balanced_token_sequence' is inlined into 'attribute_argument_clause'. */
1968/* The rule 'balanced_token' is inlined into 'balanced_token_sequence'. */
1969
1970asm_or_symbolrename_opt:	/* GCC extensions */
1971	/* empty */ {
1972		$$ = NULL;
1973	}
1974|	T_ASM T_LPAREN T_STRING T_RPAREN gcc_attribute_specifier_list_opt {
1975		freeyyv(&$3, T_STRING);
1976		$$ = NULL;
1977	}
1978|	T_SYMBOLRENAME T_LPAREN T_NAME T_RPAREN
1979	    gcc_attribute_specifier_list_opt {
1980		$$ = $3;
1981	}
1982;
1983
1984/* K&R ???, C90 ???, C99 6.8, C11 ???, C23 6.8.1 */
1985statement:
1986	expression_statement
1987|	non_expr_statement
1988;
1989
1990/* Helper to avoid shift/reduce conflict in 'label: __attribute__ ;'. */
1991no_attr_statement:
1992	expression_statement
1993|	no_attr_non_expr_statement
1994;
1995
1996non_expr_statement:		/* helper for C99 6.8 */
1997	gcc_attribute_specifier /* ((__fallthrough__)) */ T_SEMI
1998|	no_attr_non_expr_statement
1999;
2000
2001/* Helper to avoid shift/reduce conflict in 'label: __attribute__ ;'. */
2002no_attr_non_expr_statement:
2003	labeled_statement
2004|	compound_statement
2005|	selection_statement
2006|	iteration_statement
2007|	jump_statement {
2008		suppress_fallthrough = false;
2009	}
2010|	asm_statement
2011;
2012
2013/* TODO: Implement 'unlabeled_statement' from C23 6.8.1. */
2014
2015/* TODO: Implement 'primary_block' from C23 6.8.1. */
2016
2017/* TODO: Implement 'secondary_block' from C23 6.8.1. */
2018
2019/* C23 6.8.2 */
2020label:
2021	T_NAME T_COLON {
2022		set_sym_kind(SK_LABEL);
2023		named_label(getsym($1));
2024	}
2025|	T_CASE constant_expression T_COLON {
2026		case_label($2);
2027		suppress_fallthrough = true;
2028	}
2029|	T_CASE constant_expression T_ELLIPSIS constant_expression T_COLON {
2030		/* XXX: We don't fill all cases */
2031		case_label($2);
2032		suppress_fallthrough = true;
2033	}
2034|	T_DEFAULT T_COLON {
2035		default_label();
2036		suppress_fallthrough = true;
2037	}
2038;
2039
2040/* C99 6.8.1, C23 6.8.2 */
2041labeled_statement:
2042	label gcc_attribute_specifier_list_opt no_attr_statement
2043;
2044
2045/* C99 6.8.2, C23 6.8.3 */
2046compound_statement:
2047	compound_statement_lbrace compound_statement_rbrace
2048|	compound_statement_lbrace block_item_list compound_statement_rbrace
2049;
2050
2051compound_statement_lbrace:
2052	T_LBRACE {
2053		block_level++;
2054		mem_block_level++;
2055		debug_step("%s: mem_block_level = %zu",
2056		    "compound_statement_lbrace", mem_block_level);
2057		begin_declaration_level(DLK_AUTO);
2058	}
2059;
2060
2061compound_statement_rbrace:
2062	T_RBRACE {
2063		end_declaration_level();
2064		if (!in_statement_expr())
2065			level_free_all(mem_block_level);	/* leak */
2066		mem_block_level--;
2067		debug_step("%s: mem_block_level = %zu",
2068		    "compound_statement_rbrace", mem_block_level);
2069		block_level--;
2070		suppress_fallthrough = false;
2071	}
2072;
2073
2074/* C99 6.8.2, C23 6.8.3 */
2075block_item_list:
2076	block_item
2077|	block_item_list block_item {
2078		if ($1 && !$2)
2079			/* declarations after statements is a C99 feature */
2080			c99ism(327);
2081		$$ = $1 || $2;
2082	}
2083;
2084
2085/* C99 6.8.2, C23 6.8.3 */
2086block_item:
2087	declaration_or_error {
2088		$$ = false;
2089		restore_warning_flags();
2090	}
2091|	statement {
2092		$$ = true;
2093		restore_warning_flags();
2094	}
2095;
2096
2097/* C99 6.8.3, C23 6.8.4 */
2098expression_statement:
2099	expression T_SEMI {
2100		expr($1, false, false, false, false);
2101		suppress_fallthrough = false;
2102	}
2103|	T_SEMI {
2104		check_statement_reachable();
2105		suppress_fallthrough = false;
2106	}
2107|	attribute_specifier_sequence expression T_SEMI {
2108		debug_attribute_list(&$1);
2109		expr($2, false, false, false, false);
2110		suppress_fallthrough = false;
2111	}
2112;
2113
2114/* C99 6.8.4, C23 6.8.5.1 */
2115selection_statement:
2116	if_without_else %prec T_THEN {
2117		save_warning_flags();
2118		stmt_if_then_stmt();
2119		stmt_if_else_stmt(false);
2120	}
2121|	if_without_else T_ELSE {
2122		save_warning_flags();
2123		stmt_if_then_stmt();
2124	} statement {
2125		clear_warning_flags();
2126		stmt_if_else_stmt(true);
2127	}
2128|	if_without_else T_ELSE error {
2129		clear_warning_flags();
2130		stmt_if_else_stmt(false);
2131	}
2132|	switch_expr statement {
2133		clear_warning_flags();
2134		stmt_switch_expr_stmt();
2135	}
2136|	switch_expr error {
2137		clear_warning_flags();
2138		stmt_switch_expr_stmt();
2139	}
2140;
2141
2142if_without_else:		/* see C99 6.8.4 */
2143	if_expr statement
2144|	if_expr error
2145;
2146
2147if_expr:			/* see C99 6.8.4 */
2148	T_IF T_LPAREN expression T_RPAREN {
2149		stmt_if_expr($3);
2150		clear_warning_flags();
2151	}
2152;
2153
2154switch_expr:			/* see C99 6.8.4 */
2155	T_SWITCH T_LPAREN expression T_RPAREN {
2156		stmt_switch_expr($3);
2157		clear_warning_flags();
2158	}
2159;
2160
2161/* C99 6.8.5, C23 6.8.6.1 */
2162iteration_statement:
2163	while_expr statement {
2164		clear_warning_flags();
2165		stmt_while_expr_stmt();
2166	}
2167|	while_expr error {
2168		clear_warning_flags();
2169		stmt_while_expr_stmt();
2170	}
2171|	do_statement T_WHILE T_LPAREN expression T_RPAREN T_SEMI {
2172		stmt_do_while_expr($4);
2173		suppress_fallthrough = false;
2174	}
2175|	do error {
2176		clear_warning_flags();
2177		stmt_do_while_expr(NULL);
2178	}
2179|	for_exprs statement {
2180		clear_warning_flags();
2181		stmt_for_exprs_stmt();
2182		end_declaration_level();
2183		block_level--;
2184	}
2185|	for_exprs error {
2186		clear_warning_flags();
2187		stmt_for_exprs_stmt();
2188		end_declaration_level();
2189		block_level--;
2190	}
2191;
2192
2193while_expr:			/* see C99 6.8.5 */
2194	T_WHILE T_LPAREN expression T_RPAREN {
2195		stmt_while_expr($3);
2196		clear_warning_flags();
2197	}
2198;
2199
2200do_statement:			/* see C99 6.8.5 */
2201	do statement {
2202		clear_warning_flags();
2203	}
2204;
2205
2206do:				/* see C99 6.8.5 */
2207	T_DO {
2208		stmt_do();
2209	}
2210;
2211
2212for_start:			/* see C99 6.8.5 */
2213	T_FOR T_LPAREN {
2214		begin_declaration_level(DLK_AUTO);
2215		block_level++;
2216	}
2217;
2218
2219for_exprs:			/* see C99 6.8.5 */
2220	for_start
2221	    begin_type_declaration_specifiers end_type
2222	    notype_init_declarator_list T_SEMI
2223	    expression_opt T_SEMI
2224	    expression_opt T_RPAREN {
2225		/* variable declaration in for loop */
2226		c99ism(325);
2227		stmt_for_exprs(NULL, $6, $8);
2228		clear_warning_flags();
2229	}
2230|	for_start
2231	    expression_opt T_SEMI
2232	    expression_opt T_SEMI
2233	    expression_opt T_RPAREN {
2234		stmt_for_exprs($2, $4, $6);
2235		clear_warning_flags();
2236	}
2237;
2238
2239/* C99 6.8.6, C23 6.8.7.1 */
2240jump_statement:
2241	goto identifier T_SEMI {
2242		stmt_goto(getsym($2));
2243	}
2244|	goto error T_SEMI {
2245		set_sym_kind(SK_VCFT);
2246	}
2247|	T_CONTINUE T_SEMI {
2248		stmt_continue();
2249	}
2250|	T_BREAK T_SEMI {
2251		stmt_break();
2252	}
2253|	T_RETURN sys T_SEMI {
2254		stmt_return($2, NULL);
2255	}
2256|	T_RETURN sys expression T_SEMI {
2257		stmt_return($2, $3);
2258	}
2259;
2260
2261goto:				/* see C99 6.8.6 */
2262	T_GOTO {
2263		set_sym_kind(SK_LABEL);
2264	}
2265;
2266
2267asm_statement:			/* GCC extension */
2268	T_ASM T_LPAREN read_until_rparen T_SEMI {
2269		dcs_set_asm();
2270	}
2271|	T_ASM type_qualifier T_LPAREN read_until_rparen T_SEMI {
2272		dcs_set_asm();
2273	}
2274|	T_ASM error
2275;
2276
2277read_until_rparen:		/* helper for 'asm_statement' */
2278	/* empty */ {
2279		read_until_rparen();
2280	}
2281;
2282
2283/* C99 6.9, C23 6.9.1 */
2284translation_unit:
2285	external_declaration
2286|	translation_unit external_declaration
2287;
2288
2289/* C99 6.9, C23 6.9.1 */
2290external_declaration:
2291	function_definition {
2292		global_clean_up_decl(false);
2293		clear_warning_flags();
2294	}
2295|	top_level_declaration {
2296		global_clean_up_decl(false);
2297		clear_warning_flags();
2298	}
2299|	asm_statement		/* GCC extension */
2300|	T_SEMI {		/* GCC extension */
2301		/*
2302		 * TODO: Only allow this in GCC mode, not in plain C99.
2303		 * This is one of the top 10 warnings in the NetBSD build.
2304		 */
2305		if (!allow_trad && !allow_c99)
2306			/* empty declaration */
2307			error(0);
2308		else if (allow_c90)
2309			/* empty declaration */
2310			warning(0);
2311	}
2312;
2313
2314/*
2315 * On the top level, lint allows several forms of declarations that it doesn't
2316 * allow in functions.  For example, a single ';' is an empty declaration and
2317 * is supported by some compilers, but in a function it would be an empty
2318 * statement, not a declaration.  This makes a difference in C90 mode, where
2319 * a statement must not be followed by a declaration.
2320 *
2321 * See 'declaration' for all other declarations.
2322 */
2323top_level_declaration:		/* C99 6.9 calls this 'declaration' */
2324	begin_type end_type notype_init_declarator_list T_SEMI {
2325		/* TODO: Make this an error in C99 mode as well. */
2326		if (!allow_trad && !allow_c99)
2327			/* old-style declaration; add 'int' */
2328			error(1);
2329		else if (allow_c90)
2330			/* old-style declaration; add 'int' */
2331			warning(1);
2332	}
2333|	declaration
2334|	error T_SEMI {
2335		global_clean_up();
2336	}
2337|	error T_RBRACE {
2338		global_clean_up();
2339	}
2340;
2341
2342/* C99 6.9.1, C23 6.9.2 */
2343function_definition:
2344	func_declarator {
2345		if ($1->s_type->t_tspec != FUNC) {
2346			/* syntax error '%s' */
2347			error(249, yytext);
2348			YYERROR;
2349		}
2350		if ($1->s_type->t_typedef) {
2351			/* ()-less function definition */
2352			error(64);
2353			YYERROR;
2354		}
2355		check_extern_declaration($1);
2356		begin_function($1);
2357		block_level++;
2358		begin_declaration_level(DLK_OLD_STYLE_PARAMS);
2359		if (lwarn == LWARN_NONE)
2360			$1->s_used = true;
2361	} arg_declaration_list_opt {
2362		end_declaration_level();
2363		block_level--;
2364		check_func_lint_directives();
2365		check_func_old_style_parameters();
2366		begin_control_statement(CS_FUNCTION_BODY);
2367	} compound_statement {
2368		end_function();
2369		end_control_statement(CS_FUNCTION_BODY);
2370	}
2371;
2372
2373func_declarator:
2374	begin_type end_type notype_declarator {
2375		if (!allow_trad)
2376			/* old-style declaration; add 'int' */
2377			error(1);
2378		$$ = $3;
2379	}
2380|	begin_type_declmods end_type notype_declarator {
2381		if (!allow_trad)
2382			/* old-style declaration; add 'int' */
2383			error(1);
2384		$$ = $3;
2385	}
2386|	begin_type_declaration_specifiers end_type type_declarator {
2387		$$ = $3;
2388	}
2389;
2390
2391arg_declaration_list_opt:	/* C99 6.9.1p13 example 1 */
2392	/* empty */
2393|	arg_declaration_list
2394;
2395
2396arg_declaration_list:		/* C99 6.9.1p13 example 1 */
2397	arg_declaration
2398|	arg_declaration_list arg_declaration
2399	/* XXX or better "arg_declaration error" ? */
2400|	error
2401;
2402
2403/*
2404 * "arg_declaration" is separated from "declaration" because it
2405 * needs other error handling.
2406 */
2407arg_declaration:
2408	begin_type_declmods end_type T_SEMI {
2409		/* empty declaration */
2410		warning(2);
2411	}
2412|	begin_type_declmods end_type notype_init_declarator_list T_SEMI
2413|	begin_type_declaration_specifiers end_type T_SEMI {
2414		if (!dcs->d_nonempty_decl)
2415			/* empty declaration */
2416			warning(2);
2417		else
2418			/* '%s' declared in parameter declaration list */
2419			warning(3, type_name(dcs->d_type));
2420	}
2421|	begin_type_declaration_specifiers end_type
2422	    type_init_declarator_list T_SEMI {
2423		if (dcs->d_nonempty_decl)
2424			/* '%s' declared in parameter declaration list */
2425			warning(3, type_name(dcs->d_type));
2426	}
2427|	begin_type_declmods error
2428|	begin_type_declaration_specifiers error
2429;
2430
2431/* https://gcc.gnu.org/onlinedocs/gcc/Attribute-Syntax.html */
2432gcc_attribute_specifier_list_opt:
2433	/* empty */
2434|	gcc_attribute_specifier_list
2435;
2436
2437gcc_attribute_specifier_list:
2438	gcc_attribute_specifier
2439|	gcc_attribute_specifier_list gcc_attribute_specifier
2440;
2441
2442gcc_attribute_specifier:
2443	T_ATTRIBUTE T_LPAREN T_LPAREN {
2444		in_gcc_attribute = true;
2445	} gcc_attribute_list {
2446		in_gcc_attribute = false;
2447	} T_RPAREN T_RPAREN
2448;
2449
2450gcc_attribute_list:
2451	gcc_attribute
2452|	gcc_attribute_list T_COMMA gcc_attribute
2453;
2454
2455gcc_attribute:
2456	/* empty */
2457|	T_NAME {
2458		const char *name = $1->sb_name;
2459		if (is_either(name, "packed", "__packed__"))
2460			dcs_add_packed();
2461		else if (is_either(name, "used", "__used__") ||
2462		    is_either(name, "unused", "__unused__"))
2463			dcs_set_used();
2464		else if (is_either(name, "fallthrough", "__fallthrough__"))
2465			suppress_fallthrough = true;
2466	}
2467|	T_NAME T_LPAREN T_RPAREN
2468|	T_NAME T_LPAREN argument_expression_list T_RPAREN {
2469		const char *name = $1->sb_name;
2470		if (is_either(name, "aligned", "__aligned__")
2471		    && $3->args_len == 1)
2472			dcs_add_alignas($3->args[0]);
2473	}
2474|	type_qualifier {
2475		if (!$1.tq_const)
2476			yyerror("Bad attribute");
2477	}
2478;
2479
2480/* The rule 'function_body' from C23 6.9.2 is inlined into 'function_definition'. */
2481
2482sys:
2483	/* empty */ {
2484		$$ = in_system_header;
2485	}
2486;
2487
2488%%
2489
2490/* ARGSUSED */
2491int
2492yyerror(const char *msg)
2493{
2494	/* syntax error '%s' */
2495	error(249, yytext);
2496	if (++sytxerr >= 5)
2497		norecover();
2498	return 0;
2499}
2500
2501#if YYDEBUG && YYBYACC
2502static const char *
2503cgram_to_string(int tok, YYSTYPE val)
2504{
2505
2506	switch (tok) {
2507	case T_INCDEC:
2508		return val.y_inc ? "++" : "--";
2509	case T_MULTIPLICATIVE:
2510	case T_ADDITIVE:
2511	case T_SHIFT:
2512	case T_RELATIONAL:
2513	case T_EQUALITY:
2514	case T_OPASSIGN:
2515		return op_name(val.y_op);
2516	case T_SCLASS:
2517		return scl_name(val.y_scl);
2518	case T_TYPE:
2519	case T_STRUCT_OR_UNION:
2520		return tspec_name(val.y_tspec);
2521	case T_QUAL:
2522		return type_qualifiers_string(val.y_type_qualifiers);
2523	case T_FUNCTION_SPECIFIER:
2524		return function_specifier_name(val.y_function_specifier);
2525	case T_NAME:
2526		return val.y_name->sb_name;
2527	default:
2528		return "<none>";
2529	}
2530}
2531#endif
2532
2533static void
2534cgram_declare(sym_t *decl, bool has_initializer, sbuf_t *renaming)
2535{
2536	declare(decl, has_initializer, renaming);
2537	if (renaming != NULL)
2538		freeyyv(&renaming, T_NAME);
2539}
2540
2541/*
2542 * Discard all input tokens up to and including the next unmatched right
2543 * parenthesis.
2544 */
2545static void
2546read_until_rparen(void)
2547{
2548	int level;
2549
2550	if (yychar < 0)
2551		yychar = yylex();
2552	freeyyv(&yylval, yychar);
2553
2554	level = 1;
2555	while (yychar > 0) {
2556		if (yychar == T_LPAREN)
2557			level++;
2558		if (yychar == T_RPAREN && --level == 0)
2559			break;
2560		freeyyv(&yylval, yychar = yylex());
2561	}
2562
2563	yyclearin;
2564}
2565
2566static balanced_token_sequence
2567read_balanced_token_sequence(void)
2568{
2569	lint_assert(yychar < 0);
2570	balanced_token_sequence seq = lex_balanced();
2571	yyclearin;
2572	return seq;
2573}
2574
2575static sym_t *
2576symbolrename(sym_t *s, sbuf_t *sb)
2577{
2578	if (sb != NULL)
2579		s->s_rename = sb->sb_name;
2580	return s;
2581}
2582