]> gcc.gnu.org Git - gcc.git/blame - gcc/c-common.h
configure.in: Define macros that affect features before testing for features.
[gcc.git] / gcc / c-common.h
CommitLineData
7f4edbcb 1/* Definitions for c-common.c.
517cbe13
JL
2 Copyright (C) 1987, 1993, 1994, 1995, 1997, 1998,
3 1999, 2000 Free Software Foundation, Inc.
7f4edbcb
BS
4
5This file is part of GNU CC.
6
7GNU CC is free software; you can redistribute it and/or modify
8it under the terms of the GNU General Public License as published by
9the Free Software Foundation; either version 2, or (at your option)
10any later version.
11
12GNU CC is distributed in the hope that it will be useful,
13but WITHOUT ANY WARRANTY; without even the implied warranty of
14MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15GNU General Public License for more details.
16
17You should have received a copy of the GNU General Public License
18along with GNU CC; see the file COPYING. If not, write to
19the Free Software Foundation, 59 Temple Place - Suite 330,
20Boston, MA 02111-1307, USA. */
21
0e5921e8
ZW
22#ifndef GCC_C_COMMON_H
23#define GCC_C_COMMON_H
24
f2c5f623
BC
25/* Usage of TREE_LANG_FLAG_?:
26 0: COMPOUND_STMT_NO_SCOPE (in COMPOUND_STMT).
27 TREE_NEGATED_INT (in INTEGER_CST).
28 IDENTIFIER_MARKED (used by search routines).
29 SCOPE_BEGIN_P (in SCOPE_STMT)
30 DECL_PRETTY_FUNCTION_P (in VAR_DECL)
31 NEW_FOR_SCOPE_P (in FOR_STMT)
32 1: C_DECLARED_LABEL_FLAG (in LABEL_DECL)
33 STMT_IS_FULL_EXPR_P (in _STMT)
34 2: STMT_LINENO_FOR_FN_P (in _STMT)
35 3: SCOPE_NO_CLEANUPS_P (in SCOPE_STMT)
36 4: SCOPE_PARTIAL_P (in SCOPE_STMT)
37*/
38
0e5921e8
ZW
39/* Reserved identifiers. This is the union of all the keywords for C,
40 C++, and Objective C. All the type modifiers have to be in one
41 block at the beginning, because they are used as mask bits. There
42 are 27 type modifiers; if we add many more we will have to redesign
43 the mask mechanism. */
f09f1de5
MM
44
45enum rid
46{
0e5921e8
ZW
47 /* Modifiers: */
48 /* C, in empirical order of frequency. */
49 RID_STATIC = 0,
50 RID_UNSIGNED, RID_LONG, RID_CONST, RID_EXTERN,
51 RID_REGISTER, RID_TYPEDEF, RID_SHORT, RID_INLINE,
52 RID_VOLATILE, RID_SIGNED, RID_AUTO, RID_RESTRICT,
53
54 /* C extensions */
55 RID_BOUNDED, RID_UNBOUNDED, RID_COMPLEX,
56
57 /* C++ */
58 RID_FRIEND, RID_VIRTUAL, RID_EXPLICIT, RID_EXPORT, RID_MUTABLE,
59
60 /* ObjC */
61 RID_IN, RID_OUT, RID_INOUT, RID_BYCOPY, RID_BYREF, RID_ONEWAY,
62
63 /* C */
64 RID_INT, RID_CHAR, RID_FLOAT, RID_DOUBLE, RID_VOID,
65 RID_ENUM, RID_STRUCT, RID_UNION, RID_IF, RID_ELSE,
66 RID_WHILE, RID_DO, RID_FOR, RID_SWITCH, RID_CASE,
67 RID_DEFAULT, RID_BREAK, RID_CONTINUE, RID_RETURN, RID_GOTO,
68 RID_SIZEOF,
69
70 /* C extensions */
71 RID_ASM, RID_TYPEOF, RID_ALIGNOF, RID_ATTRIBUTE, RID_VA_ARG,
72 RID_EXTENSION, RID_IMAGPART, RID_REALPART, RID_LABEL, RID_PTRBASE,
73 RID_PTREXTENT, RID_PTRVALUE,
74
75 /* C++ */
76 RID_BOOL, RID_WCHAR, RID_CLASS,
77 RID_PUBLIC, RID_PRIVATE, RID_PROTECTED,
78 RID_TEMPLATE, RID_NULL, RID_CATCH,
79 RID_DELETE, RID_FALSE, RID_NAMESPACE,
80 RID_NEW, RID_OPERATOR, RID_THIS,
81 RID_THROW, RID_TRUE, RID_TRY,
82 RID_TYPENAME, RID_TYPEID, RID_USING,
83
84 /* casts */
85 RID_CONSTCAST, RID_DYNCAST, RID_REINTCAST, RID_STATCAST,
86
87 /* alternate spellings */
88 RID_AND, RID_AND_EQ, RID_NOT, RID_NOT_EQ,
89 RID_OR, RID_OR_EQ, RID_XOR, RID_XOR_EQ,
90 RID_BITAND, RID_BITOR, RID_COMPL,
91
92 /* Objective C */
93 RID_ID, RID_AT_ENCODE, RID_AT_END,
94 RID_AT_CLASS, RID_AT_ALIAS, RID_AT_DEFS,
95 RID_AT_PRIVATE, RID_AT_PROTECTED, RID_AT_PUBLIC,
96 RID_AT_PROTOCOL, RID_AT_SELECTOR, RID_AT_INTERFACE,
97 RID_AT_IMPLEMENTATION,
98
99 RID_MAX,
100
101 RID_FIRST_MODIFIER = RID_STATIC,
102 RID_LAST_MODIFIER = RID_ONEWAY
f09f1de5
MM
103};
104
f09f1de5
MM
105/* The elements of `ridpointers' are identifier nodes for the reserved
106 type names and storage classes. It is indexed by a RID_... value. */
107extern tree *ridpointers;
108
7f4edbcb
BS
109/* Standard named or nameless data types of the C compiler. */
110
111enum c_tree_index
112{
7f4edbcb
BS
113 CTI_WCHAR_TYPE,
114 CTI_SIGNED_WCHAR_TYPE,
115 CTI_UNSIGNED_WCHAR_TYPE,
c5ab7f91 116 CTI_WINT_TYPE,
3c786c69 117 CTI_C_SIZE_TYPE, /* For format checking only. */
cd732418
JM
118 CTI_SIGNED_SIZE_TYPE, /* For format checking only. */
119 CTI_UNSIGNED_PTRDIFF_TYPE, /* For format checking only. */
7f4edbcb
BS
120 CTI_WIDEST_INT_LIT_TYPE,
121 CTI_WIDEST_UINT_LIT_TYPE,
122
7f4edbcb
BS
123 CTI_CHAR_ARRAY_TYPE,
124 CTI_WCHAR_ARRAY_TYPE,
125 CTI_INT_ARRAY_TYPE,
126 CTI_STRING_TYPE,
127 CTI_CONST_STRING_TYPE,
128
7f4edbcb
BS
129 CTI_BOOLEAN_TYPE,
130 CTI_BOOLEAN_TRUE,
131 CTI_BOOLEAN_FALSE,
132 CTI_DEFAULT_FUNCTION_TYPE,
133 CTI_VOID_LIST,
134
135 CTI_VOID_FTYPE,
136 CTI_VOID_FTYPE_PTR,
137 CTI_INT_FTYPE_INT,
138 CTI_PTR_FTYPE_SIZETYPE,
7aba5a5f
CD
139
140 CTI_G77_INTEGER_TYPE,
141 CTI_G77_UINTEGER_TYPE,
142 CTI_G77_LONGINT_TYPE,
143 CTI_G77_ULONGINT_TYPE,
144
63ad61ed
ZW
145 /* These are not types, but we have to look them up all the time. */
146 CTI_FUNCTION_ID,
147 CTI_PRETTY_FUNCTION_ID,
148 CTI_FUNC_ID,
149
ae499cce
MM
150 CTI_VOID_ZERO,
151
7f4edbcb
BS
152 CTI_MAX
153};
154
7f4edbcb
BS
155#define wchar_type_node c_global_trees[CTI_WCHAR_TYPE]
156#define signed_wchar_type_node c_global_trees[CTI_SIGNED_WCHAR_TYPE]
157#define unsigned_wchar_type_node c_global_trees[CTI_UNSIGNED_WCHAR_TYPE]
c5ab7f91 158#define wint_type_node c_global_trees[CTI_WINT_TYPE]
3c786c69 159#define c_size_type_node c_global_trees[CTI_C_SIZE_TYPE]
cd732418
JM
160#define signed_size_type_node c_global_trees[CTI_SIGNED_SIZE_TYPE]
161#define unsigned_ptrdiff_type_node c_global_trees[CTI_UNSIGNED_PTRDIFF_TYPE]
7f4edbcb
BS
162#define widest_integer_literal_type_node c_global_trees[CTI_WIDEST_INT_LIT_TYPE]
163#define widest_unsigned_literal_type_node c_global_trees[CTI_WIDEST_UINT_LIT_TYPE]
164
7f4edbcb
BS
165#define boolean_type_node c_global_trees[CTI_BOOLEAN_TYPE]
166#define boolean_true_node c_global_trees[CTI_BOOLEAN_TRUE]
167#define boolean_false_node c_global_trees[CTI_BOOLEAN_FALSE]
168
7f4edbcb
BS
169#define char_array_type_node c_global_trees[CTI_CHAR_ARRAY_TYPE]
170#define wchar_array_type_node c_global_trees[CTI_WCHAR_ARRAY_TYPE]
171#define int_array_type_node c_global_trees[CTI_INT_ARRAY_TYPE]
172#define string_type_node c_global_trees[CTI_STRING_TYPE]
173#define const_string_type_node c_global_trees[CTI_CONST_STRING_TYPE]
174
175#define default_function_type c_global_trees[CTI_DEFAULT_FUNCTION_TYPE]
176#define void_list_node c_global_trees[CTI_VOID_LIST]
177#define void_ftype c_global_trees[CTI_VOID_FTYPE]
178#define void_ftype_ptr c_global_trees[CTI_VOID_FTYPE_PTR]
179#define int_ftype_int c_global_trees[CTI_INT_FTYPE_INT]
180#define ptr_ftype_sizetype c_global_trees[CTI_PTR_FTYPE_SIZETYPE]
181
7aba5a5f
CD
182/* g77 integer types, which which must be kept in sync with f/com.h */
183#define g77_integer_type_node c_global_trees[CTI_G77_INTEGER_TYPE]
184#define g77_uinteger_type_node c_global_trees[CTI_G77_UINTEGER_TYPE]
185#define g77_longint_type_node c_global_trees[CTI_G77_LONGINT_TYPE]
186#define g77_ulongint_type_node c_global_trees[CTI_G77_ULONGINT_TYPE]
187
63ad61ed
ZW
188#define function_id_node c_global_trees[CTI_FUNCTION_ID]
189#define pretty_function_id_node c_global_trees[CTI_PRETTY_FUNCTION_ID]
190#define func_id_node c_global_trees[CTI_FUNC_ID]
191
ae499cce
MM
192/* A node for `((void) 0)'. */
193#define void_zero_node c_global_trees[CTI_VOID_ZERO]
194
ab76ca54
MM
195extern tree c_global_trees[CTI_MAX];
196
197typedef enum c_language_kind
198{
199 clk_c, /* A dialect of C: K&R C, ANSI/ISO C89, C2000,
200 etc. */
201 clk_cplusplus, /* ANSI/ISO C++ */
202 clk_objective_c /* Objective C */
203}
204c_language_kind;
205
ae499cce
MM
206/* Information about a statement tree. */
207
208struct stmt_tree_s {
209 /* The last statement added to the tree. */
210 tree x_last_stmt;
211 /* The type of the last expression statement. (This information is
212 needed to implement the statement-expression extension.) */
213 tree x_last_expr_type;
214 /* In C++, Non-zero if we should treat statements as full
215 expressions. In particular, this variable is no-zero if at the
216 end of a statement we should destroy any temporaries created
217 during that statement. Similarly, if, at the end of a block, we
218 should destroy any local variables in this block. Normally, this
219 variable is non-zero, since those are the normal semantics of
220 C++.
221
222 However, in order to represent aggregate initialization code as
223 tree structure, we use statement-expressions. The statements
224 within the statement expression should not result in cleanups
225 being run until the entire enclosing statement is complete.
226
227 This flag has no effect in C. */
228 int stmts_are_full_exprs_p;
229};
230
231typedef struct stmt_tree_s *stmt_tree;
232
233/* Global state pertinent to the current function. Some C dialects
234 extend this structure with additional fields. */
235
236struct language_function {
237 /* While we are parsing the function, this contains information
238 about the statement-tree that we are building. */
239 struct stmt_tree_s x_stmt_tree;
240};
241
242/* When building a statement-tree, this is the last statement added to
243 the tree. */
244
245#define last_tree (current_stmt_tree ()->x_last_stmt)
246
247/* The type of the last expression-statement we have seen. */
248
249#define last_expr_type (current_stmt_tree ()->x_last_expr_type)
250
251/* The type of a function that walks over tree structure. */
252
253typedef tree (*walk_tree_fn) PARAMS ((tree *,
254 int *,
255 void *));
256
257extern stmt_tree current_stmt_tree PARAMS ((void));
258extern void begin_stmt_tree PARAMS ((tree *));
56cb9733 259extern tree add_stmt PARAMS ((tree));
ae499cce
MM
260extern void finish_stmt_tree PARAMS ((tree *));
261
262extern int statement_code_p PARAMS ((enum tree_code));
263extern int (*lang_statement_code_p) PARAMS ((enum tree_code));
264extern tree walk_stmt_tree PARAMS ((tree *,
265 walk_tree_fn,
266 void *));
54f7877c
MM
267extern void prep_stmt PARAMS ((tree));
268extern void (*lang_expand_stmt) PARAMS ((tree));
269extern void expand_stmt PARAMS ((tree));
ae499cce 270
56cb9733
MM
271/* LAST_TREE contains the last statement parsed. These are chained
272 together through the TREE_CHAIN field, but often need to be
273 re-organized since the parse is performed bottom-up. This macro
274 makes LAST_TREE the indicated SUBSTMT of STMT. */
275
276#define RECHAIN_STMTS(stmt, substmt) \
277 do { \
278 substmt = TREE_CHAIN (stmt); \
279 TREE_CHAIN (stmt) = NULL_TREE; \
280 last_tree = stmt; \
281 } while (0)
282
ab76ca54
MM
283/* The variant of the C language being processed. Each C language
284 front-end defines this variable. */
285
286extern c_language_kind c_language;
287
288/* Nonzero means give string constants the type `const char *', rather
289 than `char *'. */
290
291extern int flag_const_strings;
292
293/* Warn about *printf or *scanf format/argument anomalies. */
294
295extern int warn_format;
296
297/* Nonzero means do some things the same way PCC does. */
298
299extern int flag_traditional;
300
b8458e3e
JM
301/* Nonzero means enable C89 Amendment 1 features, other than digraphs. */
302
303extern int flag_isoc94;
304
ab76ca54
MM
305/* Nonzero means use the ISO C99 dialect of C. */
306
307extern int flag_isoc99;
308
530d0ba5
NB
309/* Nonzero means accept digraphs. */
310
311extern int flag_digraphs;
312
93e2382f
JM
313/* Nonzero means environment is hosted (i.e., not freestanding) */
314
315extern int flag_hosted;
316
317/* Nonzero means add default format_arg attributes for functions not
318 in ISO C. */
319
320extern int flag_noniso_default_format_attributes;
321
ab76ca54
MM
322/* Nonzero means warn about suggesting putting in ()'s. */
323
324extern int warn_parentheses;
325
326/* Warn if a type conversion is done that might have confusing results. */
327
328extern int warn_conversion;
329
330/* C types are partitioned into three subsets: object, function, and
331 incomplete types. */
332#define C_TYPE_OBJECT_P(type) \
333 (TREE_CODE (type) != FUNCTION_TYPE && TYPE_SIZE (type))
334
335#define C_TYPE_INCOMPLETE_P(type) \
336 (TREE_CODE (type) != FUNCTION_TYPE && TYPE_SIZE (type) == 0)
337
338#define C_TYPE_FUNCTION_P(type) \
339 (TREE_CODE (type) == FUNCTION_TYPE)
340
341/* For convenience we define a single macro to identify the class of
342 object or incomplete types. */
343#define C_TYPE_OBJECT_OR_INCOMPLETE_P(type) \
344 (!C_TYPE_FUNCTION_P (type))
345
346/* Record in each node resulting from a binary operator
347 what operator was specified for it. */
348#define C_EXP_ORIGINAL_CODE(exp) ((enum tree_code) TREE_COMPLEXITY (exp))
349
2ce07e2d
NS
350/* Pointer to function to generate the VAR_DECL for __FUNCTION__ etc.
351 ID is the identifier to use, NAME is the string.
352 TYPE_DEP indicates whether it depends on type of the function or not
353 (i.e. __PRETTY_FUNCTION__). */
354
355extern tree (*make_fname_decl) PARAMS ((tree, const char *, int));
356
6e090c76
KG
357extern void declare_function_name PARAMS ((void));
358extern void decl_attributes PARAMS ((tree, tree, tree));
359extern void init_function_format_info PARAMS ((void));
360extern void check_function_format PARAMS ((tree, tree, tree));
361extern void c_apply_type_quals_to_decl PARAMS ((int, tree));
7f4edbcb
BS
362/* Print an error message for invalid operands to arith operation CODE.
363 NOP_EXPR is used as a special case (see truthvalue_conversion). */
6e090c76
KG
364extern void binary_op_error PARAMS ((enum tree_code));
365extern void c_expand_expr_stmt PARAMS ((tree));
366extern void c_expand_start_cond PARAMS ((tree, int, int));
367extern void c_expand_start_else PARAMS ((void));
368extern void c_expand_end_cond PARAMS ((void));
7f4edbcb 369/* Validate the expression after `case' and apply default promotions. */
6e090c76 370extern tree check_case_value PARAMS ((tree));
7f4edbcb 371/* Concatenate a list of STRING_CST nodes into one STRING_CST. */
6e090c76
KG
372extern tree combine_strings PARAMS ((tree));
373extern void constant_expression_warning PARAMS ((tree));
374extern tree convert_and_check PARAMS ((tree, tree));
375extern void overflow_warning PARAMS ((tree));
376extern void unsigned_conversion_warning PARAMS ((tree, tree));
ab76ca54 377
7f4edbcb
BS
378/* Read the rest of the current #-directive line. */
379#if USE_CPPLIB
6e090c76 380extern char *get_directive_line PARAMS ((void));
7f4edbcb
BS
381#define GET_DIRECTIVE_LINE() get_directive_line ()
382#else
6e090c76 383extern char *get_directive_line PARAMS ((FILE *));
7f4edbcb
BS
384#define GET_DIRECTIVE_LINE() get_directive_line (finput)
385#endif
386
387/* Subroutine of build_binary_op, used for comparison operations.
388 See if the operands have both been converted from subword integer types
389 and, if so, perhaps change them both back to their original type. */
6e090c76 390extern tree shorten_compare PARAMS ((tree *, tree *, tree *, enum tree_code *));
7f4edbcb
BS
391/* Prepare expr to be an argument of a TRUTH_NOT_EXPR,
392 or validate its data type for an `if' or `while' statement or ?..: exp. */
6e090c76
KG
393extern tree truthvalue_conversion PARAMS ((tree));
394extern tree type_for_mode PARAMS ((enum machine_mode, int));
395extern tree type_for_size PARAMS ((unsigned, int));
7f4edbcb 396
50e60bc3
ZW
397extern unsigned int min_precision PARAMS ((tree, int));
398
399/* Add qualifiers to a type, in the fashion for C. */
400extern tree c_build_qualified_type PARAMS ((tree, int));
401
7f4edbcb
BS
402/* Build tree nodes and builtin functions common to both C and C++ language
403 frontends. */
6e090c76 404extern void c_common_nodes_and_builtins PARAMS ((int, int, int));
d3707adb 405
6e090c76 406extern tree build_va_arg PARAMS ((tree, tree));
7e8176d7 407
c530479e
RH
408/* Nonzero if the type T promotes to itself.
409 ANSI C states explicitly the list of types that promote;
410 in particular, short promotes to int even if they have the same width. */
411#define C_PROMOTING_INTEGER_TYPE_P(t) \
412 (TREE_CODE ((t)) == INTEGER_TYPE \
413 && (TYPE_MAIN_VARIANT (t) == char_type_node \
414 || TYPE_MAIN_VARIANT (t) == signed_char_type_node \
415 || TYPE_MAIN_VARIANT (t) == unsigned_char_type_node \
416 || TYPE_MAIN_VARIANT (t) == short_integer_type_node \
417 || TYPE_MAIN_VARIANT (t) == short_unsigned_type_node))
418
6e090c76
KG
419extern int self_promoting_args_p PARAMS ((tree));
420extern tree simple_type_promotes_to PARAMS ((tree));
d7e7759d 421
ae499cce
MM
422/* These macros provide convenient access to the various _STMT nodes. */
423
424/* Nonzero if this statement should be considered a full-expression,
425 i.e., if temporaries created during this statement should have
426 their destructors run at the end of this statement. (In C, this
427 will always be false, since there are no destructors.) */
428#define STMT_IS_FULL_EXPR_P(NODE) TREE_LANG_FLAG_1 ((NODE))
35b1567d
BC
429
430/* IF_STMT accessors. These give access to the condtion of the if
431 statement, the then block of the if statement, and the else block
432 of the if stsatement if it exists. */
d7e7759d
BC
433#define IF_COND(NODE) TREE_OPERAND (IF_STMT_CHECK (NODE), 0)
434#define THEN_CLAUSE(NODE) TREE_OPERAND (IF_STMT_CHECK (NODE), 1)
435#define ELSE_CLAUSE(NODE) TREE_OPERAND (IF_STMT_CHECK (NODE), 2)
35b1567d
BC
436
437/* WHILE_STMT accessors. These give access to the condtion of the
438 while statement and the body of the while statement, respectively. */
d7e7759d
BC
439#define WHILE_COND(NODE) TREE_OPERAND (WHILE_STMT_CHECK (NODE), 0)
440#define WHILE_BODY(NODE) TREE_OPERAND (WHILE_STMT_CHECK (NODE), 1)
35b1567d
BC
441
442/* DO_STMT accessors. These give access to the condition of the do
443 statement and the body of the do statement, respectively. */
d7e7759d
BC
444#define DO_COND(NODE) TREE_OPERAND (DO_STMT_CHECK (NODE), 0)
445#define DO_BODY(NODE) TREE_OPERAND (DO_STMT_CHECK (NODE), 1)
35b1567d
BC
446
447/* RETURN_STMT accessor. This gives the expression associated with a
448 return statement. */
d7e7759d 449#define RETURN_EXPR(NODE) TREE_OPERAND (RETURN_STMT_CHECK (NODE), 0)
35b1567d
BC
450
451/* EXPR_STMT accessor. This gives the expression associated with an
452 expression statement. */
d7e7759d 453#define EXPR_STMT_EXPR(NODE) TREE_OPERAND (EXPR_STMT_CHECK (NODE), 0)
35b1567d
BC
454
455/* FOR_STMT accessors. These give access to the init statement,
456 condition, update expression, and body of the for statement,
457 respectively. */
d7e7759d
BC
458#define FOR_INIT_STMT(NODE) TREE_OPERAND (FOR_STMT_CHECK (NODE), 0)
459#define FOR_COND(NODE) TREE_OPERAND (FOR_STMT_CHECK (NODE), 1)
460#define FOR_EXPR(NODE) TREE_OPERAND (FOR_STMT_CHECK (NODE), 2)
461#define FOR_BODY(NODE) TREE_OPERAND (FOR_STMT_CHECK (NODE), 3)
35b1567d
BC
462
463/* SWITCH_STMT accessors. These give access to the condition and body
464 of the switch statement, respectively. */
d7e7759d
BC
465#define SWITCH_COND(NODE) TREE_OPERAND (SWITCH_STMT_CHECK (NODE), 0)
466#define SWITCH_BODY(NODE) TREE_OPERAND (SWITCH_STMT_CHECK (NODE), 1)
35b1567d
BC
467
468/* CASE_LABEL accessors. These give access to the high and low values
469 of a case label, respectively. */
d7e7759d
BC
470#define CASE_LOW(NODE) TREE_OPERAND (CASE_LABEL_CHECK (NODE), 0)
471#define CASE_HIGH(NODE) TREE_OPERAND (CASE_LABEL_CHECK (NODE), 1)
56cb9733 472#define CASE_LABEL_DECL(NODE) TREE_OPERAND (CASE_LABEL_CHECK (NODE), 2)
35b1567d
BC
473
474/* GOTO_STMT accessor. This gives access to the label associated with
475 a goto statement. */
d7e7759d 476#define GOTO_DESTINATION(NODE) TREE_OPERAND (GOTO_STMT_CHECK (NODE), 0)
35b1567d
BC
477
478/* COMPOUND_STMT accessor. This gives access to the TREE_LIST of
479 statements assocated with a compound statement. The result is the
480 first statement in the list. Succeeding nodes can be acccessed by
481 calling TREE_CHAIN on a node in the list. */
d7e7759d 482#define COMPOUND_BODY(NODE) TREE_OPERAND (COMPOUND_STMT_CHECK (NODE), 0)
35b1567d
BC
483
484/* ASM_STMT accessors. ASM_STRING returns a STRING_CST for the
485 instruction (e.g., "mov x, y"). ASM_OUTPUTS, ASM_INPUTS, and
486 ASM_CLOBBERS represent the outputs, inputs, and clobbers for the
487 statement. */
d7e7759d
BC
488#define ASM_CV_QUAL(NODE) TREE_OPERAND (ASM_STMT_CHECK (NODE), 0)
489#define ASM_STRING(NODE) TREE_OPERAND (ASM_STMT_CHECK (NODE), 1)
490#define ASM_OUTPUTS(NODE) TREE_OPERAND (ASM_STMT_CHECK (NODE), 2)
491#define ASM_INPUTS(NODE) TREE_OPERAND (ASM_STMT_CHECK (NODE), 3)
492#define ASM_CLOBBERS(NODE) TREE_OPERAND (ASM_STMT_CHECK (NODE), 4)
35b1567d
BC
493
494/* DECL_STMT accessor. This gives access to the DECL associated with
495 the given declaration statement. */
d7e7759d 496#define DECL_STMT_DECL(NODE) TREE_OPERAND (DECL_STMT_CHECK (NODE), 0)
35b1567d
BC
497
498/* STMT_EXPR accessor. */
d7e7759d 499#define STMT_EXPR_STMT(NODE) TREE_OPERAND (STMT_EXPR_CHECK (NODE), 0)
35b1567d
BC
500
501/* LABEL_STMT accessor. This gives access to the label associated with
502 the given label statement. */
d7e7759d
BC
503#define LABEL_STMT_LABEL(NODE) TREE_OPERAND (LABEL_STMT_CHECK (NODE), 0)
504
505/* Nonzero if this SCOPE_STMT is for the beginning of a scope. */
506#define SCOPE_BEGIN_P(NODE) \
507 (TREE_LANG_FLAG_0 (SCOPE_STMT_CHECK (NODE)))
508
509/* Nonzero if this SCOPE_STMT is for the end of a scope. */
510#define SCOPE_END_P(NODE) \
511 (!SCOPE_BEGIN_P (SCOPE_STMT_CHECK (NODE)))
512
513/* The BLOCK containing the declarations contained in this scope. */
514#define SCOPE_STMT_BLOCK(NODE) \
515 (TREE_OPERAND (SCOPE_STMT_CHECK (NODE), 0))
516
517/* Nonzero for a SCOPE_STMT if there were no variables in this scope. */
518#define SCOPE_NULLIFIED_P(NODE) \
519 (SCOPE_STMT_BLOCK ((NODE)) == NULL_TREE)
520
521/* Nonzero for a SCOPE_STMT which represents a lexical scope, but
522 which should be treated as non-existant from the point of view of
523 running cleanup actions. */
524#define SCOPE_NO_CLEANUPS_P(NODE) \
525 (TREE_LANG_FLAG_3 (SCOPE_STMT_CHECK (NODE)))
526
527/* Nonzero for a SCOPE_STMT if this statement is for a partial scope.
528 For example, in:
529
530 S s;
531 l:
532 S s2;
533 goto l;
534
535 there is (implicitly) a new scope after `l', even though there are
536 no curly braces. In particular, when we hit the goto, we must
537 destroy s2 and then re-construct it. For the implicit scope,
538 SCOPE_PARTIAL_P will be set. */
539#define SCOPE_PARTIAL_P(NODE) \
540 (TREE_LANG_FLAG_4 (SCOPE_STMT_CHECK (NODE)))
541
542/* Nonzero for an ASM_STMT if the assembly statement is volatile. */
543#define ASM_VOLATILE_P(NODE) \
544 (ASM_CV_QUAL (ASM_STMT_CHECK (NODE)) != NULL_TREE)
545
546/* The line-number at which a statement began. But if
547 STMT_LINENO_FOR_FN_P does holds, then this macro gives the
548 line number for the end of the current function instead. */
549#define STMT_LINENO(NODE) \
550 (TREE_COMPLEXITY ((NODE)))
551
552/* If non-zero, the STMT_LINENO for NODE is the line at which the
553 function ended. */
554#define STMT_LINENO_FOR_FN_P(NODE) \
555 (TREE_LANG_FLAG_2 ((NODE)))
c7d87c0a 556
f2c5f623
BC
557/* Nonzero if we want the new ISO rules for pushing a new scope for `for'
558 initialization variables. */
559#define NEW_FOR_SCOPE_P(NODE) (TREE_LANG_FLAG_0 (NODE))
c7d87c0a
BC
560
561#define DEFTREECODE(SYM, NAME, TYPE, LENGTH) SYM,
562
563enum c_tree_code {
564 C_DUMMY_TREE_CODE = LAST_AND_UNUSED_TREE_CODE,
565#include "c-common.def"
566 LAST_C_TREE_CODE
567};
568
569#undef DEFTREECODE
570
571extern void add_c_tree_codes PARAMS ((void));
f2c5f623 572extern void genrtl_do_pushlevel PARAMS ((void));
f2c5f623
BC
573extern void genrtl_goto_stmt PARAMS ((tree));
574extern void genrtl_expr_stmt PARAMS ((tree));
575extern void genrtl_decl_stmt PARAMS ((tree));
576extern void genrtl_if_stmt PARAMS ((tree));
577extern void genrtl_while_stmt PARAMS ((tree));
578extern void genrtl_do_stmt PARAMS ((tree));
579extern void genrtl_return_stmt PARAMS ((tree));
580extern void genrtl_for_stmt PARAMS ((tree));
581extern void genrtl_break_stmt PARAMS ((void));
582extern void genrtl_continue_stmt PARAMS ((void));
583extern void genrtl_scope_stmt PARAMS ((tree));
584extern void genrtl_switch_stmt PARAMS ((tree));
56cb9733 585extern void genrtl_case_label PARAMS ((tree));
4cf88f57 586extern void genrtl_compound_stmt PARAMS ((tree));
f2c5f623
BC
587extern void genrtl_asm_stmt PARAMS ((tree, tree,
588 tree, tree,
589 tree));
590extern void genrtl_decl_cleanup PARAMS ((tree, tree));
591extern int stmts_are_full_exprs_p PARAMS ((void));
592typedef void (*expand_expr_stmt_fn) PARAMS ((tree));
593extern expand_expr_stmt_fn lang_expand_expr_stmt;
594extern int anon_aggr_type_p PARAMS ((tree));
595
596/* For a VAR_DECL that is an anonymous union, these are the various
597 sub-variables that make up the anonymous union. */
598#define DECL_ANON_UNION_ELEMS(NODE) DECL_ARGUMENTS ((NODE))
599
600extern void emit_local_var PARAMS ((tree));
601extern void make_rtl_for_local_static PARAMS ((tree));
602extern tree expand_cond PARAMS ((tree));
f2c5f623 603extern void c_expand_return PARAMS ((tree));
f2c5f623 604extern void do_case PARAMS ((tree, tree));
0dfdeca6 605extern tree build_stmt PARAMS ((enum tree_code, ...));
56cb9733 606extern tree build_case_label PARAMS ((tree, tree, tree));
0dfdeca6
BC
607extern tree build_continue_stmt PARAMS ((void));
608extern tree build_break_stmt PARAMS ((void));
609extern tree build_return_stmt PARAMS ((tree));
f2c5f623
BC
610
611#define COMPOUND_STMT_NO_SCOPE(NODE) TREE_LANG_FLAG_0 (NODE)
612
613extern void c_expand_asm_operands PARAMS ((tree, tree, tree, tree, int, const char *, int));
614extern int current_function_name_declared PARAMS ((void));
615extern void set_current_function_name_declared PARAMS ((int));
ab76ca54
MM
616
617/* These functions must be defined by each front-end which implements
618 a variant of the C language. They are used in c-common.c. */
619
620extern tree build_unary_op PARAMS ((enum tree_code,
621 tree, int));
622extern tree build_binary_op PARAMS ((enum tree_code,
623 tree, tree, int));
624extern int lvalue_p PARAMS ((tree));
625extern tree default_conversion PARAMS ((tree));
626
627/* Given two integer or real types, return the type for their sum.
628 Given two compatible ANSI C types, returns the merged type. */
629
630extern tree common_type PARAMS ((tree, tree));
44835fdd
MM
631
632extern tree expand_tree_builtin PARAMS ((tree, tree, tree));
0e5921e8 633
56cb9733
MM
634extern tree decl_constant_value PARAMS ((tree));
635
0e5921e8
ZW
636/* Hook currently used only by the C++ front end to reset internal state
637 after entering or leaving a header file. */
638extern void extract_interface_info PARAMS ((void));
639
640/* Information recorded about each file examined during compilation. */
641
642struct c_fileinfo
643{
644 int time; /* Time spent in the file. */
645 short interface_only; /* Flags - used only by C++ */
646 short interface_unknown;
647};
648
649struct c_fileinfo *get_fileinfo PARAMS ((const char *));
650extern void dump_time_statistics PARAMS ((void));
651
652#endif
This page took 0.28496 seconds and 5 git commands to generate.