118334Speter/* Definitions for C parsing and type checking.
290083Sobrien   Copyright (C) 1987, 1993, 1994, 1995, 1997, 1998,
3169699Skan   1999, 2000, 2001, 2002, 2003, 2004, 2005 Free Software Foundation, Inc.
418334Speter
590083SobrienThis file is part of GCC.
618334Speter
790083SobrienGCC is free software; you can redistribute it and/or modify it under
890083Sobrienthe terms of the GNU General Public License as published by the Free
990083SobrienSoftware Foundation; either version 2, or (at your option) any later
1090083Sobrienversion.
1118334Speter
1290083SobrienGCC is distributed in the hope that it will be useful, but WITHOUT ANY
1390083SobrienWARRANTY; without even the implied warranty of MERCHANTABILITY or
1490083SobrienFITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
1590083Sobrienfor more details.
1618334Speter
1718334SpeterYou should have received a copy of the GNU General Public License
1890083Sobrienalong with GCC; see the file COPYING.  If not, write to the Free
19169699SkanSoftware Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
20169699Skan02110-1301, USA.  */
2118334Speter
2290083Sobrien#ifndef GCC_C_TREE_H
2390083Sobrien#define GCC_C_TREE_H
2418334Speter
2590083Sobrien#include "c-common.h"
26169699Skan#include "toplev.h"
27169699Skan#include "diagnostic.h"
2890083Sobrien
29169699Skan/* struct lang_identifier is private to c-decl.c, but langhooks.c needs to
30169699Skan   know how big it is.  This is sanity-checked in c-decl.c.  */
31169699Skan#define C_SIZEOF_STRUCT_LANG_IDENTIFIER \
32169699Skan  (sizeof (struct c_common_identifier) + 3 * sizeof (void *))
3318334Speter
3490083Sobrien/* Language-specific declaration information.  */
3590083Sobrien
36117404Skanstruct lang_decl GTY(())
3790083Sobrien{
38169699Skan  char dummy;
3990083Sobrien};
4090083Sobrien
4118334Speter/* In a RECORD_TYPE or UNION_TYPE, nonzero if any component is read-only.  */
4290083Sobrien#define C_TYPE_FIELDS_READONLY(TYPE) TREE_LANG_FLAG_1 (TYPE)
4318334Speter
4418334Speter/* In a RECORD_TYPE or UNION_TYPE, nonzero if any component is volatile.  */
4590083Sobrien#define C_TYPE_FIELDS_VOLATILE(TYPE) TREE_LANG_FLAG_2 (TYPE)
4618334Speter
4718334Speter/* In a RECORD_TYPE or UNION_TYPE or ENUMERAL_TYPE
4818334Speter   nonzero if the definition of the type has already started.  */
4990083Sobrien#define C_TYPE_BEING_DEFINED(TYPE) TYPE_LANG_FLAG_0 (TYPE)
5018334Speter
51132727Skan/* In an incomplete RECORD_TYPE or UNION_TYPE, a list of variable
52132727Skan   declarations whose type would be completed by completing that type.  */
53132727Skan#define C_TYPE_INCOMPLETE_VARS(TYPE) TYPE_VFIELD (TYPE)
54132727Skan
5590083Sobrien/* In an IDENTIFIER_NODE, nonzero if this identifier is actually a
5690083Sobrien   keyword.  C_RID_CODE (node) is then the RID_* value of the keyword,
5790083Sobrien   and C_RID_YYCODE is the token number wanted by Yacc.  */
5890083Sobrien#define C_IS_RESERVED_WORD(ID) TREE_LANG_FLAG_0 (ID)
5952300Sobrien
60117404Skanstruct lang_type GTY(())
6118334Speter{
62169699Skan  /* In a RECORD_TYPE, a sorted array of the fields of the type.  */
63132727Skan  struct sorted_fields_type * GTY ((reorder ("resort_sorted_fields"))) s;
64169699Skan  /* In an ENUMERAL_TYPE, the min and max values.  */
65169699Skan  tree enum_min;
66169699Skan  tree enum_max;
67169699Skan  /* In a RECORD_TYPE, information specific to Objective-C, such
68169699Skan     as a list of adopted protocols or a pointer to a corresponding
69169699Skan     @interface.  See objc/objc-act.h for details.  */
70169699Skan  tree objc_info;
7118334Speter};
7218334Speter
7318334Speter/* Record whether a type or decl was written with nonconstant size.
7418334Speter   Note that TYPE_SIZE may have simplified to a constant.  */
7590083Sobrien#define C_TYPE_VARIABLE_SIZE(TYPE) TYPE_LANG_FLAG_1 (TYPE)
7690083Sobrien#define C_DECL_VARIABLE_SIZE(TYPE) DECL_LANG_FLAG_0 (TYPE)
7718334Speter
7818334Speter/* Record whether a typedef for type `int' was actually `signed int'.  */
7990083Sobrien#define C_TYPEDEF_EXPLICITLY_SIGNED(EXP) DECL_LANG_FLAG_1 (EXP)
8018334Speter
8196276Sobrien/* For a FUNCTION_DECL, nonzero if it was defined without an explicit
8296276Sobrien   return type.  */
8396276Sobrien#define C_FUNCTION_IMPLICIT_INT(EXP) DECL_LANG_FLAG_1 (EXP)
8496276Sobrien
85132727Skan/* For a FUNCTION_DECL, nonzero if it was an implicit declaration.  */
86132727Skan#define C_DECL_IMPLICIT(EXP) DECL_LANG_FLAG_2 (EXP)
8718334Speter
88169699Skan/* For FUNCTION_DECLs, evaluates true if the decl is built-in but has
89169699Skan   been declared.  */
90169699Skan#define C_DECL_DECLARED_BUILTIN(EXP)		\
91169699Skan  DECL_LANG_FLAG_3 (FUNCTION_DECL_CHECK (EXP))
92132727Skan
93169699Skan/* For FUNCTION_DECLs, evaluates true if the decl is built-in, has a
94169699Skan   built-in prototype and does not have a non-built-in prototype.  */
95169699Skan#define C_DECL_BUILTIN_PROTOTYPE(EXP)		\
96169699Skan  DECL_LANG_FLAG_6 (FUNCTION_DECL_CHECK (EXP))
97169699Skan
98169699Skan/* Record whether a decl was declared register.  This is strictly a
99169699Skan   front-end flag, whereas DECL_REGISTER is used for code generation;
100169699Skan   they may differ for structures with volatile fields.  */
101169699Skan#define C_DECL_REGISTER(EXP) DECL_LANG_FLAG_4 (EXP)
102169699Skan
103169699Skan/* Record whether a decl was used in an expression anywhere except an
104169699Skan   unevaluated operand of sizeof / typeof / alignof.  This is only
105169699Skan   used for functions declared static but not defined, though outside
106169699Skan   sizeof and typeof it is set for other function decls as well.  */
107169699Skan#define C_DECL_USED(EXP) DECL_LANG_FLAG_5 (FUNCTION_DECL_CHECK (EXP))
108169699Skan
109169699Skan/* Record whether a label was defined in a statement expression which
110169699Skan   has finished and so can no longer be jumped to.  */
111169699Skan#define C_DECL_UNJUMPABLE_STMT_EXPR(EXP)	\
112169699Skan  DECL_LANG_FLAG_6 (LABEL_DECL_CHECK (EXP))
113169699Skan
114169699Skan/* Record whether a label was the subject of a goto from outside the
115169699Skan   current level of statement expression nesting and so cannot be
116169699Skan   defined right now.  */
117169699Skan#define C_DECL_UNDEFINABLE_STMT_EXPR(EXP)	\
118169699Skan  DECL_LANG_FLAG_7 (LABEL_DECL_CHECK (EXP))
119169699Skan
120169699Skan/* Record whether a label was defined in the scope of an identifier
121169699Skan   with variably modified type which has finished and so can no longer
122169699Skan   be jumped to.  */
123169699Skan#define C_DECL_UNJUMPABLE_VM(EXP)	\
124169699Skan  DECL_LANG_FLAG_3 (LABEL_DECL_CHECK (EXP))
125169699Skan
126169699Skan/* Record whether a label was the subject of a goto from outside the
127169699Skan   current level of scopes of identifiers with variably modified type
128169699Skan   and so cannot be defined right now.  */
129169699Skan#define C_DECL_UNDEFINABLE_VM(EXP)	\
130169699Skan  DECL_LANG_FLAG_5 (LABEL_DECL_CHECK (EXP))
131169699Skan
132169699Skan/* Record whether a variable has been declared threadprivate by
133169699Skan   #pragma omp threadprivate.  */
134169699Skan#define C_DECL_THREADPRIVATE_P(DECL) DECL_LANG_FLAG_3 (VAR_DECL_CHECK (DECL))
135169699Skan
136132727Skan/* Nonzero for a decl which either doesn't exist or isn't a prototype.
137132727Skan   N.B. Could be simplified if all built-in decls had complete prototypes
138132727Skan   (but this is presently difficult because some of them need FILE*).  */
139132727Skan#define C_DECL_ISNT_PROTOTYPE(EXP)			\
140132727Skan       (EXP == 0					\
141132727Skan	|| (TYPE_ARG_TYPES (TREE_TYPE (EXP)) == 0	\
142132727Skan	    && !DECL_BUILT_IN (EXP)))
143132727Skan
14418334Speter/* For FUNCTION_TYPE, a hidden list of types of arguments.  The same as
14518334Speter   TYPE_ARG_TYPES for functions with prototypes, but created for functions
14618334Speter   without prototypes.  */
147169699Skan#define TYPE_ACTUAL_ARG_TYPES(NODE) TYPE_LANG_SLOT_1 (NODE)
14818334Speter
149169699Skan/* Record parser information about an expression that is irrelevant
150169699Skan   for code generation alongside a tree representing its value.  */
151169699Skanstruct c_expr
152169699Skan{
153169699Skan  /* The value of the expression.  */
154169699Skan  tree value;
155169699Skan  /* Record the original binary operator of an expression, which may
156169699Skan     have been changed by fold, STRING_CST for unparenthesized string
157169699Skan     constants, or ERROR_MARK for other expressions (including
158169699Skan     parenthesized expressions).  */
159169699Skan  enum tree_code original_code;
160169699Skan};
16190083Sobrien
162169699Skan/* A kind of type specifier.  Note that this information is currently
163169699Skan   only used to distinguish tag definitions, tag references and typeof
164169699Skan   uses.  */
165169699Skanenum c_typespec_kind {
166169699Skan  /* A reserved keyword type specifier.  */
167169699Skan  ctsk_resword,
168169699Skan  /* A reference to a tag, previously declared, such as "struct foo".
169169699Skan     This includes where the previous declaration was as a different
170169699Skan     kind of tag, in which case this is only valid if shadowing that
171169699Skan     tag in an inner scope.  */
172169699Skan  ctsk_tagref,
173169699Skan  /* A reference to a tag, not previously declared in a visible
174169699Skan     scope.  */
175169699Skan  ctsk_tagfirstref,
176169699Skan  /* A definition of a tag such as "struct foo { int a; }".  */
177169699Skan  ctsk_tagdef,
178169699Skan  /* A typedef name.  */
179169699Skan  ctsk_typedef,
180169699Skan  /* An ObjC-specific kind of type specifier.  */
181169699Skan  ctsk_objc,
182169699Skan  /* A typeof specifier.  */
183169699Skan  ctsk_typeof
184169699Skan};
185169699Skan
186169699Skan/* A type specifier: this structure is created in the parser and
187169699Skan   passed to declspecs_add_type only.  */
188169699Skanstruct c_typespec {
189169699Skan  /* What kind of type specifier this is.  */
190169699Skan  enum c_typespec_kind kind;
191169699Skan  /* The specifier itself.  */
192169699Skan  tree spec;
193169699Skan};
194169699Skan
195169699Skan/* A storage class specifier.  */
196169699Skanenum c_storage_class {
197169699Skan  csc_none,
198169699Skan  csc_auto,
199169699Skan  csc_extern,
200169699Skan  csc_register,
201169699Skan  csc_static,
202169699Skan  csc_typedef
203169699Skan};
204169699Skan
205169699Skan/* A type specifier keyword "void", "_Bool", "char", "int", "float",
206169699Skan   "double", or none of these.  */
207169699Skanenum c_typespec_keyword {
208169699Skan  cts_none,
209169699Skan  cts_void,
210169699Skan  cts_bool,
211169699Skan  cts_char,
212169699Skan  cts_int,
213169699Skan  cts_float,
214169699Skan  cts_double,
215169699Skan  cts_dfloat32,
216169699Skan  cts_dfloat64,
217169699Skan  cts_dfloat128
218169699Skan};
219169699Skan
220169699Skan/* A sequence of declaration specifiers in C.  */
221169699Skanstruct c_declspecs {
222169699Skan  /* The type specified, if a single type specifier such as a struct,
223169699Skan     union or enum specifier, typedef name or typeof specifies the
224169699Skan     whole type, or NULL_TREE if none or a keyword such as "void" or
225169699Skan     "char" is used.  Does not include qualifiers.  */
226169699Skan  tree type;
227169699Skan  /* The attributes from a typedef decl.  */
228169699Skan  tree decl_attr;
229169699Skan  /* When parsing, the attributes.  Outside the parser, this will be
230169699Skan     NULL; attributes (possibly from multiple lists) will be passed
231169699Skan     separately.  */
232169699Skan  tree attrs;
233169699Skan  /* Any type specifier keyword used such as "int", not reflecting
234169699Skan     modifiers such as "short", or cts_none if none.  */
235169699Skan  enum c_typespec_keyword typespec_word;
236169699Skan  /* The storage class specifier, or csc_none if none.  */
237169699Skan  enum c_storage_class storage_class;
238169699Skan  /* Whether any declaration specifiers have been seen at all.  */
239169699Skan  BOOL_BITFIELD declspecs_seen_p : 1;
240169699Skan  /* Whether a type specifier has been seen.  */
241169699Skan  BOOL_BITFIELD type_seen_p : 1;
242169699Skan  /* Whether something other than a storage class specifier or
243169699Skan     attribute has been seen.  This is used to warn for the
244169699Skan     obsolescent usage of storage class specifiers other than at the
245169699Skan     start of the list.  (Doing this properly would require function
246169699Skan     specifiers to be handled separately from storage class
247169699Skan     specifiers.)  */
248169699Skan  BOOL_BITFIELD non_sc_seen_p : 1;
249169699Skan  /* Whether the type is specified by a typedef or typeof name.  */
250169699Skan  BOOL_BITFIELD typedef_p : 1;
251169699Skan  /* Whether a struct, union or enum type either had its content
252169699Skan     defined by a type specifier in the list or was the first visible
253169699Skan     declaration of its tag.  */
254169699Skan  BOOL_BITFIELD tag_defined_p : 1;
255169699Skan  /* Whether the type is explicitly "signed" or specified by a typedef
256169699Skan     whose type is explicitly "signed".  */
257169699Skan  BOOL_BITFIELD explicit_signed_p : 1;
258169699Skan  /* Whether the specifiers include a deprecated typedef.  */
259169699Skan  BOOL_BITFIELD deprecated_p : 1;
260260918Spfg  /* APPLE LOCAL begin "unavailable" attribute (radar 2809697) */
261260918Spfg  /* Whether the specifiers include a unavailable typedef.  */
262260918Spfg  BOOL_BITFIELD unavailable_p : 1;
263260918Spfg  /* APPLE LOCAL end "unavailable" attribute (radar 2809697) */
264169699Skan  /* Whether the type defaulted to "int" because there were no type
265169699Skan     specifiers.  */
266169699Skan  BOOL_BITFIELD default_int_p;
267169699Skan  /* Whether "long" was specified.  */
268169699Skan  BOOL_BITFIELD long_p : 1;
269169699Skan  /* Whether "long" was specified more than once.  */
270169699Skan  BOOL_BITFIELD long_long_p : 1;
271169699Skan  /* Whether "short" was specified.  */
272169699Skan  BOOL_BITFIELD short_p : 1;
273169699Skan  /* Whether "signed" was specified.  */
274169699Skan  BOOL_BITFIELD signed_p : 1;
275169699Skan  /* Whether "unsigned" was specified.  */
276169699Skan  BOOL_BITFIELD unsigned_p : 1;
277169699Skan  /* Whether "complex" was specified.  */
278169699Skan  BOOL_BITFIELD complex_p : 1;
279169699Skan  /* Whether "inline" was specified.  */
280169699Skan  BOOL_BITFIELD inline_p : 1;
281169699Skan  /* Whether "__thread" was specified.  */
282169699Skan  BOOL_BITFIELD thread_p : 1;
283169699Skan  /* Whether "const" was specified.  */
284169699Skan  BOOL_BITFIELD const_p : 1;
285169699Skan  /* Whether "volatile" was specified.  */
286169699Skan  BOOL_BITFIELD volatile_p : 1;
287169699Skan  /* Whether "restrict" was specified.  */
288169699Skan  BOOL_BITFIELD restrict_p : 1;
289169699Skan};
290169699Skan
291169699Skan/* The various kinds of declarators in C.  */
292169699Skanenum c_declarator_kind {
293169699Skan  /* An identifier.  */
294169699Skan  cdk_id,
295169699Skan  /* A function.  */
296169699Skan  cdk_function,
297169699Skan  /* An array.  */
298169699Skan  cdk_array,
299169699Skan  /* A pointer.  */
300169699Skan  cdk_pointer,
301261188Spfg  /* APPLE LOCAL blocks (C++ ch) */
302261188Spfg  cdk_block_pointer,
303169699Skan  /* Parenthesized declarator with nested attributes.  */
304169699Skan  cdk_attrs
305169699Skan};
306169699Skan
307169699Skan/* Information about the parameters in a function declarator.  */
308169699Skanstruct c_arg_info {
309169699Skan  /* A list of parameter decls.  */
310169699Skan  tree parms;
311169699Skan  /* A list of structure, union and enum tags defined.  */
312169699Skan  tree tags;
313169699Skan  /* A list of argument types to go in the FUNCTION_TYPE.  */
314169699Skan  tree types;
315169699Skan  /* A list of non-parameter decls (notably enumeration constants)
316169699Skan     defined with the parameters.  */
317169699Skan  tree others;
318169699Skan  /* A list of VLA sizes from the parameters.  In a function
319169699Skan     definition, these are used to ensure that side-effects in sizes
320169699Skan     of arrays converted to pointers (such as a parameter int i[n++])
321169699Skan     take place; otherwise, they are ignored.  */
322169699Skan  tree pending_sizes;
323169699Skan  /* True when these arguments had [*].  */
324169699Skan  BOOL_BITFIELD had_vla_unspec : 1;
325169699Skan};
326169699Skan
327169699Skan/* A declarator.  */
328169699Skanstruct c_declarator {
329169699Skan  /* The kind of declarator.  */
330169699Skan  enum c_declarator_kind kind;
331169699Skan  /* Except for cdk_id, the contained declarator.  For cdk_id, NULL.  */
332169699Skan  struct c_declarator *declarator;
333169699Skan  location_t id_loc; /* Currently only set for cdk_id. */
334169699Skan  union {
335169699Skan    /* For identifiers, an IDENTIFIER_NODE or NULL_TREE if an abstract
336169699Skan       declarator.  */
337169699Skan    tree id;
338169699Skan    /* For functions.  */
339169699Skan    struct c_arg_info *arg_info;
340169699Skan    /* For arrays.  */
341169699Skan    struct {
342169699Skan      /* The array dimension, or NULL for [] and [*].  */
343169699Skan      tree dimen;
344169699Skan      /* The qualifiers inside [].  */
345169699Skan      int quals;
346169699Skan      /* The attributes (currently ignored) inside [].  */
347169699Skan      tree attrs;
348169699Skan      /* Whether [static] was used.  */
349169699Skan      BOOL_BITFIELD static_p : 1;
350169699Skan      /* Whether [*] was used.  */
351169699Skan      BOOL_BITFIELD vla_unspec_p : 1;
352169699Skan    } array;
353169699Skan    /* For pointers, the qualifiers on the pointer type.  */
354169699Skan    int pointer_quals;
355169699Skan    /* For attributes.  */
356169699Skan    tree attrs;
357169699Skan  } u;
358169699Skan};
359169699Skan
360169699Skan/* A type name.  */
361169699Skanstruct c_type_name {
362169699Skan  /* The declaration specifiers.  */
363169699Skan  struct c_declspecs *specs;
364169699Skan  /* The declarator.  */
365169699Skan  struct c_declarator *declarator;
366169699Skan};
367169699Skan
368169699Skan/* A parameter.  */
369169699Skanstruct c_parm {
370169699Skan  /* The declaration specifiers, minus any prefix attributes.  */
371169699Skan  struct c_declspecs *specs;
372169699Skan  /* The attributes.  */
373169699Skan  tree attrs;
374169699Skan  /* The declarator.  */
375169699Skan  struct c_declarator *declarator;
376169699Skan};
377169699Skan
378132727Skan/* Save and restore the variables in this file and elsewhere
379132727Skan   that keep track of the progress of compilation of the current function.
380132727Skan   Used for nested functions.  */
381132727Skan
382132727Skanstruct language_function GTY(())
383132727Skan{
384132727Skan  struct c_language_function base;
385169699Skan  tree x_break_label;
386169699Skan  tree x_cont_label;
387169699Skan  struct c_switch * GTY((skip)) x_switch_stack;
388169699Skan  struct c_arg_info * GTY((skip)) arg_info;
389132727Skan  int returns_value;
390132727Skan  int returns_null;
391132727Skan  int returns_abnormally;
392132727Skan  int warn_about_return_type;
393132727Skan};
394132727Skan
395169699Skan/* Save lists of labels used or defined in particular contexts.
396169699Skan   Allocated on the parser obstack.  */
397169699Skan
398169699Skanstruct c_label_list
399169699Skan{
400169699Skan  /* The label at the head of the list.  */
401169699Skan  tree label;
402169699Skan  /* The rest of the list.  */
403169699Skan  struct c_label_list *next;
404169699Skan};
405169699Skan
406169699Skan/* Statement expression context.  */
407169699Skan
408169699Skanstruct c_label_context_se
409169699Skan{
410169699Skan  /* The labels defined at this level of nesting.  */
411169699Skan  struct c_label_list *labels_def;
412169699Skan  /* The labels used at this level of nesting.  */
413169699Skan  struct c_label_list *labels_used;
414169699Skan  /* The next outermost context.  */
415169699Skan  struct c_label_context_se *next;
416169699Skan};
417169699Skan
418169699Skan/* Context of variably modified declarations.  */
419169699Skan
420169699Skanstruct c_label_context_vm
421169699Skan{
422169699Skan  /* The labels defined at this level of nesting.  */
423169699Skan  struct c_label_list *labels_def;
424169699Skan  /* The labels used at this level of nesting.  */
425169699Skan  struct c_label_list *labels_used;
426169699Skan  /* The scope of this context.  Multiple contexts may be at the same
427169699Skan     numbered scope, since each variably modified declaration starts a
428169699Skan     new context.  */
429169699Skan  unsigned scope;
430169699Skan  /* The next outermost context.  */
431169699Skan  struct c_label_context_vm *next;
432169699Skan};
433169699Skan
43418334Speter
435169699Skan/* in c-parser.c */
436132727Skanextern void c_parse_init (void);
43790083Sobrien
43818334Speter/* in c-aux-info.c */
439132727Skanextern void gen_aux_info_record (tree, int, int, int);
44018334Speter
44190083Sobrien/* in c-decl.c */
442169699Skanextern struct obstack parser_obstack;
443169699Skanextern tree c_break_label;
444169699Skanextern tree c_cont_label;
445117404Skan
446132727Skanextern int global_bindings_p (void);
447169699Skanextern void push_scope (void);
448169699Skanextern tree pop_scope (void);
449132727Skanextern void insert_block (tree);
450132727Skanextern void c_expand_body (tree);
45150453Sobrien
452132727Skanextern void c_init_decl_processing (void);
453132727Skanextern void c_dup_lang_specific_decl (tree);
454132727Skanextern void c_print_identifier (FILE *, tree, int);
455169699Skanextern int quals_from_declspecs (const struct c_declspecs *);
456169699Skanextern struct c_declarator *build_array_declarator (tree, struct c_declspecs *,
457169699Skan						    bool, bool);
458132727Skanextern tree build_enumerator (tree, tree);
459169699Skanextern tree check_for_loop_decls (void);
460132727Skanextern void mark_forward_parm_decls (void);
461132727Skanextern void declare_parm_level (void);
462169699Skanextern void undeclared_variable (tree, location_t);
463132727Skanextern tree declare_label (tree);
464132727Skanextern tree define_label (location_t, tree);
465169699Skanextern void c_maybe_initialize_eh (void);
466132727Skanextern void finish_decl (tree, tree, tree);
467132727Skanextern tree finish_enum (tree, tree, tree);
468132727Skanextern void finish_function (void);
469132727Skanextern tree finish_struct (tree, tree, tree);
470169699Skanextern struct c_arg_info *get_parm_info (bool);
471169699Skanextern tree grokfield (struct c_declarator *, struct c_declspecs *, tree);
472169699Skanextern tree groktypename (struct c_type_name *);
473261188Spfg/* APPLE LOCAL blocks 6339747 */
474261188Spfgextern tree grokblockdecl (struct c_declspecs *, struct c_declarator *);
475169699Skanextern tree grokparm (const struct c_parm *);
476132727Skanextern tree implicitly_declare (tree);
477132727Skanextern void keep_next_level (void);
478132727Skanextern void pending_xref_error (void);
479132727Skanextern void c_push_function_context (struct function *);
480132727Skanextern void c_pop_function_context (struct function *);
481169699Skanextern void push_parm_decl (const struct c_parm *);
482169699Skanextern struct c_declarator *set_array_declarator_inner (struct c_declarator *,
483169699Skan							struct c_declarator *,
484169699Skan							bool);
485169699Skanextern tree builtin_function (const char *, tree, int, enum built_in_class,
486169699Skan			      const char *, tree);
487169699Skanextern void shadow_tag (const struct c_declspecs *);
488169699Skanextern void shadow_tag_warned (const struct c_declspecs *, int);
489132727Skanextern tree start_enum (tree);
490169699Skanextern int  start_function (struct c_declspecs *, struct c_declarator *, tree);
491169699Skanextern tree start_decl (struct c_declarator *, struct c_declspecs *, bool,
492169699Skan			tree);
493132727Skanextern tree start_struct (enum tree_code, tree);
494132727Skanextern void store_parm_decls (void);
495169699Skanextern void store_parm_decls_from (struct c_arg_info *);
496132727Skanextern tree xref_tag (enum tree_code, tree);
497169699Skanextern struct c_typespec parser_xref_tag (enum tree_code, tree);
498169699Skanextern int c_expand_decl (tree);
499169699Skanextern struct c_parm *build_c_parm (struct c_declspecs *, tree,
500169699Skan				    struct c_declarator *);
501169699Skanextern struct c_declarator *build_attrs_declarator (tree,
502169699Skan						    struct c_declarator *);
503169699Skanextern struct c_declarator *build_function_declarator (struct c_arg_info *,
504169699Skan						       struct c_declarator *);
505169699Skanextern struct c_declarator *build_id_declarator (tree);
506169699Skanextern struct c_declarator *make_pointer_declarator (struct c_declspecs *,
507169699Skan						     struct c_declarator *);
508261188Spfg/* APPLE LOCAL begin radar 5814025 - blocks (C++ cg) */
509261188Spfgextern struct c_declarator *make_block_pointer_declarator (struct c_declspecs *,
510261188Spfg							   struct c_declarator *);
511261188Spfg/* APPLE LOCAL end radar 5814025 - blocks (C++ cg) */
512169699Skanextern struct c_declspecs *build_null_declspecs (void);
513169699Skanextern struct c_declspecs *declspecs_add_qual (struct c_declspecs *, tree);
514169699Skanextern struct c_declspecs *declspecs_add_type (struct c_declspecs *,
515169699Skan					       struct c_typespec);
516169699Skanextern struct c_declspecs *declspecs_add_scspec (struct c_declspecs *, tree);
517169699Skanextern struct c_declspecs *declspecs_add_attrs (struct c_declspecs *, tree);
518169699Skanextern struct c_declspecs *finish_declspecs (struct c_declspecs *);
519132727Skan
52090083Sobrien/* in c-objc-common.c */
521132727Skanextern int c_disregard_inline_limits (tree);
522132727Skanextern int c_cannot_inline_tree_fn (tree *);
523132727Skanextern bool c_objc_common_init (void);
524169699Skanextern bool c_missing_noreturn_ok_p (tree);
525169699Skanextern tree c_objc_common_truthvalue_conversion (tree expr);
526132727Skanextern bool c_warn_unused_global_decl (tree);
527169699Skanextern void c_initialize_diagnostics (diagnostic_context *);
528169699Skanextern bool c_vla_unspec_p (tree x, tree fn);
52918334Speter
53052300Sobrien#define c_build_type_variant(TYPE, CONST_P, VOLATILE_P)		  \
53190083Sobrien  c_build_qualified_type ((TYPE),				  \
53252300Sobrien			  ((CONST_P) ? TYPE_QUAL_CONST : 0) |	  \
53352300Sobrien			  ((VOLATILE_P) ? TYPE_QUAL_VOLATILE : 0))
53418334Speter
53518334Speter/* in c-typeck.c */
536169699Skanextern int in_alignof;
537169699Skanextern int in_sizeof;
538169699Skanextern int in_typeof;
53918334Speter
540169699Skanextern struct c_switch *c_switch_stack;
541169699Skanextern struct c_label_context_se *label_context_stack_se;
542169699Skanextern struct c_label_context_vm *label_context_stack_vm;
543132727Skan
544132727Skanextern tree require_complete_type (tree);
545169699Skanextern int same_translation_unit_p (tree, tree);
546169699Skanextern int comptypes (tree, tree);
547169699Skanextern bool c_vla_type_p (tree);
548132727Skanextern bool c_mark_addressable (tree);
549132727Skanextern void c_incomplete_type_error (tree, tree);
550132727Skanextern tree c_type_promotes_to (tree);
551169699Skanextern struct c_expr default_function_array_conversion (struct c_expr);
552169699Skanextern tree composite_type (tree, tree);
553132727Skanextern tree build_component_ref (tree, tree);
554132727Skanextern tree build_array_ref (tree, tree);
555169699Skanextern tree build_external_ref (tree, int, location_t);
556169699Skanextern void pop_maybe_used (bool);
557169699Skanextern struct c_expr c_expr_sizeof_expr (struct c_expr);
558169699Skanextern struct c_expr c_expr_sizeof_type (struct c_type_name *);
559169699Skanextern struct c_expr parser_build_unary_op (enum tree_code, struct c_expr);
560169699Skanextern struct c_expr parser_build_binary_op (enum tree_code, struct c_expr,
561169699Skan					     struct c_expr);
562132727Skanextern tree build_conditional_expr (tree, tree, tree);
563169699Skanextern tree build_compound_expr (tree, tree);
564169699Skanextern tree c_cast_expr (struct c_type_name *, tree);
565132727Skanextern tree build_c_cast (tree, tree);
566132727Skanextern void store_init_value (tree, tree);
567132727Skanextern void error_init (const char *);
568132727Skanextern void pedwarn_init (const char *);
569169699Skanextern void maybe_warn_string_init (tree, struct c_expr);
570132727Skanextern void start_init (tree, tree, int);
571132727Skanextern void finish_init (void);
572132727Skanextern void really_start_incremental_init (tree);
573132727Skanextern void push_init_level (int);
574169699Skanextern struct c_expr pop_init_level (int);
575132727Skanextern void set_init_index (tree, tree);
576132727Skanextern void set_init_label (tree);
577169699Skanextern void process_init_element (struct c_expr);
578132727Skanextern tree build_compound_literal (tree, tree);
579132727Skanextern tree c_start_case (tree);
580169699Skanextern void c_finish_case (tree);
581169699Skanextern tree build_asm_expr (tree, tree, tree, tree, bool);
582169699Skanextern tree build_asm_stmt (tree, tree);
583132727Skanextern tree c_convert_parm_for_inlining (tree, tree, tree, int);
584169699Skanextern int c_types_compatible_p (tree, tree);
585169699Skanextern tree c_begin_compound_stmt (bool);
586169699Skanextern tree c_end_compound_stmt (tree, bool);
587169699Skanextern void c_finish_if_stmt (location_t, tree, tree, tree, bool);
588260918Spfg/* APPLE LOCAL begin for-fsf-4_4 3274130 5295549 */ \
589260918Spfgextern void c_finish_loop (location_t, tree, tree, tree, tree, tree, tree,
590260918Spfg			   bool);
591260918Spfg/* APPLE LOCAL end for-fsf-4_4 3274130 5295549 */ \
592169699Skanextern tree c_begin_stmt_expr (void);
593169699Skanextern tree c_finish_stmt_expr (tree);
594169699Skanextern tree c_process_expr_stmt (tree);
595169699Skanextern tree c_finish_expr_stmt (tree);
596169699Skanextern tree c_finish_return (tree);
597169699Skanextern tree c_finish_bc_stmt (tree *, bool);
598169699Skanextern tree c_finish_goto_label (tree);
599169699Skanextern tree c_finish_goto_ptr (tree);
600169699Skanextern void c_begin_vm_scope (unsigned int);
601169699Skanextern void c_end_vm_scope (unsigned int);
602169699Skanextern tree c_expr_to_decl (tree, bool *, bool *, bool *);
603169699Skanextern tree c_begin_omp_parallel (void);
604169699Skanextern tree c_finish_omp_parallel (tree, tree);
605169699Skanextern tree c_finish_omp_clauses (tree);
606132727Skan
60718334Speter/* Set to 0 at beginning of a function definition, set to 1 if
60818334Speter   a return statement that specifies a return value is seen.  */
60918334Speter
61018334Speterextern int current_function_returns_value;
61118334Speter
61218334Speter/* Set to 0 at beginning of a function definition, set to 1 if
61318334Speter   a return statement with no argument is seen.  */
61418334Speter
61518334Speterextern int current_function_returns_null;
61618334Speter
61796276Sobrien/* Set to 0 at beginning of a function definition, set to 1 if
61896276Sobrien   a call to a noreturn function is seen.  */
61996276Sobrien
62096276Sobrienextern int current_function_returns_abnormally;
62196276Sobrien
62218334Speter/* Nonzero means we are reading code that came from a system header file.  */
62318334Speter
62418334Speterextern int system_header_p;
62518334Speter
626169699Skan/* True means global_bindings_p should return false even if the scope stack
627169699Skan   says we are in file scope.  */
628169699Skan
629169699Skanextern bool c_override_global_bindings_to_false;
630169699Skan
631169699Skan/* True means we've initialized exception handling.  */
632169699Skanextern bool c_eh_initialized_p;
633169699Skan
63450453Sobrien/* In c-decl.c */
635132727Skanextern void c_finish_incomplete_decl (tree);
636132727Skanextern void c_write_global_declarations (void);
63750453Sobrien
638261188Spfg/* APPLE LOCAL radar 5741070  */
639261188Spfgextern tree c_return_interface_record_type (tree);
640132727Skan/* In order for the format checking to accept the C frontend
641132727Skan   diagnostic framework extensions, you must include this file before
642132727Skan   toplev.h, not after.  */
643169699Skan#if GCC_VERSION >= 4001
644169699Skan#define ATTRIBUTE_GCC_CDIAG(m, n) __attribute__ ((__format__ (GCC_DIAG_STYLE, m ,n))) ATTRIBUTE_NONNULL(m)
645169699Skan#else
646169699Skan#define ATTRIBUTE_GCC_CDIAG(m, n) ATTRIBUTE_NONNULL(m)
647169699Skan#endif
648132727Skan
649169699Skanextern void pedwarn_c90 (const char *, ...) ATTRIBUTE_GCC_CDIAG(1,2);
650169699Skanextern void pedwarn_c99 (const char *, ...) ATTRIBUTE_GCC_CDIAG(1,2);
651169699Skan
65290083Sobrien#endif /* ! GCC_C_TREE_H */
653