118334Speter/* Process declarations and variables for C compiler.
290075Sobrien   Copyright (C) 1988, 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000,
3189824Sdas   2001, 2002, 2003, 2004, 2005, 2006, 2007 Free Software Foundation, Inc.
418334Speter
590075SobrienThis file is part of GCC.
618334Speter
790075SobrienGCC is free software; you can redistribute it and/or modify it under
890075Sobrienthe terms of the GNU General Public License as published by the Free
990075SobrienSoftware Foundation; either version 2, or (at your option) any later
1090075Sobrienversion.
1118334Speter
1290075SobrienGCC is distributed in the hope that it will be useful, but WITHOUT ANY
1390075SobrienWARRANTY; without even the implied warranty of MERCHANTABILITY or
1490075SobrienFITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
1590075Sobrienfor more details.
1618334Speter
1718334SpeterYou should have received a copy of the GNU General Public License
1890075Sobrienalong 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
2296549Sobrien/* $FreeBSD$ */
23189824Sdas/* Merged C99 inline changes from gcc trunk 122565 2007-03-05 */
24189824Sdas/* Fixed problems with compiling inline-25.c and inline-26.c */
25189824Sdas/* XXX still fails inline-29.c, inline-31.c, and inline-32.c */
2696549Sobrien
2718334Speter/* Process declarations and symbol lookup for C front end.
2818334Speter   Also constructs types; the standard scalar types at initialization,
2918334Speter   and structure, union, array and enum types when they are declared.  */
3018334Speter
3118334Speter/* ??? not all decl nodes are given the most useful possible
3218334Speter   line numbers.  For example, the CONST_DECLs for enum values.  */
3318334Speter
3418334Speter#include "config.h"
3550397Sobrien#include "system.h"
36132730Skan#include "coretypes.h"
37169699Skan#include "input.h"
38132730Skan#include "tm.h"
3990075Sobrien#include "intl.h"
4018334Speter#include "tree.h"
4190075Sobrien#include "tree-inline.h"
4290075Sobrien#include "rtl.h"
4318334Speter#include "flags.h"
4490075Sobrien#include "function.h"
4518334Speter#include "output.h"
4690075Sobrien#include "expr.h"
4718334Speter#include "c-tree.h"
4850397Sobrien#include "toplev.h"
4990075Sobrien#include "ggc.h"
5090075Sobrien#include "tm_p.h"
5150397Sobrien#include "cpplib.h"
5290075Sobrien#include "target.h"
5390075Sobrien#include "debug.h"
54132730Skan#include "opts.h"
5590075Sobrien#include "timevar.h"
5690075Sobrien#include "c-common.h"
5796263Sobrien#include "c-pragma.h"
58169699Skan#include "langhooks.h"
59169699Skan#include "tree-mudflap.h"
60169699Skan#include "tree-gimple.h"
61169699Skan#include "diagnostic.h"
62169699Skan#include "tree-dump.h"
63132730Skan#include "cgraph.h"
64132730Skan#include "hashtab.h"
65117421Skan#include "libfuncs.h"
66117421Skan#include "except.h"
67132730Skan#include "langhooks-def.h"
68169699Skan#include "pointer-set.h"
6950397Sobrien
7018334Speter/* In grokdeclarator, distinguish syntactic contexts of declarators.  */
7118334Speterenum decl_context
7218334Speter{ NORMAL,			/* Ordinary declaration */
7318334Speter  FUNCDEF,			/* Function definition */
7418334Speter  PARM,				/* Declaration of parm before function body */
7518334Speter  FIELD,			/* Declaration inside struct or union */
7618334Speter  TYPENAME};			/* Typename (inside cast or sizeof)  */
7718334Speter
7818334Speter
7918334Speter/* Nonzero if we have seen an invalid cross reference
8018334Speter   to a struct, union, or enum, but not yet printed the message.  */
81169699Skantree pending_invalid_xref;
8218334Speter
8318334Speter/* File and line to appear in the eventual error message.  */
84132730Skanlocation_t pending_invalid_xref_location;
8518334Speter
86169699Skan/* True means we've initialized exception handling.  */
87169699Skanbool c_eh_initialized_p;
88169699Skan
8918334Speter/* While defining an enum type, this is 1 plus the last enumerator
9018334Speter   constant value.  Note that will do not have to save this or `enum_overflow'
9118334Speter   around nested function definition since such a definition could only
9218334Speter   occur in an enum value expression and we don't use these variables in
9318334Speter   that case.  */
9418334Speter
9518334Speterstatic tree enum_next_value;
9618334Speter
9718334Speter/* Nonzero means that there was overflow computing enum_next_value.  */
9818334Speter
9918334Speterstatic int enum_overflow;
10018334Speter
101169699Skan/* The file and line that the prototype came from if this is an
102169699Skan   old-style definition; used for diagnostics in
103169699Skan   store_parm_decls_oldstyle.  */
10418334Speter
105169699Skanstatic location_t current_function_prototype_locus;
10618334Speter
107169699Skan/* Whether this prototype was built-in.  */
10818334Speter
109169699Skanstatic bool current_function_prototype_built_in;
11018334Speter
111169699Skan/* The argument type information of this prototype.  */
112132730Skan
113169699Skanstatic tree current_function_prototype_arg_types;
114132730Skan
115169699Skan/* The argument information structure for the function currently being
116169699Skan   defined.  */
11718334Speter
118169699Skanstatic struct c_arg_info *current_function_arg_info;
11918334Speter
120169699Skan/* The obstack on which parser and related data structures, which are
121169699Skan   not live beyond their top-level declaration or definition, are
122169699Skan   allocated.  */
123169699Skanstruct obstack parser_obstack;
124132730Skan
12590075Sobrien/* The current statement tree.  */
12690075Sobrien
127117421Skanstatic GTY(()) struct stmt_tree_s c_stmt_tree;
12890075Sobrien
129132730Skan/* State saving variables.  */
130169699Skantree c_break_label;
131169699Skantree c_cont_label;
13218334Speter
133169699Skan/* Linked list of TRANSLATION_UNIT_DECLS for the translation units
134169699Skan   included in this invocation.  Note that the current translation
135169699Skan   unit is not included in this list.  */
13618334Speter
137169699Skanstatic GTY(()) tree all_translation_units;
13818334Speter
139169699Skan/* A list of decls to be made automatically visible in each file scope.  */
140169699Skanstatic GTY(()) tree visible_builtins;
14118334Speter
14218334Speter/* Set to 0 at beginning of a function definition, set to 1 if
14318334Speter   a return statement that specifies a return value is seen.  */
14418334Speter
14518334Speterint current_function_returns_value;
14618334Speter
14718334Speter/* Set to 0 at beginning of a function definition, set to 1 if
14818334Speter   a return statement with no argument is seen.  */
14918334Speter
15018334Speterint current_function_returns_null;
15118334Speter
15296263Sobrien/* Set to 0 at beginning of a function definition, set to 1 if
15396263Sobrien   a call to a noreturn function is seen.  */
15496263Sobrien
15596263Sobrienint current_function_returns_abnormally;
15696263Sobrien
15718334Speter/* Set to nonzero by `grokdeclarator' for a function
15818334Speter   whose return type is defaulted, if warnings for this are desired.  */
15918334Speter
16018334Speterstatic int warn_about_return_type;
16118334Speter
162169699Skan/* Nonzero when the current toplevel function contains a declaration
163169699Skan   of a nested function which is never defined.  */
164169699Skan
165169699Skanstatic bool undef_nested_function;
166169699Skan
167169699Skan/* True means global_bindings_p should return false even if the scope stack
168169699Skan   says we are in file scope.  */
169169699Skanbool c_override_global_bindings_to_false;
170169699Skan
17118334Speter
172169699Skan/* Each c_binding structure describes one binding of an identifier to
173169699Skan   a decl.  All the decls in a scope - irrespective of namespace - are
174169699Skan   chained together by the ->prev field, which (as the name implies)
175169699Skan   runs in reverse order.  All the decls in a given namespace bound to
176169699Skan   a given identifier are chained by the ->shadowed field, which runs
177169699Skan   from inner to outer scopes.
17818334Speter
179169699Skan   The ->decl field usually points to a DECL node, but there are two
180169699Skan   exceptions.  In the namespace of type tags, the bound entity is a
181169699Skan   RECORD_TYPE, UNION_TYPE, or ENUMERAL_TYPE node.  If an undeclared
182169699Skan   identifier is encountered, it is bound to error_mark_node to
183169699Skan   suppress further errors about that identifier in the current
184169699Skan   function.
185169699Skan
186169699Skan   The ->type field stores the type of the declaration in this scope;
187169699Skan   if NULL, the type is the type of the ->decl field.  This is only of
188169699Skan   relevance for objects with external or internal linkage which may
189169699Skan   be redeclared in inner scopes, forming composite types that only
190169699Skan   persist for the duration of those scopes.  In the external scope,
191169699Skan   this stores the composite of all the types declared for this
192169699Skan   object, visible or not.  The ->inner_comp field (used only at file
193169699Skan   scope) stores whether an incomplete array type at file scope was
194169699Skan   completed at an inner scope to an array size other than 1.
195169699Skan
196169699Skan   The depth field is copied from the scope structure that holds this
197169699Skan   decl.  It is used to preserve the proper ordering of the ->shadowed
198169699Skan   field (see bind()) and also for a handful of special-case checks.
199169699Skan   Finally, the invisible bit is true for a decl which should be
200169699Skan   ignored for purposes of normal name lookup, and the nested bit is
201169699Skan   true for a decl that's been bound a second time in an inner scope;
202169699Skan   in all such cases, the binding in the outer scope will have its
203169699Skan   invisible bit true.  */
204169699Skan
205169699Skanstruct c_binding GTY((chain_next ("%h.prev")))
206169699Skan{
207169699Skan  tree decl;			/* the decl bound */
208169699Skan  tree type;			/* the type in this scope */
209169699Skan  tree id;			/* the identifier it's bound to */
210169699Skan  struct c_binding *prev;	/* the previous decl in this scope */
211169699Skan  struct c_binding *shadowed;	/* the innermost decl shadowed by this one */
212169699Skan  unsigned int depth : 28;      /* depth of this scope */
213169699Skan  BOOL_BITFIELD invisible : 1;  /* normal lookup should ignore this binding */
214169699Skan  BOOL_BITFIELD nested : 1;     /* do not set DECL_CONTEXT when popping */
215169699Skan  BOOL_BITFIELD inner_comp : 1; /* incomplete array completed in inner scope */
216169699Skan  /* one free bit */
217169699Skan};
218169699Skan#define B_IN_SCOPE(b1, b2) ((b1)->depth == (b2)->depth)
219169699Skan#define B_IN_CURRENT_SCOPE(b) ((b)->depth == current_scope->depth)
220169699Skan#define B_IN_FILE_SCOPE(b) ((b)->depth == 1 /*file_scope->depth*/)
221169699Skan#define B_IN_EXTERNAL_SCOPE(b) ((b)->depth == 0 /*external_scope->depth*/)
222169699Skan
223169699Skan#define I_SYMBOL_BINDING(node) \
224169699Skan  (((struct lang_identifier *) IDENTIFIER_NODE_CHECK(node))->symbol_binding)
225169699Skan#define I_SYMBOL_DECL(node) \
226169699Skan (I_SYMBOL_BINDING(node) ? I_SYMBOL_BINDING(node)->decl : 0)
227169699Skan
228169699Skan#define I_TAG_BINDING(node) \
229169699Skan  (((struct lang_identifier *) IDENTIFIER_NODE_CHECK(node))->tag_binding)
230169699Skan#define I_TAG_DECL(node) \
231169699Skan (I_TAG_BINDING(node) ? I_TAG_BINDING(node)->decl : 0)
232169699Skan
233169699Skan#define I_LABEL_BINDING(node) \
234169699Skan  (((struct lang_identifier *) IDENTIFIER_NODE_CHECK(node))->label_binding)
235169699Skan#define I_LABEL_DECL(node) \
236169699Skan (I_LABEL_BINDING(node) ? I_LABEL_BINDING(node)->decl : 0)
237169699Skan
238169699Skan/* Each C symbol points to three linked lists of c_binding structures.
239169699Skan   These describe the values of the identifier in the three different
240169699Skan   namespaces defined by the language.  */
241169699Skan
242169699Skanstruct lang_identifier GTY(())
243169699Skan{
244169699Skan  struct c_common_identifier common_id;
245169699Skan  struct c_binding *symbol_binding; /* vars, funcs, constants, typedefs */
246169699Skan  struct c_binding *tag_binding;    /* struct/union/enum tags */
247169699Skan  struct c_binding *label_binding;  /* labels */
248169699Skan};
249169699Skan
250169699Skan/* Validate c-lang.c's assumptions.  */
251169699Skanextern char C_SIZEOF_STRUCT_LANG_IDENTIFIER_isnt_accurate
252169699Skan[(sizeof(struct lang_identifier) == C_SIZEOF_STRUCT_LANG_IDENTIFIER) ? 1 : -1];
253169699Skan
254169699Skan/* The resulting tree type.  */
255169699Skan
256169699Skanunion lang_tree_node
257169699Skan  GTY((desc ("TREE_CODE (&%h.generic) == IDENTIFIER_NODE"),
258169699Skan       chain_next ("TREE_CODE (&%h.generic) == INTEGER_TYPE ? (union lang_tree_node *) TYPE_NEXT_VARIANT (&%h.generic) : (union lang_tree_node *) TREE_CHAIN (&%h.generic)")))
259169699Skan{
260169699Skan  union tree_node GTY ((tag ("0"),
261169699Skan			desc ("tree_node_structure (&%h)")))
262169699Skan    generic;
263169699Skan  struct lang_identifier GTY ((tag ("1"))) identifier;
264169699Skan};
265169699Skan
266169699Skan/* Each c_scope structure describes the complete contents of one
267169699Skan   scope.  Four scopes are distinguished specially: the innermost or
268169699Skan   current scope, the innermost function scope, the file scope (always
269169699Skan   the second to outermost) and the outermost or external scope.
270169699Skan
271132730Skan   Most declarations are recorded in the current scope.
27218334Speter
273132730Skan   All normal label declarations are recorded in the innermost
274132730Skan   function scope, as are bindings of undeclared identifiers to
275132730Skan   error_mark_node.  (GCC permits nested functions as an extension,
276132730Skan   hence the 'innermost' qualifier.)  Explicitly declared labels
277132730Skan   (using the __label__ extension) appear in the current scope.
27818334Speter
279169699Skan   Being in the file scope (current_scope == file_scope) causes
280132730Skan   special behavior in several places below.  Also, under some
281132730Skan   conditions the Objective-C front end records declarations in the
282169699Skan   file scope even though that isn't the current scope.
28318334Speter
284169699Skan   All declarations with external linkage are recorded in the external
285169699Skan   scope, even if they aren't visible there; this models the fact that
286169699Skan   such declarations are visible to the entire program, and (with a
287169699Skan   bit of cleverness, see pushdecl) allows diagnosis of some violations
288169699Skan   of C99 6.2.2p7 and 6.2.7p2:
28918334Speter
290169699Skan     If, within the same translation unit, the same identifier appears
291169699Skan     with both internal and external linkage, the behavior is
292169699Skan     undefined.
29318334Speter
294169699Skan     All declarations that refer to the same object or function shall
295169699Skan     have compatible type; otherwise, the behavior is undefined.
296169699Skan
297169699Skan   Initially only the built-in declarations, which describe compiler
298169699Skan   intrinsic functions plus a subset of the standard library, are in
299169699Skan   this scope.
300169699Skan
301169699Skan   The order of the blocks list matters, and it is frequently appended
302169699Skan   to.  To avoid having to walk all the way to the end of the list on
303169699Skan   each insertion, or reverse the list later, we maintain a pointer to
304169699Skan   the last list entry.  (FIXME: It should be feasible to use a reversed
305169699Skan   list here.)
306169699Skan
307169699Skan   The bindings list is strictly in reverse order of declarations;
308169699Skan   pop_scope relies on this.  */
309169699Skan
310169699Skan
311169699Skanstruct c_scope GTY((chain_next ("%h.outer")))
312132730Skan{
313132730Skan  /* The scope containing this one.  */
314132730Skan  struct c_scope *outer;
31518334Speter
316132730Skan  /* The next outermost function scope.  */
317132730Skan  struct c_scope *outer_function;
31818334Speter
319169699Skan  /* All bindings in this scope.  */
320169699Skan  struct c_binding *bindings;
32118334Speter
322132730Skan  /* For each scope (except the global one), a chain of BLOCK nodes
323132730Skan     for all the scopes that were entered and exited one level down.  */
324132730Skan  tree blocks;
325132730Skan  tree blocks_last;
32618334Speter
327169699Skan  /* The depth of this scope.  Used to keep the ->shadowed chain of
328169699Skan     bindings sorted innermost to outermost.  */
329169699Skan  unsigned int depth : 28;
330169699Skan
331132730Skan  /* True if we are currently filling this scope with parameter
332132730Skan     declarations.  */
333132730Skan  BOOL_BITFIELD parm_flag : 1;
33418334Speter
335169699Skan  /* True if we saw [*] in this scope.  Used to give an error messages
336169699Skan     if these appears in a function definition.  */
337169699Skan  BOOL_BITFIELD had_vla_unspec : 1;
338169699Skan
339132730Skan  /* True if we already complained about forward parameter decls
340132730Skan     in this scope.  This prevents double warnings on
341132730Skan     foo (int a; int b; ...)  */
342132730Skan  BOOL_BITFIELD warned_forward_parm_decls : 1;
34390075Sobrien
344132730Skan  /* True if this is the outermost block scope of a function body.
345132730Skan     This scope contains the parameters, the local variables declared
346132730Skan     in the outermost block, and all the labels (except those in
347132730Skan     nested functions, or declared at block scope with __label__).  */
348132730Skan  BOOL_BITFIELD function_body : 1;
34918334Speter
350132730Skan  /* True means make a BLOCK for this scope no matter what.  */
351132730Skan  BOOL_BITFIELD keep : 1;
352132730Skan};
35318334Speter
354132730Skan/* The scope currently in effect.  */
35518334Speter
356132730Skanstatic GTY(()) struct c_scope *current_scope;
35718334Speter
358132730Skan/* The innermost function scope.  Ordinary (not explicitly declared)
359132730Skan   labels, bindings to error_mark_node, and the lazily-created
360132730Skan   bindings of __func__ and its friends get this scope.  */
36118334Speter
362132730Skanstatic GTY(()) struct c_scope *current_function_scope;
36318334Speter
364169699Skan/* The C file scope.  This is reset for each input translation unit.  */
36518334Speter
366169699Skanstatic GTY(()) struct c_scope *file_scope;
36718334Speter
368169699Skan/* The outermost scope.  This is used for all declarations with
369169699Skan   external linkage, and only these, hence the name.  */
370169699Skan
371169699Skanstatic GTY(()) struct c_scope *external_scope;
372169699Skan
373169699Skan/* A chain of c_scope structures awaiting reuse.  */
374169699Skan
375169699Skanstatic GTY((deletable)) struct c_scope *scope_freelist;
376169699Skan
377169699Skan/* A chain of c_binding structures awaiting reuse.  */
378169699Skan
379169699Skanstatic GTY((deletable)) struct c_binding *binding_freelist;
380169699Skan
381132730Skan/* Append VAR to LIST in scope SCOPE.  */
382132730Skan#define SCOPE_LIST_APPEND(scope, list, decl) do {	\
383132730Skan  struct c_scope *s_ = (scope);				\
384132730Skan  tree d_ = (decl);					\
385132730Skan  if (s_->list##_last)					\
386132730Skan    TREE_CHAIN (s_->list##_last) = d_;			\
387132730Skan  else							\
388132730Skan    s_->list = d_;					\
389132730Skan  s_->list##_last = d_;					\
390132730Skan} while (0)
39118334Speter
392132730Skan/* Concatenate FROM in scope FSCOPE onto TO in scope TSCOPE.  */
393132730Skan#define SCOPE_LIST_CONCAT(tscope, to, fscope, from) do {	\
394132730Skan  struct c_scope *t_ = (tscope);				\
395132730Skan  struct c_scope *f_ = (fscope);				\
396132730Skan  if (t_->to##_last)						\
397132730Skan    TREE_CHAIN (t_->to##_last) = f_->from;			\
398132730Skan  else								\
399132730Skan    t_->to = f_->from;						\
400132730Skan  t_->to##_last = f_->from##_last;				\
401132730Skan} while (0)
40290075Sobrien
403132730Skan/* True means unconditionally make a BLOCK for the next scope pushed.  */
40418334Speter
405132730Skanstatic bool keep_next_level_flag;
40618334Speter
407169699Skan/* True means the next call to push_scope will be the outermost scope
408132730Skan   of a function body, so do not push a new scope, merely cease
409132730Skan   expecting parameter decls.  */
410132730Skan
411132730Skanstatic bool next_is_function_body;
412132730Skan
41318334Speter/* Functions called automatically at the beginning and end of execution.  */
41418334Speter
415169699Skanstatic GTY(()) tree static_ctors;
416169699Skanstatic GTY(()) tree static_dtors;
41718334Speter
41818334Speter/* Forward declarations.  */
419169699Skanstatic tree lookup_name_in_scope (tree, struct c_scope *);
420169699Skanstatic tree c_make_fname_decl (tree, int);
421169699Skanstatic tree grokdeclarator (const struct c_declarator *,
422169699Skan			    struct c_declspecs *,
423169699Skan			    enum decl_context, bool, tree *);
424169699Skanstatic tree grokparms (struct c_arg_info *, bool);
425132730Skanstatic void layout_array_type (tree);
42618334Speter
427169699Skan/* T is a statement.  Add it to the statement-tree.  This is the
428169699Skan   C/ObjC version--C++ has a slightly different version of this
429169699Skan   function.  */
430169699Skan
431169699Skantree
432169699Skanadd_stmt (tree t)
433169699Skan{
434169699Skan  enum tree_code code = TREE_CODE (t);
435169699Skan
436169699Skan  if (EXPR_P (t) && code != LABEL_EXPR)
437169699Skan    {
438169699Skan      if (!EXPR_HAS_LOCATION (t))
439169699Skan	SET_EXPR_LOCATION (t, input_location);
440169699Skan    }
441169699Skan
442169699Skan  if (code == LABEL_EXPR || code == CASE_LABEL_EXPR)
443169699Skan    STATEMENT_LIST_HAS_LABEL (cur_stmt_list) = 1;
444169699Skan
445169699Skan  /* Add T to the statement-tree.  Non-side-effect statements need to be
446169699Skan     recorded during statement expressions.  */
447169699Skan  append_to_statement_list_force (t, &cur_stmt_list);
448169699Skan
449169699Skan  return t;
450169699Skan}
451169699Skan
45290075Sobrien/* States indicating how grokdeclarator() should handle declspecs marked
45390075Sobrien   with __attribute__((deprecated)).  An object declared as
45490075Sobrien   __attribute__((deprecated)) suppresses warnings of uses of other
45590075Sobrien   deprecated items.  */
456260919Spfg/* APPLE LOCAL begin "unavailable" attribute (radar 2809697) */
457260919Spfg/* Also add an __attribute__((unavailable)).  An object declared as
458260919Spfg   __attribute__((unavailable)) suppresses any reports of being
459260919Spfg   declared with unavailable or deprecated items.  */
460260919Spfg/* APPLE LOCAL end "unavailable" attribute (radar 2809697) */
461132730Skan
46290075Sobrienenum deprecated_states {
46390075Sobrien  DEPRECATED_NORMAL,
46490075Sobrien  DEPRECATED_SUPPRESS
465260919Spfg  /* APPLE LOCAL "unavailable" attribute (radar 2809697) */
466260919Spfg  , DEPRECATED_UNAVAILABLE_SUPPRESS
46790075Sobrien};
46890075Sobrien
46990075Sobrienstatic enum deprecated_states deprecated_state = DEPRECATED_NORMAL;
47090075Sobrien
47118334Spetervoid
472132730Skanc_print_identifier (FILE *file, tree node, int indent)
47318334Speter{
474169699Skan  print_node (file, "symbol", I_SYMBOL_DECL (node), indent + 4);
475169699Skan  print_node (file, "tag", I_TAG_DECL (node), indent + 4);
476169699Skan  print_node (file, "label", I_LABEL_DECL (node), indent + 4);
47790075Sobrien  if (C_IS_RESERVED_WORD (node))
47890075Sobrien    {
47990075Sobrien      tree rid = ridpointers[C_RID_CODE (node)];
48090075Sobrien      indent_to (file, indent + 4);
481169699Skan      fprintf (file, "rid %p \"%s\"",
482132730Skan	       (void *) rid, IDENTIFIER_POINTER (rid));
48390075Sobrien    }
48418334Speter}
485169699Skan
486169699Skan/* Establish a binding between NAME, an IDENTIFIER_NODE, and DECL,
487169699Skan   which may be any of several kinds of DECL or TYPE or error_mark_node,
488169699Skan   in the scope SCOPE.  */
489169699Skanstatic void
490169699Skanbind (tree name, tree decl, struct c_scope *scope, bool invisible, bool nested)
491169699Skan{
492169699Skan  struct c_binding *b, **here;
493169699Skan
494169699Skan  if (binding_freelist)
495169699Skan    {
496169699Skan      b = binding_freelist;
497169699Skan      binding_freelist = b->prev;
498169699Skan    }
499169699Skan  else
500169699Skan    b = GGC_NEW (struct c_binding);
501169699Skan
502169699Skan  b->shadowed = 0;
503169699Skan  b->decl = decl;
504169699Skan  b->id = name;
505169699Skan  b->depth = scope->depth;
506169699Skan  b->invisible = invisible;
507169699Skan  b->nested = nested;
508169699Skan  b->inner_comp = 0;
509169699Skan
510169699Skan  b->type = 0;
511169699Skan
512169699Skan  b->prev = scope->bindings;
513169699Skan  scope->bindings = b;
514169699Skan
515169699Skan  if (!name)
516169699Skan    return;
517169699Skan
518169699Skan  switch (TREE_CODE (decl))
519169699Skan    {
520169699Skan    case LABEL_DECL:     here = &I_LABEL_BINDING (name);   break;
521169699Skan    case ENUMERAL_TYPE:
522169699Skan    case UNION_TYPE:
523169699Skan    case RECORD_TYPE:    here = &I_TAG_BINDING (name);     break;
524169699Skan    case VAR_DECL:
525169699Skan    case FUNCTION_DECL:
526169699Skan    case TYPE_DECL:
527169699Skan    case CONST_DECL:
528169699Skan    case PARM_DECL:
529169699Skan    case ERROR_MARK:     here = &I_SYMBOL_BINDING (name);  break;
530169699Skan
531169699Skan    default:
532169699Skan      gcc_unreachable ();
533169699Skan    }
534169699Skan
535169699Skan  /* Locate the appropriate place in the chain of shadowed decls
536169699Skan     to insert this binding.  Normally, scope == current_scope and
537169699Skan     this does nothing.  */
538169699Skan  while (*here && (*here)->depth > scope->depth)
539169699Skan    here = &(*here)->shadowed;
540169699Skan
541169699Skan  b->shadowed = *here;
542169699Skan  *here = b;
543169699Skan}
544169699Skan
545169699Skan/* Clear the binding structure B, stick it on the binding_freelist,
546169699Skan   and return the former value of b->prev.  This is used by pop_scope
547169699Skan   and get_parm_info to iterate destructively over all the bindings
548169699Skan   from a given scope.  */
549169699Skanstatic struct c_binding *
550169699Skanfree_binding_and_advance (struct c_binding *b)
551169699Skan{
552169699Skan  struct c_binding *prev = b->prev;
553169699Skan
554169699Skan  memset (b, 0, sizeof (struct c_binding));
555169699Skan  b->prev = binding_freelist;
556169699Skan  binding_freelist = b;
557169699Skan
558169699Skan  return prev;
559169699Skan}
560169699Skan
56118334Speter
56218334Speter/* Hook called at end of compilation to assume 1 elt
563132730Skan   for a file-scope tentative array defn that wasn't complete before.  */
56490075Sobrien
56518334Spetervoid
566132730Skanc_finish_incomplete_decl (tree decl)
56718334Speter{
56850397Sobrien  if (TREE_CODE (decl) == VAR_DECL)
56918334Speter    {
57018334Speter      tree type = TREE_TYPE (decl);
57150397Sobrien      if (type != error_mark_node
57250397Sobrien	  && TREE_CODE (type) == ARRAY_TYPE
573169699Skan	  && !DECL_EXTERNAL (decl)
57450397Sobrien	  && TYPE_DOMAIN (type) == 0)
57518334Speter	{
576169699Skan	  warning (0, "array %q+D assumed to have one element", decl);
57750397Sobrien
578169699Skan	  complete_array_type (&TREE_TYPE (decl), NULL_TREE, true);
57918334Speter
58018334Speter	  layout_decl (decl, 0);
58118334Speter	}
58218334Speter    }
58318334Speter}
58418334Speter
585132730Skan/* The Objective-C front-end often needs to determine the current scope.  */
58618334Speter
587132730Skanvoid *
588169699Skanobjc_get_current_scope (void)
58918334Speter{
590132730Skan  return current_scope;
59118334Speter}
59218334Speter
593132730Skan/* The following function is used only by Objective-C.  It needs to live here
594132730Skan   because it accesses the innards of c_scope.  */
595132730Skan
59618334Spetervoid
597132730Skanobjc_mark_locals_volatile (void *enclosing_blk)
59818334Speter{
599132730Skan  struct c_scope *scope;
600169699Skan  struct c_binding *b;
601132730Skan
602132730Skan  for (scope = current_scope;
603132730Skan       scope && scope != enclosing_blk;
604132730Skan       scope = scope->outer)
605132730Skan    {
606169699Skan      for (b = scope->bindings; b; b = b->prev)
607169699Skan	objc_volatilize_decl (b->decl);
608132730Skan
609132730Skan      /* Do not climb up past the current function.  */
610132730Skan      if (scope->function_body)
611132730Skan	break;
612132730Skan    }
61318334Speter}
61418334Speter
615169699Skan/* Nonzero if we are currently in file scope.  */
61618334Speter
61718334Speterint
618132730Skanglobal_bindings_p (void)
61918334Speter{
620169699Skan  return current_scope == file_scope && !c_override_global_bindings_to_false;
62118334Speter}
62218334Speter
623132730Skanvoid
624132730Skankeep_next_level (void)
625132730Skan{
626132730Skan  keep_next_level_flag = true;
627132730Skan}
62818334Speter
629132730Skan/* Identify this scope as currently being filled with parameters.  */
630132730Skan
63118334Spetervoid
632132730Skandeclare_parm_level (void)
63318334Speter{
634132730Skan  current_scope->parm_flag = true;
63518334Speter}
63618334Speter
63718334Spetervoid
638169699Skanpush_scope (void)
63918334Speter{
640132730Skan  if (next_is_function_body)
641132730Skan    {
642132730Skan      /* This is the transition from the parameters to the top level
643132730Skan	 of the function body.  These are the same scope
644132730Skan	 (C99 6.2.1p4,6) so we do not push another scope structure.
645132730Skan	 next_is_function_body is set only by store_parm_decls, which
646132730Skan	 in turn is called when and only when we are about to
647132730Skan	 encounter the opening curly brace for the function body.
64818334Speter
649132730Skan	 The outermost block of a function always gets a BLOCK node,
650132730Skan	 because the debugging output routines expect that each
651132730Skan	 function has at least one BLOCK.  */
652132730Skan      current_scope->parm_flag         = false;
653132730Skan      current_scope->function_body     = true;
654132730Skan      current_scope->keep              = true;
655132730Skan      current_scope->outer_function    = current_function_scope;
656132730Skan      current_function_scope           = current_scope;
65718334Speter
658132730Skan      keep_next_level_flag = false;
659132730Skan      next_is_function_body = false;
660132730Skan    }
661132730Skan  else
66218334Speter    {
663169699Skan      struct c_scope *scope;
664169699Skan      if (scope_freelist)
665169699Skan	{
666169699Skan	  scope = scope_freelist;
667169699Skan	  scope_freelist = scope->outer;
668169699Skan	}
669169699Skan      else
670169699Skan	scope = GGC_CNEW (struct c_scope);
671132730Skan
672132730Skan      scope->keep          = keep_next_level_flag;
673132730Skan      scope->outer         = current_scope;
674169699Skan      scope->depth	   = current_scope ? (current_scope->depth + 1) : 0;
675169699Skan
676169699Skan      /* Check for scope depth overflow.  Unlikely (2^28 == 268,435,456) but
677169699Skan	 possible.  */
678169699Skan      if (current_scope && scope->depth == 0)
679169699Skan	{
680169699Skan	  scope->depth--;
681169699Skan	  sorry ("GCC supports only %u nested scopes", scope->depth);
682169699Skan	}
683169699Skan
684132730Skan      current_scope        = scope;
685132730Skan      keep_next_level_flag = false;
68618334Speter    }
68718334Speter}
68818334Speter
689169699Skan/* Set the TYPE_CONTEXT of all of TYPE's variants to CONTEXT.  */
69050397Sobrien
691169699Skanstatic void
692169699Skanset_type_context (tree type, tree context)
693169699Skan{
694169699Skan  for (type = TYPE_MAIN_VARIANT (type); type;
695169699Skan       type = TYPE_NEXT_VARIANT (type))
696169699Skan    TYPE_CONTEXT (type) = context;
697169699Skan}
69850397Sobrien
699169699Skan/* Exit a scope.  Restore the state of the identifier-decl mappings
700169699Skan   that were in effect when this scope was entered.  Return a BLOCK
701169699Skan   node containing all the DECLs in this scope that are of interest
702169699Skan   to debug info generation.  */
70350397Sobrien
70418334Spetertree
705169699Skanpop_scope (void)
70618334Speter{
707132730Skan  struct c_scope *scope = current_scope;
708169699Skan  tree block, context, p;
709169699Skan  struct c_binding *b;
71018334Speter
711169699Skan  bool functionbody = scope->function_body;
712169699Skan  bool keep = functionbody || scope->keep || scope->bindings;
71318334Speter
714169699Skan  c_end_vm_scope (scope->depth);
71518334Speter
716132730Skan  /* If appropriate, create a BLOCK to record the decls for the life
717132730Skan     of this function.  */
71818334Speter  block = 0;
719132730Skan  if (keep)
72018334Speter    {
721132730Skan      block = make_node (BLOCK);
722132730Skan      BLOCK_SUBBLOCKS (block) = scope->blocks;
723132730Skan      TREE_USED (block) = 1;
72418334Speter
725169699Skan      /* In each subblock, record that this is its superior.  */
726169699Skan      for (p = scope->blocks; p; p = TREE_CHAIN (p))
727169699Skan	BLOCK_SUPERCONTEXT (p) = block;
72818334Speter
729169699Skan      BLOCK_VARS (block) = 0;
730169699Skan    }
73118334Speter
732169699Skan  /* The TYPE_CONTEXTs for all of the tagged types belonging to this
733169699Skan     scope must be set so that they point to the appropriate
734169699Skan     construct, i.e.  either to the current FUNCTION_DECL node, or
735169699Skan     else to the BLOCK node we just constructed.
73618334Speter
737169699Skan     Note that for tagged types whose scope is just the formal
738169699Skan     parameter list for some function type specification, we can't
739169699Skan     properly set their TYPE_CONTEXTs here, because we don't have a
740169699Skan     pointer to the appropriate FUNCTION_TYPE node readily available
741169699Skan     to us.  For those cases, the TYPE_CONTEXTs of the relevant tagged
742169699Skan     type nodes get set in `grokdeclarator' as soon as we have created
743169699Skan     the FUNCTION_TYPE node which will represent the "scope" for these
744169699Skan     "parameter list local" tagged types.  */
745169699Skan  if (scope->function_body)
746169699Skan    context = current_function_decl;
747169699Skan  else if (scope == file_scope)
748169699Skan    {
749169699Skan      tree file_decl = build_decl (TRANSLATION_UNIT_DECL, 0, 0);
750169699Skan      TREE_CHAIN (file_decl) = all_translation_units;
751169699Skan      all_translation_units = file_decl;
752169699Skan      context = file_decl;
753169699Skan    }
754169699Skan  else
755169699Skan    context = block;
756132730Skan
757169699Skan  /* Clear all bindings in this scope.  */
758169699Skan  for (b = scope->bindings; b; b = free_binding_and_advance (b))
75918334Speter    {
760169699Skan      p = b->decl;
761132730Skan      switch (TREE_CODE (p))
76218334Speter	{
763132730Skan	case LABEL_DECL:
764169699Skan	  /* Warnings for unused labels, errors for undefined labels.  */
765132730Skan	  if (TREE_USED (p) && !DECL_INITIAL (p))
76618334Speter	    {
767169699Skan	      error ("label %q+D used but not defined", p);
768132730Skan	      DECL_INITIAL (p) = error_mark_node;
76918334Speter	    }
770132730Skan	  else if (!TREE_USED (p) && warn_unused_label)
771132730Skan	    {
772132730Skan	      if (DECL_INITIAL (p))
773169699Skan		warning (0, "label %q+D defined but not used", p);
774132730Skan	      else
775169699Skan		warning (0, "label %q+D declared but not defined", p);
776132730Skan	    }
777169699Skan	  /* Labels go in BLOCK_VARS.  */
778169699Skan	  TREE_CHAIN (p) = BLOCK_VARS (block);
779169699Skan	  BLOCK_VARS (block) = p;
780169699Skan	  gcc_assert (I_LABEL_BINDING (b->id) == b);
781169699Skan	  I_LABEL_BINDING (b->id) = b->shadowed;
782169699Skan	  break;
78318334Speter
784169699Skan	case ENUMERAL_TYPE:
785169699Skan	case UNION_TYPE:
786169699Skan	case RECORD_TYPE:
787169699Skan	  set_type_context (p, context);
788169699Skan
789169699Skan	  /* Types may not have tag-names, in which case the type
790169699Skan	     appears in the bindings list with b->id NULL.  */
791169699Skan	  if (b->id)
792169699Skan	    {
793169699Skan	      gcc_assert (I_TAG_BINDING (b->id) == b);
794169699Skan	      I_TAG_BINDING (b->id) = b->shadowed;
795169699Skan	    }
796132730Skan	  break;
79718334Speter
798132730Skan	case FUNCTION_DECL:
799169699Skan	  /* Propagate TREE_ADDRESSABLE from nested functions to their
800169699Skan	     containing functions.  */
801169699Skan	  if (!TREE_ASM_WRITTEN (p)
802132730Skan	      && DECL_INITIAL (p) != 0
803132730Skan	      && TREE_ADDRESSABLE (p)
804132730Skan	      && DECL_ABSTRACT_ORIGIN (p) != 0
805132730Skan	      && DECL_ABSTRACT_ORIGIN (p) != p)
806132730Skan	    TREE_ADDRESSABLE (DECL_ABSTRACT_ORIGIN (p)) = 1;
807169699Skan	  if (!DECL_EXTERNAL (p)
808190404Sdas	      && DECL_INITIAL (p) == 0
809190404Sdas	      && scope != file_scope
810190404Sdas	      && scope != external_scope)
811169699Skan	    {
812169699Skan	      error ("nested function %q+D declared but never defined", p);
813169699Skan	      undef_nested_function = true;
814169699Skan	    }
815189824Sdas	  /* C99 6.7.4p6: "a function with external linkage... declared
816189824Sdas	     with an inline function specifier ... shall also be defined in the
817189824Sdas	     same translation unit."  */
818189824Sdas	  else if (DECL_DECLARED_INLINE_P (p)
819189824Sdas		   && TREE_PUBLIC (p)
820189824Sdas		   && !DECL_INITIAL (p)
821189824Sdas		   && !flag_gnu89_inline)
822189824Sdas	    pedwarn ("inline function %q+D declared but never defined", p);
823189824Sdas
824169699Skan	  goto common_symbol;
82518334Speter
826132730Skan	case VAR_DECL:
827169699Skan	  /* Warnings for unused variables.  */
828169699Skan	  if (!TREE_USED (p)
829169699Skan	      && !TREE_NO_WARNING (p)
830132730Skan	      && !DECL_IN_SYSTEM_HEADER (p)
831132730Skan	      && DECL_NAME (p)
832169699Skan	      && !DECL_ARTIFICIAL (p)
833169699Skan	      && scope != file_scope
834169699Skan	      && scope != external_scope)
835169699Skan	    warning (OPT_Wunused_variable, "unused variable %q+D", p);
83618334Speter
837169699Skan	  if (b->inner_comp)
838132730Skan	    {
839169699Skan	      error ("type of array %q+D completed incompatibly with"
840169699Skan		     " implicit initialization", p);
841132730Skan	    }
842169699Skan
843169699Skan	  /* Fall through.  */
844169699Skan	case TYPE_DECL:
845169699Skan	case CONST_DECL:
846169699Skan	common_symbol:
847169699Skan	  /* All of these go in BLOCK_VARS, but only if this is the
848169699Skan	     binding in the home scope.  */
849169699Skan	  if (!b->nested)
850169699Skan	    {
851169699Skan	      TREE_CHAIN (p) = BLOCK_VARS (block);
852169699Skan	      BLOCK_VARS (block) = p;
853169699Skan	    }
854169699Skan	  /* If this is the file scope, and we are processing more
855169699Skan	     than one translation unit in this compilation, set
856169699Skan	     DECL_CONTEXT of each decl to the TRANSLATION_UNIT_DECL.
857169699Skan	     This makes same_translation_unit_p work, and causes
858169699Skan	     static declarations to be given disambiguating suffixes.  */
859169699Skan	  if (scope == file_scope && num_in_fnames > 1)
860169699Skan	    {
861169699Skan	      DECL_CONTEXT (p) = context;
862169699Skan	      if (TREE_CODE (p) == TYPE_DECL)
863169699Skan		set_type_context (TREE_TYPE (p), context);
864169699Skan	    }
865169699Skan
866169699Skan	  /* Fall through.  */
867169699Skan	  /* Parameters go in DECL_ARGUMENTS, not BLOCK_VARS, and have
868169699Skan	     already been put there by store_parm_decls.  Unused-
869169699Skan	     parameter warnings are handled by function.c.
870169699Skan	     error_mark_node obviously does not go in BLOCK_VARS and
871169699Skan	     does not get unused-variable warnings.  */
872169699Skan	case PARM_DECL:
873169699Skan	case ERROR_MARK:
874169699Skan	  /* It is possible for a decl not to have a name.  We get
875169699Skan	     here with b->id NULL in this case.  */
876169699Skan	  if (b->id)
877169699Skan	    {
878169699Skan	      gcc_assert (I_SYMBOL_BINDING (b->id) == b);
879169699Skan	      I_SYMBOL_BINDING (b->id) = b->shadowed;
880169699Skan	      if (b->shadowed && b->shadowed->type)
881169699Skan		TREE_TYPE (b->shadowed->decl) = b->shadowed->type;
882169699Skan	    }
883132730Skan	  break;
884169699Skan
885169699Skan	default:
886169699Skan	  gcc_unreachable ();
887132730Skan	}
888132730Skan    }
88950397Sobrien
89018334Speter
891169699Skan  /* Dispose of the block that we just made inside some higher level.  */
892169699Skan  if ((scope->function_body || scope == file_scope) && context)
893132730Skan    {
894169699Skan      DECL_INITIAL (context) = block;
895169699Skan      BLOCK_SUPERCONTEXT (block) = context;
89618334Speter    }
897132730Skan  else if (scope->outer)
89818334Speter    {
899132730Skan      if (block)
900132730Skan	SCOPE_LIST_APPEND (scope->outer, blocks, block);
901132730Skan      /* If we did not make a block for the scope just exited, any
902132730Skan	 blocks made for inner scopes must be carried forward so they
903132730Skan	 will later become subblocks of something else.  */
904132730Skan      else if (scope->blocks)
905132730Skan	SCOPE_LIST_CONCAT (scope->outer, blocks, scope, blocks);
90618334Speter    }
90718334Speter
908132730Skan  /* Pop the current scope, and free the structure for reuse.  */
909169699Skan  current_scope = scope->outer;
910169699Skan  if (scope->function_body)
911169699Skan    current_function_scope = scope->outer_function;
91218334Speter
913169699Skan  memset (scope, 0, sizeof (struct c_scope));
914169699Skan  scope->outer = scope_freelist;
915169699Skan  scope_freelist = scope;
916169699Skan
91718334Speter  return block;
91818334Speter}
91918334Speter
920169699Skanvoid
921169699Skanpush_file_scope (void)
922169699Skan{
923169699Skan  tree decl;
924169699Skan
925169699Skan  if (file_scope)
926169699Skan    return;
927169699Skan
928169699Skan  push_scope ();
929169699Skan  file_scope = current_scope;
930169699Skan
931169699Skan  start_fname_decls ();
932169699Skan
933169699Skan  for (decl = visible_builtins; decl; decl = TREE_CHAIN (decl))
934169699Skan    bind (DECL_NAME (decl), decl, file_scope,
935169699Skan	  /*invisible=*/false, /*nested=*/true);
936169699Skan}
937169699Skan
938169699Skanvoid
939169699Skanpop_file_scope (void)
940169699Skan{
941169699Skan  /* In case there were missing closebraces, get us back to the global
942169699Skan     binding level.  */
943169699Skan  while (current_scope != file_scope)
944169699Skan    pop_scope ();
945169699Skan
946169699Skan  /* __FUNCTION__ is defined at file scope ("").  This
947169699Skan     call may not be necessary as my tests indicate it
948169699Skan     still works without it.  */
949169699Skan  finish_fname_decls ();
950169699Skan
951169699Skan  /* This is the point to write out a PCH if we're doing that.
952169699Skan     In that case we do not want to do anything else.  */
953169699Skan  if (pch_file)
954169699Skan    {
955169699Skan      c_common_write_pch ();
956169699Skan      return;
957169699Skan    }
958169699Skan
959169699Skan  /* Pop off the file scope and close this translation unit.  */
960169699Skan  pop_scope ();
961169699Skan  file_scope = 0;
962169699Skan
963169699Skan  maybe_apply_pending_pragma_weaks ();
964169699Skan  cgraph_finalize_compilation_unit ();
965169699Skan}
966169699Skan
967132730Skan/* Insert BLOCK at the end of the list of subblocks of the current
968132730Skan   scope.  This is used when a BIND_EXPR is expanded, to handle the
969132730Skan   BLOCK node inside the BIND_EXPR.  */
97018334Speter
97118334Spetervoid
972132730Skaninsert_block (tree block)
97318334Speter{
97418334Speter  TREE_USED (block) = 1;
975132730Skan  SCOPE_LIST_APPEND (current_scope, blocks, block);
97618334Speter}
97718334Speter
97818334Speter/* Push a definition or a declaration of struct, union or enum tag "name".
97918334Speter   "type" should be the type node.
98018334Speter   We assume that the tag "name" is not already defined.
98118334Speter
98218334Speter   Note that the definition may really be just a forward reference.
98318334Speter   In that case, the TYPE_SIZE will be zero.  */
98418334Speter
985169699Skanstatic void
986132730Skanpushtag (tree name, tree type)
98718334Speter{
988132730Skan  /* Record the identifier as the type's name if it has none.  */
989169699Skan  if (name && !TYPE_NAME (type))
990169699Skan    TYPE_NAME (type) = name;
991169699Skan  bind (name, type, current_scope, /*invisible=*/false, /*nested=*/false);
992132730Skan
99318334Speter  /* Create a fake NULL-named TYPE_DECL node whose TREE_TYPE will be the
994132730Skan     tagged type we just added to the current scope.  This fake
99518334Speter     NULL-named TYPE_DECL node helps dwarfout.c to know when it needs
99618334Speter     to output a representation of a tagged type, and it also gives
99718334Speter     us a convenient place to record the "scope start" address for the
99818334Speter     tagged type.  */
99918334Speter
100018334Speter  TYPE_STUB_DECL (type) = pushdecl (build_decl (TYPE_DECL, NULL_TREE, type));
100150397Sobrien
100250397Sobrien  /* An approximation for now, so we can tell this is a function-scope tag.
1003169699Skan     This will be updated in pop_scope.  */
100450397Sobrien  TYPE_CONTEXT (type) = DECL_CONTEXT (TYPE_STUB_DECL (type));
100518334Speter}
100618334Speter
1007132730Skan/* Subroutine of compare_decls.  Allow harmless mismatches in return
1008132730Skan   and argument types provided that the type modes match.  This function
1009132730Skan   return a unified type given a suitable match, and 0 otherwise.  */
101018334Speter
1011132730Skanstatic tree
1012132730Skanmatch_builtin_function_types (tree newtype, tree oldtype)
1013132730Skan{
1014132730Skan  tree newrettype, oldrettype;
1015132730Skan  tree newargs, oldargs;
1016132730Skan  tree trytype, tryargs;
101718334Speter
1018132730Skan  /* Accept the return type of the new declaration if same modes.  */
1019132730Skan  oldrettype = TREE_TYPE (oldtype);
1020132730Skan  newrettype = TREE_TYPE (newtype);
102150397Sobrien
1022132730Skan  if (TYPE_MODE (oldrettype) != TYPE_MODE (newrettype))
1023132730Skan    return 0;
1024132730Skan
1025132730Skan  oldargs = TYPE_ARG_TYPES (oldtype);
1026132730Skan  newargs = TYPE_ARG_TYPES (newtype);
1027132730Skan  tryargs = newargs;
1028132730Skan
1029132730Skan  while (oldargs || newargs)
1030132730Skan    {
1031169699Skan      if (!oldargs
1032169699Skan	  || !newargs
1033169699Skan	  || !TREE_VALUE (oldargs)
1034169699Skan	  || !TREE_VALUE (newargs)
1035132730Skan	  || TYPE_MODE (TREE_VALUE (oldargs))
1036132730Skan	     != TYPE_MODE (TREE_VALUE (newargs)))
1037132730Skan	return 0;
1038132730Skan
1039132730Skan      oldargs = TREE_CHAIN (oldargs);
1040132730Skan      newargs = TREE_CHAIN (newargs);
1041132730Skan    }
1042132730Skan
1043132730Skan  trytype = build_function_type (newrettype, tryargs);
1044132730Skan  return build_type_attribute_variant (trytype, TYPE_ATTRIBUTES (oldtype));
1045132730Skan}
1046132730Skan
1047169699Skan/* Subroutine of diagnose_mismatched_decls.  Check for function type
1048132730Skan   mismatch involving an empty arglist vs a nonempty one and give clearer
1049169699Skan   diagnostics.  */
1050132730Skanstatic void
1051132730Skandiagnose_arglist_conflict (tree newdecl, tree olddecl,
1052132730Skan			   tree newtype, tree oldtype)
105318334Speter{
1054132730Skan  tree t;
105518334Speter
1056132730Skan  if (TREE_CODE (olddecl) != FUNCTION_DECL
1057169699Skan      || !comptypes (TREE_TYPE (oldtype), TREE_TYPE (newtype))
1058132730Skan      || !((TYPE_ARG_TYPES (oldtype) == 0 && DECL_INITIAL (olddecl) == 0)
1059132730Skan	   ||
1060132730Skan	   (TYPE_ARG_TYPES (newtype) == 0 && DECL_INITIAL (newdecl) == 0)))
1061132730Skan    return;
1062132730Skan
1063132730Skan  t = TYPE_ARG_TYPES (oldtype);
1064132730Skan  if (t == 0)
1065132730Skan    t = TYPE_ARG_TYPES (newtype);
1066132730Skan  for (; t; t = TREE_CHAIN (t))
106790075Sobrien    {
1068132730Skan      tree type = TREE_VALUE (t);
1069132730Skan
1070132730Skan      if (TREE_CHAIN (t) == 0
1071132730Skan	  && TYPE_MAIN_VARIANT (type) != void_type_node)
107290075Sobrien	{
1073169699Skan	  inform ("a parameter list with an ellipsis can%'t match "
1074132730Skan		  "an empty parameter name list declaration");
1075132730Skan	  break;
107690075Sobrien	}
107718334Speter
1078132730Skan      if (c_type_promotes_to (type) != type)
1079132730Skan	{
1080169699Skan	  inform ("an argument type that has a default promotion can%'t match "
1081132730Skan		  "an empty parameter name list declaration");
1082132730Skan	  break;
1083132730Skan	}
108490075Sobrien    }
1085132730Skan}
108690075Sobrien
1087132730Skan/* Another subroutine of diagnose_mismatched_decls.  OLDDECL is an
1088132730Skan   old-style function definition, NEWDECL is a prototype declaration.
1089132730Skan   Diagnose inconsistencies in the argument list.  Returns TRUE if
1090132730Skan   the prototype is compatible, FALSE if not.  */
1091132730Skanstatic bool
1092132730Skanvalidate_proto_after_old_defn (tree newdecl, tree newtype, tree oldtype)
1093132730Skan{
1094132730Skan  tree newargs, oldargs;
1095132730Skan  int i;
109618334Speter
1097169699Skan#define END_OF_ARGLIST(t) ((t) == void_type_node)
1098132730Skan
1099132730Skan  oldargs = TYPE_ACTUAL_ARG_TYPES (oldtype);
1100132730Skan  newargs = TYPE_ARG_TYPES (newtype);
1101132730Skan  i = 1;
1102132730Skan
1103132730Skan  for (;;)
1104132730Skan    {
1105132730Skan      tree oldargtype = TREE_VALUE (oldargs);
1106132730Skan      tree newargtype = TREE_VALUE (newargs);
1107132730Skan
1108169699Skan      if (oldargtype == error_mark_node || newargtype == error_mark_node)
1109169699Skan	return false;
1110169699Skan
1111169699Skan      oldargtype = TYPE_MAIN_VARIANT (oldargtype);
1112169699Skan      newargtype = TYPE_MAIN_VARIANT (newargtype);
1113169699Skan
1114132730Skan      if (END_OF_ARGLIST (oldargtype) && END_OF_ARGLIST (newargtype))
1115132730Skan	break;
1116132730Skan
1117132730Skan      /* Reaching the end of just one list means the two decls don't
1118132730Skan	 agree on the number of arguments.  */
1119132730Skan      if (END_OF_ARGLIST (oldargtype))
1120132730Skan	{
1121169699Skan	  error ("prototype for %q+D declares more arguments "
1122169699Skan		 "than previous old-style definition", newdecl);
1123132730Skan	  return false;
1124132730Skan	}
1125132730Skan      else if (END_OF_ARGLIST (newargtype))
1126132730Skan	{
1127169699Skan	  error ("prototype for %q+D declares fewer arguments "
1128169699Skan		 "than previous old-style definition", newdecl);
1129132730Skan	  return false;
1130132730Skan	}
1131132730Skan
1132132730Skan      /* Type for passing arg must be consistent with that declared
1133132730Skan	 for the arg.  */
1134169699Skan      else if (!comptypes (oldargtype, newargtype))
1135132730Skan	{
1136169699Skan	  error ("prototype for %q+D declares argument %d"
1137169699Skan		 " with incompatible type",
1138169699Skan		 newdecl, i);
1139132730Skan	  return false;
1140132730Skan	}
1141132730Skan
1142132730Skan      oldargs = TREE_CHAIN (oldargs);
1143132730Skan      newargs = TREE_CHAIN (newargs);
1144132730Skan      i++;
1145132730Skan    }
1146132730Skan
1147132730Skan  /* If we get here, no errors were found, but do issue a warning
1148132730Skan     for this poor-style construct.  */
1149169699Skan  warning (0, "prototype for %q+D follows non-prototype definition",
1150169699Skan	   newdecl);
1151132730Skan  return true;
1152132730Skan#undef END_OF_ARGLIST
1153132730Skan}
1154132730Skan
1155132730Skan/* Subroutine of diagnose_mismatched_decls.  Report the location of DECL,
1156132730Skan   first in a pair of mismatched declarations, using the diagnostic
1157132730Skan   function DIAG.  */
1158132730Skanstatic void
1159169699Skanlocate_old_decl (tree decl, void (*diag)(const char *, ...) ATTRIBUTE_GCC_CDIAG(1,2))
1160132730Skan{
1161132730Skan  if (TREE_CODE (decl) == FUNCTION_DECL && DECL_BUILT_IN (decl))
1162132730Skan    ;
1163132730Skan  else if (DECL_INITIAL (decl))
1164169699Skan    diag (G_("previous definition of %q+D was here"), decl);
1165132730Skan  else if (C_DECL_IMPLICIT (decl))
1166169699Skan    diag (G_("previous implicit declaration of %q+D was here"), decl);
1167132730Skan  else
1168169699Skan    diag (G_("previous declaration of %q+D was here"), decl);
1169132730Skan}
1170132730Skan
1171132730Skan/* Subroutine of duplicate_decls.  Compare NEWDECL to OLDDECL.
1172132730Skan   Returns true if the caller should proceed to merge the two, false
1173132730Skan   if OLDDECL should simply be discarded.  As a side effect, issues
1174132730Skan   all necessary diagnostics for invalid or poor-style combinations.
1175132730Skan   If it returns true, writes the types of NEWDECL and OLDDECL to
1176132730Skan   *NEWTYPEP and *OLDTYPEP - these may have been adjusted from
1177132730Skan   TREE_TYPE (NEWDECL, OLDDECL) respectively.  */
1178132730Skan
1179132730Skanstatic bool
1180132730Skandiagnose_mismatched_decls (tree newdecl, tree olddecl,
1181132730Skan			   tree *newtypep, tree *oldtypep)
1182132730Skan{
1183132730Skan  tree newtype, oldtype;
1184132730Skan  bool pedwarned = false;
1185132730Skan  bool warned = false;
1186169699Skan  bool retval = true;
1187132730Skan
1188169699Skan#define DECL_EXTERN_INLINE(DECL) (DECL_DECLARED_INLINE_P (DECL)  \
1189169699Skan				  && DECL_EXTERNAL (DECL))
1190169699Skan
1191132730Skan  /* If we have error_mark_node for either decl or type, just discard
1192132730Skan     the previous decl - we're in an error cascade already.  */
1193132730Skan  if (olddecl == error_mark_node || newdecl == error_mark_node)
1194132730Skan    return false;
1195132730Skan  *oldtypep = oldtype = TREE_TYPE (olddecl);
1196132730Skan  *newtypep = newtype = TREE_TYPE (newdecl);
1197132730Skan  if (oldtype == error_mark_node || newtype == error_mark_node)
1198132730Skan    return false;
1199132730Skan
1200132730Skan  /* Two different categories of symbol altogether.  This is an error
1201132730Skan     unless OLDDECL is a builtin.  OLDDECL will be discarded in any case.  */
120218334Speter  if (TREE_CODE (olddecl) != TREE_CODE (newdecl))
120318334Speter    {
1204169699Skan      if (!(TREE_CODE (olddecl) == FUNCTION_DECL
1205169699Skan	    && DECL_BUILT_IN (olddecl)
1206169699Skan	    && !C_DECL_DECLARED_BUILTIN (olddecl)))
1207132730Skan	{
1208169699Skan	  error ("%q+D redeclared as different kind of symbol", newdecl);
1209132730Skan	  locate_old_decl (olddecl, error);
1210132730Skan	}
1211132730Skan      else if (TREE_PUBLIC (newdecl))
1212169699Skan	warning (0, "built-in function %q+D declared as non-function",
1213169699Skan		 newdecl);
1214169699Skan      else
1215169699Skan	warning (OPT_Wshadow, "declaration of %q+D shadows "
1216169699Skan		 "a built-in function", newdecl);
1217132730Skan      return false;
1218132730Skan    }
1219132730Skan
1220161660Skan  /* Enumerators have no linkage, so may only be declared once in a
1221161660Skan     given scope.  */
1222161660Skan  if (TREE_CODE (olddecl) == CONST_DECL)
1223161660Skan    {
1224169699Skan      error ("redeclaration of enumerator %q+D", newdecl);
1225161660Skan      locate_old_decl (olddecl, error);
1226161660Skan      return false;
1227161660Skan    }
1228161660Skan
1229169699Skan  if (!comptypes (oldtype, newtype))
1230132730Skan    {
123118334Speter      if (TREE_CODE (olddecl) == FUNCTION_DECL
1232169699Skan	  && DECL_BUILT_IN (olddecl) && !C_DECL_DECLARED_BUILTIN (olddecl))
123318334Speter	{
1234132730Skan	  /* Accept harmless mismatch in function types.
1235132730Skan	     This is for the ffs and fprintf builtins.  */
1236132730Skan	  tree trytype = match_builtin_function_types (newtype, oldtype);
1237132730Skan
1238169699Skan	  if (trytype && comptypes (newtype, trytype))
1239132730Skan	    *oldtypep = oldtype = trytype;
1240132730Skan	  else
124118334Speter	    {
1242132730Skan	      /* If types don't match for a built-in, throw away the
1243132730Skan		 built-in.  No point in calling locate_old_decl here, it
1244169699Skan		 won't print anything.  */
1245169699Skan	      warning (0, "conflicting types for built-in function %q+D",
1246169699Skan		       newdecl);
1247132730Skan	      return false;
124818334Speter	    }
124918334Speter	}
1250132730Skan      else if (TREE_CODE (olddecl) == FUNCTION_DECL
1251169699Skan	       && DECL_IS_BUILTIN (olddecl))
1252132730Skan	{
1253132730Skan	  /* A conflicting function declaration for a predeclared
1254132730Skan	     function that isn't actually built in.  Objective C uses
1255132730Skan	     these.  The new declaration silently overrides everything
1256132730Skan	     but the volatility (i.e. noreturn) indication.  See also
1257132730Skan	     below.  FIXME: Make Objective C use normal builtins.  */
1258132730Skan	  TREE_THIS_VOLATILE (newdecl) |= TREE_THIS_VOLATILE (olddecl);
1259132730Skan	  return false;
1260132730Skan	}
1261132730Skan      /* Permit void foo (...) to match int foo (...) if the latter is
1262132730Skan	 the definition and implicit int was used.  See
1263132730Skan	 c-torture/compile/920625-2.c.  */
1264132730Skan      else if (TREE_CODE (newdecl) == FUNCTION_DECL && DECL_INITIAL (newdecl)
1265132730Skan	       && TYPE_MAIN_VARIANT (TREE_TYPE (oldtype)) == void_type_node
1266132730Skan	       && TYPE_MAIN_VARIANT (TREE_TYPE (newtype)) == integer_type_node
1267169699Skan	       && C_FUNCTION_IMPLICIT_INT (newdecl) && !DECL_INITIAL (olddecl))
1268132730Skan	{
1269169699Skan	  pedwarn ("conflicting types for %q+D", newdecl);
1270132730Skan	  /* Make sure we keep void as the return type.  */
1271132730Skan	  TREE_TYPE (newdecl) = *newtypep = newtype = oldtype;
1272132730Skan	  C_FUNCTION_IMPLICIT_INT (newdecl) = 0;
1273132730Skan	  pedwarned = true;
1274132730Skan	}
1275169699Skan      /* Permit void foo (...) to match an earlier call to foo (...) with
1276169699Skan	 no declared type (thus, implicitly int).  */
1277169699Skan      else if (TREE_CODE (newdecl) == FUNCTION_DECL
1278169699Skan	       && TYPE_MAIN_VARIANT (TREE_TYPE (newtype)) == void_type_node
1279169699Skan	       && TYPE_MAIN_VARIANT (TREE_TYPE (oldtype)) == integer_type_node
1280169699Skan	       && C_DECL_IMPLICIT (olddecl) && !DECL_INITIAL (olddecl))
1281169699Skan	{
1282169699Skan	  pedwarn ("conflicting types for %q+D", newdecl);
1283169699Skan	  /* Make sure we keep void as the return type.  */
1284169699Skan	  TREE_TYPE (olddecl) = *oldtypep = oldtype = newtype;
1285169699Skan	  pedwarned = true;
1286169699Skan	}
128718334Speter      else
128818334Speter	{
1289169699Skan	  if (TYPE_QUALS (newtype) != TYPE_QUALS (oldtype))
1290169699Skan	    error ("conflicting type qualifiers for %q+D", newdecl);
1291169699Skan	  else
1292169699Skan	    error ("conflicting types for %q+D", newdecl);
1293132730Skan	  diagnose_arglist_conflict (newdecl, olddecl, newtype, oldtype);
1294132730Skan	  locate_old_decl (olddecl, error);
1295132730Skan	  return false;
129618334Speter	}
1297132730Skan    }
129818334Speter
1299132730Skan  /* Redeclaration of a type is a constraint violation (6.7.2.3p1),
1300132730Skan     but silently ignore the redeclaration if either is in a system
1301132730Skan     header.  (Conflicting redeclarations were handled above.)  */
1302132730Skan  if (TREE_CODE (newdecl) == TYPE_DECL)
1303132730Skan    {
1304132730Skan      if (DECL_IN_SYSTEM_HEADER (newdecl) || DECL_IN_SYSTEM_HEADER (olddecl))
1305169699Skan	return true;  /* Allow OLDDECL to continue in use.  */
1306169699Skan
1307169699Skan      error ("redefinition of typedef %q+D", newdecl);
1308132730Skan      locate_old_decl (olddecl, error);
1309132730Skan      return false;
131018334Speter    }
131118334Speter
1312132730Skan  /* Function declarations can either be 'static' or 'extern' (no
1313132730Skan     qualifier is equivalent to 'extern' - C99 6.2.2p5) and therefore
1314189824Sdas     can never conflict with each other on account of linkage
1315189824Sdas     (6.2.2p4).  Multiple definitions are not allowed (6.9p3,5) but
1316189824Sdas     gnu89 mode permits two definitions if one is 'extern inline' and
1317189824Sdas     one is not.  The non- extern-inline definition supersedes the
1318189824Sdas     extern-inline definition.  */
1319169699Skan
1320132730Skan  else if (TREE_CODE (newdecl) == FUNCTION_DECL)
132118334Speter    {
1322132730Skan      /* If you declare a built-in function name as static, or
1323132730Skan	 define the built-in with an old-style definition (so we
1324132730Skan	 can't validate the argument list) the built-in definition is
1325132730Skan	 overridden, but optionally warn this was a bad choice of name.  */
1326132730Skan      if (DECL_BUILT_IN (olddecl)
1327169699Skan	  && !C_DECL_DECLARED_BUILTIN (olddecl)
1328132730Skan	  && (!TREE_PUBLIC (newdecl)
1329132730Skan	      || (DECL_INITIAL (newdecl)
1330132730Skan		  && !TYPE_ARG_TYPES (TREE_TYPE (newdecl)))))
133118334Speter	{
1332169699Skan	  warning (OPT_Wshadow, "declaration of %q+D shadows "
1333169699Skan		   "a built-in function", newdecl);
133418334Speter	  /* Discard the old built-in function.  */
1335132730Skan	  return false;
133618334Speter	}
1337169699Skan
1338132730Skan      if (DECL_INITIAL (newdecl))
133918334Speter	{
1340169699Skan	  if (DECL_INITIAL (olddecl))
134118334Speter	    {
1342169699Skan	      /* If both decls are in the same TU and the new declaration
1343169699Skan		 isn't overriding an extern inline reject the new decl.
1344189824Sdas		 In c99, no overriding is allowed in the same translation
1345189824Sdas		 unit.  */
1346189824Sdas	      if ((!DECL_EXTERN_INLINE (olddecl)
1347189824Sdas		   || DECL_EXTERN_INLINE (newdecl)
1348189824Sdas		   || (!flag_gnu89_inline
1349189824Sdas		       && (!DECL_DECLARED_INLINE_P (olddecl)
1350189824Sdas			   || !lookup_attribute ("gnu_inline",
1351189824Sdas						 DECL_ATTRIBUTES (olddecl)))
1352189824Sdas		       && (!DECL_DECLARED_INLINE_P (newdecl)
1353189824Sdas			   || !lookup_attribute ("gnu_inline",
1354189824Sdas						 DECL_ATTRIBUTES (newdecl))))
1355189824Sdas		  )
1356169699Skan		  && same_translation_unit_p (newdecl, olddecl))
1357169699Skan		{
1358169699Skan		  error ("redefinition of %q+D", newdecl);
1359169699Skan		  locate_old_decl (olddecl, error);
1360169699Skan		  return false;
1361169699Skan		}
136218334Speter	    }
1363132730Skan	}
1364132730Skan      /* If we have a prototype after an old-style function definition,
1365132730Skan	 the argument types must be checked specially.  */
1366132730Skan      else if (DECL_INITIAL (olddecl)
1367132730Skan	       && !TYPE_ARG_TYPES (oldtype) && TYPE_ARG_TYPES (newtype)
1368132730Skan	       && TYPE_ACTUAL_ARG_TYPES (oldtype)
1369132730Skan	       && !validate_proto_after_old_defn (newdecl, newtype, oldtype))
1370132730Skan	{
1371132730Skan	  locate_old_decl (olddecl, error);
1372132730Skan	  return false;
1373132730Skan	}
1374169699Skan      /* A non-static declaration (even an "extern") followed by a
1375169699Skan	 static declaration is undefined behavior per C99 6.2.2p3-5,7.
1376169699Skan	 The same is true for a static forward declaration at block
1377169699Skan	 scope followed by a non-static declaration/definition at file
1378169699Skan	 scope.  Static followed by non-static at the same scope is
1379169699Skan	 not undefined behavior, and is the most convenient way to get
1380169699Skan	 some effects (see e.g.  what unwind-dw2-fde-glibc.c does to
1381169699Skan	 the definition of _Unwind_Find_FDE in unwind-dw2-fde.c), but
1382169699Skan	 we do diagnose it if -Wtraditional.  */
1383132730Skan      if (TREE_PUBLIC (olddecl) && !TREE_PUBLIC (newdecl))
1384132730Skan	{
1385169699Skan	  /* Two exceptions to the rule.  If olddecl is an extern
1386169699Skan	     inline, or a predeclared function that isn't actually
1387169699Skan	     built in, newdecl silently overrides olddecl.  The latter
1388169699Skan	     occur only in Objective C; see also above.  (FIXME: Make
1389169699Skan	     Objective C use normal builtins.)  */
1390169699Skan	  if (!DECL_IS_BUILTIN (olddecl)
1391169699Skan	      && !DECL_EXTERN_INLINE (olddecl))
139218334Speter	    {
1393169699Skan	      error ("static declaration of %q+D follows "
1394169699Skan		     "non-static declaration", newdecl);
1395169699Skan	      locate_old_decl (olddecl, error);
139618334Speter	    }
1397169699Skan	  return false;
139818334Speter	}
1399169699Skan      else if (TREE_PUBLIC (newdecl) && !TREE_PUBLIC (olddecl))
140096263Sobrien	{
1401169699Skan	  if (DECL_CONTEXT (olddecl))
1402169699Skan	    {
1403169699Skan	      error ("non-static declaration of %q+D follows "
1404169699Skan		     "static declaration", newdecl);
1405169699Skan	      locate_old_decl (olddecl, error);
1406169699Skan	      return false;
1407169699Skan	    }
1408169699Skan	  else if (warn_traditional)
1409169699Skan	    {
1410169699Skan	      warning (OPT_Wtraditional, "non-static declaration of %q+D "
1411169699Skan		       "follows static declaration", newdecl);
1412169699Skan	      warned = true;
1413169699Skan	    }
141496263Sobrien	}
1415189824Sdas
1416189824Sdas      /* Make sure gnu_inline attribute is either not present, or
1417189824Sdas	 present on all inline decls.  */
1418189824Sdas      if (DECL_DECLARED_INLINE_P (olddecl)
1419189824Sdas	  && DECL_DECLARED_INLINE_P (newdecl))
1420189824Sdas	{
1421189824Sdas	  bool newa = lookup_attribute ("gnu_inline",
1422189824Sdas					DECL_ATTRIBUTES (newdecl)) != NULL;
1423189824Sdas	  bool olda = lookup_attribute ("gnu_inline",
1424189824Sdas					DECL_ATTRIBUTES (olddecl)) != NULL;
1425189824Sdas	  if (newa != olda)
1426189824Sdas	    {
1427189824Sdas	      error ("%<gnu_inline%> attribute present on %q+D",
1428189824Sdas		     newa ? newdecl : olddecl);
1429189824Sdas	      error ("%Jbut not here", newa ? olddecl : newdecl);
1430189824Sdas	    }
1431189824Sdas	}
143218334Speter    }
1433132730Skan  else if (TREE_CODE (newdecl) == VAR_DECL)
143418334Speter    {
1435132730Skan      /* Only variables can be thread-local, and all declarations must
1436132730Skan	 agree on this property.  */
1437169699Skan      if (C_DECL_THREADPRIVATE_P (olddecl) && !DECL_THREAD_LOCAL_P (newdecl))
143818334Speter	{
1439169699Skan	  /* Nothing to check.  Since OLDDECL is marked threadprivate
1440169699Skan	     and NEWDECL does not have a thread-local attribute, we
1441169699Skan	     will merge the threadprivate attribute into NEWDECL.  */
1442169699Skan	  ;
1443169699Skan	}
1444169699Skan      else if (DECL_THREAD_LOCAL_P (newdecl) != DECL_THREAD_LOCAL_P (olddecl))
1445169699Skan	{
1446169699Skan	  if (DECL_THREAD_LOCAL_P (newdecl))
1447169699Skan	    error ("thread-local declaration of %q+D follows "
1448169699Skan		   "non-thread-local declaration", newdecl);
1449132730Skan	  else
1450169699Skan	    error ("non-thread-local declaration of %q+D follows "
1451169699Skan		   "thread-local declaration", newdecl);
1452132730Skan
1453132730Skan	  locate_old_decl (olddecl, error);
1454132730Skan	  return false;
145518334Speter	}
1456132730Skan
1457132730Skan      /* Multiple initialized definitions are not allowed (6.9p3,5).  */
1458132730Skan      if (DECL_INITIAL (newdecl) && DECL_INITIAL (olddecl))
145918334Speter	{
1460169699Skan	  error ("redefinition of %q+D", newdecl);
1461132730Skan	  locate_old_decl (olddecl, error);
1462132730Skan	  return false;
146318334Speter	}
146418334Speter
1465169699Skan      /* Objects declared at file scope: if the first declaration had
1466169699Skan	 external linkage (even if it was an external reference) the
1467169699Skan	 second must have external linkage as well, or the behavior is
1468169699Skan	 undefined.  If the first declaration had internal linkage, then
1469169699Skan	 the second must too, or else be an external reference (in which
1470169699Skan	 case the composite declaration still has internal linkage).
1471169699Skan	 As for function declarations, we warn about the static-then-
1472169699Skan	 extern case only for -Wtraditional.  See generally 6.2.2p3-5,7.  */
1473169699Skan      if (DECL_FILE_SCOPE_P (newdecl)
1474169699Skan	  && TREE_PUBLIC (newdecl) != TREE_PUBLIC (olddecl))
147518334Speter	{
1476169699Skan	  if (DECL_EXTERNAL (newdecl))
147718334Speter	    {
1478169699Skan	      if (!DECL_FILE_SCOPE_P (olddecl))
1479169699Skan		{
1480169699Skan		  error ("extern declaration of %q+D follows "
1481169699Skan			 "declaration with no linkage", newdecl);
1482169699Skan		  locate_old_decl (olddecl, error);
1483169699Skan		  return false;
1484169699Skan		}
1485169699Skan	      else if (warn_traditional)
1486169699Skan		{
1487169699Skan		  warning (OPT_Wtraditional, "non-static declaration of %q+D "
1488169699Skan			   "follows static declaration", newdecl);
1489169699Skan		  warned = true;
1490169699Skan		}
1491169699Skan	    }
1492169699Skan	  else
1493169699Skan	    {
1494132730Skan	      if (TREE_PUBLIC (newdecl))
1495169699Skan		error ("non-static declaration of %q+D follows "
1496169699Skan		       "static declaration", newdecl);
1497132730Skan	      else
1498169699Skan		error ("static declaration of %q+D follows "
1499169699Skan		       "non-static declaration", newdecl);
150018334Speter
1501132730Skan	      locate_old_decl (olddecl, error);
1502132730Skan	      return false;
150318334Speter	    }
150418334Speter	}
1505132730Skan      /* Two objects with the same name declared at the same block
1506132730Skan	 scope must both be external references (6.7p3).  */
1507169699Skan      else if (!DECL_FILE_SCOPE_P (newdecl))
1508132730Skan	{
1509132730Skan	  if (DECL_EXTERNAL (newdecl))
1510169699Skan	    {
1511169699Skan	      /* Extern with initializer at block scope, which will
1512169699Skan		 already have received an error.  */
1513169699Skan	    }
1514132730Skan	  else if (DECL_EXTERNAL (olddecl))
1515169699Skan	    {
1516169699Skan	      error ("declaration of %q+D with no linkage follows "
1517169699Skan		     "extern declaration", newdecl);
1518169699Skan	      locate_old_decl (olddecl, error);
1519169699Skan	    }
1520132730Skan	  else
1521169699Skan	    {
1522169699Skan	      error ("redeclaration of %q+D with no linkage", newdecl);
1523169699Skan	      locate_old_decl (olddecl, error);
1524169699Skan	    }
1525117421Skan
1526132730Skan	  return false;
1527132730Skan	}
152818334Speter    }
1529132730Skan
1530132730Skan  /* warnings */
1531169699Skan  /* All decls must agree on a visibility.  */
1532169699Skan  if (CODE_CONTAINS_STRUCT (TREE_CODE (newdecl), TS_DECL_WITH_VIS)
1533169699Skan      && DECL_VISIBILITY_SPECIFIED (newdecl) && DECL_VISIBILITY_SPECIFIED (olddecl)
1534132730Skan      && DECL_VISIBILITY (newdecl) != DECL_VISIBILITY (olddecl))
1535117421Skan    {
1536169699Skan      warning (0, "redeclaration of %q+D with different visibility "
1537169699Skan	       "(old visibility preserved)", newdecl);
1538132730Skan      warned = true;
1539117421Skan    }
1540132730Skan
1541132730Skan  if (TREE_CODE (newdecl) == FUNCTION_DECL)
1542117421Skan    {
1543132730Skan      /* Diagnose inline __attribute__ ((noinline)) which is silly.  */
1544132730Skan      if (DECL_DECLARED_INLINE_P (newdecl)
1545132730Skan	  && lookup_attribute ("noinline", DECL_ATTRIBUTES (olddecl)))
154618334Speter	{
1547169699Skan	  warning (OPT_Wattributes, "inline declaration of %qD follows "
1548169699Skan		   "declaration with attribute noinline", newdecl);
1549132730Skan	  warned = true;
155018334Speter	}
1551132730Skan      else if (DECL_DECLARED_INLINE_P (olddecl)
1552132730Skan	       && lookup_attribute ("noinline", DECL_ATTRIBUTES (newdecl)))
155318334Speter	{
1554169699Skan	  warning (OPT_Wattributes, "declaration of %q+D with attribute "
1555169699Skan		   "noinline follows inline declaration ", newdecl);
1556132730Skan	  warned = true;
155718334Speter	}
1558132730Skan
1559132730Skan      /* Inline declaration after use or definition.
1560132730Skan	 ??? Should we still warn about this now we have unit-at-a-time
1561169699Skan	 mode and can get it right?
1562169699Skan	 Definitely don't complain if the decls are in different translation
1563189824Sdas	 units.
1564189824Sdas	 C99 permits this, so don't warn in that case.  (The function
1565189824Sdas	 may not be inlined everywhere in function-at-a-time mode, but
1566189824Sdas	 we still shouldn't warn.)  */
1567169699Skan      if (DECL_DECLARED_INLINE_P (newdecl) && !DECL_DECLARED_INLINE_P (olddecl)
1568189824Sdas	  && same_translation_unit_p (olddecl, newdecl)
1569189824Sdas	  && flag_gnu89_inline)
157018334Speter	{
1571132730Skan	  if (TREE_USED (olddecl))
157218334Speter	    {
1573169699Skan	      warning (0, "%q+D declared inline after being called", olddecl);
1574132730Skan	      warned = true;
157518334Speter	    }
1576132730Skan	  else if (DECL_INITIAL (olddecl))
1577132730Skan	    {
1578169699Skan	      warning (0, "%q+D declared inline after its definition", olddecl);
1579132730Skan	      warned = true;
1580132730Skan	    }
158118334Speter	}
1582132730Skan    }
1583132730Skan  else /* PARM_DECL, VAR_DECL */
1584132730Skan    {
1585169699Skan      /* Redeclaration of a parameter is a constraint violation (this is
1586169699Skan	 not explicitly stated, but follows from C99 6.7p3 [no more than
1587169699Skan	 one declaration of the same identifier with no linkage in the
1588169699Skan	 same scope, except type tags] and 6.2.2p6 [parameters have no
1589169699Skan	 linkage]).  We must check for a forward parameter declaration,
1590169699Skan	 indicated by TREE_ASM_WRITTEN on the old declaration - this is
1591169699Skan	 an extension, the mandatory diagnostic for which is handled by
1592169699Skan	 mark_forward_parm_decls.  */
1593169699Skan
1594132730Skan      if (TREE_CODE (newdecl) == PARM_DECL
1595132730Skan	  && (!TREE_ASM_WRITTEN (olddecl) || TREE_ASM_WRITTEN (newdecl)))
159618334Speter	{
1597169699Skan	  error ("redefinition of parameter %q+D", newdecl);
1598132730Skan	  locate_old_decl (olddecl, error);
1599132730Skan	  return false;
1600132730Skan	}
160118334Speter    }
160218334Speter
1603132730Skan  /* Optional warning for completely redundant decls.  */
1604132730Skan  if (!warned && !pedwarned
1605132730Skan      && warn_redundant_decls
1606132730Skan      /* Don't warn about a function declaration followed by a
1607132730Skan	 definition.  */
1608132730Skan      && !(TREE_CODE (newdecl) == FUNCTION_DECL
1609132730Skan	   && DECL_INITIAL (newdecl) && !DECL_INITIAL (olddecl))
1610169699Skan      /* Don't warn about redundant redeclarations of builtins.  */
1611132730Skan      && !(TREE_CODE (newdecl) == FUNCTION_DECL
1612132730Skan	   && !DECL_BUILT_IN (newdecl)
1613132730Skan	   && DECL_BUILT_IN (olddecl)
1614169699Skan	   && !C_DECL_DECLARED_BUILTIN (olddecl))
1615132730Skan      /* Don't warn about an extern followed by a definition.  */
1616132730Skan      && !(DECL_EXTERNAL (olddecl) && !DECL_EXTERNAL (newdecl))
1617132730Skan      /* Don't warn about forward parameter decls.  */
1618132730Skan      && !(TREE_CODE (newdecl) == PARM_DECL
1619149846Sobrien	   && TREE_ASM_WRITTEN (olddecl) && !TREE_ASM_WRITTEN (newdecl))
1620149846Sobrien      /* Don't warn about a variable definition following a declaration.  */
1621149846Sobrien      && !(TREE_CODE (newdecl) == VAR_DECL
1622149846Sobrien	   && DECL_INITIAL (newdecl) && !DECL_INITIAL (olddecl)))
162318334Speter    {
1624169699Skan      warning (OPT_Wredundant_decls, "redundant redeclaration of %q+D",
1625169699Skan	       newdecl);
1626132730Skan      warned = true;
162718334Speter    }
162818334Speter
1629132730Skan  /* Report location of previous decl/defn in a consistent manner.  */
1630132730Skan  if (warned || pedwarned)
1631169699Skan    locate_old_decl (olddecl, pedwarned ? pedwarn : warning0);
163218334Speter
1633169699Skan#undef DECL_EXTERN_INLINE
1634169699Skan
1635169699Skan  return retval;
1636132730Skan}
163718334Speter
1638132730Skan/* Subroutine of duplicate_decls.  NEWDECL has been found to be
1639132730Skan   consistent with OLDDECL, but carries new information.  Merge the
1640132730Skan   new information into OLDDECL.  This function issues no
1641132730Skan   diagnostics.  */
1642132730Skan
1643132730Skanstatic void
1644132730Skanmerge_decls (tree newdecl, tree olddecl, tree newtype, tree oldtype)
1645132730Skan{
1646189824Sdas  bool new_is_definition = (TREE_CODE (newdecl) == FUNCTION_DECL
1647189824Sdas			    && DECL_INITIAL (newdecl) != 0);
1648189824Sdas  bool new_is_prototype = (TREE_CODE (newdecl) == FUNCTION_DECL
1649189824Sdas			   && TYPE_ARG_TYPES (TREE_TYPE (newdecl)) != 0);
1650189824Sdas  bool old_is_prototype = (TREE_CODE (olddecl) == FUNCTION_DECL
1651189824Sdas			   && TYPE_ARG_TYPES (TREE_TYPE (olddecl)) != 0);
1652189824Sdas  bool extern_changed = false;
1653132730Skan
1654169699Skan  /* For real parm decl following a forward decl, rechain the old decl
1655169699Skan     in its new location and clear TREE_ASM_WRITTEN (it's not a
1656169699Skan     forward decl anymore).  */
1657132730Skan  if (TREE_CODE (newdecl) == PARM_DECL
1658169699Skan      && TREE_ASM_WRITTEN (olddecl) && !TREE_ASM_WRITTEN (newdecl))
165918334Speter    {
1660169699Skan      struct c_binding *b, **here;
1661169699Skan
1662169699Skan      for (here = &current_scope->bindings; *here; here = &(*here)->prev)
1663169699Skan	if ((*here)->decl == olddecl)
1664169699Skan	  goto found;
1665169699Skan      gcc_unreachable ();
1666169699Skan
1667169699Skan    found:
1668169699Skan      b = *here;
1669169699Skan      *here = b->prev;
1670169699Skan      b->prev = current_scope->bindings;
1671169699Skan      current_scope->bindings = b;
1672169699Skan
1673132730Skan      TREE_ASM_WRITTEN (olddecl) = 0;
1674132730Skan    }
167550397Sobrien
1676132730Skan  DECL_ATTRIBUTES (newdecl)
1677169699Skan    = targetm.merge_decl_attributes (olddecl, newdecl);
167818334Speter
1679132730Skan  /* Merge the data types specified in the two decls.  */
1680132730Skan  TREE_TYPE (newdecl)
1681132730Skan    = TREE_TYPE (olddecl)
1682169699Skan    = composite_type (newtype, oldtype);
168318334Speter
1684132730Skan  /* Lay the type out, unless already done.  */
1685169699Skan  if (!comptypes (oldtype, TREE_TYPE (newdecl)))
1686132730Skan    {
1687132730Skan      if (TREE_TYPE (newdecl) != error_mark_node)
1688132730Skan	layout_type (TREE_TYPE (newdecl));
1689132730Skan      if (TREE_CODE (newdecl) != FUNCTION_DECL
1690132730Skan	  && TREE_CODE (newdecl) != TYPE_DECL
1691132730Skan	  && TREE_CODE (newdecl) != CONST_DECL)
1692132730Skan	layout_decl (newdecl, 0);
1693132730Skan    }
1694132730Skan  else
1695132730Skan    {
1696132730Skan      /* Since the type is OLDDECL's, make OLDDECL's size go with.  */
1697132730Skan      DECL_SIZE (newdecl) = DECL_SIZE (olddecl);
1698132730Skan      DECL_SIZE_UNIT (newdecl) = DECL_SIZE_UNIT (olddecl);
1699132730Skan      DECL_MODE (newdecl) = DECL_MODE (olddecl);
1700259705Spfg      if (DECL_ALIGN (olddecl) > DECL_ALIGN (newdecl))
1701259705Spfg	{
1702259705Spfg	  DECL_ALIGN (newdecl) = DECL_ALIGN (olddecl);
1703259705Spfg	  DECL_USER_ALIGN (newdecl) |= DECL_ALIGN (olddecl);
1704259705Spfg	}
1705132730Skan    }
170618334Speter
170790075Sobrien
1708132730Skan  /* Merge the type qualifiers.  */
1709132730Skan  if (TREE_READONLY (newdecl))
1710132730Skan    TREE_READONLY (olddecl) = 1;
171118334Speter
1712132730Skan  if (TREE_THIS_VOLATILE (newdecl))
1713169699Skan    TREE_THIS_VOLATILE (olddecl) = 1;
171418334Speter
1715169699Skan  /* Merge deprecatedness.  */
1716169699Skan  if (TREE_DEPRECATED (newdecl))
1717169699Skan    TREE_DEPRECATED (olddecl) = 1;
1718169699Skan
1719260919Spfg  /* APPLE LOCAL begin "unavailable" attribute (radar 2809697) */
1720260919Spfg  /* Merge unavailableness.  */
1721260919Spfg  if (TREE_UNAVAILABLE (newdecl))
1722260919Spfg    TREE_UNAVAILABLE (olddecl) = 1;
1723260919Spfg  /* APPLE LOCAL end "unavailable" attribute (radar 2809697) */
1724260919Spfg
1725169699Skan  /* Keep source location of definition rather than declaration and of
1726169699Skan     prototype rather than non-prototype unless that prototype is
1727169699Skan     built-in.  */
1728169699Skan  if ((DECL_INITIAL (newdecl) == 0 && DECL_INITIAL (olddecl) != 0)
1729169699Skan      || (old_is_prototype && !new_is_prototype
1730169699Skan	  && !C_DECL_BUILTIN_PROTOTYPE (olddecl)))
1731132730Skan    DECL_SOURCE_LOCATION (newdecl) = DECL_SOURCE_LOCATION (olddecl);
173218334Speter
1733132730Skan  /* Merge the initialization information.  */
1734132730Skan   if (DECL_INITIAL (newdecl) == 0)
1735132730Skan    DECL_INITIAL (newdecl) = DECL_INITIAL (olddecl);
173618334Speter
1737169699Skan  /* Merge the threadprivate attribute.  */
1738169699Skan  if (TREE_CODE (olddecl) == VAR_DECL && C_DECL_THREADPRIVATE_P (olddecl))
1739169699Skan    {
1740169699Skan      DECL_TLS_MODEL (newdecl) = DECL_TLS_MODEL (olddecl);
1741169699Skan      C_DECL_THREADPRIVATE_P (newdecl) = 1;
1742169699Skan    }
174390075Sobrien
1744169699Skan  if (CODE_CONTAINS_STRUCT (TREE_CODE (olddecl), TS_DECL_WITH_VIS))
1745169699Skan    {
1746169699Skan      /* Merge the unused-warning information.  */
1747169699Skan      if (DECL_IN_SYSTEM_HEADER (olddecl))
1748169699Skan	DECL_IN_SYSTEM_HEADER (newdecl) = 1;
1749169699Skan      else if (DECL_IN_SYSTEM_HEADER (newdecl))
1750169699Skan	DECL_IN_SYSTEM_HEADER (olddecl) = 1;
1751132730Skan
1752169699Skan      /* Merge the section attribute.
1753169699Skan	 We want to issue an error if the sections conflict but that
1754169699Skan	 must be done later in decl_attributes since we are called
1755169699Skan	 before attributes are assigned.  */
1756169699Skan      if (DECL_SECTION_NAME (newdecl) == NULL_TREE)
1757169699Skan	DECL_SECTION_NAME (newdecl) = DECL_SECTION_NAME (olddecl);
1758132730Skan
1759169699Skan      /* Copy the assembler name.
1760169699Skan	 Currently, it can only be defined in the prototype.  */
1761169699Skan      COPY_DECL_ASSEMBLER_NAME (olddecl, newdecl);
176218334Speter
1763169699Skan      /* Use visibility of whichever declaration had it specified */
1764169699Skan      if (DECL_VISIBILITY_SPECIFIED (olddecl))
1765169699Skan	{
1766169699Skan	  DECL_VISIBILITY (newdecl) = DECL_VISIBILITY (olddecl);
1767169699Skan	  DECL_VISIBILITY_SPECIFIED (newdecl) = 1;
1768169699Skan	}
176996263Sobrien
1770169699Skan      if (TREE_CODE (newdecl) == FUNCTION_DECL)
1771169699Skan	{
1772169699Skan	  DECL_STATIC_CONSTRUCTOR(newdecl) |= DECL_STATIC_CONSTRUCTOR(olddecl);
1773169699Skan	  DECL_STATIC_DESTRUCTOR (newdecl) |= DECL_STATIC_DESTRUCTOR (olddecl);
1774169699Skan	  DECL_NO_LIMIT_STACK (newdecl) |= DECL_NO_LIMIT_STACK (olddecl);
1775169699Skan	  DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (newdecl)
1776169699Skan	    |= DECL_NO_INSTRUMENT_FUNCTION_ENTRY_EXIT (olddecl);
1777169699Skan	  TREE_THIS_VOLATILE (newdecl) |= TREE_THIS_VOLATILE (olddecl);
1778169699Skan	  TREE_READONLY (newdecl) |= TREE_READONLY (olddecl);
1779169699Skan	  DECL_IS_MALLOC (newdecl) |= DECL_IS_MALLOC (olddecl);
1780169699Skan	  DECL_IS_PURE (newdecl) |= DECL_IS_PURE (olddecl);
1781169699Skan	  DECL_IS_NOVOPS (newdecl) |= DECL_IS_NOVOPS (olddecl);
1782169699Skan	}
1783169699Skan
1784169699Skan      /* Merge the storage class information.  */
1785169699Skan      merge_weak (newdecl, olddecl);
1786169699Skan
1787169699Skan      /* For functions, static overrides non-static.  */
1788169699Skan      if (TREE_CODE (newdecl) == FUNCTION_DECL)
1789169699Skan	{
1790169699Skan	  TREE_PUBLIC (newdecl) &= TREE_PUBLIC (olddecl);
1791169699Skan	  /* This is since we don't automatically
1792169699Skan	     copy the attributes of NEWDECL into OLDDECL.  */
1793169699Skan	  TREE_PUBLIC (olddecl) = TREE_PUBLIC (newdecl);
1794169699Skan	  /* If this clears `static', clear it in the identifier too.  */
1795169699Skan	  if (!TREE_PUBLIC (olddecl))
1796169699Skan	    TREE_PUBLIC (DECL_NAME (olddecl)) = 0;
1797169699Skan	}
179818334Speter    }
1799169699Skan
1800189824Sdas  /* In c99, 'extern' declaration before (or after) 'inline' means this
1801189824Sdas     function is not DECL_EXTERNAL, unless 'gnu_inline' attribute
1802189824Sdas     is present.  */
1803189824Sdas  if (TREE_CODE (newdecl) == FUNCTION_DECL
1804189824Sdas      && !flag_gnu89_inline
1805189824Sdas      && (DECL_DECLARED_INLINE_P (newdecl)
1806189824Sdas	  || DECL_DECLARED_INLINE_P (olddecl))
1807189824Sdas      && (!DECL_DECLARED_INLINE_P (newdecl)
1808189824Sdas	  || !DECL_DECLARED_INLINE_P (olddecl)
1809189824Sdas	  || !DECL_EXTERNAL (olddecl))
1810189824Sdas      && DECL_EXTERNAL (newdecl)
1811189824Sdas      && !lookup_attribute ("gnu_inline", DECL_ATTRIBUTES (newdecl)))
1812189824Sdas    DECL_EXTERNAL (newdecl) = 0;
1813189824Sdas
181418334Speter  if (DECL_EXTERNAL (newdecl))
181518334Speter    {
1816132730Skan      TREE_STATIC (newdecl) = TREE_STATIC (olddecl);
1817132730Skan      DECL_EXTERNAL (newdecl) = DECL_EXTERNAL (olddecl);
1818132730Skan
181918334Speter      /* An extern decl does not override previous storage class.  */
182018334Speter      TREE_PUBLIC (newdecl) = TREE_PUBLIC (olddecl);
1821169699Skan      if (!DECL_EXTERNAL (newdecl))
1822132730Skan	{
1823132730Skan	  DECL_CONTEXT (newdecl) = DECL_CONTEXT (olddecl);
1824132730Skan	  DECL_COMMON (newdecl) = DECL_COMMON (olddecl);
1825132730Skan	}
182618334Speter    }
182718334Speter  else
182818334Speter    {
182918334Speter      TREE_STATIC (olddecl) = TREE_STATIC (newdecl);
183018334Speter      TREE_PUBLIC (olddecl) = TREE_PUBLIC (newdecl);
183118334Speter    }
183218334Speter
183350397Sobrien  if (TREE_CODE (newdecl) == FUNCTION_DECL)
183418334Speter    {
183590075Sobrien      /* If we're redefining a function previously defined as extern
183690075Sobrien	 inline, make sure we emit debug info for the inline before we
1837169699Skan	 throw it away, in case it was inlined into a function that
1838169699Skan	 hasn't been written out yet.  */
1839110623Skan      if (new_is_definition && DECL_INITIAL (olddecl))
184090075Sobrien	{
1841132730Skan	  if (TREE_USED (olddecl)
1842132730Skan	      /* In unit-at-a-time mode we never inline re-defined extern
1843169699Skan		 inline functions.  */
1844132730Skan	      && !flag_unit_at_a_time
1845132730Skan	      && cgraph_function_possibly_inlined_p (olddecl))
1846110623Skan	    (*debug_hooks->outlining_inline_function) (olddecl);
184790075Sobrien
184890075Sobrien	  /* The new defn must not be inline.  */
184990075Sobrien	  DECL_INLINE (newdecl) = 0;
185090075Sobrien	  DECL_UNINLINABLE (newdecl) = 1;
185190075Sobrien	}
185290075Sobrien      else
185390075Sobrien	{
1854169699Skan	  /* If either decl says `inline', this fn is inline, unless
1855169699Skan	     its definition was passed already.  */
185690075Sobrien	  if (DECL_DECLARED_INLINE_P (newdecl)
185790075Sobrien	      || DECL_DECLARED_INLINE_P (olddecl))
185890075Sobrien	    DECL_DECLARED_INLINE_P (newdecl) = 1;
185990075Sobrien
186090075Sobrien	  DECL_UNINLINABLE (newdecl) = DECL_UNINLINABLE (olddecl)
186190075Sobrien	    = (DECL_UNINLINABLE (newdecl) || DECL_UNINLINABLE (olddecl));
186290075Sobrien	}
186390075Sobrien
186418334Speter      if (DECL_BUILT_IN (olddecl))
186518334Speter	{
1866169699Skan	  /* If redeclaring a builtin function, it stays built in.
1867169699Skan	     But it gets tagged as having been declared.  */
1868132730Skan	  DECL_BUILT_IN_CLASS (newdecl) = DECL_BUILT_IN_CLASS (olddecl);
1869132730Skan	  DECL_FUNCTION_CODE (newdecl) = DECL_FUNCTION_CODE (olddecl);
1870169699Skan	  C_DECL_DECLARED_BUILTIN (newdecl) = 1;
1871169699Skan	  if (new_is_prototype)
1872169699Skan	    C_DECL_BUILTIN_PROTOTYPE (newdecl) = 0;
1873169699Skan	  else
1874169699Skan	    C_DECL_BUILTIN_PROTOTYPE (newdecl)
1875169699Skan	      = C_DECL_BUILTIN_PROTOTYPE (olddecl);
187618334Speter	}
187790075Sobrien
187850397Sobrien      /* Also preserve various other info from the definition.  */
1879169699Skan      if (!new_is_definition)
188050397Sobrien	{
188150397Sobrien	  DECL_RESULT (newdecl) = DECL_RESULT (olddecl);
1882132730Skan	  DECL_INITIAL (newdecl) = DECL_INITIAL (olddecl);
1883169699Skan	  DECL_STRUCT_FUNCTION (newdecl) = DECL_STRUCT_FUNCTION (olddecl);
188490075Sobrien	  DECL_SAVED_TREE (newdecl) = DECL_SAVED_TREE (olddecl);
188550397Sobrien	  DECL_ARGUMENTS (newdecl) = DECL_ARGUMENTS (olddecl);
188690075Sobrien
188790075Sobrien	  /* Set DECL_INLINE on the declaration if we've got a body
188890075Sobrien	     from which to instantiate.  */
1889169699Skan	  if (DECL_INLINE (olddecl) && !DECL_UNINLINABLE (newdecl))
189090075Sobrien	    {
189190075Sobrien	      DECL_INLINE (newdecl) = 1;
189290075Sobrien	      DECL_ABSTRACT_ORIGIN (newdecl)
1893132730Skan		= DECL_ABSTRACT_ORIGIN (olddecl);
189490075Sobrien	    }
189550397Sobrien	}
189690075Sobrien      else
189790075Sobrien	{
189890075Sobrien	  /* If a previous declaration said inline, mark the
189990075Sobrien	     definition as inlinable.  */
190090075Sobrien	  if (DECL_DECLARED_INLINE_P (newdecl)
1901169699Skan	      && !DECL_UNINLINABLE (newdecl))
190290075Sobrien	    DECL_INLINE (newdecl) = 1;
190390075Sobrien	}
190450397Sobrien    }
190518334Speter
1906189824Sdas   extern_changed = DECL_EXTERNAL (olddecl) && !DECL_EXTERNAL (newdecl);
1907189824Sdas
190818334Speter  /* Copy most of the decl-specific fields of NEWDECL into OLDDECL.
1909169699Skan     But preserve OLDDECL's DECL_UID and DECL_CONTEXT.  */
191018334Speter  {
191190075Sobrien    unsigned olddecl_uid = DECL_UID (olddecl);
1912169699Skan    tree olddecl_context = DECL_CONTEXT (olddecl);
191318334Speter
191490075Sobrien    memcpy ((char *) olddecl + sizeof (struct tree_common),
191590075Sobrien	    (char *) newdecl + sizeof (struct tree_common),
1916169699Skan	    sizeof (struct tree_decl_common) - sizeof (struct tree_common));
1917169699Skan    switch (TREE_CODE (olddecl))
1918169699Skan      {
1919169699Skan      case FIELD_DECL:
1920169699Skan      case VAR_DECL:
1921169699Skan      case PARM_DECL:
1922169699Skan      case LABEL_DECL:
1923169699Skan      case RESULT_DECL:
1924169699Skan      case CONST_DECL:
1925169699Skan      case TYPE_DECL:
1926169699Skan      case FUNCTION_DECL:
1927169699Skan	memcpy ((char *) olddecl + sizeof (struct tree_decl_common),
1928169699Skan		(char *) newdecl + sizeof (struct tree_decl_common),
1929169699Skan		tree_code_size (TREE_CODE (olddecl)) - sizeof (struct tree_decl_common));
1930169699Skan	break;
1931169699Skan
1932169699Skan      default:
1933169699Skan
1934169699Skan	memcpy ((char *) olddecl + sizeof (struct tree_decl_common),
1935169699Skan		(char *) newdecl + sizeof (struct tree_decl_common),
1936169699Skan		sizeof (struct tree_decl_non_common) - sizeof (struct tree_decl_common));
1937169699Skan      }
193818334Speter    DECL_UID (olddecl) = olddecl_uid;
1939169699Skan    DECL_CONTEXT (olddecl) = olddecl_context;
194018334Speter  }
194118334Speter
1942132730Skan  /* If OLDDECL had its DECL_RTL instantiated, re-invoke make_decl_rtl
1943119268Skan     so that encode_section_info has a chance to look at the new decl
1944119268Skan     flags and attributes.  */
1945119268Skan  if (DECL_RTL_SET_P (olddecl)
1946119268Skan      && (TREE_CODE (olddecl) == FUNCTION_DECL
1947119268Skan	  || (TREE_CODE (olddecl) == VAR_DECL
1948119268Skan	      && TREE_STATIC (olddecl))))
1949169699Skan    make_decl_rtl (olddecl);
1950189824Sdas
1951189824Sdas  /* If we changed a function from DECL_EXTERNAL to !DECL_EXTERNAL,
1952189824Sdas     and the definition is coming from the old version, cgraph needs
1953189824Sdas     to be called again.  */
1954189824Sdas  if (extern_changed && !new_is_definition
1955189824Sdas      && TREE_CODE (olddecl) == FUNCTION_DECL && DECL_INITIAL (olddecl))
1956189824Sdas    cgraph_finalize_function (olddecl, false);
1957132730Skan}
1958119268Skan
1959132730Skan/* Handle when a new declaration NEWDECL has the same name as an old
1960132730Skan   one OLDDECL in the same binding contour.  Prints an error message
1961132730Skan   if appropriate.
1962132730Skan
1963132730Skan   If safely possible, alter OLDDECL to look like NEWDECL, and return
1964132730Skan   true.  Otherwise, return false.  */
1965132730Skan
1966132730Skanstatic bool
1967132730Skanduplicate_decls (tree newdecl, tree olddecl)
1968132730Skan{
1969169699Skan  tree newtype = NULL, oldtype = NULL;
1970132730Skan
1971132730Skan  if (!diagnose_mismatched_decls (newdecl, olddecl, &newtype, &oldtype))
1972169699Skan    {
1973169699Skan      /* Avoid `unused variable' and other warnings warnings for OLDDECL.  */
1974169699Skan      TREE_NO_WARNING (olddecl) = 1;
1975169699Skan      return false;
1976169699Skan    }
1977132730Skan
1978132730Skan  merge_decls (newdecl, olddecl, newtype, oldtype);
1979132730Skan  return true;
198018334Speter}
1981169699Skan
1982132730Skan
1983169699Skan/* Check whether decl-node NEW_DECL shadows an existing declaration.  */
1984132730Skanstatic void
1985169699Skanwarn_if_shadowing (tree new_decl)
1986132730Skan{
1987169699Skan  struct c_binding *b;
1988132730Skan
1989169699Skan  /* Shadow warnings wanted?  */
1990169699Skan  if (!warn_shadow
1991132730Skan      /* No shadow warnings for internally generated vars.  */
1992169699Skan      || DECL_IS_BUILTIN (new_decl)
1993132730Skan      /* No shadow warnings for vars made for inlining.  */
1994169699Skan      || DECL_FROM_INLINE (new_decl))
199590075Sobrien    return;
199690075Sobrien
1997169699Skan  /* Is anything being shadowed?  Invisible decls do not count.  */
1998169699Skan  for (b = I_SYMBOL_BINDING (DECL_NAME (new_decl)); b; b = b->shadowed)
1999169699Skan    if (b->decl && b->decl != new_decl && !b->invisible)
2000169699Skan      {
2001169699Skan	tree old_decl = b->decl;
200290075Sobrien
2003169699Skan	if (old_decl == error_mark_node)
2004169699Skan	  {
2005169699Skan	    warning (OPT_Wshadow, "declaration of %q+D shadows previous "
2006169699Skan		     "non-variable", new_decl);
2007169699Skan	    break;
2008169699Skan	  }
2009169699Skan	else if (TREE_CODE (old_decl) == PARM_DECL)
2010169699Skan	  warning (OPT_Wshadow, "declaration of %q+D shadows a parameter",
2011169699Skan		   new_decl);
2012169699Skan	else if (DECL_FILE_SCOPE_P (old_decl))
2013169699Skan	  warning (OPT_Wshadow, "declaration of %q+D shadows a global "
2014169699Skan		   "declaration", new_decl);
2015169699Skan	else if (TREE_CODE (old_decl) == FUNCTION_DECL
2016169699Skan		 && DECL_BUILT_IN (old_decl))
2017169699Skan	  {
2018169699Skan	    warning (OPT_Wshadow, "declaration of %q+D shadows "
2019169699Skan		     "a built-in function", new_decl);
2020169699Skan	    break;
2021169699Skan	  }
2022169699Skan	else
2023169699Skan	  warning (OPT_Wshadow, "declaration of %q+D shadows a previous local",
2024169699Skan		   new_decl);
2025169699Skan
2026169699Skan	warning (OPT_Wshadow, "%Jshadowed declaration is here", old_decl);
2027169699Skan
2028169699Skan	break;
2029169699Skan      }
2030132730Skan}
2031132730Skan
2032132730Skan
2033132730Skan/* Subroutine of pushdecl.
2034132730Skan
2035132730Skan   X is a TYPE_DECL for a typedef statement.  Create a brand new
2036132730Skan   ..._TYPE node (which will be just a variant of the existing
2037132730Skan   ..._TYPE node with identical properties) and then install X
2038132730Skan   as the TYPE_NAME of this brand new (duplicate) ..._TYPE node.
2039132730Skan
2040132730Skan   The whole point here is to end up with a situation where each
2041132730Skan   and every ..._TYPE node the compiler creates will be uniquely
2042132730Skan   associated with AT MOST one node representing a typedef name.
2043132730Skan   This way, even though the compiler substitutes corresponding
2044132730Skan   ..._TYPE nodes for TYPE_DECL (i.e. "typedef name") nodes very
2045132730Skan   early on, later parts of the compiler can always do the reverse
2046132730Skan   translation and get back the corresponding typedef name.  For
2047132730Skan   example, given:
2048132730Skan
2049169699Skan	typedef struct S MY_TYPE;
2050132730Skan	MY_TYPE object;
2051132730Skan
2052132730Skan   Later parts of the compiler might only know that `object' was of
2053132730Skan   type `struct S' if it were not for code just below.  With this
2054132730Skan   code however, later parts of the compiler see something like:
2055132730Skan
2056132730Skan	struct S' == struct S
2057132730Skan	typedef struct S' MY_TYPE;
2058132730Skan	struct S' object;
2059132730Skan
2060132730Skan    And they can then deduce (from the node for type struct S') that
2061132730Skan    the original object declaration was:
2062132730Skan
2063132730Skan		MY_TYPE object;
2064132730Skan
2065132730Skan    Being able to do this is important for proper support of protoize,
2066132730Skan    and also for generating precise symbolic debugging information
2067132730Skan    which takes full account of the programmer's (typedef) vocabulary.
2068132730Skan
2069132730Skan    Obviously, we don't want to generate a duplicate ..._TYPE node if
2070132730Skan    the TYPE_DECL node that we are now processing really represents a
2071132730Skan    standard built-in type.
2072132730Skan
2073132730Skan    Since all standard types are effectively declared at line zero
2074132730Skan    in the source file, we can easily check to see if we are working
2075132730Skan    on a standard type by checking the current value of lineno.  */
2076132730Skan
2077132730Skanstatic void
2078132730Skanclone_underlying_type (tree x)
2079132730Skan{
2080169699Skan  if (DECL_IS_BUILTIN (x))
208190075Sobrien    {
2082132730Skan      if (TYPE_NAME (TREE_TYPE (x)) == 0)
2083132730Skan	TYPE_NAME (TREE_TYPE (x)) = x;
208490075Sobrien    }
2085132730Skan  else if (TREE_TYPE (x) != error_mark_node
2086132730Skan	   && DECL_ORIGINAL_TYPE (x) == NULL_TREE)
208790075Sobrien    {
2088132730Skan      tree tt = TREE_TYPE (x);
2089132730Skan      DECL_ORIGINAL_TYPE (x) = tt;
2090169699Skan      tt = build_variant_type_copy (tt);
2091132730Skan      TYPE_NAME (tt) = x;
2092132730Skan      TREE_USED (tt) = TREE_USED (x);
2093132730Skan      TREE_TYPE (x) = tt;
209490075Sobrien    }
209590075Sobrien}
209690075Sobrien
209718334Speter/* Record a decl-node X as belonging to the current lexical scope.
209818334Speter   Check for errors (such as an incompatible declaration for the same
209918334Speter   name already seen in the same scope).
210018334Speter
210118334Speter   Returns either X or an old decl for the same name.
210218334Speter   If an old decl is returned, it may have been smashed
210318334Speter   to agree with what X says.  */
210418334Speter
210518334Spetertree
2106132730Skanpushdecl (tree x)
210718334Speter{
210890075Sobrien  tree name = DECL_NAME (x);
2109132730Skan  struct c_scope *scope = current_scope;
2110169699Skan  struct c_binding *b;
2111169699Skan  bool nested = false;
211218334Speter
211390075Sobrien  /* Functions need the lang_decl data.  */
2114169699Skan  if (TREE_CODE (x) == FUNCTION_DECL && !DECL_LANG_SPECIFIC (x))
2115169699Skan    DECL_LANG_SPECIFIC (x) = GGC_CNEW (struct lang_decl);
211690075Sobrien
2117169699Skan  /* Must set DECL_CONTEXT for everything not at file scope or
2118169699Skan     DECL_FILE_SCOPE_P won't work.  Local externs don't count
2119169699Skan     unless they have initializers (which generate code).  */
2120169699Skan  if (current_function_decl
2121169699Skan      && ((TREE_CODE (x) != FUNCTION_DECL && TREE_CODE (x) != VAR_DECL)
2122169699Skan	  || DECL_INITIAL (x) || !DECL_EXTERNAL (x)))
2123132730Skan    DECL_CONTEXT (x) = current_function_decl;
212418334Speter
2125169699Skan  /* If this is of variably modified type, prevent jumping into its
2126169699Skan     scope.  */
2127169699Skan  if ((TREE_CODE (x) == VAR_DECL || TREE_CODE (x) == TYPE_DECL)
2128169699Skan      && variably_modified_type_p (TREE_TYPE (x), NULL_TREE))
2129169699Skan    c_begin_vm_scope (scope->depth);
2130169699Skan
2131169699Skan  /* Anonymous decls are just inserted in the scope.  */
2132169699Skan  if (!name)
213318334Speter    {
2134169699Skan      bind (name, x, scope, /*invisible=*/false, /*nested=*/false);
2135169699Skan      return x;
2136169699Skan    }
213718334Speter
2138169699Skan  /* First, see if there is another declaration with the same name in
2139169699Skan     the current scope.  If there is, duplicate_decls may do all the
2140169699Skan     work for us.  If duplicate_decls returns false, that indicates
2141169699Skan     two incompatible decls in the same scope; we are to silently
2142169699Skan     replace the old one (duplicate_decls has issued all appropriate
2143169699Skan     diagnostics).  In particular, we should not consider possible
2144169699Skan     duplicates in the external scope, or shadowing.  */
2145169699Skan  b = I_SYMBOL_BINDING (name);
2146169699Skan  if (b && B_IN_SCOPE (b, scope))
2147169699Skan    {
2148169699Skan      struct c_binding *b_ext, *b_use;
2149169699Skan      tree type = TREE_TYPE (x);
2150169699Skan      tree visdecl = b->decl;
2151169699Skan      tree vistype = TREE_TYPE (visdecl);
2152169699Skan      if (TREE_CODE (TREE_TYPE (x)) == ARRAY_TYPE
2153169699Skan	  && COMPLETE_TYPE_P (TREE_TYPE (x)))
2154169699Skan	b->inner_comp = false;
2155169699Skan      b_use = b;
2156169699Skan      b_ext = b;
2157169699Skan      /* If this is an external linkage declaration, we should check
2158169699Skan	 for compatibility with the type in the external scope before
2159169699Skan	 setting the type at this scope based on the visible
2160169699Skan	 information only.  */
2161169699Skan      if (TREE_PUBLIC (x) && TREE_PUBLIC (visdecl))
2162169699Skan	{
2163169699Skan	  while (b_ext && !B_IN_EXTERNAL_SCOPE (b_ext))
2164169699Skan	    b_ext = b_ext->shadowed;
2165169699Skan	  if (b_ext)
2166169699Skan	    {
2167169699Skan	      b_use = b_ext;
2168169699Skan	      if (b_use->type)
2169169699Skan		TREE_TYPE (b_use->decl) = b_use->type;
2170169699Skan	    }
2171169699Skan	}
2172169699Skan      if (duplicate_decls (x, b_use->decl))
2173169699Skan	{
2174169699Skan	  if (b_use != b)
2175169699Skan	    {
2176169699Skan	      /* Save the updated type in the external scope and
2177169699Skan		 restore the proper type for this scope.  */
2178169699Skan	      tree thistype;
2179169699Skan	      if (comptypes (vistype, type))
2180169699Skan		thistype = composite_type (vistype, type);
2181169699Skan	      else
2182169699Skan		thistype = TREE_TYPE (b_use->decl);
2183169699Skan	      b_use->type = TREE_TYPE (b_use->decl);
2184169699Skan	      if (TREE_CODE (b_use->decl) == FUNCTION_DECL
2185169699Skan		  && DECL_BUILT_IN (b_use->decl))
2186169699Skan		thistype
2187169699Skan		  = build_type_attribute_variant (thistype,
2188169699Skan						  TYPE_ATTRIBUTES
2189169699Skan						  (b_use->type));
2190169699Skan	      TREE_TYPE (b_use->decl) = thistype;
2191169699Skan	    }
2192169699Skan	  return b_use->decl;
2193169699Skan	}
2194169699Skan      else
2195169699Skan	goto skip_external_and_shadow_checks;
2196169699Skan    }
2197169699Skan
2198169699Skan  /* All declarations with external linkage, and all external
2199169699Skan     references, go in the external scope, no matter what scope is
2200169699Skan     current.  However, the binding in that scope is ignored for
2201169699Skan     purposes of normal name lookup.  A separate binding structure is
2202169699Skan     created in the requested scope; this governs the normal
2203169699Skan     visibility of the symbol.
2204169699Skan
2205169699Skan     The binding in the externals scope is used exclusively for
2206169699Skan     detecting duplicate declarations of the same object, no matter
2207169699Skan     what scope they are in; this is what we do here.  (C99 6.2.7p2:
2208169699Skan     All declarations that refer to the same object or function shall
2209169699Skan     have compatible type; otherwise, the behavior is undefined.)  */
2210169699Skan  if (DECL_EXTERNAL (x) || scope == file_scope)
2211169699Skan    {
2212169699Skan      tree type = TREE_TYPE (x);
2213169699Skan      tree vistype = 0;
2214169699Skan      tree visdecl = 0;
2215169699Skan      bool type_saved = false;
2216169699Skan      if (b && !B_IN_EXTERNAL_SCOPE (b)
2217169699Skan	  && (TREE_CODE (b->decl) == FUNCTION_DECL
2218169699Skan	      || TREE_CODE (b->decl) == VAR_DECL)
2219169699Skan	  && DECL_FILE_SCOPE_P (b->decl))
2220169699Skan	{
2221169699Skan	  visdecl = b->decl;
2222169699Skan	  vistype = TREE_TYPE (visdecl);
2223169699Skan	}
2224169699Skan      if (scope != file_scope
222590075Sobrien	  && !DECL_IN_SYSTEM_HEADER (x))
2226169699Skan	warning (OPT_Wnested_externs, "nested extern declaration of %qD", x);
222790075Sobrien
2228169699Skan      while (b && !B_IN_EXTERNAL_SCOPE (b))
222950397Sobrien	{
2230169699Skan	  /* If this decl might be modified, save its type.  This is
2231169699Skan	     done here rather than when the decl is first bound
2232169699Skan	     because the type may change after first binding, through
2233169699Skan	     being completed or through attributes being added.  If we
2234169699Skan	     encounter multiple such decls, only the first should have
2235169699Skan	     its type saved; the others will already have had their
2236169699Skan	     proper types saved and the types will not have changed as
2237169699Skan	     their scopes will not have been re-entered.  */
2238169699Skan	  if (DECL_P (b->decl) && DECL_FILE_SCOPE_P (b->decl) && !type_saved)
223918334Speter	    {
2240169699Skan	      b->type = TREE_TYPE (b->decl);
2241169699Skan	      type_saved = true;
224218334Speter	    }
2243169699Skan	  if (B_IN_FILE_SCOPE (b)
2244169699Skan	      && TREE_CODE (b->decl) == VAR_DECL
2245169699Skan	      && TREE_STATIC (b->decl)
2246169699Skan	      && TREE_CODE (TREE_TYPE (b->decl)) == ARRAY_TYPE
2247169699Skan	      && !TYPE_DOMAIN (TREE_TYPE (b->decl))
2248169699Skan	      && TREE_CODE (type) == ARRAY_TYPE
2249169699Skan	      && TYPE_DOMAIN (type)
2250169699Skan	      && TYPE_MAX_VALUE (TYPE_DOMAIN (type))
2251169699Skan	      && !integer_zerop (TYPE_MAX_VALUE (TYPE_DOMAIN (type))))
2252169699Skan	    {
2253169699Skan	      /* Array type completed in inner scope, which should be
2254169699Skan		 diagnosed if the completion does not have size 1 and
2255169699Skan		 it does not get completed in the file scope.  */
2256169699Skan	      b->inner_comp = true;
2257169699Skan	    }
2258169699Skan	  b = b->shadowed;
225918334Speter	}
2260169699Skan
2261169699Skan      /* If a matching external declaration has been found, set its
2262169699Skan	 type to the composite of all the types of that declaration.
2263169699Skan	 After the consistency checks, it will be reset to the
2264169699Skan	 composite of the visible types only.  */
2265169699Skan      if (b && (TREE_PUBLIC (x) || same_translation_unit_p (x, b->decl))
2266169699Skan	  && b->type)
2267169699Skan	TREE_TYPE (b->decl) = b->type;
2268169699Skan
2269169699Skan      /* The point of the same_translation_unit_p check here is,
2270169699Skan	 we want to detect a duplicate decl for a construct like
2271169699Skan	 foo() { extern bar(); } ... static bar();  but not if
2272169699Skan	 they are in different translation units.  In any case,
2273169699Skan	 the static does not go in the externals scope.  */
2274169699Skan      if (b
2275169699Skan	  && (TREE_PUBLIC (x) || same_translation_unit_p (x, b->decl))
2276169699Skan	  && duplicate_decls (x, b->decl))
227790075Sobrien	{
2278169699Skan	  tree thistype;
2279169699Skan	  if (vistype)
228090075Sobrien	    {
2281169699Skan	      if (comptypes (vistype, type))
2282169699Skan		thistype = composite_type (vistype, type);
2283169699Skan	      else
2284169699Skan		thistype = TREE_TYPE (b->decl);
228590075Sobrien	    }
228618334Speter	  else
2287169699Skan	    thistype = type;
2288169699Skan	  b->type = TREE_TYPE (b->decl);
2289169699Skan	  if (TREE_CODE (b->decl) == FUNCTION_DECL && DECL_BUILT_IN (b->decl))
2290169699Skan	    thistype
2291169699Skan	      = build_type_attribute_variant (thistype,
2292169699Skan					      TYPE_ATTRIBUTES (b->type));
2293169699Skan	  TREE_TYPE (b->decl) = thistype;
2294169699Skan	  bind (name, b->decl, scope, /*invisible=*/false, /*nested=*/true);
2295169699Skan	  return b->decl;
229618334Speter	}
2297169699Skan      else if (TREE_PUBLIC (x))
229818334Speter	{
2299169699Skan	  if (visdecl && !b && duplicate_decls (x, visdecl))
230018334Speter	    {
2301169699Skan	      /* An external declaration at block scope referring to a
2302169699Skan		 visible entity with internal linkage.  The composite
2303169699Skan		 type will already be correct for this scope, so we
2304169699Skan		 just need to fall through to make the declaration in
2305169699Skan		 this scope.  */
2306169699Skan	      nested = true;
2307169699Skan	      x = visdecl;
230818334Speter	    }
2309169699Skan	  else
2310169699Skan	    {
2311169699Skan	      bind (name, x, external_scope, /*invisible=*/true,
2312169699Skan		    /*nested=*/false);
2313169699Skan	      nested = true;
2314169699Skan	    }
231518334Speter	}
2316169699Skan    }
231790075Sobrien
2318169699Skan  if (TREE_CODE (x) != PARM_DECL)
2319169699Skan    warn_if_shadowing (x);
232018334Speter
2321169699Skan skip_external_and_shadow_checks:
2322169699Skan  if (TREE_CODE (x) == TYPE_DECL)
2323169699Skan    clone_underlying_type (x);
232418334Speter
2325169699Skan  bind (name, x, scope, /*invisible=*/false, nested);
232690075Sobrien
2327169699Skan  /* If x's type is incomplete because it's based on a
2328169699Skan     structure or union which has not yet been fully declared,
2329169699Skan     attach it to that structure or union type, so we can go
2330169699Skan     back and complete the variable declaration later, if the
2331169699Skan     structure or union gets fully declared.
2332132730Skan
2333169699Skan     If the input is erroneous, we can have error_mark in the type
2334169699Skan     slot (e.g. "f(void a, ...)") - that doesn't count as an
2335169699Skan     incomplete type.  */
2336169699Skan  if (TREE_TYPE (x) != error_mark_node
2337169699Skan      && !COMPLETE_TYPE_P (TREE_TYPE (x)))
2338169699Skan    {
2339169699Skan      tree element = TREE_TYPE (x);
234018334Speter
2341169699Skan      while (TREE_CODE (element) == ARRAY_TYPE)
2342169699Skan	element = TREE_TYPE (element);
2343169699Skan      element = TYPE_MAIN_VARIANT (element);
234418334Speter
2345169699Skan      if ((TREE_CODE (element) == RECORD_TYPE
2346169699Skan	   || TREE_CODE (element) == UNION_TYPE)
2347169699Skan	  && (TREE_CODE (x) != TYPE_DECL
2348169699Skan	      || TREE_CODE (TREE_TYPE (x)) == ARRAY_TYPE)
2349169699Skan	  && !COMPLETE_TYPE_P (element))
2350169699Skan	C_TYPE_INCOMPLETE_VARS (element)
2351169699Skan	  = tree_cons (NULL_TREE, x, C_TYPE_INCOMPLETE_VARS (element));
2352169699Skan    }
235318334Speter  return x;
235418334Speter}
235518334Speter
2356169699Skan/* Record X as belonging to file scope.
2357132730Skan   This is used only internally by the Objective-C front end,
2358132730Skan   and is limited to its needs.  duplicate_decls is not called;
2359132730Skan   if there is any preexisting decl for this identifier, it is an ICE.  */
236018334Speter
236118334Spetertree
2362132730Skanpushdecl_top_level (tree x)
236318334Speter{
2364132730Skan  tree name;
2365169699Skan  bool nested = false;
2366169699Skan  gcc_assert (TREE_CODE (x) == VAR_DECL || TREE_CODE (x) == CONST_DECL);
236718334Speter
2368132730Skan  name = DECL_NAME (x);
2369132730Skan
2370169699Skan gcc_assert (TREE_CODE (x) == CONST_DECL || !I_SYMBOL_BINDING (name));
2371132730Skan
2372169699Skan  if (TREE_PUBLIC (x))
2373169699Skan    {
2374169699Skan      bind (name, x, external_scope, /*invisible=*/true, /*nested=*/false);
2375169699Skan      nested = true;
2376169699Skan    }
2377169699Skan  if (file_scope)
2378169699Skan    bind (name, x, file_scope, /*invisible=*/false, nested);
2379132730Skan
2380132730Skan  return x;
238118334Speter}
238218334Speter
2383169699Skanstatic void
2384169699Skanimplicit_decl_warning (tree id, tree olddecl)
2385169699Skan{
2386169699Skan  void (*diag) (const char *, ...) ATTRIBUTE_GCC_CDIAG(1,2);
2387169699Skan  switch (mesg_implicit_function_declaration)
2388169699Skan    {
2389169699Skan    case 0: return;
2390169699Skan    case 1: diag = warning0; break;
2391169699Skan    case 2: diag = error;   break;
2392169699Skan    default: gcc_unreachable ();
2393169699Skan    }
2394169699Skan
2395169699Skan  diag (G_("implicit declaration of function %qE"), id);
2396169699Skan  if (olddecl)
2397169699Skan    locate_old_decl (olddecl, diag);
2398169699Skan}
2399169699Skan
2400132730Skan/* Generate an implicit declaration for identifier FUNCTIONID as a
2401132730Skan   function of type int ().  */
240218334Speter
240318334Spetertree
2404132730Skanimplicitly_declare (tree functionid)
240518334Speter{
2406169699Skan  struct c_binding *b;
2407169699Skan  tree decl = 0;
2408169699Skan  tree asmspec_tree;
240918334Speter
2410169699Skan  for (b = I_SYMBOL_BINDING (functionid); b; b = b->shadowed)
2411169699Skan    {
2412169699Skan      if (B_IN_SCOPE (b, external_scope))
2413169699Skan	{
2414169699Skan	  decl = b->decl;
2415169699Skan	  break;
2416169699Skan	}
2417169699Skan    }
2418169699Skan
2419132730Skan  if (decl)
2420132730Skan    {
2421169699Skan      if (decl == error_mark_node)
2422169699Skan	return decl;
2423169699Skan
2424169699Skan      /* FIXME: Objective-C has weird not-really-builtin functions
2425169699Skan	 which are supposed to be visible automatically.  They wind up
2426169699Skan	 in the external scope because they're pushed before the file
2427169699Skan	 scope gets created.  Catch this here and rebind them into the
2428169699Skan	 file scope.  */
2429169699Skan      if (!DECL_BUILT_IN (decl) && DECL_IS_BUILTIN (decl))
2430132730Skan	{
2431169699Skan	  bind (functionid, decl, file_scope,
2432169699Skan		/*invisible=*/false, /*nested=*/true);
2433169699Skan	  return decl;
2434132730Skan	}
2435169699Skan      else
2436169699Skan	{
2437169699Skan	  tree newtype = default_function_type;
2438169699Skan	  if (b->type)
2439169699Skan	    TREE_TYPE (decl) = b->type;
2440169699Skan	  /* Implicit declaration of a function already declared
2441169699Skan	     (somehow) in a different scope, or as a built-in.
2442169699Skan	     If this is the first time this has happened, warn;
2443169699Skan	     then recycle the old declaration but with the new type.  */
2444169699Skan	  if (!C_DECL_IMPLICIT (decl))
2445169699Skan	    {
2446169699Skan	      implicit_decl_warning (functionid, decl);
2447169699Skan	      C_DECL_IMPLICIT (decl) = 1;
2448169699Skan	    }
2449169699Skan	  if (DECL_BUILT_IN (decl))
2450169699Skan	    {
2451169699Skan	      newtype = build_type_attribute_variant (newtype,
2452169699Skan						      TYPE_ATTRIBUTES
2453169699Skan						      (TREE_TYPE (decl)));
2454169699Skan	      if (!comptypes (newtype, TREE_TYPE (decl)))
2455169699Skan		{
2456169699Skan		  warning (0, "incompatible implicit declaration of built-in"
2457169699Skan			   " function %qD", decl);
2458169699Skan		  newtype = TREE_TYPE (decl);
2459169699Skan		}
2460169699Skan	    }
2461169699Skan	  else
2462169699Skan	    {
2463169699Skan	      if (!comptypes (newtype, TREE_TYPE (decl)))
2464169699Skan		{
2465169699Skan		  error ("incompatible implicit declaration of function %qD",
2466169699Skan			 decl);
2467169699Skan		  locate_old_decl (decl, error);
2468169699Skan		}
2469169699Skan	    }
2470169699Skan	  b->type = TREE_TYPE (decl);
2471169699Skan	  TREE_TYPE (decl) = newtype;
2472169699Skan	  bind (functionid, decl, current_scope,
2473169699Skan		/*invisible=*/false, /*nested=*/true);
2474169699Skan	  return decl;
2475169699Skan	}
2476132730Skan    }
247718334Speter
2478132730Skan  /* Not seen before.  */
2479132730Skan  decl = build_decl (FUNCTION_DECL, functionid, default_function_type);
248018334Speter  DECL_EXTERNAL (decl) = 1;
248118334Speter  TREE_PUBLIC (decl) = 1;
2482132730Skan  C_DECL_IMPLICIT (decl) = 1;
2483169699Skan  implicit_decl_warning (functionid, 0);
2484169699Skan  asmspec_tree = maybe_apply_renaming_pragma (decl, /*asmname=*/NULL);
2485169699Skan  if (asmspec_tree)
2486169699Skan    set_user_assembler_name (decl, TREE_STRING_POINTER (asmspec_tree));
248718334Speter
2488132730Skan  /* C89 says implicit declarations are in the innermost block.
2489117421Skan     So we record the decl in the standard fashion.  */
2490132730Skan  decl = pushdecl (decl);
249118334Speter
2492132730Skan  /* No need to call objc_check_decl here - it's a function type.  */
2493169699Skan  rest_of_decl_compilation (decl, 0, 0);
249418334Speter
2495132730Skan  /* Write a record describing this implicit function declaration
2496132730Skan     to the prototypes file (if requested).  */
249718334Speter  gen_aux_info_record (decl, 0, 1, 0);
249818334Speter
249990075Sobrien  /* Possibly apply some default attributes to this implicit declaration.  */
250090075Sobrien  decl_attributes (&decl, NULL_TREE, 0);
250118334Speter
250218334Speter  return decl;
250318334Speter}
250418334Speter
2505132730Skan/* Issue an error message for a reference to an undeclared variable
2506132730Skan   ID, including a reference to a builtin outside of function-call
2507132730Skan   context.  Establish a binding of the identifier to error_mark_node
2508132730Skan   in an appropriate scope, which will suppress further errors for the
2509169699Skan   same identifier.  The error message should be given location LOC.  */
2510132730Skanvoid
2511169699Skanundeclared_variable (tree id, location_t loc)
2512132730Skan{
2513132730Skan  static bool already = false;
2514132730Skan  struct c_scope *scope;
251518334Speter
2516132730Skan  if (current_function_decl == 0)
251718334Speter    {
2518169699Skan      error ("%H%qE undeclared here (not in a function)", &loc, id);
2519132730Skan      scope = current_scope;
252018334Speter    }
252118334Speter  else
252218334Speter    {
2523169699Skan      error ("%H%qE undeclared (first use in this function)", &loc, id);
2524132730Skan
2525169699Skan      if (!already)
2526132730Skan	{
2527169699Skan	  error ("%H(Each undeclared identifier is reported only once", &loc);
2528169699Skan	  error ("%Hfor each function it appears in.)", &loc);
2529132730Skan	  already = true;
2530132730Skan	}
2531132730Skan
2532169699Skan      /* If we are parsing old-style parameter decls, current_function_decl
2533169699Skan	 will be nonnull but current_function_scope will be null.  */
2534169699Skan      scope = current_function_scope ? current_function_scope : current_scope;
253518334Speter    }
2536169699Skan  bind (id, error_mark_node, scope, /*invisible=*/false, /*nested=*/false);
253718334Speter}
253818334Speter
2539132730Skan/* Subroutine of lookup_label, declare_label, define_label: construct a
2540132730Skan   LABEL_DECL with all the proper frills.  */
2541132730Skan
2542132730Skanstatic tree
2543132730Skanmake_label (tree name, location_t location)
2544132730Skan{
2545132730Skan  tree label = build_decl (LABEL_DECL, name, void_type_node);
2546132730Skan
2547132730Skan  DECL_CONTEXT (label) = current_function_decl;
2548132730Skan  DECL_MODE (label) = VOIDmode;
2549132730Skan  DECL_SOURCE_LOCATION (label) = location;
2550132730Skan
2551132730Skan  return label;
2552132730Skan}
2553132730Skan
2554132730Skan/* Get the LABEL_DECL corresponding to identifier NAME as a label.
255518334Speter   Create one if none exists so far for the current function.
2556132730Skan   This is called when a label is used in a goto expression or
2557132730Skan   has its address taken.  */
255818334Speter
255918334Spetertree
2560132730Skanlookup_label (tree name)
256118334Speter{
2562132730Skan  tree label;
256318334Speter
256418334Speter  if (current_function_decl == 0)
256518334Speter    {
2566169699Skan      error ("label %qE referenced outside of any function", name);
256718334Speter      return 0;
256818334Speter    }
256918334Speter
2570132730Skan  /* Use a label already defined or ref'd with this name, but not if
2571132730Skan     it is inherited from a containing function and wasn't declared
2572132730Skan     using __label__.  */
2573169699Skan  label = I_LABEL_DECL (name);
2574132730Skan  if (label && (DECL_CONTEXT (label) == current_function_decl
2575132730Skan		|| C_DECLARED_LABEL_FLAG (label)))
257618334Speter    {
2577132730Skan      /* If the label has only been declared, update its apparent
2578132730Skan	 location to point here, for better diagnostics if it
2579132730Skan	 turns out not to have been defined.  */
2580132730Skan      if (!TREE_USED (label))
2581132730Skan	DECL_SOURCE_LOCATION (label) = input_location;
2582132730Skan      return label;
258318334Speter    }
258418334Speter
2585132730Skan  /* No label binding for that identifier; make one.  */
2586132730Skan  label = make_label (name, input_location);
258718334Speter
2588132730Skan  /* Ordinary labels go in the current function scope.  */
2589169699Skan  bind (name, label, current_function_scope,
2590169699Skan	/*invisible=*/false, /*nested=*/false);
2591132730Skan  return label;
259218334Speter}
259318334Speter
2594132730Skan/* Make a label named NAME in the current function, shadowing silently
2595132730Skan   any that may be inherited from containing functions or containing
2596132730Skan   scopes.  This is called for __label__ declarations.  */
259718334Speter
259818334Spetertree
2599132730Skandeclare_label (tree name)
260018334Speter{
2601169699Skan  struct c_binding *b = I_LABEL_BINDING (name);
2602169699Skan  tree label;
260318334Speter
2604132730Skan  /* Check to make sure that the label hasn't already been declared
2605132730Skan     at this scope */
2606169699Skan  if (b && B_IN_CURRENT_SCOPE (b))
2607169699Skan    {
2608169699Skan      error ("duplicate label declaration %qE", name);
2609169699Skan      locate_old_decl (b->decl, error);
261018334Speter
2611169699Skan      /* Just use the previous declaration.  */
2612169699Skan      return b->decl;
2613169699Skan    }
261418334Speter
2615132730Skan  label = make_label (name, input_location);
2616132730Skan  C_DECLARED_LABEL_FLAG (label) = 1;
261718334Speter
2618132730Skan  /* Declared labels go in the current scope.  */
2619169699Skan  bind (name, label, current_scope,
2620169699Skan	/*invisible=*/false, /*nested=*/false);
2621132730Skan  return label;
262218334Speter}
262318334Speter
262418334Speter/* Define a label, specifying the location in the source file.
262518334Speter   Return the LABEL_DECL node for the label, if the definition is valid.
262618334Speter   Otherwise return 0.  */
262718334Speter
262818334Spetertree
2629132730Skandefine_label (location_t location, tree name)
263018334Speter{
2631132730Skan  /* Find any preexisting label with this name.  It is an error
2632132730Skan     if that label has already been defined in this function, or
2633132730Skan     if there is a containing function with a declared label with
2634132730Skan     the same name.  */
2635169699Skan  tree label = I_LABEL_DECL (name);
2636169699Skan  struct c_label_list *nlist_se, *nlist_vm;
263718334Speter
2638132730Skan  if (label
2639132730Skan      && ((DECL_CONTEXT (label) == current_function_decl
2640132730Skan	   && DECL_INITIAL (label) != 0)
2641132730Skan	  || (DECL_CONTEXT (label) != current_function_decl
2642132730Skan	      && C_DECLARED_LABEL_FLAG (label))))
264318334Speter    {
2644169699Skan      error ("%Hduplicate label %qD", &location, label);
2645169699Skan      locate_old_decl (label, error);
264618334Speter      return 0;
264718334Speter    }
2648132730Skan  else if (label && DECL_CONTEXT (label) == current_function_decl)
2649132730Skan    {
2650132730Skan      /* The label has been used or declared already in this function,
2651132730Skan	 but not defined.  Update its location to point to this
2652132730Skan	 definition.  */
2653169699Skan      if (C_DECL_UNDEFINABLE_STMT_EXPR (label))
2654169699Skan	error ("%Jjump into statement expression", label);
2655169699Skan      if (C_DECL_UNDEFINABLE_VM (label))
2656169699Skan	error ("%Jjump into scope of identifier with variably modified type",
2657169699Skan	       label);
2658132730Skan      DECL_SOURCE_LOCATION (label) = location;
2659132730Skan    }
266018334Speter  else
266118334Speter    {
2662132730Skan      /* No label binding for that identifier; make one.  */
2663132730Skan      label = make_label (name, location);
2664132730Skan
2665132730Skan      /* Ordinary labels go in the current function scope.  */
2666169699Skan      bind (name, label, current_function_scope,
2667169699Skan	    /*invisible=*/false, /*nested=*/false);
266818334Speter    }
2669132730Skan
2670169699Skan  if (!in_system_header && lookup_name (name))
2671169699Skan    warning (OPT_Wtraditional, "%Htraditional C lacks a separate namespace "
2672169699Skan	     "for labels, identifier %qE conflicts", &location, name);
2673132730Skan
2674169699Skan  nlist_se = XOBNEW (&parser_obstack, struct c_label_list);
2675169699Skan  nlist_se->next = label_context_stack_se->labels_def;
2676169699Skan  nlist_se->label = label;
2677169699Skan  label_context_stack_se->labels_def = nlist_se;
2678169699Skan
2679169699Skan  nlist_vm = XOBNEW (&parser_obstack, struct c_label_list);
2680169699Skan  nlist_vm->next = label_context_stack_vm->labels_def;
2681169699Skan  nlist_vm->label = label;
2682169699Skan  label_context_stack_vm->labels_def = nlist_vm;
2683169699Skan
2684132730Skan  /* Mark label as having been defined.  */
2685132730Skan  DECL_INITIAL (label) = error_mark_node;
2686132730Skan  return label;
268718334Speter}
268818334Speter
268918334Speter/* Given NAME, an IDENTIFIER_NODE,
269018334Speter   return the structure (or union or enum) definition for that name.
2691132730Skan   If THISLEVEL_ONLY is nonzero, searches only the current_scope.
269218334Speter   CODE says which kind of type the caller wants;
269318334Speter   it is RECORD_TYPE or UNION_TYPE or ENUMERAL_TYPE.
269418334Speter   If the wrong kind of type is found, an error is reported.  */
269518334Speter
269618334Speterstatic tree
2697132730Skanlookup_tag (enum tree_code code, tree name, int thislevel_only)
269818334Speter{
2699169699Skan  struct c_binding *b = I_TAG_BINDING (name);
2700132730Skan  int thislevel = 0;
270118334Speter
2702169699Skan  if (!b || !b->decl)
2703132730Skan    return 0;
2704132730Skan
2705132730Skan  /* We only care about whether it's in this level if
2706132730Skan     thislevel_only was set or it might be a type clash.  */
2707169699Skan  if (thislevel_only || TREE_CODE (b->decl) != code)
270818334Speter    {
2709169699Skan      /* For our purposes, a tag in the external scope is the same as
2710169699Skan	 a tag in the file scope.  (Primarily relevant to Objective-C
2711169699Skan	 and its builtin structure tags, which get pushed before the
2712169699Skan	 file scope is created.)  */
2713169699Skan      if (B_IN_CURRENT_SCOPE (b)
2714169699Skan	  || (current_scope == file_scope && B_IN_EXTERNAL_SCOPE (b)))
2715132730Skan	thislevel = 1;
271618334Speter    }
2717132730Skan
2718132730Skan  if (thislevel_only && !thislevel)
2719132730Skan    return 0;
2720132730Skan
2721169699Skan  if (TREE_CODE (b->decl) != code)
2722132730Skan    {
2723132730Skan      /* Definition isn't the kind we were looking for.  */
2724132730Skan      pending_invalid_xref = name;
2725132730Skan      pending_invalid_xref_location = input_location;
2726132730Skan
2727132730Skan      /* If in the same binding level as a declaration as a tag
2728132730Skan	 of a different type, this must not be allowed to
2729132730Skan	 shadow that tag, so give the error immediately.
2730132730Skan	 (For example, "struct foo; union foo;" is invalid.)  */
2731132730Skan      if (thislevel)
2732132730Skan	pending_xref_error ();
2733132730Skan    }
2734169699Skan  return b->decl;
273518334Speter}
273618334Speter
273718334Speter/* Print an error message now
273818334Speter   for a recent invalid struct, union or enum cross reference.
273918334Speter   We don't print them immediately because they are not invalid
274018334Speter   when used in the `struct foo;' construct for shadowing.  */
274118334Speter
274218334Spetervoid
2743132730Skanpending_xref_error (void)
274418334Speter{
274518334Speter  if (pending_invalid_xref != 0)
2746169699Skan    error ("%H%qE defined as wrong kind of tag",
2747169699Skan	   &pending_invalid_xref_location, pending_invalid_xref);
274818334Speter  pending_invalid_xref = 0;
274918334Speter}
275018334Speter
275118334Speter
2752132730Skan/* Look up NAME in the current scope and its superiors
275318334Speter   in the namespace of variables, functions and typedefs.
275418334Speter   Return a ..._DECL node of some kind representing its definition,
275518334Speter   or return 0 if it is undefined.  */
275618334Speter
275718334Spetertree
2758132730Skanlookup_name (tree name)
275918334Speter{
2760169699Skan  struct c_binding *b = I_SYMBOL_BINDING (name);
2761169699Skan  if (b && !b->invisible)
2762169699Skan    return b->decl;
2763169699Skan  return 0;
276418334Speter}
276518334Speter
2766169699Skan/* Similar to `lookup_name' but look only at the indicated scope.  */
276718334Speter
2768132730Skanstatic tree
2769169699Skanlookup_name_in_scope (tree name, struct c_scope *scope)
277018334Speter{
2771169699Skan  struct c_binding *b;
277218334Speter
2773169699Skan  for (b = I_SYMBOL_BINDING (name); b; b = b->shadowed)
2774169699Skan    if (B_IN_SCOPE (b, scope))
2775169699Skan      return b->decl;
2776132730Skan  return 0;
277718334Speter}
277818334Speter
277918334Speter/* Create the predefined scalar types of C,
278050397Sobrien   and some nodes representing standard constants (0, 1, (void *) 0).
2781132730Skan   Initialize the global scope.
278218334Speter   Make definitions for built-in primitive functions.  */
278318334Speter
278418334Spetervoid
2785132730Skanc_init_decl_processing (void)
278618334Speter{
2787132730Skan  location_t save_loc = input_location;
278818334Speter
2789169699Skan  /* Initialize reserved words for parser.  */
279090075Sobrien  c_parse_init ();
279190075Sobrien
2792132730Skan  current_function_decl = 0;
279390075Sobrien
2794169699Skan  gcc_obstack_init (&parser_obstack);
279518334Speter
2796169699Skan  /* Make the externals scope.  */
2797169699Skan  push_scope ();
2798169699Skan  external_scope = current_scope;
2799169699Skan
2800132730Skan  /* Declarations from c_common_nodes_and_builtins must not be associated
2801132730Skan     with this input file, lest we get differences between using and not
2802132730Skan     using preprocessed headers.  */
2803169699Skan#ifdef USE_MAPPED_LOCATION
2804169699Skan  input_location = BUILTINS_LOCATION;
2805169699Skan#else
2806169699Skan  input_location.file = "<built-in>";
2807132730Skan  input_location.line = 0;
2808169699Skan#endif
2809132730Skan
2810169699Skan  build_common_tree_nodes (flag_signed_char, false);
2811132730Skan
281290075Sobrien  c_common_nodes_and_builtins ();
281318334Speter
2814132730Skan  /* In C, comparisons and TRUTH_* expressions have type int.  */
2815132730Skan  truthvalue_type_node = integer_type_node;
2816132730Skan  truthvalue_true_node = integer_one_node;
2817132730Skan  truthvalue_false_node = integer_zero_node;
281818334Speter
2819132730Skan  /* Even in C99, which has a real boolean type.  */
282090075Sobrien  pushdecl (build_decl (TYPE_DECL, get_identifier ("_Bool"),
2821132730Skan			boolean_type_node));
282218334Speter
2823132730Skan  input_location = save_loc;
2824132730Skan
2825169699Skan  pedantic_lvalues = true;
282618334Speter
282790075Sobrien  make_fname_decl = c_make_fname_decl;
282890075Sobrien  start_fname_decls ();
282990075Sobrien}
283018334Speter
283190075Sobrien/* Create the VAR_DECL for __FUNCTION__ etc. ID is the name to give the
283290075Sobrien   decl, NAME is the initialization string and TYPE_DEP indicates whether
283390075Sobrien   NAME depended on the type of the function.  As we don't yet implement
283490075Sobrien   delayed emission of static data, we mark the decl as emitted
283590075Sobrien   so it is not placed in the output.  Anything using it must therefore pull
2836132730Skan   out the STRING_CST initializer directly.  FIXME.  */
283718334Speter
283890075Sobrienstatic tree
2839132730Skanc_make_fname_decl (tree id, int type_dep)
284090075Sobrien{
284190075Sobrien  const char *name = fname_as_string (type_dep);
284290075Sobrien  tree decl, type, init;
284390075Sobrien  size_t length = strlen (name);
284418334Speter
2845169699Skan  type = build_array_type (char_type_node,
2846169699Skan			   build_index_type (size_int (length)));
2847169699Skan  type = c_build_qualified_type (type, TYPE_QUAL_CONST);
284818334Speter
284990075Sobrien  decl = build_decl (VAR_DECL, id, type);
2850132730Skan
285190075Sobrien  TREE_STATIC (decl) = 1;
285290075Sobrien  TREE_READONLY (decl) = 1;
285390075Sobrien  DECL_ARTIFICIAL (decl) = 1;
2854132730Skan
285590075Sobrien  init = build_string (length + 1, name);
2856169699Skan  free ((char *) name);
285790075Sobrien  TREE_TYPE (init) = type;
285890075Sobrien  DECL_INITIAL (decl) = init;
285918334Speter
286090075Sobrien  TREE_USED (decl) = 1;
2861132730Skan
2862169699Skan  if (current_function_decl
2863169699Skan      /* For invalid programs like this:
2864169699Skan
2865169699Skan         void foo()
2866169699Skan         const char* p = __FUNCTION__;
2867169699Skan
2868169699Skan	 the __FUNCTION__ is believed to appear in K&R style function
2869169699Skan	 parameter declarator.  In that case we still don't have
2870169699Skan	 function_scope.  */
2871169699Skan      && (!errorcount || current_function_scope))
2872132730Skan    {
2873132730Skan      DECL_CONTEXT (decl) = current_function_decl;
2874169699Skan      bind (id, decl, current_function_scope,
2875169699Skan	    /*invisible=*/false, /*nested=*/false);
2876132730Skan    }
2877132730Skan
287890075Sobrien  finish_decl (decl, init, NULL_TREE);
287918334Speter
288090075Sobrien  return decl;
288118334Speter}
288218334Speter
288318334Speter/* Return a definition for a builtin function named NAME and whose data type
288418334Speter   is TYPE.  TYPE should be a function type with argument types.
288518334Speter   FUNCTION_CODE tells later passes how to compile calls to this function.
288618334Speter   See tree.h for its possible values.
288718334Speter
288818334Speter   If LIBRARY_NAME is nonzero, use that for DECL_ASSEMBLER_NAME,
2889117421Skan   the name to be called if we can't opencode the function.  If
2890117421Skan   ATTRS is nonzero, use that for the function's attribute list.  */
289118334Speter
289218334Spetertree
2893132730Skanbuiltin_function (const char *name, tree type, int function_code,
2894169699Skan		  enum built_in_class cl, const char *library_name,
2895132730Skan		  tree attrs)
289618334Speter{
2897169699Skan  tree id = get_identifier (name);
2898169699Skan  tree decl = build_decl (FUNCTION_DECL, id, type);
2899169699Skan  TREE_PUBLIC (decl) = 1;
290018334Speter  DECL_EXTERNAL (decl) = 1;
2901169699Skan  DECL_LANG_SPECIFIC (decl) = GGC_CNEW (struct lang_decl);
2902169699Skan  DECL_BUILT_IN_CLASS (decl) = cl;
2903169699Skan  DECL_FUNCTION_CODE (decl) = function_code;
2904169699Skan  C_DECL_BUILTIN_PROTOTYPE (decl) = (TYPE_ARG_TYPES (type) != 0);
290518334Speter  if (library_name)
290690075Sobrien    SET_DECL_ASSEMBLER_NAME (decl, get_identifier (library_name));
290790075Sobrien
2908169699Skan  /* Should never be called on a symbol with a preexisting meaning.  */
2909169699Skan  gcc_assert (!I_SYMBOL_BINDING (id));
291018334Speter
2911169699Skan  bind (id, decl, external_scope, /*invisible=*/true, /*nested=*/false);
2912169699Skan
2913169699Skan  /* Builtins in the implementation namespace are made visible without
2914169699Skan     needing to be explicitly declared.  See push_file_scope.  */
2915169699Skan  if (name[0] == '_' && (name[1] == '_' || ISUPPER (name[1])))
2916169699Skan    {
2917169699Skan      TREE_CHAIN (decl) = visible_builtins;
2918169699Skan      visible_builtins = decl;
2919169699Skan    }
2920169699Skan
292190075Sobrien  /* Possibly apply some default attributes to this built-in function.  */
2922117421Skan  if (attrs)
2923117421Skan    decl_attributes (&decl, attrs, ATTR_FLAG_BUILT_IN);
2924117421Skan  else
2925117421Skan    decl_attributes (&decl, NULL_TREE, 0);
292690075Sobrien
292718334Speter  return decl;
292818334Speter}
292918334Speter
293018334Speter/* Called when a declaration is seen that contains no names to declare.
293118334Speter   If its type is a reference to a structure, union or enum inherited
293218334Speter   from a containing scope, shadow that tag name for the current scope
293318334Speter   with a forward reference.
293418334Speter   If its type defines a new named structure or union
293518334Speter   or defines an enum, it is valid but we need not do anything here.
293618334Speter   Otherwise, it is an error.  */
293718334Speter
293818334Spetervoid
2939169699Skanshadow_tag (const struct c_declspecs *declspecs)
294018334Speter{
294118334Speter  shadow_tag_warned (declspecs, 0);
294218334Speter}
294318334Speter
2944169699Skan/* WARNED is 1 if we have done a pedwarn, 2 if we have done a warning,
2945169699Skan   but no pedwarn.  */
294618334Spetervoid
2947169699Skanshadow_tag_warned (const struct c_declspecs *declspecs, int warned)
294818334Speter{
2949169699Skan  bool found_tag = false;
295018334Speter
2951169699Skan  if (declspecs->type && !declspecs->default_int_p && !declspecs->typedef_p)
295218334Speter    {
2953169699Skan      tree value = declspecs->type;
295490075Sobrien      enum tree_code code = TREE_CODE (value);
295518334Speter
295618334Speter      if (code == RECORD_TYPE || code == UNION_TYPE || code == ENUMERAL_TYPE)
295718334Speter	/* Used to test also that TYPE_SIZE (value) != 0.
295818334Speter	   That caused warning for `struct foo;' at top level in the file.  */
295918334Speter	{
2960132730Skan	  tree name = TYPE_NAME (value);
296190075Sobrien	  tree t;
296218334Speter
2963169699Skan	  found_tag = true;
296418334Speter
296518334Speter	  if (name == 0)
296618334Speter	    {
296718334Speter	      if (warned != 1 && code != ENUMERAL_TYPE)
296818334Speter		/* Empty unnamed enum OK */
296918334Speter		{
297018334Speter		  pedwarn ("unnamed struct/union that defines no instances");
297118334Speter		  warned = 1;
297218334Speter		}
297318334Speter	    }
2974169699Skan	  else if (!declspecs->tag_defined_p
2975169699Skan		   && declspecs->storage_class != csc_none)
2976169699Skan	    {
2977169699Skan	      if (warned != 1)
2978169699Skan		pedwarn ("empty declaration with storage class specifier "
2979169699Skan			 "does not redeclare tag");
2980169699Skan	      warned = 1;
2981169699Skan	      pending_xref_error ();
2982169699Skan	    }
2983169699Skan	  else if (!declspecs->tag_defined_p
2984169699Skan		   && (declspecs->const_p
2985169699Skan		       || declspecs->volatile_p
2986169699Skan		       || declspecs->restrict_p))
2987169699Skan	    {
2988169699Skan	      if (warned != 1)
2989169699Skan		pedwarn ("empty declaration with type qualifier "
2990169699Skan			 "does not redeclare tag");
2991169699Skan	      warned = 1;
2992169699Skan	      pending_xref_error ();
2993169699Skan	    }
299418334Speter	  else
299518334Speter	    {
2996169699Skan	      pending_invalid_xref = 0;
2997132730Skan	      t = lookup_tag (code, name, 1);
299818334Speter
299918334Speter	      if (t == 0)
300018334Speter		{
300118334Speter		  t = make_node (code);
300218334Speter		  pushtag (name, t);
300318334Speter		}
300418334Speter	    }
300518334Speter	}
300618334Speter      else
300718334Speter	{
3008169699Skan	  if (warned != 1 && !in_system_header)
300918334Speter	    {
3010169699Skan	      pedwarn ("useless type name in empty declaration");
3011169699Skan	      warned = 1;
301218334Speter	    }
301318334Speter	}
301418334Speter    }
3015169699Skan  else if (warned != 1 && !in_system_header && declspecs->typedef_p)
3016169699Skan    {
3017169699Skan      pedwarn ("useless type name in empty declaration");
3018169699Skan      warned = 1;
3019169699Skan    }
302018334Speter
3021169699Skan  pending_invalid_xref = 0;
302218334Speter
3023169699Skan  if (declspecs->inline_p)
3024169699Skan    {
3025169699Skan      error ("%<inline%> in empty declaration");
3026169699Skan      warned = 1;
3027169699Skan    }
3028169699Skan
3029169699Skan  if (current_scope == file_scope && declspecs->storage_class == csc_auto)
3030169699Skan    {
3031169699Skan      error ("%<auto%> in file-scope empty declaration");
3032169699Skan      warned = 1;
3033169699Skan    }
3034169699Skan
3035169699Skan  if (current_scope == file_scope && declspecs->storage_class == csc_register)
3036169699Skan    {
3037169699Skan      error ("%<register%> in file-scope empty declaration");
3038169699Skan      warned = 1;
3039169699Skan    }
3040169699Skan
3041169699Skan  if (!warned && !in_system_header && declspecs->storage_class != csc_none)
3042169699Skan    {
3043169699Skan      warning (0, "useless storage class specifier in empty declaration");
3044169699Skan      warned = 2;
3045169699Skan    }
3046169699Skan
3047169699Skan  if (!warned && !in_system_header && declspecs->thread_p)
3048169699Skan    {
3049169699Skan      warning (0, "useless %<__thread%> in empty declaration");
3050169699Skan      warned = 2;
3051169699Skan    }
3052169699Skan
3053169699Skan  if (!warned && !in_system_header && (declspecs->const_p
3054169699Skan				       || declspecs->volatile_p
3055169699Skan				       || declspecs->restrict_p))
3056169699Skan    {
3057169699Skan      warning (0, "useless type qualifier in empty declaration");
3058169699Skan      warned = 2;
3059169699Skan    }
3060169699Skan
306118334Speter  if (warned != 1)
306218334Speter    {
3063169699Skan      if (!found_tag)
306418334Speter	pedwarn ("empty declaration");
306518334Speter    }
306618334Speter}
306718334Speter
306890075Sobrien
3069169699Skan/* Return the qualifiers from SPECS as a bitwise OR of TYPE_QUAL_*
3070169699Skan   bits.  SPECS represents declaration specifiers that the grammar
3071169699Skan   only permits to contain type qualifiers and attributes.  */
3072169699Skan
3073169699Skanint
3074169699Skanquals_from_declspecs (const struct c_declspecs *specs)
307590075Sobrien{
3076169699Skan  int quals = ((specs->const_p ? TYPE_QUAL_CONST : 0)
3077169699Skan	       | (specs->volatile_p ? TYPE_QUAL_VOLATILE : 0)
3078169699Skan	       | (specs->restrict_p ? TYPE_QUAL_RESTRICT : 0));
3079169699Skan  gcc_assert (!specs->type
3080169699Skan	      && !specs->decl_attr
3081169699Skan	      && specs->typespec_word == cts_none
3082169699Skan	      && specs->storage_class == csc_none
3083169699Skan	      && !specs->typedef_p
3084169699Skan	      && !specs->explicit_signed_p
3085169699Skan	      && !specs->deprecated_p
3086169699Skan	      && !specs->long_p
3087169699Skan	      && !specs->long_long_p
3088169699Skan	      && !specs->short_p
3089169699Skan	      && !specs->signed_p
3090169699Skan	      && !specs->unsigned_p
3091169699Skan	      && !specs->complex_p
3092169699Skan	      && !specs->inline_p
3093169699Skan	      && !specs->thread_p);
3094169699Skan  return quals;
3095169699Skan}
3096169699Skan
3097169699Skan/* Construct an array declarator.  EXPR is the expression inside [],
3098169699Skan   or NULL_TREE.  QUALS are the type qualifiers inside the [] (to be
3099169699Skan   applied to the pointer to which a parameter array is converted).
3100169699Skan   STATIC_P is true if "static" is inside the [], false otherwise.
3101169699Skan   VLA_UNSPEC_P is true if the array is [*], a VLA of unspecified
3102169699Skan   length which is nevertheless a complete type, false otherwise.  The
3103169699Skan   field for the contained declarator is left to be filled in by
3104169699Skan   set_array_declarator_inner.  */
3105169699Skan
3106169699Skanstruct c_declarator *
3107169699Skanbuild_array_declarator (tree expr, struct c_declspecs *quals, bool static_p,
3108169699Skan			bool vla_unspec_p)
3109169699Skan{
3110169699Skan  struct c_declarator *declarator = XOBNEW (&parser_obstack,
3111169699Skan					    struct c_declarator);
3112169699Skan  declarator->kind = cdk_array;
3113169699Skan  declarator->declarator = 0;
3114169699Skan  declarator->u.array.dimen = expr;
3115169699Skan  if (quals)
3116169699Skan    {
3117169699Skan      declarator->u.array.attrs = quals->attrs;
3118169699Skan      declarator->u.array.quals = quals_from_declspecs (quals);
3119169699Skan    }
3120169699Skan  else
3121169699Skan    {
3122169699Skan      declarator->u.array.attrs = NULL_TREE;
3123169699Skan      declarator->u.array.quals = 0;
3124169699Skan    }
3125169699Skan  declarator->u.array.static_p = static_p;
3126169699Skan  declarator->u.array.vla_unspec_p = vla_unspec_p;
312790075Sobrien  if (pedantic && !flag_isoc99)
312890075Sobrien    {
3129169699Skan      if (static_p || quals != NULL)
3130169699Skan	pedwarn ("ISO C90 does not support %<static%> or type "
3131169699Skan		 "qualifiers in parameter array declarators");
313290075Sobrien      if (vla_unspec_p)
3133169699Skan	pedwarn ("ISO C90 does not support %<[*]%> array declarators");
313490075Sobrien    }
313590075Sobrien  if (vla_unspec_p)
3136169699Skan    {
3137169699Skan      if (!current_scope->parm_flag)
3138169699Skan	{
3139169699Skan	  /* C99 6.7.5.2p4 */
3140169699Skan	  error ("%<[*]%> not allowed in other than function prototype scope");
3141169699Skan	  declarator->u.array.vla_unspec_p = false;
3142169699Skan	  return NULL;
3143169699Skan	}
3144169699Skan      current_scope->had_vla_unspec = true;
3145169699Skan    }
3146169699Skan  return declarator;
314790075Sobrien}
314890075Sobrien
3149169699Skan/* Set the contained declarator of an array declarator.  DECL is the
3150169699Skan   declarator, as constructed by build_array_declarator; INNER is what
3151169699Skan   appears on the left of the [].  ABSTRACT_P is true if it is an
3152169699Skan   abstract declarator, false otherwise; this is used to reject static
3153169699Skan   and type qualifiers in abstract declarators, where they are not in
3154169699Skan   the C99 grammar (subject to possible change in DR#289).  */
315590075Sobrien
3156169699Skanstruct c_declarator *
3157169699Skanset_array_declarator_inner (struct c_declarator *decl,
3158169699Skan			    struct c_declarator *inner, bool abstract_p)
315990075Sobrien{
3160169699Skan  decl->declarator = inner;
3161169699Skan  if (abstract_p && (decl->u.array.quals != TYPE_UNQUALIFIED
3162169699Skan		     || decl->u.array.attrs != NULL_TREE
3163169699Skan		     || decl->u.array.static_p))
316490075Sobrien    error ("static or type qualifiers in abstract declarator");
316590075Sobrien  return decl;
316690075Sobrien}
3167169699Skan
3168169699Skan/* INIT is a constructor that forms DECL's initializer.  If the final
3169169699Skan   element initializes a flexible array field, add the size of that
3170169699Skan   initializer to DECL's size.  */
3171169699Skan
3172169699Skanstatic void
3173169699Skanadd_flexible_array_elts_to_size (tree decl, tree init)
3174169699Skan{
3175169699Skan  tree elt, type;
3176169699Skan
3177169699Skan  if (VEC_empty (constructor_elt, CONSTRUCTOR_ELTS (init)))
3178169699Skan    return;
3179169699Skan
3180169699Skan  elt = VEC_last (constructor_elt, CONSTRUCTOR_ELTS (init))->value;
3181169699Skan  type = TREE_TYPE (elt);
3182169699Skan  if (TREE_CODE (type) == ARRAY_TYPE
3183169699Skan      && TYPE_SIZE (type) == NULL_TREE
3184169699Skan      && TYPE_DOMAIN (type) != NULL_TREE
3185169699Skan      && TYPE_MAX_VALUE (TYPE_DOMAIN (type)) == NULL_TREE)
3186169699Skan    {
3187169699Skan      complete_array_type (&type, elt, false);
3188169699Skan      DECL_SIZE (decl)
3189169699Skan	= size_binop (PLUS_EXPR, DECL_SIZE (decl), TYPE_SIZE (type));
3190169699Skan      DECL_SIZE_UNIT (decl)
3191169699Skan	= size_binop (PLUS_EXPR, DECL_SIZE_UNIT (decl), TYPE_SIZE_UNIT (type));
3192169699Skan    }
3193169699Skan}
319490075Sobrien
319518334Speter/* Decode a "typename", such as "int **", returning a ..._TYPE node.  */
319618334Speter
319718334Spetertree
3198169699Skangroktypename (struct c_type_name *type_name)
319918334Speter{
3200169699Skan  tree type;
3201169699Skan  tree attrs = type_name->specs->attrs;
320290075Sobrien
3203169699Skan  type_name->specs->attrs = NULL_TREE;
320490075Sobrien
3205169699Skan  type = grokdeclarator (type_name->declarator, type_name->specs, TYPENAME,
3206169699Skan			 false, NULL);
320790075Sobrien
320890075Sobrien  /* Apply attributes.  */
3209169699Skan  decl_attributes (&type, attrs, 0);
321090075Sobrien
3211169699Skan  return type;
321218334Speter}
321318334Speter
321418334Speter/* Decode a declarator in an ordinary declaration or data definition.
321518334Speter   This is called as soon as the type information and variable name
321618334Speter   have been parsed, before parsing the initializer if any.
321718334Speter   Here we create the ..._DECL node, fill in its type,
321818334Speter   and put it on the list of decls for the current context.
321918334Speter   The ..._DECL node is returned as the value.
322018334Speter
322118334Speter   Exception: for arrays where the length is not specified,
322218334Speter   the type is left null, to be filled in by `finish_decl'.
322318334Speter
322418334Speter   Function definitions do not come here; they go to start_function
322518334Speter   instead.  However, external and forward declarations of functions
322618334Speter   do go through here.  Structure field declarations are done by
322718334Speter   grokfield and not through here.  */
322818334Speter
322918334Spetertree
3230169699Skanstart_decl (struct c_declarator *declarator, struct c_declspecs *declspecs,
3231169699Skan	    bool initialized, tree attributes)
323218334Speter{
323390075Sobrien  tree decl;
323490075Sobrien  tree tem;
3235132730Skan
323690075Sobrien  /* An object declared as __attribute__((deprecated)) suppresses
323790075Sobrien     warnings of uses of other deprecated items.  */
3238260919Spfg  /* APPLE LOCAL begin "unavailable" attribute (radar 2809697) */
3239260919Spfg  /* An object declared as __attribute__((unavailable)) suppresses
3240260919Spfg     any reports of being declared with unavailable or deprecated
3241260919Spfg     items.  An object declared as __attribute__((deprecated))
3242260919Spfg     suppresses warnings of uses of other deprecated items.  */
3243260919Spfg#ifdef A_LESS_INEFFICENT_WAY /* which I really don't want to do!  */
324490075Sobrien  if (lookup_attribute ("deprecated", attributes))
324590075Sobrien    deprecated_state = DEPRECATED_SUPPRESS;
3246260919Spfg  else if (lookup_attribute ("unavailable", attributes))
3247260919Spfg    deprecated_state = DEPRECATED_UNAVAILABLE_SUPPRESS;
3248260919Spfg#else /* a more efficient way doing what lookup_attribute would do */
3249260919Spfg  tree a;
325018334Speter
3251260919Spfg  for (a = attributes; a; a = TREE_CHAIN (a))
3252260919Spfg    {
3253260919Spfg      tree name = TREE_PURPOSE (a);
3254260919Spfg      if (TREE_CODE (name) == IDENTIFIER_NODE)
3255260919Spfg        if (is_attribute_p ("deprecated", name))
3256260919Spfg	  {
3257260919Spfg	    deprecated_state = DEPRECATED_SUPPRESS;
3258260919Spfg	    break;
3259260919Spfg	  }
3260260919Spfg        if (is_attribute_p ("unavailable", name))
3261260919Spfg	  {
3262260919Spfg	    deprecated_state = DEPRECATED_UNAVAILABLE_SUPPRESS;
3263260919Spfg	    break;
3264260919Spfg	  }
3265260919Spfg    }
3266260919Spfg#endif
3267260919Spfg  /* APPLE LOCAL end "unavailable" attribute (radar 2809697) */
3268260919Spfg
326990075Sobrien  decl = grokdeclarator (declarator, declspecs,
3270132730Skan			 NORMAL, initialized, NULL);
3271169699Skan  if (!decl)
3272169699Skan    return 0;
3273132730Skan
327490075Sobrien  deprecated_state = DEPRECATED_NORMAL;
327518334Speter
327690075Sobrien  if (warn_main > 0 && TREE_CODE (decl) != FUNCTION_DECL
327790075Sobrien      && MAIN_NAME_P (DECL_NAME (decl)))
3278169699Skan    warning (OPT_Wmain, "%q+D is usually a function", decl);
327950397Sobrien
328018334Speter  if (initialized)
328118334Speter    /* Is it valid for this decl to have an initializer at all?
328218334Speter       If not, set INITIALIZED to zero, which will indirectly
3283169699Skan       tell 'finish_decl' to ignore the initializer once it is parsed.  */
328418334Speter    switch (TREE_CODE (decl))
328518334Speter      {
328618334Speter      case TYPE_DECL:
3287169699Skan	error ("typedef %qD is initialized (use __typeof__ instead)", decl);
3288104761Skan	initialized = 0;
328918334Speter	break;
329018334Speter
329118334Speter      case FUNCTION_DECL:
3292169699Skan	error ("function %qD is initialized like a variable", decl);
329318334Speter	initialized = 0;
329418334Speter	break;
329518334Speter
329618334Speter      case PARM_DECL:
329718334Speter	/* DECL_INITIAL in a PARM_DECL is really DECL_ARG_TYPE.  */
3298169699Skan	error ("parameter %qD is initialized", decl);
329918334Speter	initialized = 0;
330018334Speter	break;
330118334Speter
330218334Speter      default:
3303169699Skan	/* Don't allow initializations for incomplete types except for
3304169699Skan	   arrays which might be completed by the initialization.  */
330590075Sobrien
3306169699Skan	/* This can happen if the array size is an undefined macro.
3307169699Skan	   We already gave a warning, so we don't need another one.  */
330890075Sobrien	if (TREE_TYPE (decl) == error_mark_node)
330990075Sobrien	  initialized = 0;
331090075Sobrien	else if (COMPLETE_TYPE_P (TREE_TYPE (decl)))
331118334Speter	  {
331218334Speter	    /* A complete type is ok if size is fixed.  */
331318334Speter
331418334Speter	    if (TREE_CODE (TYPE_SIZE (TREE_TYPE (decl))) != INTEGER_CST
331518334Speter		|| C_DECL_VARIABLE_SIZE (decl))
331618334Speter	      {
331718334Speter		error ("variable-sized object may not be initialized");
331818334Speter		initialized = 0;
331918334Speter	      }
332018334Speter	  }
332118334Speter	else if (TREE_CODE (TREE_TYPE (decl)) != ARRAY_TYPE)
332218334Speter	  {
3323169699Skan	    error ("variable %qD has initializer but incomplete type", decl);
332418334Speter	    initialized = 0;
332518334Speter	  }
3326169699Skan	else if (C_DECL_VARIABLE_SIZE (decl))
332718334Speter	  {
3328169699Skan	    /* Although C99 is unclear about whether incomplete arrays
3329169699Skan	       of VLAs themselves count as VLAs, it does not make
3330169699Skan	       sense to permit them to be initialized given that
3331169699Skan	       ordinary VLAs may not be initialized.  */
3332169699Skan	    error ("variable-sized object may not be initialized");
333318334Speter	    initialized = 0;
333418334Speter	  }
333518334Speter      }
333618334Speter
333718334Speter  if (initialized)
333818334Speter    {
3339169699Skan      if (current_scope == file_scope)
334018334Speter	TREE_STATIC (decl) = 1;
334118334Speter
3342169699Skan      /* Tell 'pushdecl' this is an initialized decl
334318334Speter	 even though we don't yet have the initializer expression.
3344169699Skan	 Also tell 'finish_decl' it may store the real initializer.  */
334518334Speter      DECL_INITIAL (decl) = error_mark_node;
334618334Speter    }
334718334Speter
334818334Speter  /* If this is a function declaration, write a record describing it to the
334918334Speter     prototypes file (if requested).  */
335018334Speter
335118334Speter  if (TREE_CODE (decl) == FUNCTION_DECL)
335218334Speter    gen_aux_info_record (decl, 0, 0, TYPE_ARG_TYPES (TREE_TYPE (decl)) != 0);
335318334Speter
335450397Sobrien  /* ANSI specifies that a tentative definition which is not merged with
335550397Sobrien     a non-tentative definition behaves exactly like a definition with an
335650397Sobrien     initializer equal to zero.  (Section 3.7.2)
3357117421Skan
3358117421Skan     -fno-common gives strict ANSI behavior, though this tends to break
3359117421Skan     a large body of code that grew up without this rule.
3360117421Skan
3361117421Skan     Thread-local variables are never common, since there's no entrenched
3362117421Skan     body of code to break, and it allows more efficient variable references
3363132730Skan     in the presence of dynamic linking.  */
3364117421Skan
3365117421Skan  if (TREE_CODE (decl) == VAR_DECL
3366117421Skan      && !initialized
3367117421Skan      && TREE_PUBLIC (decl)
3368169699Skan      && !DECL_THREAD_LOCAL_P (decl)
3369117421Skan      && !flag_no_common)
337050397Sobrien    DECL_COMMON (decl) = 1;
337118334Speter
337218334Speter  /* Set attributes here so if duplicate decl, will have proper attributes.  */
337390075Sobrien  decl_attributes (&decl, attributes, 0);
337418334Speter
3375189824Sdas  /* Handle gnu_inline attribute.  */
3376189824Sdas  if (declspecs->inline_p
3377189824Sdas      && !flag_gnu89_inline
3378189824Sdas      && TREE_CODE (decl) == FUNCTION_DECL
3379189824Sdas      && lookup_attribute ("gnu_inline", DECL_ATTRIBUTES (decl)))
3380189824Sdas    {
3381189824Sdas      if (declspecs->storage_class == csc_auto && current_scope != file_scope)
3382189824Sdas	;
3383189824Sdas      else if (declspecs->storage_class != csc_static)
3384189824Sdas	DECL_EXTERNAL (decl) = !DECL_EXTERNAL (decl);
3385189824Sdas    }
3386189824Sdas
3387132730Skan  if (TREE_CODE (decl) == FUNCTION_DECL
3388132730Skan      && targetm.calls.promote_prototypes (TREE_TYPE (decl)))
3389132730Skan    {
3390169699Skan      struct c_declarator *ce = declarator;
339196263Sobrien
3392169699Skan      if (ce->kind == cdk_pointer)
3393169699Skan	ce = declarator->declarator;
3394169699Skan      if (ce->kind == cdk_function)
3395132730Skan	{
3396169699Skan	  tree args = ce->u.arg_info->parms;
3397132730Skan	  for (; args; args = TREE_CHAIN (args))
3398132730Skan	    {
3399132730Skan	      tree type = TREE_TYPE (args);
3400169699Skan	      if (type && INTEGRAL_TYPE_P (type)
3401132730Skan		  && TYPE_PRECISION (type) < TYPE_PRECISION (integer_type_node))
3402132730Skan		DECL_ARG_TYPE (args) = integer_type_node;
3403132730Skan	    }
3404132730Skan	}
3405132730Skan    }
3406132730Skan
340790075Sobrien  if (TREE_CODE (decl) == FUNCTION_DECL
340890075Sobrien      && DECL_DECLARED_INLINE_P (decl)
340990075Sobrien      && DECL_UNINLINABLE (decl)
341090075Sobrien      && lookup_attribute ("noinline", DECL_ATTRIBUTES (decl)))
3411169699Skan    warning (OPT_Wattributes, "inline function %q+D given attribute noinline",
3412169699Skan	     decl);
341390075Sobrien
3414189824Sdas  /* C99 6.7.4p3: An inline definition of a function with external
3415189824Sdas     linkage shall not contain a definition of a modifiable object
3416189824Sdas     with static storage duration...  */
3417189824Sdas  if (TREE_CODE (decl) == VAR_DECL
3418189824Sdas      && current_scope != file_scope
3419189824Sdas      && TREE_STATIC (decl)
3420189824Sdas      && !TREE_READONLY (decl)
3421189824Sdas      && DECL_DECLARED_INLINE_P (current_function_decl)
3422189824Sdas      && DECL_EXTERNAL (current_function_decl))
3423189824Sdas    pedwarn ("%q+D is static but declared in inline function %qD "
3424189824Sdas	     "which is not static", decl, current_function_decl);
3425189824Sdas
3426132730Skan  /* Add this decl to the current scope.
342718334Speter     TEM may equal DECL or it may be a previous decl of the same name.  */
342818334Speter  tem = pushdecl (decl);
342918334Speter
3430169699Skan  if (initialized && DECL_EXTERNAL (tem))
343118334Speter    {
3432169699Skan      DECL_EXTERNAL (tem) = 0;
3433169699Skan      TREE_STATIC (tem) = 1;
343418334Speter    }
343518334Speter
343618334Speter  return tem;
343718334Speter}
343818334Speter
3439169699Skan/* Initialize EH if not initialized yet and exceptions are enabled.  */
3440169699Skan
3441169699Skanvoid
3442169699Skanc_maybe_initialize_eh (void)
3443169699Skan{
3444169699Skan  if (!flag_exceptions || c_eh_initialized_p)
3445169699Skan    return;
3446169699Skan
3447169699Skan  c_eh_initialized_p = true;
3448169699Skan  eh_personality_libfunc
3449169699Skan    = init_one_libfunc (USING_SJLJ_EXCEPTIONS
3450169699Skan			? "__gcc_personality_sj0"
3451169699Skan			: "__gcc_personality_v0");
3452169699Skan  default_init_unwind_resume_libfunc ();
3453169699Skan  using_eh_for_cleanups ();
3454169699Skan}
3455169699Skan
345618334Speter/* Finish processing of a declaration;
345718334Speter   install its initial value.
345818334Speter   If the length of an array type is not known before,
345918334Speter   it must be determined now, from the initial value, or it is an error.  */
346018334Speter
346118334Spetervoid
3462132730Skanfinish_decl (tree decl, tree init, tree asmspec_tree)
346318334Speter{
3464169699Skan  tree type;
346518334Speter  int was_incomplete = (DECL_SIZE (decl) == 0);
346690075Sobrien  const char *asmspec = 0;
346718334Speter
346890075Sobrien  /* If a name was specified, get the string.  */
3469169699Skan  if ((TREE_CODE (decl) == FUNCTION_DECL || TREE_CODE (decl) == VAR_DECL)
3470169699Skan      && DECL_FILE_SCOPE_P (decl))
347196263Sobrien    asmspec_tree = maybe_apply_renaming_pragma (decl, asmspec_tree);
347218334Speter  if (asmspec_tree)
347318334Speter    asmspec = TREE_STRING_POINTER (asmspec_tree);
347418334Speter
347518334Speter  /* If `start_decl' didn't like having an initialization, ignore it now.  */
347618334Speter  if (init != 0 && DECL_INITIAL (decl) == 0)
347718334Speter    init = 0;
3478132730Skan
347918334Speter  /* Don't crash if parm is initialized.  */
348018334Speter  if (TREE_CODE (decl) == PARM_DECL)
348118334Speter    init = 0;
348218334Speter
348318334Speter  if (init)
3484104761Skan    store_init_value (decl, init);
348518334Speter
3486132730Skan  if (c_dialect_objc () && (TREE_CODE (decl) == VAR_DECL
3487169699Skan			    || TREE_CODE (decl) == FUNCTION_DECL
3488169699Skan			    || TREE_CODE (decl) == FIELD_DECL))
3489132730Skan    objc_check_decl (decl);
3490132730Skan
3491169699Skan  type = TREE_TYPE (decl);
3492169699Skan
3493132730Skan  /* Deduce size of array from initialization, if not already known.  */
349418334Speter  if (TREE_CODE (type) == ARRAY_TYPE
349518334Speter      && TYPE_DOMAIN (type) == 0
349618334Speter      && TREE_CODE (decl) != TYPE_DECL)
349718334Speter    {
3498169699Skan      bool do_default
349918334Speter	= (TREE_STATIC (decl)
350018334Speter	   /* Even if pedantic, an external linkage array
350118334Speter	      may have incomplete type at first.  */
350218334Speter	   ? pedantic && !TREE_PUBLIC (decl)
350318334Speter	   : !DECL_EXTERNAL (decl));
350418334Speter      int failure
3505169699Skan	= complete_array_type (&TREE_TYPE (decl), DECL_INITIAL (decl),
3506169699Skan			       do_default);
350718334Speter
350818334Speter      /* Get the completed type made by complete_array_type.  */
350918334Speter      type = TREE_TYPE (decl);
351018334Speter
3511169699Skan      switch (failure)
3512169699Skan	{
3513169699Skan	case 1:
3514169699Skan	  error ("initializer fails to determine size of %q+D", decl);
3515169699Skan	  break;
351618334Speter
3517169699Skan	case 2:
351818334Speter	  if (do_default)
3519169699Skan	    error ("array size missing in %q+D", decl);
352018334Speter	  /* If a `static' var's size isn't known,
352118334Speter	     make it extern as well as static, so it does not get
352218334Speter	     allocated.
352318334Speter	     If it is not `static', then do not mark extern;
352418334Speter	     finish_incomplete_decl will give it a default size
352518334Speter	     and it will get allocated.  */
3526169699Skan	  else if (!pedantic && TREE_STATIC (decl) && !TREE_PUBLIC (decl))
352718334Speter	    DECL_EXTERNAL (decl) = 1;
3528169699Skan	  break;
3529169699Skan
3530169699Skan	case 3:
3531169699Skan	  error ("zero or negative size array %q+D", decl);
3532169699Skan	  break;
3533169699Skan
3534169699Skan	case 0:
3535169699Skan	  /* For global variables, update the copy of the type that
3536169699Skan	     exists in the binding.  */
3537169699Skan	  if (TREE_PUBLIC (decl))
3538169699Skan	    {
3539169699Skan	      struct c_binding *b_ext = I_SYMBOL_BINDING (DECL_NAME (decl));
3540169699Skan	      while (b_ext && !B_IN_EXTERNAL_SCOPE (b_ext))
3541169699Skan		b_ext = b_ext->shadowed;
3542169699Skan	      if (b_ext)
3543169699Skan		{
3544169699Skan		  if (b_ext->type)
3545169699Skan		    b_ext->type = composite_type (b_ext->type, type);
3546169699Skan		  else
3547169699Skan		    b_ext->type = type;
3548169699Skan		}
3549169699Skan	    }
3550169699Skan	  break;
3551169699Skan
3552169699Skan	default:
3553169699Skan	  gcc_unreachable ();
355418334Speter	}
355518334Speter
3556169699Skan      if (DECL_INITIAL (decl))
3557169699Skan	TREE_TYPE (DECL_INITIAL (decl)) = type;
355818334Speter
355918334Speter      layout_decl (decl, 0);
356018334Speter    }
356118334Speter
356218334Speter  if (TREE_CODE (decl) == VAR_DECL)
356318334Speter    {
3564169699Skan      if (init && TREE_CODE (init) == CONSTRUCTOR)
3565169699Skan	add_flexible_array_elts_to_size (decl, init);
3566169699Skan
356790075Sobrien      if (DECL_SIZE (decl) == 0 && TREE_TYPE (decl) != error_mark_node
356890075Sobrien	  && COMPLETE_TYPE_P (TREE_TYPE (decl)))
356918334Speter	layout_decl (decl, 0);
357018334Speter
357118334Speter      if (DECL_SIZE (decl) == 0
357290075Sobrien	  /* Don't give an error if we already gave one earlier.  */
357390075Sobrien	  && TREE_TYPE (decl) != error_mark_node
357418334Speter	  && (TREE_STATIC (decl)
3575169699Skan	      /* A static variable with an incomplete type
3576169699Skan		 is an error if it is initialized.
3577169699Skan		 Also if it is not file scope.
3578169699Skan		 Otherwise, let it through, but if it is not `extern'
3579169699Skan		 then it may cause an error message later.  */
3580169699Skan	      ? (DECL_INITIAL (decl) != 0
3581132730Skan		 || !DECL_FILE_SCOPE_P (decl))
3582169699Skan	      /* An automatic variable with an incomplete type
3583169699Skan		 is an error.  */
3584169699Skan	      : !DECL_EXTERNAL (decl)))
3585169699Skan	 {
3586169699Skan	   error ("storage size of %q+D isn%'t known", decl);
3587169699Skan	   TREE_TYPE (decl) = error_mark_node;
3588169699Skan	 }
358918334Speter
359018334Speter      if ((DECL_EXTERNAL (decl) || TREE_STATIC (decl))
359118334Speter	  && DECL_SIZE (decl) != 0)
359218334Speter	{
359318334Speter	  if (TREE_CODE (DECL_SIZE (decl)) == INTEGER_CST)
359418334Speter	    constant_expression_warning (DECL_SIZE (decl));
359518334Speter	  else
3596169699Skan	    error ("storage size of %q+D isn%'t constant", decl);
359718334Speter	}
359850397Sobrien
359990075Sobrien      if (TREE_USED (type))
360050397Sobrien	TREE_USED (decl) = 1;
360118334Speter    }
360218334Speter
3603132730Skan  /* If this is a function and an assembler name is specified, reset DECL_RTL
3604132730Skan     so we can give it its new name.  Also, update built_in_decls if it
3605132730Skan     was a normal built-in.  */
360618334Speter  if (TREE_CODE (decl) == FUNCTION_DECL && asmspec)
360790075Sobrien    {
3608132730Skan      if (DECL_BUILT_IN_CLASS (decl) == BUILT_IN_NORMAL)
3609169699Skan	set_builtin_user_assembler_name (decl, asmspec);
3610169699Skan      set_user_assembler_name (decl, asmspec);
361190075Sobrien    }
361218334Speter
3613132730Skan  /* If #pragma weak was used, mark the decl weak now.  */
3614169699Skan  maybe_apply_pragma_weak (decl);
3615132730Skan
361618334Speter  /* Output the assembler code and/or RTL code for variables and functions,
361718334Speter     unless the type is an undefined structure or union.
361818334Speter     If not, it will get done when the type is completed.  */
361918334Speter
362018334Speter  if (TREE_CODE (decl) == VAR_DECL || TREE_CODE (decl) == FUNCTION_DECL)
362118334Speter    {
3622169699Skan      /* Determine the ELF visibility.  */
3623169699Skan      if (TREE_PUBLIC (decl))
3624169699Skan	c_determine_visibility (decl);
3625169699Skan
3626117421Skan      /* This is a no-op in c-lang.c or something real in objc-act.c.  */
3627132730Skan      if (c_dialect_objc ())
3628117421Skan	objc_check_decl (decl);
362990075Sobrien
3630169699Skan      if (asmspec)
3631169699Skan	{
3632169699Skan	  /* If this is not a static variable, issue a warning.
3633169699Skan	     It doesn't make any sense to give an ASMSPEC for an
3634169699Skan	     ordinary, non-register local variable.  Historically,
3635169699Skan	     GCC has accepted -- but ignored -- the ASMSPEC in
3636169699Skan	     this case.  */
3637169699Skan	  if (!DECL_FILE_SCOPE_P (decl)
3638169699Skan	      && TREE_CODE (decl) == VAR_DECL
3639169699Skan	      && !C_DECL_REGISTER (decl)
3640169699Skan	      && !TREE_STATIC (decl))
3641169699Skan	    warning (0, "ignoring asm-specifier for non-static local "
3642169699Skan		     "variable %q+D", decl);
3643169699Skan	  else
3644169699Skan	    set_user_assembler_name (decl, asmspec);
3645169699Skan	}
3646169699Skan
3647132730Skan      if (DECL_FILE_SCOPE_P (decl))
364818334Speter	{
364990075Sobrien	  if (DECL_INITIAL (decl) == NULL_TREE
365090075Sobrien	      || DECL_INITIAL (decl) == error_mark_node)
365190075Sobrien	    /* Don't output anything
365290075Sobrien	       when a tentative file-scope definition is seen.
365390075Sobrien	       But at end of compilation, do output code for them.  */
365490075Sobrien	    DECL_DEFER_OUTPUT (decl) = 1;
3655169699Skan	  rest_of_decl_compilation (decl, true, 0);
365618334Speter	}
365718334Speter      else
365818334Speter	{
3659169699Skan	  /* In conjunction with an ASMSPEC, the `register'
3660169699Skan	     keyword indicates that we should place the variable
3661169699Skan	     in a particular register.  */
3662169699Skan	  if (asmspec && C_DECL_REGISTER (decl))
366390075Sobrien	    {
3664169699Skan	      DECL_HARD_REGISTER (decl) = 1;
3665169699Skan	      /* This cannot be done for a structure with volatile
3666169699Skan		 fields, on which DECL_REGISTER will have been
3667169699Skan		 reset.  */
3668169699Skan	      if (!DECL_REGISTER (decl))
3669169699Skan		error ("cannot put object with volatile field into register");
367090075Sobrien	    }
367190075Sobrien
367290075Sobrien	  if (TREE_CODE (decl) != FUNCTION_DECL)
3673169699Skan	    {
3674169699Skan	      /* If we're building a variable sized type, and we might be
3675169699Skan		 reachable other than via the top of the current binding
3676169699Skan		 level, then create a new BIND_EXPR so that we deallocate
3677169699Skan		 the object at the right time.  */
3678169699Skan	      /* Note that DECL_SIZE can be null due to errors.  */
3679169699Skan	      if (DECL_SIZE (decl)
3680169699Skan		  && !TREE_CONSTANT (DECL_SIZE (decl))
3681169699Skan		  && STATEMENT_LIST_HAS_LABEL (cur_stmt_list))
3682169699Skan		{
3683169699Skan		  tree bind;
3684169699Skan		  bind = build3 (BIND_EXPR, void_type_node, NULL, NULL, NULL);
3685169699Skan		  TREE_SIDE_EFFECTS (bind) = 1;
3686169699Skan		  add_stmt (bind);
3687169699Skan		  BIND_EXPR_BODY (bind) = push_stmt_list ();
3688169699Skan		}
3689169699Skan	      add_stmt (build_stmt (DECL_EXPR, decl));
3690169699Skan	    }
369118334Speter	}
369290075Sobrien
3693169699Skan
3694132730Skan      if (!DECL_FILE_SCOPE_P (decl))
369518334Speter	{
369618334Speter	  /* Recompute the RTL of a local array now
369718334Speter	     if it used to be an incomplete type.  */
369818334Speter	  if (was_incomplete
3699169699Skan	      && !TREE_STATIC (decl) && !DECL_EXTERNAL (decl))
370018334Speter	    {
370118334Speter	      /* If we used it already as memory, it must stay in memory.  */
370218334Speter	      TREE_ADDRESSABLE (decl) = TREE_USED (decl);
370318334Speter	      /* If it's still incomplete now, no init will save it.  */
370418334Speter	      if (DECL_SIZE (decl) == 0)
370518334Speter		DECL_INITIAL (decl) = 0;
370618334Speter	    }
370718334Speter	}
370818334Speter    }
370918334Speter
3710132730Skan  /* If this was marked 'used', be sure it will be output.  */
3711169699Skan  if (!flag_unit_at_a_time && lookup_attribute ("used", DECL_ATTRIBUTES (decl)))
3712169699Skan    mark_decl_referenced (decl);
3713132730Skan
371418334Speter  if (TREE_CODE (decl) == TYPE_DECL)
3715169699Skan    {
3716169699Skan      if (!DECL_FILE_SCOPE_P (decl)
3717169699Skan	  && variably_modified_type_p (TREE_TYPE (decl), NULL_TREE))
3718169699Skan	add_stmt (build_stmt (DECL_EXPR, decl));
371918334Speter
3720169699Skan      rest_of_decl_compilation (decl, DECL_FILE_SCOPE_P (decl), 0);
3721169699Skan    }
3722169699Skan
372318334Speter  /* At the end of a declaration, throw away any variable type sizes
372418334Speter     of types defined inside that declaration.  There is no use
372518334Speter     computing them in the following function definition.  */
3726169699Skan  if (current_scope == file_scope)
372718334Speter    get_pending_sizes ();
372818334Speter
3729117421Skan  /* Install a cleanup (aka destructor) if one was given.  */
3730117421Skan  if (TREE_CODE (decl) == VAR_DECL && !TREE_STATIC (decl))
3731117421Skan    {
3732117421Skan      tree attr = lookup_attribute ("cleanup", DECL_ATTRIBUTES (decl));
3733117421Skan      if (attr)
3734117421Skan	{
3735117421Skan	  tree cleanup_id = TREE_VALUE (TREE_VALUE (attr));
3736117421Skan	  tree cleanup_decl = lookup_name (cleanup_id);
3737117421Skan	  tree cleanup;
3738117421Skan
3739117421Skan	  /* Build "cleanup(&decl)" for the destructor.  */
3740117421Skan	  cleanup = build_unary_op (ADDR_EXPR, decl, 0);
3741117421Skan	  cleanup = build_tree_list (NULL_TREE, cleanup);
3742117421Skan	  cleanup = build_function_call (cleanup_decl, cleanup);
3743117421Skan
3744117421Skan	  /* Don't warn about decl unused; the cleanup uses it.  */
3745117421Skan	  TREE_USED (decl) = 1;
3746169699Skan	  TREE_USED (cleanup_decl) = 1;
3747117421Skan
3748117421Skan	  /* Initialize EH, if we've been told to do so.  */
3749169699Skan	  c_maybe_initialize_eh ();
3750117421Skan
3751169699Skan	  push_cleanup (decl, cleanup, false);
3752117421Skan	}
3753117421Skan    }
375418334Speter}
375518334Speter
3756169699Skan/* Given a parsed parameter declaration, decode it into a PARM_DECL.  */
3757169699Skan
3758169699Skantree
3759169699Skangrokparm (const struct c_parm *parm)
3760169699Skan{
3761169699Skan  tree decl = grokdeclarator (parm->declarator, parm->specs, PARM, false,
3762169699Skan			      NULL);
3763169699Skan
3764169699Skan  decl_attributes (&decl, parm->attrs, 0);
3765169699Skan
3766169699Skan  return decl;
3767169699Skan}
3768169699Skan
3769132730Skan/* Given a parsed parameter declaration, decode it into a PARM_DECL
3770132730Skan   and push that on the current scope.  */
377118334Speter
377218334Spetervoid
3773169699Skanpush_parm_decl (const struct c_parm *parm)
377418334Speter{
377518334Speter  tree decl;
3776132730Skan
3777169699Skan  decl = grokdeclarator (parm->declarator, parm->specs, PARM, false, NULL);
3778169699Skan  decl_attributes (&decl, parm->attrs, 0);
377918334Speter
378018334Speter  decl = pushdecl (decl);
378118334Speter
3782132730Skan  finish_decl (decl, NULL_TREE, NULL_TREE);
378318334Speter}
378418334Speter
3785169699Skan/* Mark all the parameter declarations to date as forward decls.
3786132730Skan   Also diagnose use of this extension.  */
378718334Speter
378818334Spetervoid
3789132730Skanmark_forward_parm_decls (void)
379018334Speter{
3791169699Skan  struct c_binding *b;
3792132730Skan
3793132730Skan  if (pedantic && !current_scope->warned_forward_parm_decls)
3794132730Skan    {
3795132730Skan      pedwarn ("ISO C forbids forward parameter declarations");
3796132730Skan      current_scope->warned_forward_parm_decls = true;
3797132730Skan    }
3798132730Skan
3799169699Skan  for (b = current_scope->bindings; b; b = b->prev)
3800169699Skan    if (TREE_CODE (b->decl) == PARM_DECL)
3801169699Skan      TREE_ASM_WRITTEN (b->decl) = 1;
380218334Speter}
380318334Speter
380490075Sobrien/* Build a COMPOUND_LITERAL_EXPR.  TYPE is the type given in the compound
380590075Sobrien   literal, which may be an incomplete array type completed by the
380690075Sobrien   initializer; INIT is a CONSTRUCTOR that initializes the compound
380790075Sobrien   literal.  */
380890075Sobrien
380990075Sobrientree
3810132730Skanbuild_compound_literal (tree type, tree init)
381190075Sobrien{
381290075Sobrien  /* We do not use start_decl here because we have a type, not a declarator;
381390075Sobrien     and do not use finish_decl because the decl should be stored inside
3814169699Skan     the COMPOUND_LITERAL_EXPR rather than added elsewhere as a DECL_EXPR.  */
3815169699Skan  tree decl;
381690075Sobrien  tree complit;
381790075Sobrien  tree stmt;
3818169699Skan
3819169699Skan  if (type == error_mark_node)
3820169699Skan    return error_mark_node;
3821169699Skan
3822169699Skan  decl = build_decl (VAR_DECL, NULL_TREE, type);
382390075Sobrien  DECL_EXTERNAL (decl) = 0;
382490075Sobrien  TREE_PUBLIC (decl) = 0;
3825169699Skan  TREE_STATIC (decl) = (current_scope == file_scope);
382690075Sobrien  DECL_CONTEXT (decl) = current_function_decl;
382790075Sobrien  TREE_USED (decl) = 1;
382890075Sobrien  TREE_TYPE (decl) = type;
3829169699Skan  TREE_READONLY (decl) = TYPE_READONLY (type);
383090075Sobrien  store_init_value (decl, init);
383190075Sobrien
383290075Sobrien  if (TREE_CODE (type) == ARRAY_TYPE && !COMPLETE_TYPE_P (type))
383390075Sobrien    {
3834169699Skan      int failure = complete_array_type (&TREE_TYPE (decl),
3835169699Skan					 DECL_INITIAL (decl), true);
3836169699Skan      gcc_assert (!failure);
3837169699Skan
3838169699Skan      type = TREE_TYPE (decl);
3839169699Skan      TREE_TYPE (DECL_INITIAL (decl)) = type;
384090075Sobrien    }
384190075Sobrien
384290075Sobrien  if (type == error_mark_node || !COMPLETE_TYPE_P (type))
384390075Sobrien    return error_mark_node;
384490075Sobrien
3845169699Skan  stmt = build_stmt (DECL_EXPR, decl);
3846169699Skan  complit = build1 (COMPOUND_LITERAL_EXPR, type, stmt);
384790075Sobrien  TREE_SIDE_EFFECTS (complit) = 1;
384890075Sobrien
384990075Sobrien  layout_decl (decl, 0);
385090075Sobrien
385190075Sobrien  if (TREE_STATIC (decl))
385290075Sobrien    {
3853169699Skan      /* This decl needs a name for the assembler output.  */
3854169699Skan      set_compound_literal_name (decl);
3855102790Skan      DECL_DEFER_OUTPUT (decl) = 1;
3856102790Skan      DECL_COMDAT (decl) = 1;
3857102790Skan      DECL_ARTIFICIAL (decl) = 1;
3858169699Skan      DECL_IGNORED_P (decl) = 1;
3859102790Skan      pushdecl (decl);
3860169699Skan      rest_of_decl_compilation (decl, 1, 0);
386190075Sobrien    }
386290075Sobrien
386390075Sobrien  return complit;
386490075Sobrien}
386590075Sobrien
3866117421Skan/* Determine whether TYPE is a structure with a flexible array member,
3867117421Skan   or a union containing such a structure (possibly recursively).  */
3868117421Skan
3869117421Skanstatic bool
3870132730Skanflexible_array_type_p (tree type)
3871117421Skan{
3872117421Skan  tree x;
3873117421Skan  switch (TREE_CODE (type))
3874117421Skan    {
3875117421Skan    case RECORD_TYPE:
3876117421Skan      x = TYPE_FIELDS (type);
3877117421Skan      if (x == NULL_TREE)
3878117421Skan	return false;
3879117421Skan      while (TREE_CHAIN (x) != NULL_TREE)
3880117421Skan	x = TREE_CHAIN (x);
3881117421Skan      if (TREE_CODE (TREE_TYPE (x)) == ARRAY_TYPE
3882117421Skan	  && TYPE_SIZE (TREE_TYPE (x)) == NULL_TREE
3883117421Skan	  && TYPE_DOMAIN (TREE_TYPE (x)) != NULL_TREE
3884117421Skan	  && TYPE_MAX_VALUE (TYPE_DOMAIN (TREE_TYPE (x))) == NULL_TREE)
3885117421Skan	return true;
3886117421Skan      return false;
3887117421Skan    case UNION_TYPE:
3888117421Skan      for (x = TYPE_FIELDS (type); x != NULL_TREE; x = TREE_CHAIN (x))
3889117421Skan	{
3890117421Skan	  if (flexible_array_type_p (TREE_TYPE (x)))
3891117421Skan	    return true;
3892117421Skan	}
3893117421Skan      return false;
3894117421Skan    default:
3895117421Skan    return false;
3896117421Skan  }
3897117421Skan}
3898117421Skan
3899132730Skan/* Performs sanity checks on the TYPE and WIDTH of the bit-field NAME,
3900132730Skan   replacing with appropriate values if they are invalid.  */
3901132730Skanstatic void
3902132730Skancheck_bitfield_type_and_width (tree *type, tree *width, const char *orig_name)
3903132730Skan{
3904132730Skan  tree type_mv;
3905132730Skan  unsigned int max_width;
3906132730Skan  unsigned HOST_WIDE_INT w;
3907132730Skan  const char *name = orig_name ? orig_name: _("<anonymous>");
3908132730Skan
3909132730Skan  /* Detect and ignore out of range field width and process valid
3910132730Skan     field widths.  */
3911169699Skan  if (!INTEGRAL_TYPE_P (TREE_TYPE (*width))
3912169699Skan      || TREE_CODE (*width) != INTEGER_CST)
3913132730Skan    {
3914169699Skan      error ("bit-field %qs width not an integer constant", name);
3915132730Skan      *width = integer_one_node;
3916132730Skan    }
3917132730Skan  else
3918132730Skan    {
3919132730Skan      constant_expression_warning (*width);
3920132730Skan      if (tree_int_cst_sgn (*width) < 0)
3921132730Skan	{
3922169699Skan	  error ("negative width in bit-field %qs", name);
3923132730Skan	  *width = integer_one_node;
3924132730Skan	}
3925132730Skan      else if (integer_zerop (*width) && orig_name)
3926132730Skan	{
3927169699Skan	  error ("zero width for bit-field %qs", name);
3928132730Skan	  *width = integer_one_node;
3929132730Skan	}
3930132730Skan    }
3931132730Skan
3932132730Skan  /* Detect invalid bit-field type.  */
3933132730Skan  if (TREE_CODE (*type) != INTEGER_TYPE
3934132730Skan      && TREE_CODE (*type) != BOOLEAN_TYPE
3935132730Skan      && TREE_CODE (*type) != ENUMERAL_TYPE)
3936132730Skan    {
3937169699Skan      error ("bit-field %qs has invalid type", name);
3938132730Skan      *type = unsigned_type_node;
3939132730Skan    }
3940132730Skan
3941132730Skan  type_mv = TYPE_MAIN_VARIANT (*type);
3942132730Skan  if (pedantic
3943169699Skan      && !in_system_header
3944132730Skan      && type_mv != integer_type_node
3945132730Skan      && type_mv != unsigned_type_node
3946132730Skan      && type_mv != boolean_type_node)
3947169699Skan    pedwarn ("type of bit-field %qs is a GCC extension", name);
3948132730Skan
3949132730Skan  if (type_mv == boolean_type_node)
3950132730Skan    max_width = CHAR_TYPE_SIZE;
3951132730Skan  else
3952132730Skan    max_width = TYPE_PRECISION (*type);
3953132730Skan
3954132730Skan  if (0 < compare_tree_int (*width, max_width))
3955132730Skan    {
3956169699Skan      error ("width of %qs exceeds its type", name);
3957132730Skan      w = max_width;
3958169699Skan      *width = build_int_cst (NULL_TREE, w);
3959132730Skan    }
3960132730Skan  else
3961132730Skan    w = tree_low_cst (*width, 1);
3962132730Skan
3963169699Skan  if (TREE_CODE (*type) == ENUMERAL_TYPE)
3964169699Skan    {
3965169699Skan      struct lang_type *lt = TYPE_LANG_SPECIFIC (*type);
3966169699Skan      if (!lt
3967169699Skan	  || w < min_precision (lt->enum_min, TYPE_UNSIGNED (*type))
3968169699Skan	  || w < min_precision (lt->enum_max, TYPE_UNSIGNED (*type)))
3969169699Skan	warning (0, "%qs is narrower than values of its type", name);
3970169699Skan    }
3971132730Skan}
3972169699Skan
3973132730Skan
3974259269Spfg
3975259269Spfg/* Print warning about variable length array if necessary.  */
3976259269Spfg
3977259269Spfgstatic void
3978259269Spfgwarn_variable_length_array (const char *name, tree size)
3979259269Spfg{
3980259269Spfg  int ped = !flag_isoc99 && pedantic && warn_vla != 0;
3981259269Spfg  int const_size = TREE_CONSTANT (size);
3982259269Spfg
3983259269Spfg  if (ped)
3984259269Spfg    {
3985259269Spfg      if (const_size)
3986259269Spfg	{
3987259269Spfg	  if (name)
3988259269Spfg	    pedwarn ("ISO C90 forbids array %qs whose size "
3989259269Spfg		     "can%'t be evaluated",
3990259269Spfg		     name);
3991259269Spfg	  else
3992259269Spfg	    pedwarn ("ISO C90 forbids array whose size "
3993259269Spfg		     "can%'t be evaluated");
3994259269Spfg	}
3995259269Spfg      else
3996259269Spfg	{
3997259269Spfg	  if (name)
3998259269Spfg	    pedwarn ("ISO C90 forbids variable length array %qs",
3999259269Spfg		     name);
4000259269Spfg	  else
4001259269Spfg	    pedwarn ("ISO C90 forbids variable length array");
4002259269Spfg	}
4003259269Spfg    }
4004259269Spfg  else if (warn_vla > 0)
4005259269Spfg    {
4006259269Spfg      if (const_size)
4007259269Spfg        {
4008259269Spfg	  if (name)
4009259269Spfg	    warning (OPT_Wvla,
4010259269Spfg		     "the size of array %qs can"
4011259269Spfg		     "%'t be evaluated", name);
4012259269Spfg	  else
4013259269Spfg	    warning (OPT_Wvla,
4014259269Spfg		     "the size of array can %'t be evaluated");
4015259269Spfg	}
4016259269Spfg      else
4017259269Spfg	{
4018259269Spfg	  if (name)
4019259269Spfg	    warning (OPT_Wvla,
4020259269Spfg		     "variable length array %qs is used",
4021259269Spfg		     name);
4022259269Spfg	  else
4023259269Spfg	    warning (OPT_Wvla,
4024259269Spfg		     "variable length array is used");
4025259269Spfg	}
4026259269Spfg    }
4027259269Spfg}
4028259269Spfg
402918334Speter/* Given declspecs and a declarator,
403018334Speter   determine the name and type of the object declared
403118334Speter   and construct a ..._DECL node for it.
403218334Speter   (In one case we can return a ..._TYPE node instead.
403318334Speter    For invalid input we sometimes return 0.)
403418334Speter
4035169699Skan   DECLSPECS is a c_declspecs structure for the declaration specifiers.
403618334Speter
403718334Speter   DECL_CONTEXT says which syntactic context this declaration is in:
403818334Speter     NORMAL for most contexts.  Make a VAR_DECL or FUNCTION_DECL or TYPE_DECL.
403918334Speter     FUNCDEF for a function definition.  Like NORMAL but a few different
404018334Speter      error messages in each case.  Return value may be zero meaning
404118334Speter      this definition is too screwy to try to parse.
404218334Speter     PARM for a parameter declaration (either within a function prototype
404318334Speter      or before a function body).  Make a PARM_DECL, or return void_type_node.
404418334Speter     TYPENAME if for a typename (in a cast or sizeof).
404518334Speter      Don't make a DECL node; just return the ..._TYPE node.
404618334Speter     FIELD for a struct or union field; make a FIELD_DECL.
4047169699Skan   INITIALIZED is true if the decl has an initializer.
4048132730Skan   WIDTH is non-NULL for bit-fields, and is a pointer to an INTEGER_CST node
4049132730Skan   representing the width of the bit-field.
405018334Speter
405118334Speter   In the TYPENAME case, DECLARATOR is really an absolute declarator.
405218334Speter   It may also be so in the PARM case, for a prototype where the
405318334Speter   argument type is specified but not the name.
405418334Speter
405518334Speter   This function is where the complicated C meanings of `static'
405618334Speter   and `extern' are interpreted.  */
405718334Speter
405818334Speterstatic tree
4059169699Skangrokdeclarator (const struct c_declarator *declarator,
4060169699Skan		struct c_declspecs *declspecs,
4061169699Skan		enum decl_context decl_context, bool initialized, tree *width)
406218334Speter{
4063169699Skan  tree type = declspecs->type;
4064169699Skan  bool threadp = declspecs->thread_p;
4065169699Skan  enum c_storage_class storage_class = declspecs->storage_class;
406618334Speter  int constp;
406752284Sobrien  int restrictp;
406818334Speter  int volatilep;
406952284Sobrien  int type_quals = TYPE_UNQUALIFIED;
4070132730Skan  const char *name, *orig_name;
407118334Speter  tree typedef_type = 0;
4072169699Skan  bool funcdef_flag = false;
4073169699Skan  bool funcdef_syntax = false;
407418334Speter  int size_varies = 0;
4075169699Skan  tree decl_attr = declspecs->decl_attr;
4076169699Skan  int array_ptr_quals = TYPE_UNQUALIFIED;
4077169699Skan  tree array_ptr_attrs = NULL_TREE;
407890075Sobrien  int array_parm_static = 0;
4079169699Skan  bool array_parm_vla_unspec_p = false;
408090075Sobrien  tree returned_attrs = NULL_TREE;
4081132730Skan  bool bitfield = width != NULL;
4082132730Skan  tree element_type;
4083169699Skan  struct c_arg_info *arg_info = 0;
408418334Speter
408518334Speter  if (decl_context == FUNCDEF)
4086169699Skan    funcdef_flag = true, decl_context = NORMAL;
408718334Speter
408818334Speter  /* Look inside a declarator for the name being declared
408918334Speter     and get it as a string, for an error message.  */
409018334Speter  {
4091169699Skan    const struct c_declarator *decl = declarator;
409218334Speter    name = 0;
409318334Speter
409418334Speter    while (decl)
4095169699Skan      switch (decl->kind)
409618334Speter	{
4097169699Skan	case cdk_function:
4098169699Skan	case cdk_array:
4099169699Skan	case cdk_pointer:
4100169699Skan	  funcdef_syntax = (decl->kind == cdk_function);
4101169699Skan	  decl = decl->declarator;
410218334Speter	  break;
410318334Speter
4104169699Skan	case cdk_attrs:
4105169699Skan	  decl = decl->declarator;
410690075Sobrien	  break;
410790075Sobrien
4108169699Skan	case cdk_id:
4109169699Skan	  if (decl->u.id)
4110169699Skan	    name = IDENTIFIER_POINTER (decl->u.id);
411118334Speter	  decl = 0;
411218334Speter	  break;
411318334Speter
411418334Speter	default:
4115169699Skan	  gcc_unreachable ();
411618334Speter	}
4117132730Skan    orig_name = name;
411818334Speter    if (name == 0)
411918334Speter      name = "type name";
412018334Speter  }
412118334Speter
412218334Speter  /* A function definition's declarator must have the form of
412318334Speter     a function declarator.  */
412418334Speter
4125169699Skan  if (funcdef_flag && !funcdef_syntax)
412618334Speter    return 0;
412718334Speter
412818334Speter  /* If this looks like a function definition, make it one,
412918334Speter     even if it occurs where parms are expected.
413018334Speter     Then store_parm_decls will reject it and not use it as a parm.  */
4131260919Spfg  /* APPLE LOCAL begin "unavailable" attribute (radar 2809697) */
4132260919Spfg  if (declspecs->unavailable_p)
4133260919Spfg    error_unavailable_use (declspecs->type);
4134260919Spfg  else
4135260919Spfg  /* APPLE LOCAL end "unavailable" attribute (radar 2809697) */
4136169699Skan  if (decl_context == NORMAL && !funcdef_flag && current_scope->parm_flag)
413718334Speter    decl_context = PARM;
413818334Speter
4139169699Skan  if (declspecs->deprecated_p && deprecated_state != DEPRECATED_SUPPRESS)
4140169699Skan    warn_deprecated_use (declspecs->type);
414118334Speter
4142169699Skan  if ((decl_context == NORMAL || decl_context == FIELD)
4143169699Skan      && current_scope == file_scope
4144169699Skan      && variably_modified_type_p (type, NULL_TREE))
414518334Speter    {
4146169699Skan      error ("variably modified %qs at file scope", name);
4147169699Skan      type = integer_type_node;
414818334Speter    }
414918334Speter
415018334Speter  typedef_type = type;
4151169699Skan  size_varies = C_TYPE_VARIABLE_SIZE (type);
415218334Speter
4153169699Skan  /* Diagnose defaulting to "int".  */
415418334Speter
4155169699Skan  if (declspecs->default_int_p && !in_system_header)
415618334Speter    {
4157169699Skan      /* Issue a warning if this is an ISO C 99 program or if
4158169699Skan	 -Wreturn-type and this is a function, or if -Wimplicit;
4159169699Skan	 prefer the former warning since it is more explicit.  */
4160169699Skan      if ((warn_implicit_int || warn_return_type || flag_isoc99)
4161169699Skan	  && funcdef_flag)
4162169699Skan	warn_about_return_type = 1;
4163169699Skan      else if (warn_implicit_int || flag_isoc99)
4164169699Skan	pedwarn_c99 ("type defaults to %<int%> in declaration of %qs", name);
416518334Speter    }
416618334Speter
4167169699Skan  /* Adjust the type if a bit-field is being declared,
4168169699Skan     -funsigned-bitfields applied and the type is not explicitly
4169169699Skan     "signed".  */
4170169699Skan  if (bitfield && !flag_signed_bitfields && !declspecs->explicit_signed_p
4171169699Skan      && TREE_CODE (type) == INTEGER_TYPE)
4172169699Skan    type = c_common_unsigned_type (type);
417318334Speter
417452284Sobrien  /* Figure out the type qualifiers for the declaration.  There are
417552284Sobrien     two ways a declaration can become qualified.  One is something
417652284Sobrien     like `const int i' where the `const' is explicit.  Another is
417752284Sobrien     something like `typedef const int CI; CI i' where the type of the
4178132730Skan     declaration contains the `const'.  A third possibility is that
4179132730Skan     there is a type qualifier on the element type of a typedefed
4180132730Skan     array type, in which case we should extract that qualifier so
4181132730Skan     that c_apply_type_quals_to_decls receives the full list of
4182132730Skan     qualifiers to work with (C90 is not entirely clear about whether
4183132730Skan     duplicate qualifiers should be diagnosed in this case, but it
4184132730Skan     seems most appropriate to do so).  */
4185132730Skan  element_type = strip_array_types (type);
4186169699Skan  constp = declspecs->const_p + TYPE_READONLY (element_type);
4187169699Skan  restrictp = declspecs->restrict_p + TYPE_RESTRICT (element_type);
4188169699Skan  volatilep = declspecs->volatile_p + TYPE_VOLATILE (element_type);
4189132730Skan  if (pedantic && !flag_isoc99)
4190132730Skan    {
4191132730Skan      if (constp > 1)
4192169699Skan	pedwarn ("duplicate %<const%>");
4193132730Skan      if (restrictp > 1)
4194169699Skan	pedwarn ("duplicate %<restrict%>");
4195132730Skan      if (volatilep > 1)
4196169699Skan	pedwarn ("duplicate %<volatile%>");
4197132730Skan    }
4198169699Skan  if (!flag_gen_aux_info && (TYPE_QUALS (element_type)))
419918334Speter    type = TYPE_MAIN_VARIANT (type);
420052284Sobrien  type_quals = ((constp ? TYPE_QUAL_CONST : 0)
420152284Sobrien		| (restrictp ? TYPE_QUAL_RESTRICT : 0)
420252284Sobrien		| (volatilep ? TYPE_QUAL_VOLATILE : 0));
420318334Speter
4204169699Skan  /* Warn about storage classes that are invalid for certain
4205169699Skan     kinds of declarations (parameters, typenames, etc.).  */
420618334Speter
4207169699Skan  if (funcdef_flag
4208169699Skan      && (threadp
4209169699Skan	  || storage_class == csc_auto
4210169699Skan	  || storage_class == csc_register
4211169699Skan	  || storage_class == csc_typedef))
4212169699Skan    {
4213169699Skan      if (storage_class == csc_auto
4214169699Skan	  && (pedantic || current_scope == file_scope))
4215169699Skan	pedwarn ("function definition declared %<auto%>");
4216169699Skan      if (storage_class == csc_register)
4217169699Skan	error ("function definition declared %<register%>");
4218169699Skan      if (storage_class == csc_typedef)
4219169699Skan	error ("function definition declared %<typedef%>");
4220169699Skan      if (threadp)
4221169699Skan	error ("function definition declared %<__thread%>");
4222169699Skan      threadp = false;
4223169699Skan      if (storage_class == csc_auto
4224169699Skan	  || storage_class == csc_register
4225169699Skan	  || storage_class == csc_typedef)
4226169699Skan	storage_class = csc_none;
4227169699Skan    }
4228169699Skan  else if (decl_context != NORMAL && (storage_class != csc_none || threadp))
4229169699Skan    {
4230169699Skan      if (decl_context == PARM && storage_class == csc_register)
4231169699Skan	;
4232169699Skan      else
4233169699Skan	{
4234169699Skan	  switch (decl_context)
4235169699Skan	    {
4236169699Skan	    case FIELD:
4237169699Skan	      error ("storage class specified for structure field %qs",
4238169699Skan		     name);
4239169699Skan	      break;
4240169699Skan	    case PARM:
4241169699Skan	      error ("storage class specified for parameter %qs", name);
4242169699Skan	      break;
4243169699Skan	    default:
4244169699Skan	      error ("storage class specified for typename");
4245169699Skan	      break;
4246169699Skan	    }
4247169699Skan	  storage_class = csc_none;
4248169699Skan	  threadp = false;
4249169699Skan	}
4250169699Skan    }
4251169699Skan  else if (storage_class == csc_extern
4252169699Skan	   && initialized
4253169699Skan	   && !funcdef_flag)
4254169699Skan    {
4255169699Skan      /* 'extern' with initialization is invalid if not at file scope.  */
4256169699Skan       if (current_scope == file_scope)
4257169699Skan         {
4258169699Skan           /* It is fine to have 'extern const' when compiling at C
4259169699Skan              and C++ intersection.  */
4260169699Skan           if (!(warn_cxx_compat && constp))
4261169699Skan             warning (0, "%qs initialized and declared %<extern%>", name);
4262169699Skan         }
4263169699Skan      else
4264169699Skan	error ("%qs has both %<extern%> and initializer", name);
4265169699Skan    }
4266169699Skan  else if (current_scope == file_scope)
4267169699Skan    {
4268169699Skan      if (storage_class == csc_auto)
4269169699Skan	error ("file-scope declaration of %qs specifies %<auto%>", name);
4270169699Skan      if (pedantic && storage_class == csc_register)
4271169699Skan	pedwarn ("file-scope declaration of %qs specifies %<register%>", name);
4272169699Skan    }
4273169699Skan  else
4274169699Skan    {
4275169699Skan      if (storage_class == csc_extern && funcdef_flag)
4276169699Skan	error ("nested function %qs declared %<extern%>", name);
4277169699Skan      else if (threadp && storage_class == csc_none)
4278169699Skan	{
4279169699Skan	  error ("function-scope %qs implicitly auto and declared "
4280169699Skan		 "%<__thread%>",
4281169699Skan		 name);
4282169699Skan	  threadp = false;
4283169699Skan	}
4284169699Skan    }
428518334Speter
428618334Speter  /* Now figure out the structure of the declarator proper.
428718334Speter     Descend through it, creating more complex types, until we reach
4288169699Skan     the declared identifier (or NULL_TREE, in an absolute declarator).
4289169699Skan     At each stage we maintain an unqualified version of the type
4290169699Skan     together with any qualifiers that should be applied to it with
4291169699Skan     c_build_qualified_type; this way, array types including
4292169699Skan     multidimensional array types are first built up in unqualified
4293169699Skan     form and then the qualified form is created with
4294169699Skan     TYPE_MAIN_VARIANT pointing to the unqualified form.  */
429518334Speter
4296169699Skan  while (declarator && declarator->kind != cdk_id)
429718334Speter    {
429818334Speter      if (type == error_mark_node)
429918334Speter	{
4300169699Skan	  declarator = declarator->declarator;
430118334Speter	  continue;
430218334Speter	}
430318334Speter
4304169699Skan      /* Each level of DECLARATOR is either a cdk_array (for ...[..]),
4305169699Skan	 a cdk_pointer (for *...),
4306169699Skan	 a cdk_function (for ...(...)),
4307169699Skan	 a cdk_attrs (for nested attributes),
4308169699Skan	 or a cdk_id (for the name being declared
4309169699Skan	 or the place in an absolute declarator
431018334Speter	 where the name was omitted).
4311169699Skan	 For the last case, we have just exited the loop.
431218334Speter
431318334Speter	 At this point, TYPE is the type of elements of an array,
431418334Speter	 or for a function to return, or for a pointer to point to.
431518334Speter	 After this sequence of ifs, TYPE is the type of the
431618334Speter	 array or function or pointer, and DECLARATOR has had its
431718334Speter	 outermost layer removed.  */
431818334Speter
4319169699Skan      if (array_ptr_quals != TYPE_UNQUALIFIED
4320169699Skan	  || array_ptr_attrs != NULL_TREE
4321169699Skan	  || array_parm_static)
432218334Speter	{
432390075Sobrien	  /* Only the innermost declarator (making a parameter be of
432490075Sobrien	     array type which is converted to pointer type)
432590075Sobrien	     may have static or type qualifiers.  */
432690075Sobrien	  error ("static or type qualifiers in non-parameter array declarator");
4327169699Skan	  array_ptr_quals = TYPE_UNQUALIFIED;
4328169699Skan	  array_ptr_attrs = NULL_TREE;
432990075Sobrien	  array_parm_static = 0;
433090075Sobrien	}
433190075Sobrien
4332169699Skan      switch (declarator->kind)
433390075Sobrien	{
4334169699Skan	case cdk_attrs:
4335169699Skan	  {
4336169699Skan	    /* A declarator with embedded attributes.  */
4337169699Skan	    tree attrs = declarator->u.attrs;
4338169699Skan	    const struct c_declarator *inner_decl;
4339169699Skan	    int attr_flags = 0;
4340169699Skan	    declarator = declarator->declarator;
4341169699Skan	    inner_decl = declarator;
4342169699Skan	    while (inner_decl->kind == cdk_attrs)
4343169699Skan	      inner_decl = inner_decl->declarator;
4344169699Skan	    if (inner_decl->kind == cdk_id)
4345169699Skan	      attr_flags |= (int) ATTR_FLAG_DECL_NEXT;
4346169699Skan	    else if (inner_decl->kind == cdk_function)
4347169699Skan	      attr_flags |= (int) ATTR_FLAG_FUNCTION_NEXT;
4348169699Skan	    else if (inner_decl->kind == cdk_array)
4349169699Skan	      attr_flags |= (int) ATTR_FLAG_ARRAY_NEXT;
4350169699Skan	    returned_attrs = decl_attributes (&type,
4351169699Skan					      chainon (returned_attrs, attrs),
4352169699Skan					      attr_flags);
4353169699Skan	    break;
4354169699Skan	  }
4355169699Skan	case cdk_array:
4356169699Skan	  {
4357169699Skan	    tree itype = NULL_TREE;
4358169699Skan	    tree size = declarator->u.array.dimen;
4359169699Skan	    /* The index is a signed object `sizetype' bits wide.  */
4360169699Skan	    tree index_type = c_common_signed_type (sizetype);
436118334Speter
4362169699Skan	    array_ptr_quals = declarator->u.array.quals;
4363169699Skan	    array_ptr_attrs = declarator->u.array.attrs;
4364169699Skan	    array_parm_static = declarator->u.array.static_p;
4365169699Skan	    array_parm_vla_unspec_p = declarator->u.array.vla_unspec_p;
436690075Sobrien
4367169699Skan	    declarator = declarator->declarator;
436818334Speter
4369169699Skan	    /* Check for some types that there cannot be arrays of.  */
437018334Speter
4371169699Skan	    if (VOID_TYPE_P (type))
4372169699Skan	      {
4373169699Skan		error ("declaration of %qs as array of voids", name);
4374169699Skan		type = error_mark_node;
4375169699Skan	      }
437618334Speter
4377169699Skan	    if (TREE_CODE (type) == FUNCTION_TYPE)
4378169699Skan	      {
4379169699Skan		error ("declaration of %qs as array of functions", name);
4380169699Skan		type = error_mark_node;
4381169699Skan	      }
4382169699Skan
4383169699Skan	    if (pedantic && !in_system_header && flexible_array_type_p (type))
4384169699Skan	      pedwarn ("invalid use of structure with flexible array member");
4385169699Skan
4386169699Skan	    if (size == error_mark_node)
438718334Speter	      type = error_mark_node;
438818334Speter
4389169699Skan	    if (type == error_mark_node)
4390169699Skan	      continue;
4391117421Skan
4392169699Skan	    /* If size was specified, set ITYPE to a range-type for
4393169699Skan	       that size.  Otherwise, ITYPE remains null.  finish_decl
4394169699Skan	       may figure it out from an initial value.  */
439518334Speter
4396169699Skan	    if (size)
4397169699Skan	      {
4398169699Skan		/* Strip NON_LVALUE_EXPRs since we aren't using as an
4399169699Skan		   lvalue.  */
4400169699Skan		STRIP_TYPE_NOPS (size);
440118334Speter
4402169699Skan		if (!INTEGRAL_TYPE_P (TREE_TYPE (size)))
4403169699Skan		  {
4404169699Skan		    error ("size of array %qs has non-integer type", name);
4405169699Skan		    size = integer_one_node;
4406169699Skan		  }
440718334Speter
4408169699Skan		if (pedantic && integer_zerop (size))
4409169699Skan		  pedwarn ("ISO C forbids zero-size array %qs", name);
441018334Speter
4411169699Skan		if (TREE_CODE (size) == INTEGER_CST)
4412169699Skan		  {
4413169699Skan		    constant_expression_warning (size);
4414169699Skan		    if (tree_int_cst_sgn (size) < 0)
4415169699Skan		      {
4416169699Skan			error ("size of array %qs is negative", name);
4417169699Skan			size = integer_one_node;
4418169699Skan		      }
4419169699Skan		  }
4420169699Skan		else if ((decl_context == NORMAL || decl_context == FIELD)
4421169699Skan			 && current_scope == file_scope)
4422169699Skan		  {
4423169699Skan		    error ("variably modified %qs at file scope", name);
4424169699Skan		    size = integer_one_node;
4425169699Skan		  }
4426169699Skan		else
4427169699Skan		  {
4428169699Skan		    /* Make sure the array size remains visibly
4429169699Skan		       nonconstant even if it is (eg) a const variable
4430169699Skan		       with known value.  */
4431169699Skan		    size_varies = 1;
4432259269Spfg		    warn_variable_length_array (orig_name, size);
4433223715Suqs		    if (warn_variable_decl)
4434223715Suqs		      warning (0, "variable-sized array %qs", name);
4435169699Skan		  }
443618334Speter
4437169699Skan		if (integer_zerop (size))
4438169699Skan		  {
4439169699Skan		    /* A zero-length array cannot be represented with
4440169699Skan		       an unsigned index type, which is what we'll
4441169699Skan		       get with build_index_type.  Create an
4442169699Skan		       open-ended range instead.  */
4443169699Skan		    itype = build_range_type (sizetype, size, NULL_TREE);
4444169699Skan		  }
4445169699Skan		else
4446169699Skan		  {
4447169699Skan		    /* Arrange for the SAVE_EXPR on the inside of the
4448169699Skan		       MINUS_EXPR, which allows the -1 to get folded
4449169699Skan		       with the +1 that happens when building TYPE_SIZE.  */
4450169699Skan		    if (size_varies)
4451169699Skan		      size = variable_size (size);
445218334Speter
4453169699Skan		    /* Compute the maximum valid index, that is, size
4454169699Skan		       - 1.  Do the calculation in index_type, so that
4455169699Skan		       if it is a variable the computations will be
4456169699Skan		       done in the proper mode.  */
4457169699Skan		    itype = fold_build2 (MINUS_EXPR, index_type,
4458169699Skan					 convert (index_type, size),
4459169699Skan					 convert (index_type,
4460169699Skan						  size_one_node));
446118334Speter
4462169699Skan		    /* If that overflowed, the array is too big.  ???
4463169699Skan		       While a size of INT_MAX+1 technically shouldn't
4464169699Skan		       cause an overflow (because we subtract 1), the
4465169699Skan		       overflow is recorded during the conversion to
4466169699Skan		       index_type, before the subtraction.  Handling
4467169699Skan		       this case seems like an unnecessary
4468169699Skan		       complication.  */
4469169699Skan		    if (TREE_CODE (itype) == INTEGER_CST
4470169699Skan			&& TREE_OVERFLOW (itype))
4471169699Skan		      {
4472169699Skan			error ("size of array %qs is too large", name);
4473169699Skan			type = error_mark_node;
4474169699Skan			continue;
4475169699Skan		      }
447650397Sobrien
4477169699Skan		    itype = build_index_type (itype);
4478169699Skan		  }
4479169699Skan	      }
4480169699Skan	    else if (decl_context == FIELD)
4481169699Skan	      {
4482169699Skan		if (pedantic && !flag_isoc99 && !in_system_header)
4483169699Skan		  pedwarn ("ISO C90 does not support flexible array members");
448490075Sobrien
4485169699Skan		/* ISO C99 Flexible array members are effectively
4486169699Skan		   identical to GCC's zero-length array extension.  */
4487169699Skan		itype = build_range_type (sizetype, size_zero_node, NULL_TREE);
4488169699Skan	      }
4489169699Skan	    else if (decl_context == PARM)
4490169699Skan	      {
4491169699Skan		if (array_parm_vla_unspec_p)
4492169699Skan		  {
4493169699Skan		    if (! orig_name)
4494169699Skan		      {
4495169699Skan			/* C99 6.7.5.2p4 */
4496169699Skan			error ("%<[*]%> not allowed in other than a declaration");
4497169699Skan		      }
449818334Speter
4499169699Skan		    itype = build_range_type (sizetype, size_zero_node, NULL_TREE);
4500169699Skan		    size_varies = 1;
4501169699Skan		  }
4502169699Skan	      }
4503169699Skan	    else if (decl_context == TYPENAME)
4504169699Skan	      {
4505169699Skan		if (array_parm_vla_unspec_p)
4506169699Skan		  {
4507169699Skan		    /* The error is printed elsewhere.  We use this to
4508169699Skan		       avoid messing up with incomplete array types of
4509169699Skan		       the same type, that would otherwise be modified
4510169699Skan		       below.  */
4511169699Skan		    itype = build_range_type (sizetype, size_zero_node,
4512169699Skan					      NULL_TREE);
4513169699Skan		  }
4514169699Skan	      }
451518334Speter
4516169699Skan	     /* Complain about arrays of incomplete types.  */
4517169699Skan	    if (!COMPLETE_TYPE_P (type))
4518169699Skan	      {
4519169699Skan		error ("array type has incomplete element type");
4520169699Skan		type = error_mark_node;
4521169699Skan	      }
4522169699Skan	    else
4523169699Skan	    /* When itype is NULL, a shared incomplete array type is
4524169699Skan	       returned for all array of a given type.  Elsewhere we
4525169699Skan	       make sure we don't complete that type before copying
4526169699Skan	       it, but here we want to make sure we don't ever
4527169699Skan	       modify the shared type, so we gcc_assert (itype)
4528169699Skan	       below.  */
4529169699Skan	      type = build_array_type (type, itype);
453090075Sobrien
4531169699Skan	    if (type != error_mark_node)
4532169699Skan	      {
4533169699Skan		if (size_varies)
4534169699Skan		  {
4535169699Skan		    /* It is ok to modify type here even if itype is
4536169699Skan		       NULL: if size_varies, we're in a
4537169699Skan		       multi-dimensional array and the inner type has
4538169699Skan		       variable size, so the enclosing shared array type
4539169699Skan		       must too.  */
4540169699Skan		    if (size && TREE_CODE (size) == INTEGER_CST)
4541169699Skan		      type
4542169699Skan			= build_distinct_type_copy (TYPE_MAIN_VARIANT (type));
4543169699Skan		    C_TYPE_VARIABLE_SIZE (type) = 1;
4544169699Skan		  }
454590075Sobrien
4546169699Skan		/* The GCC extension for zero-length arrays differs from
4547169699Skan		   ISO flexible array members in that sizeof yields
4548169699Skan		   zero.  */
4549169699Skan		if (size && integer_zerop (size))
4550169699Skan		  {
4551169699Skan		    gcc_assert (itype);
4552169699Skan		    TYPE_SIZE (type) = bitsize_zero_node;
4553169699Skan		    TYPE_SIZE_UNIT (type) = size_zero_node;
4554169699Skan		  }
4555169699Skan		if (array_parm_vla_unspec_p)
4556169699Skan		  {
4557169699Skan		    gcc_assert (itype);
4558169699Skan		    /* The type is complete.  C99 6.7.5.2p4  */
4559169699Skan		    TYPE_SIZE (type) = bitsize_zero_node;
4560169699Skan		    TYPE_SIZE_UNIT (type) = size_zero_node;
4561169699Skan		  }
4562169699Skan	      }
456318334Speter
4564169699Skan	    if (decl_context != PARM
4565169699Skan		&& (array_ptr_quals != TYPE_UNQUALIFIED
4566169699Skan		    || array_ptr_attrs != NULL_TREE
4567169699Skan		    || array_parm_static))
4568169699Skan	      {
4569169699Skan		error ("static or type qualifiers in non-parameter array declarator");
4570169699Skan		array_ptr_quals = TYPE_UNQUALIFIED;
4571169699Skan		array_ptr_attrs = NULL_TREE;
4572169699Skan		array_parm_static = 0;
4573169699Skan	      }
4574169699Skan	    break;
4575169699Skan	  }
4576169699Skan	case cdk_function:
4577169699Skan	  {
4578169699Skan	    /* Say it's a definition only for the declarator closest
4579169699Skan	       to the identifier, apart possibly from some
4580169699Skan	       attributes.  */
4581169699Skan	    bool really_funcdef = false;
4582169699Skan	    tree arg_types;
4583169699Skan	    if (funcdef_flag)
4584169699Skan	      {
4585169699Skan		const struct c_declarator *t = declarator->declarator;
4586169699Skan		while (t->kind == cdk_attrs)
4587169699Skan		  t = t->declarator;
4588169699Skan		really_funcdef = (t->kind == cdk_id);
4589169699Skan	      }
459018334Speter
4591169699Skan	    /* Declaring a function type.  Make sure we have a valid
4592169699Skan	       type for the function to return.  */
4593169699Skan	    if (type == error_mark_node)
4594169699Skan	      continue;
459590075Sobrien
4596169699Skan	    size_varies = 0;
459718334Speter
4598169699Skan	    /* Warn about some types functions can't return.  */
4599169699Skan	    if (TREE_CODE (type) == FUNCTION_TYPE)
4600169699Skan	      {
4601169699Skan		error ("%qs declared as function returning a function", name);
4602169699Skan		type = integer_type_node;
4603169699Skan	      }
4604169699Skan	    if (TREE_CODE (type) == ARRAY_TYPE)
4605169699Skan	      {
4606169699Skan		error ("%qs declared as function returning an array", name);
4607169699Skan		type = integer_type_node;
4608169699Skan	      }
460918334Speter
4610169699Skan	    /* Construct the function type and go to the next
4611169699Skan	       inner layer of declarator.  */
4612169699Skan	    arg_info = declarator->u.arg_info;
4613169699Skan	    arg_types = grokparms (arg_info, really_funcdef);
4614169699Skan	    if (really_funcdef)
4615169699Skan	      put_pending_sizes (arg_info->pending_sizes);
461618334Speter
4617169699Skan	    /* Type qualifiers before the return type of the function
4618169699Skan	       qualify the return type, not the function type.  */
4619169699Skan	    if (type_quals)
4620169699Skan	      {
4621169699Skan		/* Type qualifiers on a function return type are
4622169699Skan		   normally permitted by the standard but have no
4623169699Skan		   effect, so give a warning at -Wreturn-type.
4624169699Skan		   Qualifiers on a void return type are banned on
4625169699Skan		   function definitions in ISO C; GCC used to used
4626169699Skan		   them for noreturn functions.  */
4627169699Skan		if (VOID_TYPE_P (type) && really_funcdef)
4628169699Skan		  pedwarn ("function definition has qualified void return type");
4629169699Skan		else
4630169699Skan		  warning (OPT_Wreturn_type,
4631169699Skan			   "type qualifiers ignored on function return type");
463218334Speter
4633169699Skan		type = c_build_qualified_type (type, type_quals);
4634169699Skan	      }
4635169699Skan	    type_quals = TYPE_UNQUALIFIED;
463618334Speter
4637169699Skan	    type = build_function_type (type, arg_types);
4638169699Skan	    declarator = declarator->declarator;
463918334Speter
4640169699Skan	    /* Set the TYPE_CONTEXTs for each tagged type which is local to
4641169699Skan	       the formal parameter list of this FUNCTION_TYPE to point to
4642169699Skan	       the FUNCTION_TYPE node itself.  */
464390075Sobrien	    {
4644169699Skan	      tree link;
464590075Sobrien
4646169699Skan	      for (link = arg_info->tags;
4647169699Skan		   link;
4648169699Skan		   link = TREE_CHAIN (link))
4649169699Skan		TYPE_CONTEXT (TREE_VALUE (link)) = type;
465090075Sobrien	    }
4651169699Skan	    break;
4652169699Skan	  }
4653169699Skan	case cdk_pointer:
465418334Speter	  {
4655169699Skan	    /* Merge any constancy or volatility into the target type
4656169699Skan	       for the pointer.  */
465718334Speter
4658169699Skan	    if (pedantic && TREE_CODE (type) == FUNCTION_TYPE
4659169699Skan		&& type_quals)
4660169699Skan	      pedwarn ("ISO C forbids qualified function types");
4661169699Skan	    if (type_quals)
4662169699Skan	      type = c_build_qualified_type (type, type_quals);
4663169699Skan	    size_varies = 0;
466418334Speter
4665169699Skan	    /* When the pointed-to type involves components of variable size,
4666169699Skan	       care must be taken to ensure that the size evaluation code is
4667169699Skan	       emitted early enough to dominate all the possible later uses
4668169699Skan	       and late enough for the variables on which it depends to have
4669169699Skan	       been assigned.
467018334Speter
4671169699Skan	       This is expected to happen automatically when the pointed-to
4672169699Skan	       type has a name/declaration of it's own, but special attention
4673169699Skan	       is required if the type is anonymous.
467418334Speter
4675169699Skan	       We handle the NORMAL and FIELD contexts here by attaching an
4676169699Skan	       artificial TYPE_DECL to such pointed-to type.  This forces the
4677169699Skan	       sizes evaluation at a safe point and ensures it is not deferred
4678169699Skan	       until e.g. within a deeper conditional context.
467918334Speter
4680169699Skan	       We expect nothing to be needed here for PARM or TYPENAME.
4681169699Skan	       Pushing a TYPE_DECL at this point for TYPENAME would actually
4682169699Skan	       be incorrect, as we might be in the middle of an expression
4683169699Skan	       with side effects on the pointed-to type size "arguments" prior
4684169699Skan	       to the pointer declaration point and the fake TYPE_DECL in the
4685169699Skan	       enclosing context would force the size evaluation prior to the
4686169699Skan	       side effects.  */
468752284Sobrien
4688169699Skan	    if (!TYPE_NAME (type)
4689169699Skan		&& (decl_context == NORMAL || decl_context == FIELD)
4690169699Skan		&& variably_modified_type_p (type, NULL_TREE))
4691169699Skan	      {
4692169699Skan		tree decl = build_decl (TYPE_DECL, NULL_TREE, type);
4693169699Skan		DECL_ARTIFICIAL (decl) = 1;
4694169699Skan		pushdecl (decl);
4695169699Skan		finish_decl (decl, NULL_TREE, NULL_TREE);
4696169699Skan		TYPE_NAME (type) = decl;
4697169699Skan	      }
469852284Sobrien
4699169699Skan	    type = build_pointer_type (type);
470090075Sobrien
4701169699Skan	    /* Process type qualifiers (such as const or volatile)
4702169699Skan	       that were given inside the `*'.  */
4703169699Skan	    type_quals = declarator->u.pointer_quals;
470452284Sobrien
4705169699Skan	    declarator = declarator->declarator;
4706169699Skan	    break;
4707169699Skan	  }
4708169699Skan	default:
4709169699Skan	  gcc_unreachable ();
471018334Speter	}
471118334Speter    }
471218334Speter
4713169699Skan  /* Now TYPE has the actual type, apart from any qualifiers in
4714169699Skan     TYPE_QUALS.  */
471518334Speter
4716146906Skan  /* Check the type and width of a bit-field.  */
4717146906Skan  if (bitfield)
4718146906Skan    check_bitfield_type_and_width (&type, width, orig_name);
4719146906Skan
472050397Sobrien  /* Did array size calculations overflow?  */
472150397Sobrien
472250397Sobrien  if (TREE_CODE (type) == ARRAY_TYPE
472390075Sobrien      && COMPLETE_TYPE_P (type)
4724169699Skan      && TREE_CODE (TYPE_SIZE_UNIT (type)) == INTEGER_CST
4725169699Skan      && TREE_OVERFLOW (TYPE_SIZE_UNIT (type)))
472690075Sobrien    {
4727169699Skan      error ("size of array %qs is too large", name);
472890075Sobrien      /* If we proceed with the array type as it is, we'll eventually
472990075Sobrien	 crash in tree_low_cst().  */
473090075Sobrien      type = error_mark_node;
473190075Sobrien    }
473250397Sobrien
473318334Speter  /* If this is declaring a typedef name, return a TYPE_DECL.  */
473418334Speter
4735169699Skan  if (storage_class == csc_typedef)
473618334Speter    {
473718334Speter      tree decl;
473818334Speter      if (pedantic && TREE_CODE (type) == FUNCTION_TYPE
473952284Sobrien	  && type_quals)
474090075Sobrien	pedwarn ("ISO C forbids qualified function types");
474152284Sobrien      if (type_quals)
474252284Sobrien	type = c_build_qualified_type (type, type_quals);
4743169699Skan      decl = build_decl (TYPE_DECL, declarator->u.id, type);
4744169699Skan      if (declspecs->explicit_signed_p)
474518334Speter	C_TYPEDEF_EXPLICITLY_SIGNED (decl) = 1;
474690075Sobrien      decl_attributes (&decl, returned_attrs, 0);
4747169699Skan      if (declspecs->inline_p)
4748169699Skan	pedwarn ("typedef %q+D declared %<inline%>", decl);
474918334Speter      return decl;
475018334Speter    }
475118334Speter
475218334Speter  /* If this is a type name (such as, in a cast or sizeof),
475318334Speter     compute the type and return it now.  */
475418334Speter
475518334Speter  if (decl_context == TYPENAME)
475618334Speter    {
4757169699Skan      /* Note that the grammar rejects storage classes in typenames
4758169699Skan	 and fields.  */
4759169699Skan      gcc_assert (storage_class == csc_none && !threadp
4760169699Skan		  && !declspecs->inline_p);
476118334Speter      if (pedantic && TREE_CODE (type) == FUNCTION_TYPE
476252284Sobrien	  && type_quals)
476390075Sobrien	pedwarn ("ISO C forbids const or volatile function types");
476452284Sobrien      if (type_quals)
476552284Sobrien	type = c_build_qualified_type (type, type_quals);
476690075Sobrien      decl_attributes (&type, returned_attrs, 0);
476718334Speter      return type;
476818334Speter    }
476918334Speter
4770169699Skan  if (pedantic && decl_context == FIELD
4771169699Skan      && variably_modified_type_p (type, NULL_TREE))
4772169699Skan    {
4773169699Skan      /* C99 6.7.2.1p8 */
4774169699Skan      pedwarn ("a member of a structure or union cannot have a variably modified type");
4775169699Skan    }
4776169699Skan
477718334Speter  /* Aside from typedefs and type names (handle above),
477818334Speter     `void' at top level (not within pointer)
477918334Speter     is allowed only in public variables.
478018334Speter     We don't complain about parms either, but that is because
478118334Speter     a better error message can be made later.  */
478218334Speter
478390075Sobrien  if (VOID_TYPE_P (type) && decl_context != PARM
4784169699Skan      && !((decl_context != FIELD && TREE_CODE (type) != FUNCTION_TYPE)
4785169699Skan	    && (storage_class == csc_extern
4786169699Skan		|| (current_scope == file_scope
4787169699Skan		    && !(storage_class == csc_static
4788169699Skan			 || storage_class == csc_register)))))
478918334Speter    {
4790169699Skan      error ("variable or field %qs declared void", name);
479118334Speter      type = integer_type_node;
479218334Speter    }
479318334Speter
479418334Speter  /* Now create the decl, which may be a VAR_DECL, a PARM_DECL
479518334Speter     or a FUNCTION_DECL, depending on DECL_CONTEXT and TYPE.  */
479618334Speter
479718334Speter  {
479890075Sobrien    tree decl;
479918334Speter
480018334Speter    if (decl_context == PARM)
480118334Speter      {
480290075Sobrien	tree type_as_written;
480390075Sobrien	tree promoted_type;
480418334Speter
480518334Speter	/* A parameter declared as an array of T is really a pointer to T.
480618334Speter	   One declared as a function is really a pointer to a function.  */
480718334Speter
480818334Speter	if (TREE_CODE (type) == ARRAY_TYPE)
480918334Speter	  {
481018334Speter	    /* Transfer const-ness of array into that of type pointed to.  */
481118334Speter	    type = TREE_TYPE (type);
481252284Sobrien	    if (type_quals)
481352284Sobrien	      type = c_build_qualified_type (type, type_quals);
481418334Speter	    type = build_pointer_type (type);
4815169699Skan	    type_quals = array_ptr_quals;
481690075Sobrien
4817169699Skan	    /* We don't yet implement attributes in this context.  */
4818169699Skan	    if (array_ptr_attrs != NULL_TREE)
4819169699Skan	      warning (OPT_Wattributes,
4820169699Skan		       "attributes in parameter array declarator ignored");
482190075Sobrien
482218334Speter	    size_varies = 0;
482318334Speter	  }
482418334Speter	else if (TREE_CODE (type) == FUNCTION_TYPE)
482518334Speter	  {
482652284Sobrien	    if (pedantic && type_quals)
482790075Sobrien	      pedwarn ("ISO C forbids qualified function types");
482852284Sobrien	    if (type_quals)
482952284Sobrien	      type = c_build_qualified_type (type, type_quals);
483018334Speter	    type = build_pointer_type (type);
483152284Sobrien	    type_quals = TYPE_UNQUALIFIED;
483218334Speter	  }
483390075Sobrien	else if (type_quals)
483490075Sobrien	  type = c_build_qualified_type (type, type_quals);
4835132730Skan
483690075Sobrien	type_as_written = type;
483718334Speter
4838169699Skan	decl = build_decl (PARM_DECL, declarator->u.id, type);
483918334Speter	if (size_varies)
484018334Speter	  C_DECL_VARIABLE_SIZE (decl) = 1;
484118334Speter
484218334Speter	/* Compute the type actually passed in the parmlist,
484318334Speter	   for the case where there is no prototype.
484418334Speter	   (For example, shorts and chars are passed as ints.)
484518334Speter	   When there is a prototype, this is overridden later.  */
484618334Speter
484790075Sobrien	if (type == error_mark_node)
484890075Sobrien	  promoted_type = type;
484990075Sobrien	else
4850117421Skan	  promoted_type = c_type_promotes_to (type);
485118334Speter
485290075Sobrien	DECL_ARG_TYPE (decl) = promoted_type;
4853169699Skan	if (declspecs->inline_p)
4854169699Skan	  pedwarn ("parameter %q+D declared %<inline%>", decl);
485518334Speter      }
485618334Speter    else if (decl_context == FIELD)
485718334Speter      {
4858169699Skan	/* Note that the grammar rejects storage classes in typenames
4859169699Skan	   and fields.  */
4860169699Skan	gcc_assert (storage_class == csc_none && !threadp
4861169699Skan		    && !declspecs->inline_p);
4862169699Skan
486318334Speter	/* Structure field.  It may not be a function.  */
486496263Sobrien
486518334Speter	if (TREE_CODE (type) == FUNCTION_TYPE)
486618334Speter	  {
4867169699Skan	    error ("field %qs declared as a function", name);
486818334Speter	    type = build_pointer_type (type);
486918334Speter	  }
487090075Sobrien	else if (TREE_CODE (type) != ERROR_MARK
4871169699Skan		 && !COMPLETE_OR_UNBOUND_ARRAY_TYPE_P (type))
487218334Speter	  {
4873169699Skan	    error ("field %qs has incomplete type", name);
487418334Speter	    type = error_mark_node;
487518334Speter	  }
4876169699Skan	type = c_build_qualified_type (type, type_quals);
4877169699Skan	decl = build_decl (FIELD_DECL, declarator->u.id, type);
487890075Sobrien	DECL_NONADDRESSABLE_P (decl) = bitfield;
487990075Sobrien
488018334Speter	if (size_varies)
488118334Speter	  C_DECL_VARIABLE_SIZE (decl) = 1;
488218334Speter      }
488318334Speter    else if (TREE_CODE (type) == FUNCTION_TYPE)
488418334Speter      {
4885169699Skan	if (storage_class == csc_register || threadp)
4886169699Skan	  {
4887169699Skan	    error ("invalid storage class for function %qs", name);
4888169699Skan	   }
4889169699Skan	else if (current_scope != file_scope)
4890169699Skan	  {
4891169699Skan	    /* Function declaration not at file scope.  Storage
4892169699Skan	       classes other than `extern' are not allowed, C99
4893169699Skan	       6.7.1p5, and `extern' makes no difference.  However,
4894169699Skan	       GCC allows 'auto', perhaps with 'inline', to support
4895169699Skan	       nested functions.  */
4896169699Skan	    if (storage_class == csc_auto)
4897169699Skan	      {
4898169699Skan		if (pedantic)
4899169699Skan		  pedwarn ("invalid storage class for function %qs", name);
4900169699Skan	      }
4901169699Skan	    else if (storage_class == csc_static)
4902169699Skan	      {
4903169699Skan		error ("invalid storage class for function %qs", name);
4904169699Skan		if (funcdef_flag)
4905169699Skan		  storage_class = declspecs->storage_class = csc_none;
4906169699Skan		else
4907169699Skan		  return 0;
4908169699Skan	      }
4909169699Skan	  }
491018334Speter
4911169699Skan	decl = build_decl (FUNCTION_DECL, declarator->u.id, type);
491290075Sobrien	decl = build_decl_attribute_variant (decl, decl_attr);
491318334Speter
4914169699Skan	DECL_LANG_SPECIFIC (decl) = GGC_CNEW (struct lang_decl);
491590075Sobrien
4916169699Skan	if (pedantic && type_quals && !DECL_IN_SYSTEM_HEADER (decl))
491790075Sobrien	  pedwarn ("ISO C forbids qualified function types");
491818334Speter
4919169699Skan	/* GNU C interprets a volatile-qualified function type to indicate
492052284Sobrien	   that the function does not return.  */
492152284Sobrien	if ((type_quals & TYPE_QUAL_VOLATILE)
492290075Sobrien	    && !VOID_TYPE_P (TREE_TYPE (TREE_TYPE (decl))))
4923169699Skan	  warning (0, "%<noreturn%> function returns non-void value");
492418334Speter
4925169699Skan	/* Every function declaration is an external reference
4926169699Skan	   (DECL_EXTERNAL) except for those which are not at file
4927169699Skan	   scope and are explicitly declared "auto".  This is
4928169699Skan	   forbidden by standard C (C99 6.7.1p5) and is interpreted by
4929169699Skan	   GCC to signify a forward declaration of a nested function.  */
4930169699Skan	if (storage_class == csc_auto && current_scope != file_scope)
4931169699Skan	  DECL_EXTERNAL (decl) = 0;
4932189824Sdas	/* In C99, a function which is declared 'inline' with 'extern'
4933189824Sdas	   is not an external reference (which is confusing).  It
4934189824Sdas	   means that the later definition of the function must be output
4935189824Sdas	   in this file, C99 6.7.4p6.  In GNU C89, a function declared
4936189824Sdas	   'extern inline' is an external reference.  */
4937189824Sdas	else if (declspecs->inline_p && storage_class != csc_static)
4938189824Sdas	  DECL_EXTERNAL (decl) = ((storage_class == csc_extern)
4939189824Sdas				  == flag_gnu89_inline);
4940169699Skan	else
4941189824Sdas	  DECL_EXTERNAL (decl) = !initialized;
4942169699Skan
494318334Speter	/* Record absence of global scope for `static' or `auto'.  */
494418334Speter	TREE_PUBLIC (decl)
4945169699Skan	  = !(storage_class == csc_static || storage_class == csc_auto);
494618334Speter
4947169699Skan	/* For a function definition, record the argument information
4948169699Skan	   block where store_parm_decls will look for it.  */
4949169699Skan	if (funcdef_flag)
4950169699Skan	  current_function_arg_info = arg_info;
4951169699Skan
4952169699Skan	if (declspecs->default_int_p)
495396263Sobrien	  C_FUNCTION_IMPLICIT_INT (decl) = 1;
495496263Sobrien
495518334Speter	/* Record presence of `inline', if it is reasonable.  */
4956169699Skan	if (flag_hosted && MAIN_NAME_P (declarator->u.id))
495718334Speter	  {
4958169699Skan	    if (declspecs->inline_p)
4959169699Skan	      pedwarn ("cannot inline function %<main%>");
496090075Sobrien	  }
4961169699Skan	else if (declspecs->inline_p)
496290075Sobrien	  {
4963132730Skan	    /* Record that the function is declared `inline'.  */
496490075Sobrien	    DECL_DECLARED_INLINE_P (decl) = 1;
496518334Speter
496690075Sobrien	    /* Do not mark bare declarations as DECL_INLINE.  Doing so
496790075Sobrien	       in the presence of multiple declarations can result in
496890075Sobrien	       the abstract origin pointing between the declarations,
496990075Sobrien	       which will confuse dwarf2out.  */
497090075Sobrien	    if (initialized)
4971189824Sdas	      DECL_INLINE (decl) = 1;
497218334Speter	  }
497390075Sobrien	/* If -finline-functions, assume it can be inlined.  This does
497490075Sobrien	   two things: let the function be deferred until it is actually
497590075Sobrien	   needed, and let dwarf2 know that the function is inlinable.  */
497690075Sobrien	else if (flag_inline_trees == 2 && initialized)
4977132730Skan	  DECL_INLINE (decl) = 1;
497818334Speter      }
497918334Speter    else
498018334Speter      {
498118334Speter	/* It's a variable.  */
498218334Speter	/* An uninitialized decl with `extern' is a reference.  */
4983169699Skan	int extern_ref = !initialized && storage_class == csc_extern;
498418334Speter
4985169699Skan	type = c_build_qualified_type (type, type_quals);
4986132730Skan
4987169699Skan	/* C99 6.2.2p7: It is invalid (compile-time undefined
4988169699Skan	   behavior) to create an 'extern' declaration for a
4989132730Skan	   variable if there is a global declaration that is
4990169699Skan	   'static' and the global declaration is not visible.
4991169699Skan	   (If the static declaration _is_ currently visible,
4992169699Skan	   the 'extern' declaration is taken to refer to that decl.) */
4993169699Skan	if (extern_ref && current_scope != file_scope)
4994132730Skan	  {
4995169699Skan	    tree global_decl  = identifier_global_value (declarator->u.id);
4996169699Skan	    tree visible_decl = lookup_name (declarator->u.id);
4997132730Skan
4998132730Skan	    if (global_decl
4999169699Skan		&& global_decl != visible_decl
5000132730Skan		&& TREE_CODE (global_decl) == VAR_DECL
5001132730Skan		&& !TREE_PUBLIC (global_decl))
5002169699Skan	      error ("variable previously declared %<static%> redeclared "
5003169699Skan		     "%<extern%>");
5004132730Skan	  }
5005132730Skan
5006169699Skan	decl = build_decl (VAR_DECL, declarator->u.id, type);
5007169699Skan	DECL_SOURCE_LOCATION (decl) = declarator->id_loc;
500818334Speter	if (size_varies)
500918334Speter	  C_DECL_VARIABLE_SIZE (decl) = 1;
501018334Speter
5011169699Skan	if (declspecs->inline_p)
5012169699Skan	  pedwarn ("variable %q+D declared %<inline%>", decl);
501318334Speter
5014169699Skan	/* At file scope, an initialized extern declaration may follow
5015169699Skan	   a static declaration.  In that case, DECL_EXTERNAL will be
5016169699Skan	   reset later in start_decl.  */
5017169699Skan	DECL_EXTERNAL (decl) = (storage_class == csc_extern);
5018117421Skan
5019132730Skan	/* At file scope, the presence of a `static' or `register' storage
502018334Speter	   class specifier, or the absence of all storage class specifiers
502118334Speter	   makes this declaration a definition (perhaps tentative).  Also,
5022169699Skan	   the absence of `static' makes it public.  */
5023169699Skan	if (current_scope == file_scope)
502418334Speter	  {
5025169699Skan	    TREE_PUBLIC (decl) = storage_class != csc_static;
5026117421Skan	    TREE_STATIC (decl) = !extern_ref;
502718334Speter	  }
5028132730Skan	/* Not at file scope, only `static' makes a static definition.  */
502918334Speter	else
503018334Speter	  {
5031169699Skan	    TREE_STATIC (decl) = (storage_class == csc_static);
5032117421Skan	    TREE_PUBLIC (decl) = extern_ref;
503318334Speter	  }
5034117421Skan
5035169699Skan	if (threadp)
5036117421Skan	  {
5037117421Skan	    if (targetm.have_tls)
5038169699Skan	      DECL_TLS_MODEL (decl) = decl_default_tls_model (decl);
5039117421Skan	    else
5040117421Skan	      /* A mere warning is sure to result in improper semantics
5041117421Skan		 at runtime.  Don't bother to allow this to compile.  */
5042117421Skan	      error ("thread-local storage not supported for this target");
5043117421Skan	  }
504418334Speter      }
504518334Speter
5046169699Skan    if (storage_class == csc_extern
5047169699Skan	&& variably_modified_type_p (type, NULL_TREE))
5048169699Skan      {
5049169699Skan	/* C99 6.7.5.2p2 */
5050169699Skan	error ("object with variably modified type must have no linkage");
5051169699Skan      }
5052169699Skan
505318334Speter    /* Record `register' declaration for warnings on &
505418334Speter       and in case doing stupid register allocation.  */
505518334Speter
5056169699Skan    if (storage_class == csc_register)
5057169699Skan      {
5058169699Skan	C_DECL_REGISTER (decl) = 1;
5059169699Skan	DECL_REGISTER (decl) = 1;
5060169699Skan      }
506118334Speter
506218334Speter    /* Record constancy and volatility.  */
506352284Sobrien    c_apply_type_quals_to_decl (type_quals, decl);
506418334Speter
506518334Speter    /* If a type has volatile components, it should be stored in memory.
506618334Speter       Otherwise, the fact that those components are volatile
5067169699Skan       will be ignored, and would even crash the compiler.
5068169699Skan       Of course, this only makes sense on  VAR,PARM, and RESULT decl's.   */
5069169699Skan    if (C_TYPE_FIELDS_VOLATILE (TREE_TYPE (decl))
5070169699Skan	&& (TREE_CODE (decl) == VAR_DECL ||  TREE_CODE (decl) == PARM_DECL
5071169699Skan	  || TREE_CODE (decl) == RESULT_DECL))
5072169699Skan      {
5073169699Skan	/* It is not an error for a structure with volatile fields to
5074169699Skan	   be declared register, but reset DECL_REGISTER since it
5075169699Skan	   cannot actually go in a register.  */
5076169699Skan	int was_reg = C_DECL_REGISTER (decl);
5077169699Skan	C_DECL_REGISTER (decl) = 0;
5078169699Skan	DECL_REGISTER (decl) = 0;
5079169699Skan	c_mark_addressable (decl);
5080169699Skan	C_DECL_REGISTER (decl) = was_reg;
5081169699Skan      }
508218334Speter
5083132730Skan  /* This is the earliest point at which we might know the assembler
5084132730Skan     name of a variable.  Thus, if it's known before this, die horribly.  */
5085169699Skan    gcc_assert (!DECL_ASSEMBLER_NAME_SET_P (decl));
5086132730Skan
508790075Sobrien    decl_attributes (&decl, returned_attrs, 0);
508818334Speter
508918334Speter    return decl;
509018334Speter  }
509118334Speter}
509218334Speter
509318334Speter/* Decode the parameter-list info for a function type or function definition.
5094169699Skan   The argument is the value returned by `get_parm_info' (or made in c-parse.c
509518334Speter   if there is an identifier list instead of a parameter decl list).
509618334Speter   These two functions are separate because when a function returns
509718334Speter   or receives functions then each is called multiple times but the order
509818334Speter   of calls is different.  The last call to `grokparms' is always the one
509918334Speter   that contains the formal parameter names of a function definition.
510018334Speter
510118334Speter   Return a list of arg types to use in the FUNCTION_TYPE for this function.
510218334Speter
5103169699Skan   FUNCDEF_FLAG is true for a function definition, false for
510418334Speter   a mere declaration.  A nonempty identifier-list gets an error message
5105169699Skan   when FUNCDEF_FLAG is false.  */
510618334Speter
510718334Speterstatic tree
5108169699Skangrokparms (struct c_arg_info *arg_info, bool funcdef_flag)
510918334Speter{
5110169699Skan  tree arg_types = arg_info->types;
511118334Speter
5112169699Skan  if (funcdef_flag && arg_info->had_vla_unspec)
5113169699Skan    {
5114169699Skan      /* A function definition isn't function prototype scope C99 6.2.1p4.  */
5115169699Skan      /* C99 6.7.5.2p4 */
5116169699Skan      error ("%<[*]%> not allowed in other than function prototype scope");
5117169699Skan    }
511818334Speter
5119169699Skan  if (arg_types == 0 && !funcdef_flag && !in_system_header)
5120169699Skan    warning (OPT_Wstrict_prototypes,
5121169699Skan	     "function declaration isn%'t a prototype");
512218334Speter
5123169699Skan  if (arg_types == error_mark_node)
5124169699Skan    return 0;  /* don't set TYPE_ARG_TYPES in this case */
5125169699Skan
5126169699Skan  else if (arg_types && TREE_CODE (TREE_VALUE (arg_types)) == IDENTIFIER_NODE)
512718334Speter    {
5128169699Skan      if (!funcdef_flag)
512918334Speter	pedwarn ("parameter names (without types) in function declaration");
513018334Speter
5131169699Skan      arg_info->parms = arg_info->types;
5132169699Skan      arg_info->types = 0;
513318334Speter      return 0;
513418334Speter    }
513518334Speter  else
513618334Speter    {
5137169699Skan      tree parm, type, typelt;
5138169699Skan      unsigned int parmno;
513918334Speter
5140169699Skan      /* If there is a parameter of incomplete type in a definition,
5141169699Skan	 this is an error.  In a declaration this is valid, and a
5142169699Skan	 struct or union type may be completed later, before any calls
5143169699Skan	 or definition of the function.  In the case where the tag was
5144169699Skan	 first declared within the parameter list, a warning has
5145169699Skan	 already been given.  If a parameter has void type, then
5146169699Skan	 however the function cannot be defined or called, so
5147169699Skan	 warn.  */
5148169699Skan
5149169699Skan      for (parm = arg_info->parms, typelt = arg_types, parmno = 1;
5150132730Skan	   parm;
5151169699Skan	   parm = TREE_CHAIN (parm), typelt = TREE_CHAIN (typelt), parmno++)
5152169699Skan	{
5153169699Skan	  type = TREE_VALUE (typelt);
5154169699Skan	  if (type == error_mark_node)
5155169699Skan	    continue;
5156132730Skan
5157169699Skan	  if (!COMPLETE_TYPE_P (type))
5158169699Skan	    {
5159169699Skan	      if (funcdef_flag)
5160169699Skan		{
5161169699Skan		  if (DECL_NAME (parm))
5162169699Skan		    error ("parameter %u (%q+D) has incomplete type",
5163169699Skan			   parmno, parm);
5164169699Skan		  else
5165169699Skan		    error ("%Jparameter %u has incomplete type",
5166169699Skan			   parm, parmno);
5167169699Skan
5168169699Skan		  TREE_VALUE (typelt) = error_mark_node;
5169169699Skan		  TREE_TYPE (parm) = error_mark_node;
5170169699Skan		}
5171169699Skan	      else if (VOID_TYPE_P (type))
5172169699Skan		{
5173169699Skan		  if (DECL_NAME (parm))
5174169699Skan		    warning (0, "parameter %u (%q+D) has void type",
5175169699Skan			     parmno, parm);
5176169699Skan		  else
5177169699Skan		    warning (0, "%Jparameter %u has void type",
5178169699Skan			     parm, parmno);
5179169699Skan		}
5180169699Skan	    }
5181169699Skan
5182169699Skan	  if (DECL_NAME (parm) && TREE_USED (parm))
5183169699Skan	    warn_if_shadowing (parm);
5184169699Skan	}
5185169699Skan      return arg_types;
518618334Speter    }
518718334Speter}
518818334Speter
5189169699Skan/* Take apart the current scope and return a c_arg_info structure with
5190169699Skan   info on a parameter list just parsed.
519118334Speter
5192169699Skan   This structure is later fed to 'grokparms' and 'store_parm_decls'.
519318334Speter
5194169699Skan   ELLIPSIS being true means the argument list ended in '...' so don't
5195169699Skan   append a sentinel (void_list_node) to the end of the type-list.  */
5196169699Skan
5197169699Skanstruct c_arg_info *
5198169699Skanget_parm_info (bool ellipsis)
519918334Speter{
5200169699Skan  struct c_binding *b = current_scope->bindings;
5201169699Skan  struct c_arg_info *arg_info = XOBNEW (&parser_obstack,
5202169699Skan					struct c_arg_info);
5203169699Skan  tree parms    = 0;
5204169699Skan  tree tags     = 0;
5205169699Skan  tree types    = 0;
5206169699Skan  tree others   = 0;
5207169699Skan
5208132730Skan  static bool explained_incomplete_types = false;
5209132730Skan  bool gave_void_only_once_err = false;
521018334Speter
5211169699Skan  arg_info->parms = 0;
5212169699Skan  arg_info->tags = 0;
5213169699Skan  arg_info->types = 0;
5214169699Skan  arg_info->others = 0;
5215169699Skan  arg_info->pending_sizes = 0;
5216169699Skan  arg_info->had_vla_unspec = current_scope->had_vla_unspec;
5217132730Skan
5218169699Skan  /* The bindings in this scope must not get put into a block.
5219169699Skan     We will take care of deleting the binding nodes.  */
5220169699Skan  current_scope->bindings = 0;
522118334Speter
5222169699Skan  /* This function is only called if there was *something* on the
5223169699Skan     parameter list.  */
5224169699Skan  gcc_assert (b);
5225169699Skan
5226169699Skan  /* A parameter list consisting solely of 'void' indicates that the
5227169699Skan     function takes no arguments.  But if the 'void' is qualified
5228169699Skan     (by 'const' or 'volatile'), or has a storage class specifier
5229169699Skan     ('register'), then the behavior is undefined; issue an error.
5230169699Skan     Typedefs for 'void' are OK (see DR#157).  */
5231169699Skan  if (b->prev == 0			    /* one binding */
5232169699Skan      && TREE_CODE (b->decl) == PARM_DECL   /* which is a parameter */
5233169699Skan      && !DECL_NAME (b->decl)               /* anonymous */
5234169699Skan      && VOID_TYPE_P (TREE_TYPE (b->decl))) /* of void type */
523518334Speter    {
5236169699Skan      if (TREE_THIS_VOLATILE (b->decl)
5237169699Skan	  || TREE_READONLY (b->decl)
5238169699Skan	  || C_DECL_REGISTER (b->decl))
5239169699Skan	error ("%<void%> as only parameter may not be qualified");
524018334Speter
5241169699Skan      /* There cannot be an ellipsis.  */
5242169699Skan      if (ellipsis)
5243169699Skan	error ("%<void%> must be the only parameter");
5244132730Skan
5245169699Skan      arg_info->types = void_list_node;
5246169699Skan      return arg_info;
524718334Speter    }
524818334Speter
5249169699Skan  if (!ellipsis)
5250169699Skan    types = void_list_node;
525118334Speter
5252169699Skan  /* Break up the bindings list into parms, tags, types, and others;
5253169699Skan     apply sanity checks; purge the name-to-decl bindings.  */
5254169699Skan  while (b)
525518334Speter    {
5256169699Skan      tree decl = b->decl;
5257169699Skan      tree type = TREE_TYPE (decl);
5258132730Skan      const char *keyword;
5259132730Skan
5260169699Skan      switch (TREE_CODE (decl))
526190075Sobrien	{
5262169699Skan	case PARM_DECL:
5263169699Skan	  if (b->id)
5264169699Skan	    {
5265169699Skan	      gcc_assert (I_SYMBOL_BINDING (b->id) == b);
5266169699Skan	      I_SYMBOL_BINDING (b->id) = b->shadowed;
5267169699Skan	    }
5268132730Skan
5269169699Skan	  /* Check for forward decls that never got their actual decl.  */
5270169699Skan	  if (TREE_ASM_WRITTEN (decl))
5271169699Skan	    error ("parameter %q+D has just a forward declaration", decl);
5272169699Skan	  /* Check for (..., void, ...) and issue an error.  */
5273169699Skan	  else if (VOID_TYPE_P (type) && !DECL_NAME (decl))
5274169699Skan	    {
5275169699Skan	      if (!gave_void_only_once_err)
5276169699Skan		{
5277169699Skan		  error ("%<void%> must be the only parameter");
5278169699Skan		  gave_void_only_once_err = true;
5279169699Skan		}
5280169699Skan	    }
5281169699Skan	  else
5282169699Skan	    {
5283169699Skan	      /* Valid parameter, add it to the list.  */
5284169699Skan	      TREE_CHAIN (decl) = parms;
5285169699Skan	      parms = decl;
5286132730Skan
5287169699Skan	      /* Since there is a prototype, args are passed in their
5288169699Skan		 declared types.  The back end may override this later.  */
5289169699Skan	      DECL_ARG_TYPE (decl) = type;
5290169699Skan	      types = tree_cons (0, type, types);
5291169699Skan	    }
5292169699Skan	  break;
5293169699Skan
5294169699Skan	case ENUMERAL_TYPE: keyword = "enum"; goto tag;
5295169699Skan	case UNION_TYPE:    keyword = "union"; goto tag;
5296169699Skan	case RECORD_TYPE:   keyword = "struct"; goto tag;
5297169699Skan	tag:
5298169699Skan	  /* Types may not have tag-names, in which case the type
5299169699Skan	     appears in the bindings list with b->id NULL.  */
5300169699Skan	  if (b->id)
5301169699Skan	    {
5302169699Skan	      gcc_assert (I_TAG_BINDING (b->id) == b);
5303169699Skan	      I_TAG_BINDING (b->id) = b->shadowed;
5304169699Skan	    }
5305169699Skan
5306169699Skan	  /* Warn about any struct, union or enum tags defined in a
5307169699Skan	     parameter list.  The scope of such types is limited to
5308169699Skan	     the parameter list, which is rarely if ever desirable
5309169699Skan	     (it's impossible to call such a function with type-
5310169699Skan	     correct arguments).  An anonymous union parm type is
5311169699Skan	     meaningful as a GNU extension, so don't warn for that.  */
5312169699Skan	  if (TREE_CODE (decl) != UNION_TYPE || b->id != 0)
5313169699Skan	    {
5314169699Skan	      if (b->id)
5315169699Skan		/* The %s will be one of 'struct', 'union', or 'enum'.  */
5316169699Skan		warning (0, "%<%s %E%> declared inside parameter list",
5317169699Skan			 keyword, b->id);
5318169699Skan	      else
5319169699Skan		/* The %s will be one of 'struct', 'union', or 'enum'.  */
5320169699Skan		warning (0, "anonymous %s declared inside parameter list",
5321169699Skan			 keyword);
5322169699Skan
5323169699Skan	      if (!explained_incomplete_types)
5324169699Skan		{
5325169699Skan		  warning (0, "its scope is only this definition or declaration,"
5326169699Skan			   " which is probably not what you want");
5327169699Skan		  explained_incomplete_types = true;
5328169699Skan		}
5329169699Skan	    }
5330169699Skan
5331169699Skan	  tags = tree_cons (b->id, decl, tags);
5332169699Skan	  break;
5333169699Skan
5334169699Skan	case CONST_DECL:
5335169699Skan	case TYPE_DECL:
5336169699Skan	case FUNCTION_DECL:
5337169699Skan	  /* CONST_DECLs appear here when we have an embedded enum,
5338169699Skan	     and TYPE_DECLs appear here when we have an embedded struct
5339169699Skan	     or union.  No warnings for this - we already warned about the
5340169699Skan	     type itself.  FUNCTION_DECLs appear when there is an implicit
5341169699Skan	     function declaration in the parameter list.  */
5342169699Skan
5343169699Skan	  TREE_CHAIN (decl) = others;
5344169699Skan	  others = decl;
5345169699Skan	  /* fall through */
5346169699Skan
5347169699Skan	case ERROR_MARK:
5348169699Skan	  /* error_mark_node appears here when we have an undeclared
5349169699Skan	     variable.  Just throw it away.  */
5350169699Skan	  if (b->id)
5351169699Skan	    {
5352169699Skan	      gcc_assert (I_SYMBOL_BINDING (b->id) == b);
5353169699Skan	      I_SYMBOL_BINDING (b->id) = b->shadowed;
5354169699Skan	    }
5355169699Skan	  break;
5356169699Skan
5357169699Skan	  /* Other things that might be encountered.  */
5358169699Skan	case LABEL_DECL:
5359169699Skan	case VAR_DECL:
5360169699Skan	default:
5361169699Skan	  gcc_unreachable ();
536218334Speter	}
5363132730Skan
5364169699Skan      b = free_binding_and_advance (b);
5365132730Skan    }
5366132730Skan
5367169699Skan  arg_info->parms = parms;
5368169699Skan  arg_info->tags = tags;
5369169699Skan  arg_info->types = types;
5370169699Skan  arg_info->others = others;
5371169699Skan  arg_info->pending_sizes = get_pending_sizes ();
5372169699Skan  return arg_info;
537318334Speter}
537418334Speter
537518334Speter/* Get the struct, enum or union (CODE says which) with tag NAME.
5376169699Skan   Define the tag as a forward-reference if it is not defined.
5377169699Skan   Return a c_typespec structure for the type specifier.  */
537818334Speter
5379169699Skanstruct c_typespec
5380169699Skanparser_xref_tag (enum tree_code code, tree name)
538118334Speter{
5382169699Skan  struct c_typespec ret;
538318334Speter  /* If a cross reference is requested, look up the type
538418334Speter     already defined for this tag and return it.  */
538518334Speter
5386132730Skan  tree ref = lookup_tag (code, name, 0);
538790075Sobrien  /* If this is the right type of tag, return what we found.
538890075Sobrien     (This reference will be shadowed by shadow_tag later if appropriate.)
538990075Sobrien     If this is the wrong type of tag, do not return it.  If it was the
5390132730Skan     wrong type in the same scope, we will have had an error
5391132730Skan     message already; if in a different scope and declaring
539290075Sobrien     a name, pending_xref_error will give an error message; but if in a
5393132730Skan     different scope and not declaring a name, this tag should
539490075Sobrien     shadow the previous declaration of a different type of tag, and
539590075Sobrien     this would not work properly if we return the reference found.
539690075Sobrien     (For example, with "struct foo" in an outer scope, "union foo;"
539790075Sobrien     must shadow that tag with a new one of union type.)  */
5398169699Skan  ret.kind = (ref ? ctsk_tagref : ctsk_tagfirstref);
539990075Sobrien  if (ref && TREE_CODE (ref) == code)
5400169699Skan    {
5401169699Skan      ret.spec = ref;
5402169699Skan      return ret;
5403169699Skan    }
540418334Speter
540518334Speter  /* If no such tag is yet defined, create a forward-reference node
540618334Speter     and record it as the "definition".
540718334Speter     When a real declaration of this type is found,
540818334Speter     the forward-reference will be altered into a real type.  */
540918334Speter
541018334Speter  ref = make_node (code);
541118334Speter  if (code == ENUMERAL_TYPE)
541218334Speter    {
541318334Speter      /* Give the type a default layout like unsigned int
541418334Speter	 to avoid crashing if it does not get defined.  */
541518334Speter      TYPE_MODE (ref) = TYPE_MODE (unsigned_type_node);
541618334Speter      TYPE_ALIGN (ref) = TYPE_ALIGN (unsigned_type_node);
541790075Sobrien      TYPE_USER_ALIGN (ref) = 0;
5418169699Skan      TYPE_UNSIGNED (ref) = 1;
541918334Speter      TYPE_PRECISION (ref) = TYPE_PRECISION (unsigned_type_node);
542018334Speter      TYPE_MIN_VALUE (ref) = TYPE_MIN_VALUE (unsigned_type_node);
542118334Speter      TYPE_MAX_VALUE (ref) = TYPE_MAX_VALUE (unsigned_type_node);
542218334Speter    }
542318334Speter
542418334Speter  pushtag (name, ref);
542518334Speter
5426169699Skan  ret.spec = ref;
5427169699Skan  return ret;
542818334Speter}
5429169699Skan
5430169699Skan/* Get the struct, enum or union (CODE says which) with tag NAME.
5431169699Skan   Define the tag as a forward-reference if it is not defined.
5432169699Skan   Return a tree for the type.  */
5433169699Skan
5434169699Skantree
5435169699Skanxref_tag (enum tree_code code, tree name)
5436169699Skan{
5437169699Skan  return parser_xref_tag (code, name).spec;
5438169699Skan}
543918334Speter
5440132730Skan/* Make sure that the tag NAME is defined *in the current scope*
544118334Speter   at least as a forward reference.
544290075Sobrien   CODE says which kind of tag NAME ought to be.  */
544318334Speter
544418334Spetertree
5445132730Skanstart_struct (enum tree_code code, tree name)
544618334Speter{
5447132730Skan  /* If there is already a tag defined at this scope
544818334Speter     (as a forward reference), just return it.  */
544918334Speter
545090075Sobrien  tree ref = 0;
545118334Speter
545218334Speter  if (name != 0)
5453132730Skan    ref = lookup_tag (code, name, 1);
545418334Speter  if (ref && TREE_CODE (ref) == code)
545518334Speter    {
5456161660Skan      if (TYPE_SIZE (ref))
5457169699Skan	{
545890075Sobrien	  if (code == UNION_TYPE)
5459169699Skan	    error ("redefinition of %<union %E%>", name);
5460169699Skan	  else
5461169699Skan	    error ("redefinition of %<struct %E%>", name);
5462132730Skan	}
5463161660Skan      else if (C_TYPE_BEING_DEFINED (ref))
5464161660Skan	{
5465161660Skan	  if (code == UNION_TYPE)
5466169699Skan	    error ("nested redefinition of %<union %E%>", name);
5467169699Skan	  else
5468169699Skan	    error ("nested redefinition of %<struct %E%>", name);
5469189824Sdas	  /* Don't create structures that contain themselves.  */
5470189824Sdas	  ref = NULL_TREE;
5471161660Skan	}
5472117421Skan    }
5473189824Sdas
5474189824Sdas  /* Otherwise create a forward-reference just so the tag is in scope.  */
5475189824Sdas
5476189824Sdas  if (ref == NULL_TREE || TREE_CODE (ref) != code)
5477117421Skan    {
5478117421Skan      ref = make_node (code);
5479117421Skan      pushtag (name, ref);
548018334Speter    }
5481132730Skan
548218334Speter  C_TYPE_BEING_DEFINED (ref) = 1;
548350397Sobrien  TYPE_PACKED (ref) = flag_pack_struct;
548418334Speter  return ref;
548518334Speter}
548618334Speter
5487169699Skan/* Process the specs, declarator and width (NULL if omitted)
548818334Speter   of a structure component, returning a FIELD_DECL node.
5489132730Skan   WIDTH is non-NULL for bit-fields only, and is an INTEGER_CST node.
549018334Speter
549118334Speter   This is done during the parsing of the struct declaration.
549218334Speter   The FIELD_DECL nodes are chained together and the lot of them
549318334Speter   are ultimately passed to `build_struct' to make the RECORD_TYPE node.  */
549418334Speter
549518334Spetertree
5496169699Skangrokfield (struct c_declarator *declarator, struct c_declspecs *declspecs,
5497169699Skan	   tree width)
549818334Speter{
549918334Speter  tree value;
550018334Speter
5501169699Skan  if (declarator->kind == cdk_id && declarator->u.id == NULL_TREE
5502169699Skan      && width == NULL_TREE)
550390075Sobrien    {
5504117421Skan      /* This is an unnamed decl.
5505117421Skan
5506117421Skan	 If we have something of the form "union { list } ;" then this
5507117421Skan	 is the anonymous union extension.  Similarly for struct.
5508117421Skan
5509117421Skan	 If this is something of the form "struct foo;", then
5510117421Skan	   If MS extensions are enabled, this is handled as an
5511117421Skan	     anonymous struct.
5512117421Skan	   Otherwise this is a forward declaration of a structure tag.
5513117421Skan
5514117421Skan	 If this is something of the form "foo;" and foo is a TYPE_DECL, then
5515117421Skan	   If MS extensions are enabled and foo names a structure, then
5516117421Skan	     again this is an anonymous struct.
5517117421Skan	   Otherwise this is an error.
5518117421Skan
5519132730Skan	 Oh what a horrid tangled web we weave.  I wonder if MS consciously
5520117421Skan	 took this from Plan 9 or if it was an accident of implementation
5521117421Skan	 that took root before someone noticed the bug...  */
5522117421Skan
5523169699Skan      tree type = declspecs->type;
5524169699Skan      bool type_ok = (TREE_CODE (type) == RECORD_TYPE
5525169699Skan		      || TREE_CODE (type) == UNION_TYPE);
5526169699Skan      bool ok = false;
5527102790Skan
5528169699Skan      if (type_ok
5529169699Skan	  && (flag_ms_extensions || !declspecs->typedef_p))
553090075Sobrien	{
5531117421Skan	  if (flag_ms_extensions)
5532169699Skan	    ok = true;
5533117421Skan	  else if (flag_iso)
5534169699Skan	    ok = false;
5535117421Skan	  else if (TYPE_NAME (type) == NULL)
5536169699Skan	    ok = true;
5537117421Skan	  else
5538169699Skan	    ok = false;
5539117421Skan	}
5540169699Skan      if (!ok)
5541117421Skan	{
5542169699Skan	  pedwarn ("declaration does not declare anything");
554390075Sobrien	  return NULL_TREE;
554490075Sobrien	}
5545169699Skan      if (pedantic)
5546169699Skan	pedwarn ("ISO C doesn%'t support unnamed structs/unions");
554790075Sobrien    }
554818334Speter
5549169699Skan  value = grokdeclarator (declarator, declspecs, FIELD, false,
5550132730Skan			  width ? &width : NULL);
555118334Speter
555218334Speter  finish_decl (value, NULL_TREE, NULL_TREE);
555396263Sobrien  DECL_INITIAL (value) = width;
555418334Speter
555518334Speter  return value;
555618334Speter}
555718334Speter
5558132730Skan/* Generate an error for any duplicate field names in FIELDLIST.  Munge
5559132730Skan   the list such that this does not present a problem later.  */
5560122196Skan
5561132730Skanstatic void
5562132730Skandetect_field_duplicates (tree fieldlist)
5563132730Skan{
5564132730Skan  tree x, y;
5565132730Skan  int timeout = 10;
5566122196Skan
5567132730Skan  /* First, see if there are more than "a few" fields.
5568132730Skan     This is trivially true if there are zero or one fields.  */
5569132730Skan  if (!fieldlist)
5570132730Skan    return;
5571132730Skan  x = TREE_CHAIN (fieldlist);
5572132730Skan  if (!x)
5573132730Skan    return;
5574132730Skan  do {
5575132730Skan    timeout--;
5576132730Skan    x = TREE_CHAIN (x);
5577132730Skan  } while (timeout > 0 && x);
5578132730Skan
5579132730Skan  /* If there were "few" fields, avoid the overhead of allocating
5580132730Skan     a hash table.  Instead just do the nested traversal thing.  */
5581132730Skan  if (timeout > 0)
5582132730Skan    {
5583132730Skan      for (x = TREE_CHAIN (fieldlist); x ; x = TREE_CHAIN (x))
5584132730Skan	if (DECL_NAME (x))
5585132730Skan	  {
5586132730Skan	    for (y = fieldlist; y != x; y = TREE_CHAIN (y))
5587132730Skan	      if (DECL_NAME (y) == DECL_NAME (x))
5588132730Skan		{
5589169699Skan		  error ("duplicate member %q+D", x);
5590132730Skan		  DECL_NAME (x) = NULL_TREE;
5591132730Skan		}
5592132730Skan	  }
5593132730Skan    }
5594132730Skan  else
5595132730Skan    {
5596132730Skan      htab_t htab = htab_create (37, htab_hash_pointer, htab_eq_pointer, NULL);
5597132730Skan      void **slot;
5598132730Skan
5599132730Skan      for (x = fieldlist; x ; x = TREE_CHAIN (x))
5600132730Skan	if ((y = DECL_NAME (x)) != 0)
5601132730Skan	  {
5602132730Skan	    slot = htab_find_slot (htab, y, INSERT);
5603132730Skan	    if (*slot)
5604132730Skan	      {
5605169699Skan		error ("duplicate member %q+D", x);
5606132730Skan		DECL_NAME (x) = NULL_TREE;
5607132730Skan	      }
5608132730Skan	    *slot = y;
5609132730Skan	  }
5610132730Skan
5611132730Skan      htab_delete (htab);
5612132730Skan    }
5613122196Skan}
5614132730Skan
561518334Speter/* Fill in the fields of a RECORD_TYPE or UNION_TYPE node, T.
561618334Speter   FIELDLIST is a chain of FIELD_DECL nodes for the fields.
561790075Sobrien   ATTRIBUTES are attributes to be applied to the structure.  */
561818334Speter
561918334Spetertree
5620132730Skanfinish_struct (tree t, tree fieldlist, tree attributes)
562118334Speter{
562290075Sobrien  tree x;
5623169699Skan  bool toplevel = file_scope == current_scope;
562490075Sobrien  int saw_named_field;
562518334Speter
562618334Speter  /* If this type was previously laid out as a forward reference,
562718334Speter     make sure we lay it out again.  */
562818334Speter
562918334Speter  TYPE_SIZE (t) = 0;
563018334Speter
563190075Sobrien  decl_attributes (&t, attributes, (int) ATTR_FLAG_TYPE_IN_PLACE);
563218334Speter
563350397Sobrien  if (pedantic)
563450397Sobrien    {
563550397Sobrien      for (x = fieldlist; x; x = TREE_CHAIN (x))
563650397Sobrien	if (DECL_NAME (x) != 0)
563750397Sobrien	  break;
563818334Speter
563950397Sobrien      if (x == 0)
5640169699Skan	{
5641169699Skan	  if (TREE_CODE (t) == UNION_TYPE)
5642169699Skan	    {
5643169699Skan	      if (fieldlist)
5644169699Skan		pedwarn ("union has no named members");
5645169699Skan	      else
5646169699Skan		pedwarn ("union has no members");
5647169699Skan	    }
5648169699Skan	  else
5649169699Skan	    {
5650169699Skan	      if (fieldlist)
5651169699Skan		pedwarn ("struct has no named members");
5652169699Skan	      else
5653169699Skan		pedwarn ("struct has no members");
5654169699Skan	    }
5655169699Skan	}
565650397Sobrien    }
565750397Sobrien
565896263Sobrien  /* Install struct as DECL_CONTEXT of each field decl.
5659169699Skan     Also process specified field sizes, found in the DECL_INITIAL,
5660169699Skan     storing 0 there after the type has been changed to precision equal
5661169699Skan     to its width, rather than the precision of the specified standard
5662169699Skan     type.  (Correct layout requires the original type to have been preserved
5663169699Skan     until now.)  */
566418334Speter
566590075Sobrien  saw_named_field = 0;
566618334Speter  for (x = fieldlist; x; x = TREE_CHAIN (x))
566718334Speter    {
5668169699Skan      if (TREE_TYPE (x) == error_mark_node)
5669169699Skan	continue;
5670169699Skan
567118334Speter      DECL_CONTEXT (x) = t;
567218334Speter
5673169699Skan      if (TYPE_PACKED (t) && TYPE_ALIGN (TREE_TYPE (x)) > BITS_PER_UNIT)
5674169699Skan	DECL_PACKED (x) = 1;
5675169699Skan
567618334Speter      /* If any field is const, the structure type is pseudo-const.  */
567718334Speter      if (TREE_READONLY (x))
567818334Speter	C_TYPE_FIELDS_READONLY (t) = 1;
567918334Speter      else
568018334Speter	{
568118334Speter	  /* A field that is pseudo-const makes the structure likewise.  */
568218334Speter	  tree t1 = TREE_TYPE (x);
568318334Speter	  while (TREE_CODE (t1) == ARRAY_TYPE)
568418334Speter	    t1 = TREE_TYPE (t1);
568518334Speter	  if ((TREE_CODE (t1) == RECORD_TYPE || TREE_CODE (t1) == UNION_TYPE)
568618334Speter	      && C_TYPE_FIELDS_READONLY (t1))
568718334Speter	    C_TYPE_FIELDS_READONLY (t) = 1;
568818334Speter	}
568918334Speter
569018334Speter      /* Any field that is volatile means variables of this type must be
569118334Speter	 treated in some ways as volatile.  */
569218334Speter      if (TREE_THIS_VOLATILE (x))
569318334Speter	C_TYPE_FIELDS_VOLATILE (t) = 1;
569418334Speter
569518334Speter      /* Any field of nominal variable size implies structure is too.  */
569618334Speter      if (C_DECL_VARIABLE_SIZE (x))
569718334Speter	C_TYPE_VARIABLE_SIZE (t) = 1;
569818334Speter
569996263Sobrien      if (DECL_INITIAL (x))
570018334Speter	{
5701132730Skan	  unsigned HOST_WIDE_INT width = tree_low_cst (DECL_INITIAL (x), 1);
5702132730Skan	  DECL_SIZE (x) = bitsize_int (width);
5703132730Skan	  DECL_BIT_FIELD (x) = 1;
5704132730Skan	  SET_DECL_C_BIT_FIELD (x);
570596263Sobrien	}
570696263Sobrien
570790075Sobrien      /* Detect flexible array member in an invalid context.  */
570890075Sobrien      if (TREE_CODE (TREE_TYPE (x)) == ARRAY_TYPE
570990075Sobrien	  && TYPE_SIZE (TREE_TYPE (x)) == NULL_TREE
571090075Sobrien	  && TYPE_DOMAIN (TREE_TYPE (x)) != NULL_TREE
571190075Sobrien	  && TYPE_MAX_VALUE (TYPE_DOMAIN (TREE_TYPE (x))) == NULL_TREE)
571218334Speter	{
571390075Sobrien	  if (TREE_CODE (t) == UNION_TYPE)
5714132730Skan	    {
5715132730Skan	      error ("%Jflexible array member in union", x);
5716132730Skan	      TREE_TYPE (x) = error_mark_node;
5717132730Skan	    }
571890075Sobrien	  else if (TREE_CHAIN (x) != NULL_TREE)
5719132730Skan	    {
5720132730Skan	      error ("%Jflexible array member not at end of struct", x);
5721132730Skan	      TREE_TYPE (x) = error_mark_node;
5722132730Skan	    }
5723169699Skan	  else if (!saw_named_field)
5724132730Skan	    {
5725132730Skan	      error ("%Jflexible array member in otherwise empty struct", x);
5726132730Skan	      TREE_TYPE (x) = error_mark_node;
5727132730Skan	    }
572818334Speter	}
5729117421Skan
5730132730Skan      if (pedantic && !in_system_header && TREE_CODE (t) == RECORD_TYPE
5731117421Skan	  && flexible_array_type_p (TREE_TYPE (x)))
5732132730Skan	pedwarn ("%Jinvalid use of structure with flexible array member", x);
5733117421Skan
573490075Sobrien      if (DECL_NAME (x))
573590075Sobrien	saw_named_field = 1;
573618334Speter    }
573718334Speter
5738132730Skan  detect_field_duplicates (fieldlist);
573990075Sobrien
574018334Speter  /* Now we have the nearly final fieldlist.  Record it,
574118334Speter     then lay out the structure or union (including the fields).  */
574218334Speter
574318334Speter  TYPE_FIELDS (t) = fieldlist;
574418334Speter
574518334Speter  layout_type (t);
574618334Speter
5747169699Skan  /* Give bit-fields their proper types.  */
574890075Sobrien  {
574990075Sobrien    tree *fieldlistp = &fieldlist;
575090075Sobrien    while (*fieldlistp)
5751169699Skan      if (TREE_CODE (*fieldlistp) == FIELD_DECL && DECL_INITIAL (*fieldlistp)
5752169699Skan	  && TREE_TYPE (*fieldlistp) != error_mark_node)
5753169699Skan	{
5754169699Skan	  unsigned HOST_WIDE_INT width
5755169699Skan	    = tree_low_cst (DECL_INITIAL (*fieldlistp), 1);
5756169699Skan	  tree type = TREE_TYPE (*fieldlistp);
5757169699Skan	  if (width != TYPE_PRECISION (type))
5758169699Skan	    {
5759169699Skan	      TREE_TYPE (*fieldlistp)
5760169699Skan		= c_build_bitfield_integer_type (width, TYPE_UNSIGNED (type));
5761169699Skan	      DECL_MODE (*fieldlistp) = TYPE_MODE (TREE_TYPE (*fieldlistp));
5762169699Skan	    }
5763169699Skan	  DECL_INITIAL (*fieldlistp) = 0;
5764169699Skan	}
576590075Sobrien      else
576690075Sobrien	fieldlistp = &TREE_CHAIN (*fieldlistp);
576790075Sobrien  }
576818334Speter
576990075Sobrien  /* Now we have the truly final field list.
577090075Sobrien     Store it in this type and in the variants.  */
577118334Speter
577218334Speter  TYPE_FIELDS (t) = fieldlist;
577318334Speter
5774122196Skan  /* If there are lots of fields, sort so we can look through them fast.
5775132730Skan     We arbitrarily consider 16 or more elts to be "a lot".  */
5776122196Skan
5777122196Skan  {
5778122196Skan    int len = 0;
5779122196Skan
5780122196Skan    for (x = fieldlist; x; x = TREE_CHAIN (x))
5781122196Skan      {
5782169699Skan	if (len > 15 || DECL_NAME (x) == NULL)
5783169699Skan	  break;
5784169699Skan	len += 1;
5785122196Skan      }
5786122196Skan
5787122196Skan    if (len > 15)
5788122196Skan      {
5789169699Skan	tree *field_array;
5790169699Skan	struct lang_type *space;
5791169699Skan	struct sorted_fields_type *space2;
5792132730Skan
5793169699Skan	len += list_length (x);
5794132730Skan
5795169699Skan	/* Use the same allocation policy here that make_node uses, to
5796169699Skan	  ensure that this lives as long as the rest of the struct decl.
5797169699Skan	  All decls in an inline function need to be saved.  */
5798132730Skan
5799169699Skan	space = GGC_CNEW (struct lang_type);
5800169699Skan	space2 = GGC_NEWVAR (struct sorted_fields_type,
5801169699Skan			     sizeof (struct sorted_fields_type) + len * sizeof (tree));
5802132730Skan
5803169699Skan	len = 0;
5804132730Skan	space->s = space2;
5805132730Skan	field_array = &space2->elts[0];
5806169699Skan	for (x = fieldlist; x; x = TREE_CHAIN (x))
5807169699Skan	  {
5808169699Skan	    field_array[len++] = x;
5809132730Skan
5810169699Skan	    /* If there is anonymous struct or union, break out of the loop.  */
5811169699Skan	    if (DECL_NAME (x) == NULL)
5812169699Skan	      break;
5813169699Skan	  }
5814169699Skan	/* Found no anonymous struct/union.  Add the TYPE_LANG_SPECIFIC.  */
5815169699Skan	if (x == NULL)
5816169699Skan	  {
5817169699Skan	    TYPE_LANG_SPECIFIC (t) = space;
5818169699Skan	    TYPE_LANG_SPECIFIC (t)->s->len = len;
5819169699Skan	    field_array = TYPE_LANG_SPECIFIC (t)->s->elts;
5820169699Skan	    qsort (field_array, len, sizeof (tree), field_decl_cmp);
5821169699Skan	  }
5822122196Skan      }
5823122196Skan  }
5824132730Skan
582518334Speter  for (x = TYPE_MAIN_VARIANT (t); x; x = TYPE_NEXT_VARIANT (x))
582618334Speter    {
582718334Speter      TYPE_FIELDS (x) = TYPE_FIELDS (t);
582818334Speter      TYPE_LANG_SPECIFIC (x) = TYPE_LANG_SPECIFIC (t);
5829161660Skan      C_TYPE_FIELDS_READONLY (x) = C_TYPE_FIELDS_READONLY (t);
5830161660Skan      C_TYPE_FIELDS_VOLATILE (x) = C_TYPE_FIELDS_VOLATILE (t);
5831161660Skan      C_TYPE_VARIABLE_SIZE (x) = C_TYPE_VARIABLE_SIZE (t);
583218334Speter    }
583318334Speter
583418334Speter  /* If this was supposed to be a transparent union, but we can't
583518334Speter     make it one, warn and turn off the flag.  */
583618334Speter  if (TREE_CODE (t) == UNION_TYPE
583718334Speter      && TYPE_TRANSPARENT_UNION (t)
5838146906Skan      && (!TYPE_FIELDS (t) || TYPE_MODE (t) != DECL_MODE (TYPE_FIELDS (t))))
583918334Speter    {
584018334Speter      TYPE_TRANSPARENT_UNION (t) = 0;
5841169699Skan      warning (0, "union cannot be made transparent");
584218334Speter    }
584318334Speter
584418334Speter  /* If this structure or union completes the type of any previous
584518334Speter     variable declaration, lay it out and output its rtl.  */
5846132730Skan  for (x = C_TYPE_INCOMPLETE_VARS (TYPE_MAIN_VARIANT (t));
5847132730Skan       x;
5848132730Skan       x = TREE_CHAIN (x))
584918334Speter    {
5850132730Skan      tree decl = TREE_VALUE (x);
5851132730Skan      if (TREE_CODE (TREE_TYPE (decl)) == ARRAY_TYPE)
5852132730Skan	layout_array_type (TREE_TYPE (decl));
5853132730Skan      if (TREE_CODE (decl) != TYPE_DECL)
5854132730Skan	{
5855132730Skan	  layout_decl (decl, 0);
5856132730Skan	  if (c_dialect_objc ())
5857132730Skan	    objc_check_decl (decl);
5858169699Skan	  rest_of_decl_compilation (decl, toplevel, 0);
5859169699Skan	  if (!toplevel)
5860132730Skan	    expand_decl (decl);
586118334Speter	}
586218334Speter    }
5863132730Skan  C_TYPE_INCOMPLETE_VARS (TYPE_MAIN_VARIANT (t)) = 0;
586418334Speter
586518334Speter  /* Finish debugging output for this type.  */
586618334Speter  rest_of_type_compilation (t, toplevel);
586718334Speter
5868169699Skan  /* If we're inside a function proper, i.e. not file-scope and not still
5869169699Skan     parsing parameters, then arrange for the size of a variable sized type
5870169699Skan     to be bound now.  */
5871169699Skan  if (cur_stmt_list && variably_modified_type_p (t, NULL_TREE))
5872169699Skan    add_stmt (build_stmt (DECL_EXPR, build_decl (TYPE_DECL, NULL, t)));
5873169699Skan
587418334Speter  return t;
587518334Speter}
587618334Speter
587718334Speter/* Lay out the type T, and its element type, and so on.  */
587818334Speter
587918334Speterstatic void
5880132730Skanlayout_array_type (tree t)
588118334Speter{
588218334Speter  if (TREE_CODE (TREE_TYPE (t)) == ARRAY_TYPE)
588318334Speter    layout_array_type (TREE_TYPE (t));
588418334Speter  layout_type (t);
588518334Speter}
588618334Speter
588718334Speter/* Begin compiling the definition of an enumeration type.
588818334Speter   NAME is its name (or null if anonymous).
588918334Speter   Returns the type object, as yet incomplete.
589018334Speter   Also records info about it so that build_enumerator
589118334Speter   may be used to declare the individual values as they are read.  */
589218334Speter
589318334Spetertree
5894132730Skanstart_enum (tree name)
589518334Speter{
589690075Sobrien  tree enumtype = 0;
589718334Speter
589818334Speter  /* If this is the real definition for a previous forward reference,
589918334Speter     fill in the contents in the same object that used to be the
590018334Speter     forward reference.  */
590118334Speter
590218334Speter  if (name != 0)
5903132730Skan    enumtype = lookup_tag (ENUMERAL_TYPE, name, 1);
590418334Speter
590518334Speter  if (enumtype == 0 || TREE_CODE (enumtype) != ENUMERAL_TYPE)
590618334Speter    {
590718334Speter      enumtype = make_node (ENUMERAL_TYPE);
590818334Speter      pushtag (name, enumtype);
590918334Speter    }
591018334Speter
5911161660Skan  if (C_TYPE_BEING_DEFINED (enumtype))
5912169699Skan    error ("nested redefinition of %<enum %E%>", name);
5913161660Skan
591418334Speter  C_TYPE_BEING_DEFINED (enumtype) = 1;
591518334Speter
591618334Speter  if (TYPE_VALUES (enumtype) != 0)
591718334Speter    {
591818334Speter      /* This enum is a named one that has been declared already.  */
5919169699Skan      error ("redeclaration of %<enum %E%>", name);
592018334Speter
592118334Speter      /* Completely replace its old definition.
592218334Speter	 The old enumerators remain defined, however.  */
592318334Speter      TYPE_VALUES (enumtype) = 0;
592418334Speter    }
592518334Speter
592618334Speter  enum_next_value = integer_zero_node;
592718334Speter  enum_overflow = 0;
592818334Speter
592950397Sobrien  if (flag_short_enums)
593050397Sobrien    TYPE_PACKED (enumtype) = 1;
593150397Sobrien
593218334Speter  return enumtype;
593318334Speter}
593418334Speter
593518334Speter/* After processing and defining all the values of an enumeration type,
593618334Speter   install their decls in the enumeration type and finish it off.
593718334Speter   ENUMTYPE is the type object, VALUES a list of decl-value pairs,
593818334Speter   and ATTRIBUTES are the specified attributes.
593918334Speter   Returns ENUMTYPE.  */
594018334Speter
594118334Spetertree
5942132730Skanfinish_enum (tree enumtype, tree values, tree attributes)
594318334Speter{
594490075Sobrien  tree pair, tem;
5945169699Skan  tree minnode = 0, maxnode = 0;
594690075Sobrien  int precision, unsign;
5947169699Skan  bool toplevel = (file_scope == current_scope);
5948169699Skan  struct lang_type *lt;
594918334Speter
595090075Sobrien  decl_attributes (&enumtype, attributes, (int) ATTR_FLAG_TYPE_IN_PLACE);
595118334Speter
595218334Speter  /* Calculate the maximum value of any enumerator in this type.  */
595318334Speter
595418334Speter  if (values == error_mark_node)
595518334Speter    minnode = maxnode = integer_zero_node;
595618334Speter  else
595790075Sobrien    {
595890075Sobrien      minnode = maxnode = TREE_VALUE (values);
595990075Sobrien      for (pair = TREE_CHAIN (values); pair; pair = TREE_CHAIN (pair))
596090075Sobrien	{
596190075Sobrien	  tree value = TREE_VALUE (pair);
596290075Sobrien	  if (tree_int_cst_lt (maxnode, value))
596390075Sobrien	    maxnode = value;
596490075Sobrien	  if (tree_int_cst_lt (value, minnode))
596590075Sobrien	    minnode = value;
596690075Sobrien	}
596790075Sobrien    }
596818334Speter
596990075Sobrien  /* Construct the final type of this enumeration.  It is the same
597090075Sobrien     as one of the integral types - the narrowest one that fits, except
597190075Sobrien     that normally we only go as narrow as int - and signed iff any of
597290075Sobrien     the values are negative.  */
597390075Sobrien  unsign = (tree_int_cst_sgn (minnode) >= 0);
597490075Sobrien  precision = MAX (min_precision (minnode, unsign),
597590075Sobrien		   min_precision (maxnode, unsign));
5976169699Skan
597750397Sobrien  if (TYPE_PACKED (enumtype) || precision > TYPE_PRECISION (integer_type_node))
597850397Sobrien    {
5979169699Skan      tem = c_common_type_for_size (precision, unsign);
5980169699Skan      if (tem == NULL)
598150397Sobrien	{
5982169699Skan	  warning (0, "enumeration values exceed range of largest integer");
5983169699Skan	  tem = long_long_integer_type_node;
598450397Sobrien	}
598550397Sobrien    }
598618334Speter  else
5987169699Skan    tem = unsign ? unsigned_type_node : integer_type_node;
598818334Speter
5989169699Skan  TYPE_MIN_VALUE (enumtype) = TYPE_MIN_VALUE (tem);
5990169699Skan  TYPE_MAX_VALUE (enumtype) = TYPE_MAX_VALUE (tem);
5991169699Skan  TYPE_UNSIGNED (enumtype) = TYPE_UNSIGNED (tem);
599218334Speter  TYPE_SIZE (enumtype) = 0;
5993146906Skan
5994146906Skan  /* If the precision of the type was specific with an attribute and it
5995146906Skan     was too small, give an error.  Otherwise, use it.  */
5996146906Skan  if (TYPE_PRECISION (enumtype))
5997146906Skan    {
5998146906Skan      if (precision > TYPE_PRECISION (enumtype))
5999146906Skan	error ("specified mode too small for enumeral values");
6000146906Skan    }
6001146906Skan  else
6002169699Skan    TYPE_PRECISION (enumtype) = TYPE_PRECISION (tem);
6003146906Skan
600418334Speter  layout_type (enumtype);
600518334Speter
600618334Speter  if (values != error_mark_node)
600718334Speter    {
600890075Sobrien      /* Change the type of the enumerators to be the enum type.  We
600990075Sobrien	 need to do this irrespective of the size of the enum, for
601090075Sobrien	 proper type checking.  Replace the DECL_INITIALs of the
601190075Sobrien	 enumerators, and the value slots of the list, with copies
601290075Sobrien	 that have the enum type; they cannot be modified in place
601390075Sobrien	 because they may be shared (e.g.  integer_zero_node) Finally,
601490075Sobrien	 change the purpose slots to point to the names of the decls.  */
601518334Speter      for (pair = values; pair; pair = TREE_CHAIN (pair))
601618334Speter	{
601790075Sobrien	  tree enu = TREE_PURPOSE (pair);
6018169699Skan	  tree ini = DECL_INITIAL (enu);
601990075Sobrien
602090075Sobrien	  TREE_TYPE (enu) = enumtype;
602190075Sobrien
602290075Sobrien	  /* The ISO C Standard mandates enumerators to have type int,
602390075Sobrien	     even though the underlying type of an enum type is
602490075Sobrien	     unspecified.  Here we convert any enumerators that fit in
602590075Sobrien	     an int to type int, to avoid promotions to unsigned types
602690075Sobrien	     when comparing integers with enumerators that fit in the
602790075Sobrien	     int range.  When -pedantic is given, build_enumerator()
602890075Sobrien	     would have already taken care of those that don't fit.  */
6029169699Skan	  if (int_fits_type_p (ini, integer_type_node))
6030169699Skan	    tem = integer_type_node;
603190075Sobrien	  else
6032169699Skan	    tem = enumtype;
6033169699Skan	  ini = convert (tem, ini);
603490075Sobrien
6035169699Skan	  DECL_INITIAL (enu) = ini;
603690075Sobrien	  TREE_PURPOSE (pair) = DECL_NAME (enu);
6037169699Skan	  TREE_VALUE (pair) = ini;
603818334Speter	}
603918334Speter
604018334Speter      TYPE_VALUES (enumtype) = values;
604118334Speter    }
604218334Speter
6043169699Skan  /* Record the min/max values so that we can warn about bit-field
6044169699Skan     enumerations that are too small for the values.  */
6045169699Skan  lt = GGC_CNEW (struct lang_type);
6046169699Skan  lt->enum_min = minnode;
6047169699Skan  lt->enum_max = maxnode;
6048169699Skan  TYPE_LANG_SPECIFIC (enumtype) = lt;
6049169699Skan
605018334Speter  /* Fix up all variant types of this enum type.  */
605118334Speter  for (tem = TYPE_MAIN_VARIANT (enumtype); tem; tem = TYPE_NEXT_VARIANT (tem))
605218334Speter    {
605390075Sobrien      if (tem == enumtype)
605490075Sobrien	continue;
605518334Speter      TYPE_VALUES (tem) = TYPE_VALUES (enumtype);
605618334Speter      TYPE_MIN_VALUE (tem) = TYPE_MIN_VALUE (enumtype);
605718334Speter      TYPE_MAX_VALUE (tem) = TYPE_MAX_VALUE (enumtype);
605818334Speter      TYPE_SIZE (tem) = TYPE_SIZE (enumtype);
605950397Sobrien      TYPE_SIZE_UNIT (tem) = TYPE_SIZE_UNIT (enumtype);
606018334Speter      TYPE_MODE (tem) = TYPE_MODE (enumtype);
606118334Speter      TYPE_PRECISION (tem) = TYPE_PRECISION (enumtype);
606218334Speter      TYPE_ALIGN (tem) = TYPE_ALIGN (enumtype);
606390075Sobrien      TYPE_USER_ALIGN (tem) = TYPE_USER_ALIGN (enumtype);
6064169699Skan      TYPE_UNSIGNED (tem) = TYPE_UNSIGNED (enumtype);
6065169699Skan      TYPE_LANG_SPECIFIC (tem) = TYPE_LANG_SPECIFIC (enumtype);
606618334Speter    }
606718334Speter
606818334Speter  /* Finish debugging output for this type.  */
606918334Speter  rest_of_type_compilation (enumtype, toplevel);
607018334Speter
607118334Speter  return enumtype;
607218334Speter}
607318334Speter
607418334Speter/* Build and install a CONST_DECL for one value of the
607518334Speter   current enumeration type (one that was begun with start_enum).
607618334Speter   Return a tree-list containing the CONST_DECL and its value.
607718334Speter   Assignment of sequential values by default is handled here.  */
607818334Speter
607918334Spetertree
6080132730Skanbuild_enumerator (tree name, tree value)
608118334Speter{
608290075Sobrien  tree decl, type;
608318334Speter
608418334Speter  /* Validate and default VALUE.  */
608518334Speter
608618334Speter  if (value != 0)
608718334Speter    {
6088169699Skan      /* Don't issue more errors for error_mark_node (i.e. an
6089169699Skan	 undeclared identifier) - just ignore the value expression.  */
6090169699Skan      if (value == error_mark_node)
6091169699Skan	value = 0;
6092169699Skan      else if (!INTEGRAL_TYPE_P (TREE_TYPE (value))
6093169699Skan	       || TREE_CODE (value) != INTEGER_CST)
609418334Speter	{
6095169699Skan	  error ("enumerator value for %qE is not an integer constant", name);
6096169699Skan	  value = 0;
609718334Speter	}
609818334Speter      else
609918334Speter	{
6100169699Skan	  value = default_conversion (value);
6101169699Skan	  constant_expression_warning (value);
610218334Speter	}
610318334Speter    }
610418334Speter
610518334Speter  /* Default based on previous value.  */
610618334Speter  /* It should no longer be possible to have NON_LVALUE_EXPR
610718334Speter     in the default.  */
610818334Speter  if (value == 0)
610918334Speter    {
611018334Speter      value = enum_next_value;
611118334Speter      if (enum_overflow)
611218334Speter	error ("overflow in enumeration values");
611318334Speter    }
611418334Speter
6115169699Skan  if (pedantic && !int_fits_type_p (value, integer_type_node))
611618334Speter    {
6117169699Skan      pedwarn ("ISO C restricts enumerator values to range of %<int%>");
6118169699Skan      /* XXX This causes -pedantic to change the meaning of the program.
6119169699Skan	 Remove?  -zw 2004-03-15  */
612090075Sobrien      value = convert (integer_type_node, value);
612118334Speter    }
612218334Speter
612318334Speter  /* Set basis for default for next value.  */
612418334Speter  enum_next_value = build_binary_op (PLUS_EXPR, value, integer_one_node, 0);
612518334Speter  enum_overflow = tree_int_cst_lt (enum_next_value, value);
612618334Speter
612718334Speter  /* Now create a declaration for the enum value name.  */
612818334Speter
612918334Speter  type = TREE_TYPE (value);
6130117421Skan  type = c_common_type_for_size (MAX (TYPE_PRECISION (type),
6131117421Skan				      TYPE_PRECISION (integer_type_node)),
6132117421Skan				 (TYPE_PRECISION (type)
6133117421Skan				  >= TYPE_PRECISION (integer_type_node)
6134169699Skan				  && TYPE_UNSIGNED (type)));
613518334Speter
613618334Speter  decl = build_decl (CONST_DECL, name, type);
613790075Sobrien  DECL_INITIAL (decl) = convert (type, value);
613818334Speter  pushdecl (decl);
613918334Speter
614090075Sobrien  return tree_cons (decl, value, NULL_TREE);
614118334Speter}
614290075Sobrien
614318334Speter
614418334Speter/* Create the FUNCTION_DECL for a function definition.
614590075Sobrien   DECLSPECS, DECLARATOR and ATTRIBUTES are the parts of
614618334Speter   the declaration; they describe the function's name and the type it returns,
614718334Speter   but twisted together in a fashion that parallels the syntax of C.
614818334Speter
614918334Speter   This function creates a binding context for the function body
615018334Speter   as well as setting up the FUNCTION_DECL in current_function_decl.
615118334Speter
615218334Speter   Returns 1 on success.  If the DECLARATOR is not suitable for a function
615318334Speter   (it defines a datum instead), we return 0, which tells
615490075Sobrien   yyparse to report a parse error.  */
615518334Speter
615618334Speterint
6157169699Skanstart_function (struct c_declspecs *declspecs, struct c_declarator *declarator,
6158169699Skan		tree attributes)
615918334Speter{
616018334Speter  tree decl1, old_decl;
6161169699Skan  tree restype, resdecl;
6162169699Skan  struct c_label_context_se *nstack_se;
6163169699Skan  struct c_label_context_vm *nstack_vm;
616418334Speter
616550397Sobrien  current_function_returns_value = 0;  /* Assume, until we see it does.  */
616618334Speter  current_function_returns_null = 0;
616796263Sobrien  current_function_returns_abnormally = 0;
616818334Speter  warn_about_return_type = 0;
6169169699Skan  c_switch_stack = NULL;
617018334Speter
6171169699Skan  nstack_se = XOBNEW (&parser_obstack, struct c_label_context_se);
6172169699Skan  nstack_se->labels_def = NULL;
6173169699Skan  nstack_se->labels_used = NULL;
6174169699Skan  nstack_se->next = label_context_stack_se;
6175169699Skan  label_context_stack_se = nstack_se;
617618334Speter
6177169699Skan  nstack_vm = XOBNEW (&parser_obstack, struct c_label_context_vm);
6178169699Skan  nstack_vm->labels_def = NULL;
6179169699Skan  nstack_vm->labels_used = NULL;
6180169699Skan  nstack_vm->scope = 0;
6181169699Skan  nstack_vm->next = label_context_stack_vm;
6182169699Skan  label_context_stack_vm = nstack_vm;
618318334Speter
6184169699Skan  /* Indicate no valid break/continue context by setting these variables
6185169699Skan     to some non-null, non-label value.  We'll notice and emit the proper
6186169699Skan     error message in c_finish_bc_stmt.  */
6187169699Skan  c_break_label = c_cont_label = size_zero_node;
6188169699Skan
6189169699Skan  decl1 = grokdeclarator (declarator, declspecs, FUNCDEF, true, NULL);
6190169699Skan
619118334Speter  /* If the declarator is not suitable for a function definition,
619218334Speter     cause a syntax error.  */
619318334Speter  if (decl1 == 0)
619450397Sobrien    {
6195169699Skan      label_context_stack_se = label_context_stack_se->next;
6196169699Skan      label_context_stack_vm = label_context_stack_vm->next;
619750397Sobrien      return 0;
619850397Sobrien    }
619918334Speter
620090075Sobrien  decl_attributes (&decl1, attributes, 0);
620118334Speter
620290075Sobrien  if (DECL_DECLARED_INLINE_P (decl1)
620390075Sobrien      && DECL_UNINLINABLE (decl1)
620490075Sobrien      && lookup_attribute ("noinline", DECL_ATTRIBUTES (decl1)))
6205169699Skan    warning (OPT_Wattributes, "inline function %q+D given attribute noinline",
6206169699Skan	     decl1);
620790075Sobrien
6208189824Sdas  /* Handle gnu_inline attribute.  */
6209189824Sdas  if (declspecs->inline_p
6210189824Sdas      && !flag_gnu89_inline
6211189824Sdas      && TREE_CODE (decl1) == FUNCTION_DECL
6212189824Sdas      && lookup_attribute ("gnu_inline", DECL_ATTRIBUTES (decl1)))
6213189824Sdas    {
6214189824Sdas      if (declspecs->storage_class != csc_static)
6215189824Sdas	DECL_EXTERNAL (decl1) = !DECL_EXTERNAL (decl1);
6216189824Sdas    }
6217189824Sdas
621818334Speter  announce_function (decl1);
621918334Speter
622090075Sobrien  if (!COMPLETE_OR_VOID_TYPE_P (TREE_TYPE (TREE_TYPE (decl1))))
622118334Speter    {
622290075Sobrien      error ("return type is an incomplete type");
622318334Speter      /* Make it return void instead.  */
622418334Speter      TREE_TYPE (decl1)
622518334Speter	= build_function_type (void_type_node,
622618334Speter			       TYPE_ARG_TYPES (TREE_TYPE (decl1)));
622718334Speter    }
622818334Speter
622918334Speter  if (warn_about_return_type)
6230169699Skan    pedwarn_c99 ("return type defaults to %<int%>");
623118334Speter
623218334Speter  /* Make the init_value nonzero so pushdecl knows this is not tentative.
6233169699Skan     error_mark_node is replaced below (in pop_scope) with the BLOCK.  */
623418334Speter  DECL_INITIAL (decl1) = error_mark_node;
623518334Speter
623618334Speter  /* If this definition isn't a prototype and we had a prototype declaration
6237169699Skan     before, copy the arg type info from that prototype.  */
6238169699Skan  old_decl = lookup_name_in_scope (DECL_NAME (decl1), current_scope);
6239169699Skan  if (old_decl && TREE_CODE (old_decl) != FUNCTION_DECL)
6240169699Skan    old_decl = 0;
6241169699Skan  current_function_prototype_locus = UNKNOWN_LOCATION;
6242169699Skan  current_function_prototype_built_in = false;
6243169699Skan  current_function_prototype_arg_types = NULL_TREE;
6244169699Skan  if (TYPE_ARG_TYPES (TREE_TYPE (decl1)) == 0)
624518334Speter    {
6246169699Skan      if (old_decl != 0 && TREE_CODE (TREE_TYPE (old_decl)) == FUNCTION_TYPE
6247169699Skan	  && comptypes (TREE_TYPE (TREE_TYPE (decl1)),
6248169699Skan			TREE_TYPE (TREE_TYPE (old_decl))))
6249169699Skan	{
6250169699Skan	  TREE_TYPE (decl1) = composite_type (TREE_TYPE (old_decl),
6251169699Skan					      TREE_TYPE (decl1));
6252169699Skan	  current_function_prototype_locus = DECL_SOURCE_LOCATION (old_decl);
6253169699Skan	  current_function_prototype_built_in
6254169699Skan	    = C_DECL_BUILTIN_PROTOTYPE (old_decl);
6255169699Skan	  current_function_prototype_arg_types
6256169699Skan	    = TYPE_ARG_TYPES (TREE_TYPE (decl1));
6257169699Skan	}
6258169699Skan      if (TREE_PUBLIC (decl1))
6259169699Skan	{
6260169699Skan	  /* If there is an external prototype declaration of this
6261169699Skan	     function, record its location but do not copy information
6262169699Skan	     to this decl.  This may be an invisible declaration
6263169699Skan	     (built-in or in a scope which has finished) or simply
6264169699Skan	     have more refined argument types than any declaration
6265169699Skan	     found above.  */
6266169699Skan	  struct c_binding *b;
6267169699Skan	  for (b = I_SYMBOL_BINDING (DECL_NAME (decl1)); b; b = b->shadowed)
6268169699Skan	    if (B_IN_SCOPE (b, external_scope))
6269169699Skan	      break;
6270169699Skan	  if (b)
6271169699Skan	    {
6272169699Skan	      tree ext_decl, ext_type;
6273169699Skan	      ext_decl = b->decl;
6274169699Skan	      ext_type = b->type ? b->type : TREE_TYPE (ext_decl);
6275169699Skan	      if (TREE_CODE (ext_type) == FUNCTION_TYPE
6276169699Skan		  && comptypes (TREE_TYPE (TREE_TYPE (decl1)),
6277169699Skan				TREE_TYPE (ext_type)))
6278169699Skan		{
6279169699Skan		  current_function_prototype_locus
6280169699Skan		    = DECL_SOURCE_LOCATION (ext_decl);
6281169699Skan		  current_function_prototype_built_in
6282169699Skan		    = C_DECL_BUILTIN_PROTOTYPE (ext_decl);
6283169699Skan		  current_function_prototype_arg_types
6284169699Skan		    = TYPE_ARG_TYPES (ext_type);
6285169699Skan		}
6286169699Skan	    }
6287169699Skan	}
628818334Speter    }
628918334Speter
629018334Speter  /* Optionally warn of old-fashioned def with no previous prototype.  */
629118334Speter  if (warn_strict_prototypes
6292169699Skan      && old_decl != error_mark_node
629318334Speter      && TYPE_ARG_TYPES (TREE_TYPE (decl1)) == 0
6294132730Skan      && C_DECL_ISNT_PROTOTYPE (old_decl))
6295169699Skan    warning (OPT_Wstrict_prototypes,
6296169699Skan	     "function declaration isn%'t a prototype");
629718334Speter  /* Optionally warn of any global def with no previous prototype.  */
629818334Speter  else if (warn_missing_prototypes
6299169699Skan	   && old_decl != error_mark_node
630018334Speter	   && TREE_PUBLIC (decl1)
6301169699Skan	   && !MAIN_NAME_P (DECL_NAME (decl1))
6302132730Skan	   && C_DECL_ISNT_PROTOTYPE (old_decl))
6303169699Skan    warning (OPT_Wmissing_prototypes, "no previous prototype for %q+D", decl1);
630418334Speter  /* Optionally warn of any def with no previous prototype
630518334Speter     if the function has already been used.  */
630618334Speter  else if (warn_missing_prototypes
6307169699Skan	   && old_decl != 0
6308169699Skan	   && old_decl != error_mark_node
6309169699Skan	   && TREE_USED (old_decl)
631018334Speter	   && TYPE_ARG_TYPES (TREE_TYPE (old_decl)) == 0)
6311169699Skan    warning (OPT_Wmissing_prototypes,
6312169699Skan	     "%q+D was used with no prototype before its definition", decl1);
631318334Speter  /* Optionally warn of any global def with no previous declaration.  */
631418334Speter  else if (warn_missing_declarations
631518334Speter	   && TREE_PUBLIC (decl1)
631618334Speter	   && old_decl == 0
6317169699Skan	   && !MAIN_NAME_P (DECL_NAME (decl1)))
6318169699Skan    warning (OPT_Wmissing_declarations, "no previous declaration for %q+D",
6319169699Skan	     decl1);
632018334Speter  /* Optionally warn of any def with no previous declaration
632118334Speter     if the function has already been used.  */
632218334Speter  else if (warn_missing_declarations
6323169699Skan	   && old_decl != 0
6324169699Skan	   && old_decl != error_mark_node
6325169699Skan	   && TREE_USED (old_decl)
6326132730Skan	   && C_DECL_IMPLICIT (old_decl))
6327169699Skan    warning (OPT_Wmissing_declarations,
6328169699Skan	     "%q+D was used with no declaration before its definition", decl1);
632918334Speter
633018334Speter  /* This function exists in static storage.
633118334Speter     (This does not mean `static' in the C sense!)  */
633218334Speter  TREE_STATIC (decl1) = 1;
633318334Speter
633418334Speter  /* A nested function is not global.  */
633518334Speter  if (current_function_decl != 0)
633618334Speter    TREE_PUBLIC (decl1) = 0;
633718334Speter
6338132730Skan  /* This is the earliest point at which we might know the assembler
6339132730Skan     name of the function.  Thus, if it's set before this, die horribly.  */
6340169699Skan  gcc_assert (!DECL_ASSEMBLER_NAME_SET_P (decl1));
6341132730Skan
6342132730Skan  /* If #pragma weak was used, mark the decl weak now.  */
6343169699Skan  if (current_scope == file_scope)
6344132730Skan    maybe_apply_pragma_weak (decl1);
6345132730Skan
634690075Sobrien  /* Warn for unlikely, improbable, or stupid declarations of `main'.  */
634790075Sobrien  if (warn_main > 0 && MAIN_NAME_P (DECL_NAME (decl1)))
634850397Sobrien    {
634950397Sobrien      tree args;
635050397Sobrien      int argct = 0;
635150397Sobrien
635250397Sobrien      if (TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (decl1)))
635390075Sobrien	  != integer_type_node)
6354169699Skan	pedwarn ("return type of %q+D is not %<int%>", decl1);
635550397Sobrien
635650397Sobrien      for (args = TYPE_ARG_TYPES (TREE_TYPE (decl1)); args;
635750397Sobrien	   args = TREE_CHAIN (args))
635850397Sobrien	{
635950397Sobrien	  tree type = args ? TREE_VALUE (args) : 0;
636050397Sobrien
636150397Sobrien	  if (type == void_type_node)
636250397Sobrien	    break;
636350397Sobrien
636450397Sobrien	  ++argct;
636550397Sobrien	  switch (argct)
636650397Sobrien	    {
636750397Sobrien	    case 1:
636850397Sobrien	      if (TYPE_MAIN_VARIANT (type) != integer_type_node)
6369169699Skan		pedwarn ("first argument of %q+D should be %<int%>", decl1);
637050397Sobrien	      break;
637150397Sobrien
637250397Sobrien	    case 2:
637350397Sobrien	      if (TREE_CODE (type) != POINTER_TYPE
637450397Sobrien		  || TREE_CODE (TREE_TYPE (type)) != POINTER_TYPE
637550397Sobrien		  || (TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (type)))
637650397Sobrien		      != char_type_node))
6377169699Skan		pedwarn ("second argument of %q+D should be %<char **%>",
6378169699Skan			 decl1);
637950397Sobrien	      break;
638050397Sobrien
638150397Sobrien	    case 3:
638250397Sobrien	      if (TREE_CODE (type) != POINTER_TYPE
638350397Sobrien		  || TREE_CODE (TREE_TYPE (type)) != POINTER_TYPE
638450397Sobrien		  || (TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (type)))
638550397Sobrien		      != char_type_node))
6386169699Skan		pedwarn ("third argument of %q+D should probably be "
6387169699Skan			 "%<char **%>", decl1);
638850397Sobrien	      break;
638950397Sobrien	    }
639050397Sobrien	}
639150397Sobrien
639250397Sobrien      /* It is intentional that this message does not mention the third
639390075Sobrien	 argument because it's only mentioned in an appendix of the
639490075Sobrien	 standard.  */
639550397Sobrien      if (argct > 0 && (argct < 2 || argct > 3))
6396169699Skan	pedwarn ("%q+D takes only zero or two arguments", decl1);
639750397Sobrien
6398169699Skan      if (!TREE_PUBLIC (decl1))
6399169699Skan	pedwarn ("%q+D is normally a non-static function", decl1);
640050397Sobrien    }
640150397Sobrien
640218334Speter  /* Record the decl so that the function name is defined.
640318334Speter     If we already have a decl for this name, and it is a FUNCTION_DECL,
640418334Speter     use the old decl.  */
640518334Speter
640618334Speter  current_function_decl = pushdecl (decl1);
640718334Speter
6408169699Skan  push_scope ();
6409132730Skan  declare_parm_level ();
641018334Speter
641118334Speter  restype = TREE_TYPE (TREE_TYPE (current_function_decl));
641218334Speter  /* Promote the value to int before returning it.  */
641390075Sobrien  if (c_promoting_integer_type_p (restype))
641418334Speter    {
6415117421Skan      /* It retains unsignedness if not really getting wider.  */
6416169699Skan      if (TYPE_UNSIGNED (restype)
6417117421Skan	  && (TYPE_PRECISION (restype)
6418117421Skan		  == TYPE_PRECISION (integer_type_node)))
641918334Speter	restype = unsigned_type_node;
642018334Speter      else
642118334Speter	restype = integer_type_node;
642218334Speter    }
642318334Speter
6424169699Skan  resdecl = build_decl (RESULT_DECL, NULL_TREE, restype);
6425169699Skan  DECL_ARTIFICIAL (resdecl) = 1;
6426169699Skan  DECL_IGNORED_P (resdecl) = 1;
6427169699Skan  DECL_RESULT (current_function_decl) = resdecl;
642818334Speter
642990075Sobrien  start_fname_decls ();
6430132730Skan
643118334Speter  return 1;
643218334Speter}
643318334Speter
6434132730Skan/* Subroutine of store_parm_decls which handles new-style function
6435132730Skan   definitions (prototype format). The parms already have decls, so we
6436132730Skan   need only record them as in effect and complain if any redundant
6437132730Skan   old-style parm decls were written.  */
6438132730Skanstatic void
6439169699Skanstore_parm_decls_newstyle (tree fndecl, const struct c_arg_info *arg_info)
644018334Speter{
6441169699Skan  tree decl;
644218334Speter
6443169699Skan  if (current_scope->bindings)
6444132730Skan    {
6445132730Skan      error ("%Jold-style parameter declarations in prototyped "
6446132730Skan	     "function definition", fndecl);
644718334Speter
6448132730Skan      /* Get rid of the old-style declarations.  */
6449169699Skan      pop_scope ();
6450169699Skan      push_scope ();
6451132730Skan    }
6452169699Skan  /* Don't issue this warning for nested functions, and don't issue this
6453169699Skan     warning if we got here because ARG_INFO_TYPES was error_mark_node
6454169699Skan     (this happens when a function definition has just an ellipsis in
6455169699Skan     its parameter list).  */
6456169699Skan  else if (!in_system_header && !current_function_scope
6457169699Skan	   && arg_info->types != error_mark_node)
6458169699Skan    warning (OPT_Wtraditional,
6459169699Skan	     "%Jtraditional C rejects ISO C style function definitions",
6460169699Skan	     fndecl);
646118334Speter
6462132730Skan  /* Now make all the parameter declarations visible in the function body.
6463132730Skan     We can bypass most of the grunt work of pushdecl.  */
6464169699Skan  for (decl = arg_info->parms; decl; decl = TREE_CHAIN (decl))
6465132730Skan    {
6466132730Skan      DECL_CONTEXT (decl) = current_function_decl;
6467169699Skan      if (DECL_NAME (decl))
6468132730Skan	{
6469169699Skan	  bind (DECL_NAME (decl), decl, current_scope,
6470169699Skan		/*invisible=*/false, /*nested=*/false);
6471169699Skan	  if (!TREE_USED (decl))
6472169699Skan	    warn_if_shadowing (decl);
6473132730Skan	}
6474169699Skan      else
6475169699Skan	error ("%Jparameter name omitted", decl);
6476132730Skan    }
647718334Speter
6478132730Skan  /* Record the parameter list in the function declaration.  */
6479169699Skan  DECL_ARGUMENTS (fndecl) = arg_info->parms;
648018334Speter
6481132730Skan  /* Now make all the ancillary declarations visible, likewise.  */
6482169699Skan  for (decl = arg_info->others; decl; decl = TREE_CHAIN (decl))
6483132730Skan    {
6484132730Skan      DECL_CONTEXT (decl) = current_function_decl;
6485169699Skan      if (DECL_NAME (decl))
6486169699Skan	bind (DECL_NAME (decl), decl, current_scope,
6487169699Skan	      /*invisible=*/false, /*nested=*/false);
6488132730Skan    }
648990075Sobrien
6490132730Skan  /* And all the tag declarations.  */
6491169699Skan  for (decl = arg_info->tags; decl; decl = TREE_CHAIN (decl))
6492132730Skan    if (TREE_PURPOSE (decl))
6493169699Skan      bind (TREE_PURPOSE (decl), TREE_VALUE (decl), current_scope,
6494169699Skan	    /*invisible=*/false, /*nested=*/false);
6495132730Skan}
649618334Speter
6497132730Skan/* Subroutine of store_parm_decls which handles old-style function
6498132730Skan   definitions (separate parameter list and declarations).  */
649990075Sobrien
6500132730Skanstatic void
6501169699Skanstore_parm_decls_oldstyle (tree fndecl, const struct c_arg_info *arg_info)
6502132730Skan{
6503169699Skan  struct c_binding *b;
6504132730Skan  tree parm, decl, last;
6505169699Skan  tree parmids = arg_info->parms;
6506169699Skan  struct pointer_set_t *seen_args = pointer_set_create ();
650790075Sobrien
6508169699Skan  if (!in_system_header)
6509169699Skan    warning (OPT_Wold_style_definition, "%Jold-style function definition",
6510169699Skan	     fndecl);
651118334Speter
6512132730Skan  /* Match each formal parameter name with its declaration.  Save each
6513132730Skan     decl in the appropriate TREE_PURPOSE slot of the parmids chain.  */
6514132730Skan  for (parm = parmids; parm; parm = TREE_CHAIN (parm))
6515132730Skan    {
6516132730Skan      if (TREE_VALUE (parm) == 0)
651718334Speter	{
6518132730Skan	  error ("%Jparameter name missing from parameter list", fndecl);
6519132730Skan	  TREE_PURPOSE (parm) = 0;
6520132730Skan	  continue;
652118334Speter	}
652218334Speter
6523169699Skan      b = I_SYMBOL_BINDING (TREE_VALUE (parm));
6524169699Skan      if (b && B_IN_CURRENT_SCOPE (b))
652518334Speter	{
6526169699Skan	  decl = b->decl;
6527132730Skan	  /* If we got something other than a PARM_DECL it is an error.  */
6528132730Skan	  if (TREE_CODE (decl) != PARM_DECL)
6529169699Skan	    error ("%q+D declared as a non-parameter", decl);
6530132730Skan	  /* If the declaration is already marked, we have a duplicate
6531132730Skan	     name.  Complain and ignore the duplicate.  */
6532169699Skan	  else if (pointer_set_contains (seen_args, decl))
653318334Speter	    {
6534169699Skan	      error ("multiple parameters named %q+D", decl);
6535132730Skan	      TREE_PURPOSE (parm) = 0;
6536132730Skan	      continue;
653718334Speter	    }
6538132730Skan	  /* If the declaration says "void", complain and turn it into
6539132730Skan	     an int.  */
6540132730Skan	  else if (VOID_TYPE_P (TREE_TYPE (decl)))
654118334Speter	    {
6542169699Skan	      error ("parameter %q+D declared with void type", decl);
6543132730Skan	      TREE_TYPE (decl) = integer_type_node;
6544132730Skan	      DECL_ARG_TYPE (decl) = integer_type_node;
6545132730Skan	      layout_decl (decl, 0);
654618334Speter	    }
6547169699Skan	  warn_if_shadowing (decl);
654818334Speter	}
6549132730Skan      /* If no declaration found, default to int.  */
6550132730Skan      else
655118334Speter	{
6552132730Skan	  decl = build_decl (PARM_DECL, TREE_VALUE (parm), integer_type_node);
6553132730Skan	  DECL_ARG_TYPE (decl) = TREE_TYPE (decl);
6554132730Skan	  DECL_SOURCE_LOCATION (decl) = DECL_SOURCE_LOCATION (fndecl);
6555132730Skan	  pushdecl (decl);
6556169699Skan	  warn_if_shadowing (decl);
655718334Speter
6558132730Skan	  if (flag_isoc99)
6559169699Skan	    pedwarn ("type of %q+D defaults to %<int%>", decl);
6560132730Skan	  else if (extra_warnings)
6561169699Skan	    warning (OPT_Wextra, "type of %q+D defaults to %<int%>", decl);
656218334Speter	}
656318334Speter
6564132730Skan      TREE_PURPOSE (parm) = decl;
6565169699Skan      pointer_set_insert (seen_args, decl);
656618334Speter    }
656718334Speter
6568132730Skan  /* Now examine the parms chain for incomplete declarations
6569132730Skan     and declarations with no corresponding names.  */
657018334Speter
6571169699Skan  for (b = current_scope->bindings; b; b = b->prev)
6572132730Skan    {
6573169699Skan      parm = b->decl;
6574169699Skan      if (TREE_CODE (parm) != PARM_DECL)
6575169699Skan	continue;
6576169699Skan
6577169699Skan      if (TREE_TYPE (parm) != error_mark_node
6578169699Skan	  && !COMPLETE_TYPE_P (TREE_TYPE (parm)))
6579132730Skan	{
6580169699Skan	  error ("parameter %q+D has incomplete type", parm);
6581132730Skan	  TREE_TYPE (parm) = error_mark_node;
6582132730Skan	}
658318334Speter
6584169699Skan      if (!pointer_set_contains (seen_args, parm))
658518334Speter	{
6586169699Skan	  error ("declaration for parameter %q+D but no such parameter", parm);
658718334Speter
6588132730Skan	  /* Pretend the parameter was not missing.
6589132730Skan	     This gets us to a standard state and minimizes
6590132730Skan	     further error messages.  */
6591132730Skan	  parmids = chainon (parmids, tree_cons (parm, 0, 0));
6592132730Skan	}
6593132730Skan    }
659418334Speter
6595132730Skan  /* Chain the declarations together in the order of the list of
6596132730Skan     names.  Store that chain in the function decl, replacing the
6597132730Skan     list of names.  Update the current scope to match.  */
6598132730Skan  DECL_ARGUMENTS (fndecl) = 0;
659918334Speter
6600132730Skan  for (parm = parmids; parm; parm = TREE_CHAIN (parm))
6601132730Skan    if (TREE_PURPOSE (parm))
6602132730Skan      break;
6603132730Skan  if (parm && TREE_PURPOSE (parm))
6604132730Skan    {
6605132730Skan      last = TREE_PURPOSE (parm);
6606132730Skan      DECL_ARGUMENTS (fndecl) = last;
660718334Speter
6608132730Skan      for (parm = TREE_CHAIN (parm); parm; parm = TREE_CHAIN (parm))
6609132730Skan	if (TREE_PURPOSE (parm))
6610132730Skan	  {
6611132730Skan	    TREE_CHAIN (last) = TREE_PURPOSE (parm);
6612132730Skan	    last = TREE_PURPOSE (parm);
6613132730Skan	  }
6614132730Skan      TREE_CHAIN (last) = 0;
6615132730Skan    }
661618334Speter
6617169699Skan  pointer_set_destroy (seen_args);
6618169699Skan
6619132730Skan  /* If there was a previous prototype,
6620132730Skan     set the DECL_ARG_TYPE of each argument according to
6621132730Skan     the type previously specified, and report any mismatches.  */
662218334Speter
6623169699Skan  if (current_function_prototype_arg_types)
6624132730Skan    {
6625132730Skan      tree type;
6626132730Skan      for (parm = DECL_ARGUMENTS (fndecl),
6627169699Skan	     type = current_function_prototype_arg_types;
6628132730Skan	   parm || (type && (TYPE_MAIN_VARIANT (TREE_VALUE (type))
6629132730Skan			     != void_type_node));
6630132730Skan	   parm = TREE_CHAIN (parm), type = TREE_CHAIN (type))
663118334Speter	{
6632132730Skan	  if (parm == 0 || type == 0
6633132730Skan	      || TYPE_MAIN_VARIANT (TREE_VALUE (type)) == void_type_node)
663418334Speter	    {
6635169699Skan	      if (current_function_prototype_built_in)
6636169699Skan		warning (0, "number of arguments doesn%'t match "
6637169699Skan			 "built-in prototype");
6638169699Skan	      else
6639169699Skan		{
6640169699Skan		  error ("number of arguments doesn%'t match prototype");
6641169699Skan		  error ("%Hprototype declaration",
6642169699Skan			 &current_function_prototype_locus);
6643169699Skan		}
6644132730Skan	      break;
664518334Speter	    }
6646132730Skan	  /* Type for passing arg must be consistent with that
6647132730Skan	     declared for the arg.  ISO C says we take the unqualified
6648132730Skan	     type for parameters declared with qualified type.  */
6649169699Skan	  if (!comptypes (TYPE_MAIN_VARIANT (DECL_ARG_TYPE (parm)),
6650169699Skan			  TYPE_MAIN_VARIANT (TREE_VALUE (type))))
665118334Speter	    {
6652132730Skan	      if (TYPE_MAIN_VARIANT (TREE_TYPE (parm))
6653132730Skan		  == TYPE_MAIN_VARIANT (TREE_VALUE (type)))
665418334Speter		{
6655132730Skan		  /* Adjust argument to match prototype.  E.g. a previous
6656132730Skan		     `int foo(float);' prototype causes
6657132730Skan		     `int foo(x) float x; {...}' to be treated like
6658132730Skan		     `int foo(float x) {...}'.  This is particularly
6659132730Skan		     useful for argument types like uid_t.  */
6660132730Skan		  DECL_ARG_TYPE (parm) = TREE_TYPE (parm);
666190075Sobrien
6662132730Skan		  if (targetm.calls.promote_prototypes (TREE_TYPE (current_function_decl))
6663132730Skan		      && INTEGRAL_TYPE_P (TREE_TYPE (parm))
6664132730Skan		      && TYPE_PRECISION (TREE_TYPE (parm))
6665132730Skan		      < TYPE_PRECISION (integer_type_node))
6666132730Skan		    DECL_ARG_TYPE (parm) = integer_type_node;
666790075Sobrien
6668132730Skan		  if (pedantic)
666918334Speter		    {
6670169699Skan		      /* ??? Is it possible to get here with a
6671169699Skan			 built-in prototype or will it always have
6672169699Skan			 been diagnosed as conflicting with an
6673169699Skan			 old-style definition and discarded?  */
6674169699Skan		      if (current_function_prototype_built_in)
6675169699Skan			warning (0, "promoted argument %qD "
6676169699Skan				 "doesn%'t match built-in prototype", parm);
6677169699Skan		      else
6678169699Skan			{
6679169699Skan			  pedwarn ("promoted argument %qD "
6680169699Skan				   "doesn%'t match prototype", parm);
6681169699Skan			  pedwarn ("%Hprototype declaration",
6682169699Skan				   &current_function_prototype_locus);
6683169699Skan			}
668418334Speter		    }
668518334Speter		}
6686132730Skan	      else
6687132730Skan		{
6688169699Skan		  if (current_function_prototype_built_in)
6689169699Skan		    warning (0, "argument %qD doesn%'t match "
6690169699Skan			     "built-in prototype", parm);
6691169699Skan		  else
6692169699Skan		    {
6693169699Skan		      error ("argument %qD doesn%'t match prototype", parm);
6694169699Skan		      error ("%Hprototype declaration",
6695169699Skan			     &current_function_prototype_locus);
6696169699Skan		    }
6697132730Skan		}
669818334Speter	    }
669918334Speter	}
6700132730Skan      TYPE_ACTUAL_ARG_TYPES (TREE_TYPE (fndecl)) = 0;
6701132730Skan    }
670218334Speter
6703132730Skan  /* Otherwise, create a prototype that would match.  */
670418334Speter
6705132730Skan  else
6706132730Skan    {
6707132730Skan      tree actual = 0, last = 0, type;
6708132730Skan
6709132730Skan      for (parm = DECL_ARGUMENTS (fndecl); parm; parm = TREE_CHAIN (parm))
671018334Speter	{
6711132730Skan	  type = tree_cons (NULL_TREE, DECL_ARG_TYPE (parm), NULL_TREE);
671218334Speter	  if (last)
671318334Speter	    TREE_CHAIN (last) = type;
671418334Speter	  else
671518334Speter	    actual = type;
6716132730Skan	  last = type;
6717132730Skan	}
6718132730Skan      type = tree_cons (NULL_TREE, void_type_node, NULL_TREE);
6719132730Skan      if (last)
6720132730Skan	TREE_CHAIN (last) = type;
6721132730Skan      else
6722132730Skan	actual = type;
672318334Speter
6724132730Skan      /* We are going to assign a new value for the TYPE_ACTUAL_ARG_TYPES
6725132730Skan	 of the type of this function, but we need to avoid having this
6726132730Skan	 affect the types of other similarly-typed functions, so we must
6727132730Skan	 first force the generation of an identical (but separate) type
6728132730Skan	 node for the relevant function type.  The new node we create
6729132730Skan	 will be a variant of the main variant of the original function
6730132730Skan	 type.  */
673118334Speter
6732169699Skan      TREE_TYPE (fndecl) = build_variant_type_copy (TREE_TYPE (fndecl));
673318334Speter
6734132730Skan      TYPE_ACTUAL_ARG_TYPES (TREE_TYPE (fndecl)) = actual;
6735132730Skan    }
6736132730Skan}
673718334Speter
6738169699Skan/* Store parameter declarations passed in ARG_INFO into the current
6739169699Skan   function declaration.  */
6740169699Skan
6741169699Skanvoid
6742169699Skanstore_parm_decls_from (struct c_arg_info *arg_info)
6743169699Skan{
6744169699Skan  current_function_arg_info = arg_info;
6745169699Skan  store_parm_decls ();
6746169699Skan}
6747169699Skan
6748132730Skan/* Store the parameter declarations into the current function declaration.
6749132730Skan   This is called after parsing the parameter declarations, before
6750132730Skan   digesting the body of the function.
675118334Speter
6752132730Skan   For an old-style definition, construct a prototype out of the old-style
6753132730Skan   parameter declarations and inject it into the function's type.  */
675418334Speter
6755132730Skanvoid
6756132730Skanstore_parm_decls (void)
6757132730Skan{
6758132730Skan  tree fndecl = current_function_decl;
6759169699Skan  bool proto;
676018334Speter
6761169699Skan  /* The argument information block for FNDECL.  */
6762169699Skan  struct c_arg_info *arg_info = current_function_arg_info;
6763169699Skan  current_function_arg_info = 0;
676418334Speter
6765169699Skan  /* True if this definition is written with a prototype.  Note:
6766169699Skan     despite C99 6.7.5.3p14, we can *not* treat an empty argument
6767169699Skan     list in a function definition as equivalent to (void) -- an
6768169699Skan     empty argument list specifies the function has no parameters,
6769169699Skan     but only (void) sets up a prototype for future calls.  */
6770169699Skan  proto = arg_info->types != 0;
6771169699Skan
6772169699Skan  if (proto)
6773169699Skan    store_parm_decls_newstyle (fndecl, arg_info);
6774132730Skan  else
6775169699Skan    store_parm_decls_oldstyle (fndecl, arg_info);
6776132730Skan
6777169699Skan  /* The next call to push_scope will be a function body.  */
6778132730Skan
6779132730Skan  next_is_function_body = true;
6780132730Skan
678118334Speter  /* Write a record describing this function definition to the prototypes
678218334Speter     file (if requested).  */
678318334Speter
6784169699Skan  gen_aux_info_record (fndecl, 1, 0, proto);
678518334Speter
678618334Speter  /* Initialize the RTL code for the function.  */
6787132730Skan  allocate_struct_function (fndecl);
678818334Speter
678990075Sobrien  /* Begin the statement tree for this function.  */
6790169699Skan  DECL_SAVED_TREE (fndecl) = push_stmt_list ();
679118334Speter
6792169699Skan  /* ??? Insert the contents of the pending sizes list into the function
6793169699Skan     to be evaluated.  The only reason left to have this is
6794169699Skan	void foo(int n, int array[n++])
6795169699Skan     because we throw away the array type in favor of a pointer type, and
6796169699Skan     thus won't naturally see the SAVE_EXPR containing the increment.  All
6797169699Skan     other pending sizes would be handled by gimplify_parameters.  */
6798169699Skan  {
6799169699Skan    tree t;
6800169699Skan    for (t = nreverse (get_pending_sizes ()); t ; t = TREE_CHAIN (t))
6801169699Skan      add_stmt (TREE_VALUE (t));
6802169699Skan  }
680318334Speter
680490075Sobrien  /* Even though we're inside a function body, we still don't want to
680590075Sobrien     call expand_expr to calculate the size of a variable-sized array.
680690075Sobrien     We haven't necessarily assigned RTL to all variables yet, so it's
680790075Sobrien     not safe to try to expand expressions involving them.  */
680890075Sobrien  cfun->x_dont_save_pending_sizes_p = 1;
680918334Speter}
681018334Speter
6811169699Skan/* Emit diagnostics that require gimple input for detection.  Operate on
6812169699Skan   FNDECL and all its nested functions.  */
6813169699Skan
6814169699Skanstatic void
6815169699Skanc_gimple_diagnostics_recursively (tree fndecl)
6816169699Skan{
6817169699Skan  struct cgraph_node *cgn;
6818169699Skan
6819169699Skan  /* Handle attribute((warn_unused_result)).  Relies on gimple input.  */
6820169699Skan  c_warn_unused_result (&DECL_SAVED_TREE (fndecl));
6821169699Skan
6822169699Skan  /* Notice when OpenMP structured block constraints are violated.  */
6823169699Skan  if (flag_openmp)
6824169699Skan    diagnose_omp_structured_block_errors (fndecl);
6825169699Skan
6826169699Skan  /* Finalize all nested functions now.  */
6827169699Skan  cgn = cgraph_node (fndecl);
6828169699Skan  for (cgn = cgn->nested; cgn ; cgn = cgn->next_nested)
6829169699Skan    c_gimple_diagnostics_recursively (cgn->decl);
6830169699Skan}
6831169699Skan
683218334Speter/* Finish up a function declaration and compile that function
683318334Speter   all the way to assembler language output.  The free the storage
683418334Speter   for the function definition.
683518334Speter
6836132730Skan   This is called after parsing the body of the function definition.  */
683718334Speter
683818334Spetervoid
6839132730Skanfinish_function (void)
684018334Speter{
684190075Sobrien  tree fndecl = current_function_decl;
684218334Speter
6843169699Skan  label_context_stack_se = label_context_stack_se->next;
6844169699Skan  label_context_stack_vm = label_context_stack_vm->next;
684518334Speter
6846132730Skan  if (TREE_CODE (fndecl) == FUNCTION_DECL
6847132730Skan      && targetm.calls.promote_prototypes (TREE_TYPE (fndecl)))
6848132730Skan    {
6849132730Skan      tree args = DECL_ARGUMENTS (fndecl);
6850132730Skan      for (; args; args = TREE_CHAIN (args))
6851169699Skan	{
6852169699Skan	  tree type = TREE_TYPE (args);
6853169699Skan	  if (INTEGRAL_TYPE_P (type)
6854169699Skan	      && TYPE_PRECISION (type) < TYPE_PRECISION (integer_type_node))
6855169699Skan	    DECL_ARG_TYPE (args) = integer_type_node;
6856169699Skan	}
6857132730Skan    }
6858132730Skan
6859132730Skan  if (DECL_INITIAL (fndecl) && DECL_INITIAL (fndecl) != error_mark_node)
6860132730Skan    BLOCK_SUPERCONTEXT (DECL_INITIAL (fndecl)) = fndecl;
6861132730Skan
686218334Speter  /* Must mark the RESULT_DECL as being in this function.  */
686318334Speter
6864132730Skan  if (DECL_RESULT (fndecl) && DECL_RESULT (fndecl) != error_mark_node)
6865132730Skan    DECL_CONTEXT (DECL_RESULT (fndecl)) = fndecl;
686618334Speter
686790075Sobrien  if (MAIN_NAME_P (DECL_NAME (fndecl)) && flag_hosted)
686818334Speter    {
686918334Speter      if (TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (fndecl)))
687018334Speter	  != integer_type_node)
687150397Sobrien	{
687252284Sobrien	  /* If warn_main is 1 (-Wmain) or 2 (-Wall), we have already warned.
687390075Sobrien	     If warn_main is -1 (-Wno-main) we don't want to be warned.  */
6874132730Skan	  if (!warn_main)
6875169699Skan	    pedwarn ("return type of %q+D is not %<int%>", fndecl);
687650397Sobrien	}
687718334Speter      else
687818334Speter	{
6879169699Skan	  if (flag_isoc99)
6880169699Skan	    {
6881169699Skan	      tree stmt = c_finish_return (integer_zero_node);
6882169699Skan#ifdef USE_MAPPED_LOCATION
6883169699Skan	      /* Hack.  We don't want the middle-end to warn that this return
6884169699Skan		 is unreachable, so we mark its location as special.  Using
6885169699Skan		 UNKNOWN_LOCATION has the problem that it gets clobbered in
6886169699Skan		 annotate_one_with_locus.  A cleaner solution might be to
6887169699Skan		 ensure ! should_carry_locus_p (stmt), but that needs a flag.
6888169699Skan	      */
6889169699Skan	      SET_EXPR_LOCATION (stmt, BUILTINS_LOCATION);
689090075Sobrien#else
6891169699Skan	      /* Hack.  We don't want the middle-end to warn that this
6892169699Skan		 return is unreachable, so put the statement on the
6893169699Skan		 special line 0.  */
6894169699Skan	      annotate_with_file_line (stmt, input_filename, 0);
689550397Sobrien#endif
6896169699Skan	    }
689718334Speter	}
689818334Speter    }
6899132730Skan
6900169699Skan  /* Tie off the statement tree for this function.  */
6901169699Skan  DECL_SAVED_TREE (fndecl) = pop_stmt_list (DECL_SAVED_TREE (fndecl));
6902169699Skan
690390075Sobrien  finish_fname_decls ();
690418334Speter
690596263Sobrien  /* Complain if there's just no return statement.  */
690696263Sobrien  if (warn_return_type
690796263Sobrien      && TREE_CODE (TREE_TYPE (TREE_TYPE (fndecl))) != VOID_TYPE
690896263Sobrien      && !current_function_returns_value && !current_function_returns_null
6909169699Skan      /* Don't complain if we are no-return.  */
691096263Sobrien      && !current_function_returns_abnormally
691196263Sobrien      /* Don't warn for main().  */
691296263Sobrien      && !MAIN_NAME_P (DECL_NAME (fndecl))
691396263Sobrien      /* Or if they didn't actually specify a return type.  */
691496263Sobrien      && !C_FUNCTION_IMPLICIT_INT (fndecl)
691596263Sobrien      /* Normally, with -Wreturn-type, flow will complain.  Unless we're an
691696263Sobrien	 inline function, as we might never be compiled separately.  */
691796263Sobrien      && DECL_INLINE (fndecl))
6918169699Skan    {
6919169699Skan      warning (OPT_Wreturn_type,
6920169699Skan	       "no return statement in function returning non-void");
6921169699Skan      TREE_NO_WARNING (fndecl) = 1;
6922169699Skan    }
692396263Sobrien
6924132730Skan  /* With just -Wextra, complain only if function returns both with
6925122196Skan     and without a value.  */
6926122196Skan  if (extra_warnings
6927122196Skan      && current_function_returns_value
6928122196Skan      && current_function_returns_null)
6929169699Skan    warning (OPT_Wextra, "this function may return with or without a value");
6930122196Skan
6931169699Skan  /* Store the end of the function, so that we get good line number
6932169699Skan     info for the epilogue.  */
6933169699Skan  cfun->function_end_locus = input_location;
693490075Sobrien
6935169699Skan  /* If we don't have ctors/dtors sections, and this is a static
6936169699Skan     constructor or destructor, it must be recorded now.  */
6937169699Skan  if (DECL_STATIC_CONSTRUCTOR (fndecl)
6938169699Skan      && !targetm.have_ctors_dtors)
6939169699Skan    static_ctors = tree_cons (NULL_TREE, fndecl, static_ctors);
6940169699Skan  if (DECL_STATIC_DESTRUCTOR (fndecl)
6941169699Skan      && !targetm.have_ctors_dtors)
6942169699Skan    static_dtors = tree_cons (NULL_TREE, fndecl, static_dtors);
694390075Sobrien
6944169699Skan  /* Finalize the ELF visibility for the function.  */
6945169699Skan  c_determine_visibility (fndecl);
694690075Sobrien
6947169699Skan  /* Genericize before inlining.  Delay genericizing nested functions
6948169699Skan     until their parent function is genericized.  Since finalizing
6949169699Skan     requires GENERIC, delay that as well.  */
6950169699Skan
6951169699Skan  if (DECL_INITIAL (fndecl) && DECL_INITIAL (fndecl) != error_mark_node
6952169699Skan      && !undef_nested_function)
695390075Sobrien    {
6954169699Skan      if (!decl_function_context (fndecl))
6955132730Skan	{
6956169699Skan	  c_genericize (fndecl);
6957169699Skan	  c_gimple_diagnostics_recursively (fndecl);
695890075Sobrien
6959169699Skan	  /* ??? Objc emits functions after finalizing the compilation unit.
6960169699Skan	     This should be cleaned up later and this conditional removed.  */
6961169699Skan	  if (cgraph_global_info_ready)
6962169699Skan	    {
6963169699Skan	      c_expand_body (fndecl);
6964169699Skan	      return;
6965169699Skan	    }
696690075Sobrien
6967169699Skan	  cgraph_finalize_function (fndecl, false);
6968169699Skan	}
696918334Speter      else
6970169699Skan	{
6971169699Skan	  /* Register this function with cgraph just far enough to get it
6972169699Skan	    added to our parent's nested function list.  Handy, since the
6973169699Skan	    C front end doesn't have such a list.  */
6974169699Skan	  (void) cgraph_node (fndecl);
6975169699Skan	}
697618334Speter    }
697790075Sobrien
6978169699Skan  if (!decl_function_context (fndecl))
6979169699Skan    undef_nested_function = false;
6980169699Skan
6981169699Skan  /* We're leaving the context of this function, so zap cfun.
6982169699Skan     It's still in DECL_STRUCT_FUNCTION, and we'll restore it in
6983169699Skan     tree_rest_of_compilation.  */
6984169699Skan  cfun = NULL;
6985169699Skan  current_function_decl = NULL;
6986132730Skan}
698718334Speter
6988169699Skan/* Generate the RTL for the body of FNDECL.  */
6989117421Skan
6990132730Skanvoid
6991132730Skanc_expand_body (tree fndecl)
6992132730Skan{
6993132730Skan
6994169699Skan  if (!DECL_INITIAL (fndecl)
6995169699Skan      || DECL_INITIAL (fndecl) == error_mark_node)
6996169699Skan    return;
6997169699Skan
6998169699Skan  tree_rest_of_compilation (fndecl);
6999169699Skan
7000169699Skan  if (DECL_STATIC_CONSTRUCTOR (fndecl)
7001169699Skan      && targetm.have_ctors_dtors)
7002169699Skan    targetm.asm_out.constructor (XEXP (DECL_RTL (fndecl), 0),
7003169699Skan				 DEFAULT_INIT_PRIORITY);
7004169699Skan  if (DECL_STATIC_DESTRUCTOR (fndecl)
7005169699Skan      && targetm.have_ctors_dtors)
7006169699Skan    targetm.asm_out.destructor (XEXP (DECL_RTL (fndecl), 0),
7007169699Skan				DEFAULT_INIT_PRIORITY);
700890075Sobrien}
700990075Sobrien
701090075Sobrien/* Check the declarations given in a for-loop for satisfying the C99
7011169699Skan   constraints.  If exactly one such decl is found, return it.  */
7012169699Skan
7013169699Skantree
7014132730Skancheck_for_loop_decls (void)
701590075Sobrien{
7016169699Skan  struct c_binding *b;
7017169699Skan  tree one_decl = NULL_TREE;
7018169699Skan  int n_decls = 0;
701990075Sobrien
7020169699Skan
702190075Sobrien  if (!flag_isoc99)
702218334Speter    {
702390075Sobrien      /* If we get here, declarations have been used in a for loop without
702490075Sobrien	 the C99 for loop scope.  This doesn't make much sense, so don't
702590075Sobrien	 allow it.  */
7026169699Skan      error ("%<for%> loop initial declaration used outside C99 mode");
7027169699Skan      return NULL_TREE;
702818334Speter    }
702990075Sobrien  /* C99 subclause 6.8.5 paragraph 3:
703090075Sobrien
703190075Sobrien       [#3]  The  declaration  part  of  a for statement shall only
703290075Sobrien       declare identifiers for objects having storage class auto or
703390075Sobrien       register.
703490075Sobrien
703590075Sobrien     It isn't clear whether, in this sentence, "identifiers" binds to
703690075Sobrien     "shall only declare" or to "objects" - that is, whether all identifiers
703790075Sobrien     declared must be identifiers for objects, or whether the restriction
703890075Sobrien     only applies to those that are.  (A question on this in comp.std.c
703990075Sobrien     in November 2000 received no answer.)  We implement the strictest
704090075Sobrien     interpretation, to avoid creating an extension which later causes
704190075Sobrien     problems.  */
704290075Sobrien
7043169699Skan  for (b = current_scope->bindings; b; b = b->prev)
704490075Sobrien    {
7045169699Skan      tree id = b->id;
7046169699Skan      tree decl = b->decl;
7047132730Skan
7048169699Skan      if (!id)
7049169699Skan	continue;
7050169699Skan
7051169699Skan      switch (TREE_CODE (decl))
7052169699Skan	{
7053169699Skan	case VAR_DECL:
7054169699Skan	  if (TREE_STATIC (decl))
7055169699Skan	    error ("declaration of static variable %q+D in %<for%> loop "
7056169699Skan		   "initial declaration", decl);
7057169699Skan	  else if (DECL_EXTERNAL (decl))
7058169699Skan	    error ("declaration of %<extern%> variable %q+D in %<for%> loop "
7059169699Skan		   "initial declaration", decl);
7060169699Skan	  break;
7061169699Skan
7062169699Skan	case RECORD_TYPE:
7063169699Skan	  error ("%<struct %E%> declared in %<for%> loop initial declaration",
7064169699Skan		 id);
7065169699Skan	  break;
7066169699Skan	case UNION_TYPE:
7067169699Skan	  error ("%<union %E%> declared in %<for%> loop initial declaration",
7068169699Skan		 id);
7069169699Skan	  break;
7070169699Skan	case ENUMERAL_TYPE:
7071169699Skan	  error ("%<enum %E%> declared in %<for%> loop initial declaration",
7072169699Skan		 id);
7073169699Skan	  break;
7074169699Skan	default:
7075169699Skan	  error ("declaration of non-variable %q+D in %<for%> loop "
7076169699Skan		 "initial declaration", decl);
7077169699Skan	}
7078169699Skan
7079169699Skan      n_decls++;
7080169699Skan      one_decl = decl;
708190075Sobrien    }
708290075Sobrien
7083169699Skan  return n_decls == 1 ? one_decl : NULL_TREE;
708418334Speter}
708518334Speter
708618334Speter/* Save and reinitialize the variables
708718334Speter   used during compilation of a C function.  */
708818334Speter
708918334Spetervoid
7090132730Skanc_push_function_context (struct function *f)
709118334Speter{
7092117421Skan  struct language_function *p;
7093169699Skan  p = GGC_NEW (struct language_function);
7094117421Skan  f->language = p;
709518334Speter
709690075Sobrien  p->base.x_stmt_tree = c_stmt_tree;
7097169699Skan  p->x_break_label = c_break_label;
7098169699Skan  p->x_cont_label = c_cont_label;
7099169699Skan  p->x_switch_stack = c_switch_stack;
7100169699Skan  p->arg_info = current_function_arg_info;
710118334Speter  p->returns_value = current_function_returns_value;
710218334Speter  p->returns_null = current_function_returns_null;
710396263Sobrien  p->returns_abnormally = current_function_returns_abnormally;
710418334Speter  p->warn_about_return_type = warn_about_return_type;
710518334Speter}
710618334Speter
710718334Speter/* Restore the variables used during compilation of a C function.  */
710818334Speter
710918334Spetervoid
7110132730Skanc_pop_function_context (struct function *f)
711118334Speter{
7112117421Skan  struct language_function *p = f->language;
711318334Speter
7114169699Skan  if (DECL_STRUCT_FUNCTION (current_function_decl) == 0
711590075Sobrien      && DECL_SAVED_TREE (current_function_decl) == NULL_TREE)
711618334Speter    {
711718334Speter      /* Stop pointing to the local nodes about to be freed.  */
711818334Speter      /* But DECL_INITIAL must remain nonzero so we know this
711918334Speter	 was an actual function definition.  */
712018334Speter      DECL_INITIAL (current_function_decl) = error_mark_node;
712118334Speter      DECL_ARGUMENTS (current_function_decl) = 0;
712218334Speter    }
712318334Speter
712490075Sobrien  c_stmt_tree = p->base.x_stmt_tree;
7125169699Skan  c_break_label = p->x_break_label;
7126169699Skan  c_cont_label = p->x_cont_label;
7127169699Skan  c_switch_stack = p->x_switch_stack;
7128169699Skan  current_function_arg_info = p->arg_info;
712918334Speter  current_function_returns_value = p->returns_value;
713018334Speter  current_function_returns_null = p->returns_null;
713196263Sobrien  current_function_returns_abnormally = p->returns_abnormally;
713218334Speter  warn_about_return_type = p->warn_about_return_type;
713318334Speter
7134117421Skan  f->language = NULL;
713518334Speter}
713618334Speter
7137117421Skan/* Copy the DECL_LANG_SPECIFIC data associated with DECL.  */
713818334Speter
713918334Spetervoid
7140132730Skanc_dup_lang_specific_decl (tree decl)
714190075Sobrien{
714290075Sobrien  struct lang_decl *ld;
714390075Sobrien
714490075Sobrien  if (!DECL_LANG_SPECIFIC (decl))
714590075Sobrien    return;
714690075Sobrien
7147169699Skan  ld = GGC_NEW (struct lang_decl);
7148132730Skan  memcpy (ld, DECL_LANG_SPECIFIC (decl), sizeof (struct lang_decl));
714990075Sobrien  DECL_LANG_SPECIFIC (decl) = ld;
715090075Sobrien}
715190075Sobrien
715290075Sobrien/* The functions below are required for functionality of doing
715390075Sobrien   function at once processing in the C front end. Currently these
715490075Sobrien   functions are not called from anywhere in the C front end, but as
715590075Sobrien   these changes continue, that will change.  */
715690075Sobrien
715790075Sobrien/* Returns the stmt_tree (if any) to which statements are currently
715890075Sobrien   being added.  If there is no active statement-tree, NULL is
715990075Sobrien   returned.  */
716090075Sobrien
716190075Sobrienstmt_tree
7162132730Skancurrent_stmt_tree (void)
716390075Sobrien{
716490075Sobrien  return &c_stmt_tree;
716590075Sobrien}
716690075Sobrien
716790075Sobrien/* Nonzero if TYPE is an anonymous union or struct type.  Always 0 in
716890075Sobrien   C.  */
716990075Sobrien
717090075Sobrienint
7171169699Skananon_aggr_type_p (tree ARG_UNUSED (node))
717218334Speter{
717390075Sobrien  return 0;
717418334Speter}
717590075Sobrien
7176132730Skan/* Return the global value of T as a symbol.  */
717790075Sobrien
717890075Sobrientree
7179132730Skanidentifier_global_value	(tree t)
718090075Sobrien{
7181169699Skan  struct c_binding *b;
7182132730Skan
7183169699Skan  for (b = I_SYMBOL_BINDING (t); b; b = b->shadowed)
7184169699Skan    if (B_IN_FILE_SCOPE (b) || B_IN_EXTERNAL_SCOPE (b))
7185169699Skan      return b->decl;
7186132730Skan
7187132730Skan  return 0;
718890075Sobrien}
718990075Sobrien
719090075Sobrien/* Record a builtin type for C.  If NAME is non-NULL, it is the name used;
719190075Sobrien   otherwise the name is found in ridpointers from RID_INDEX.  */
719290075Sobrien
719390075Sobrienvoid
7194132730Skanrecord_builtin_type (enum rid rid_index, const char *name, tree type)
719590075Sobrien{
7196169699Skan  tree id, decl;
719790075Sobrien  if (name == 0)
719890075Sobrien    id = ridpointers[(int) rid_index];
719990075Sobrien  else
720090075Sobrien    id = get_identifier (name);
7201169699Skan  decl = build_decl (TYPE_DECL, id, type);
7202169699Skan  pushdecl (decl);
7203169699Skan  if (debug_hooks->type_decl)
7204169699Skan    debug_hooks->type_decl (decl, false);
720590075Sobrien}
720690075Sobrien
720790075Sobrien/* Build the void_list_node (void_type_node having been created).  */
720890075Sobrientree
7209132730Skanbuild_void_list_node (void)
721090075Sobrien{
721190075Sobrien  tree t = build_tree_list (NULL_TREE, void_type_node);
721290075Sobrien  return t;
721390075Sobrien}
7214117421Skan
7215169699Skan/* Return a c_parm structure with the given SPECS, ATTRS and DECLARATOR.  */
7216117421Skan
7217169699Skanstruct c_parm *
7218169699Skanbuild_c_parm (struct c_declspecs *specs, tree attrs,
7219169699Skan	      struct c_declarator *declarator)
7220169699Skan{
7221169699Skan  struct c_parm *ret = XOBNEW (&parser_obstack, struct c_parm);
7222169699Skan  ret->specs = specs;
7223169699Skan  ret->attrs = attrs;
7224169699Skan  ret->declarator = declarator;
7225169699Skan  return ret;
7226169699Skan}
7227117421Skan
7228169699Skan/* Return a declarator with nested attributes.  TARGET is the inner
7229169699Skan   declarator to which these attributes apply.  ATTRS are the
7230169699Skan   attributes.  */
7231169699Skan
7232169699Skanstruct c_declarator *
7233169699Skanbuild_attrs_declarator (tree attrs, struct c_declarator *target)
7234117421Skan{
7235169699Skan  struct c_declarator *ret = XOBNEW (&parser_obstack, struct c_declarator);
7236169699Skan  ret->kind = cdk_attrs;
7237169699Skan  ret->declarator = target;
7238169699Skan  ret->u.attrs = attrs;
7239169699Skan  return ret;
7240117421Skan}
7241117421Skan
7242169699Skan/* Return a declarator for a function with arguments specified by ARGS
7243169699Skan   and return type specified by TARGET.  */
7244132730Skan
7245169699Skanstruct c_declarator *
7246169699Skanbuild_function_declarator (struct c_arg_info *args,
7247169699Skan			   struct c_declarator *target)
7248132730Skan{
7249169699Skan  struct c_declarator *ret = XOBNEW (&parser_obstack, struct c_declarator);
7250169699Skan  ret->kind = cdk_function;
7251169699Skan  ret->declarator = target;
7252169699Skan  ret->u.arg_info = args;
7253169699Skan  return ret;
7254132730Skan}
7255132730Skan
7256169699Skan/* Return a declarator for the identifier IDENT (which may be
7257169699Skan   NULL_TREE for an abstract declarator).  */
7258132730Skan
7259169699Skanstruct c_declarator *
7260169699Skanbuild_id_declarator (tree ident)
7261132730Skan{
7262169699Skan  struct c_declarator *ret = XOBNEW (&parser_obstack, struct c_declarator);
7263169699Skan  ret->kind = cdk_id;
7264169699Skan  ret->declarator = 0;
7265169699Skan  ret->u.id = ident;
7266169699Skan  /* Default value - may get reset to a more precise location. */
7267169699Skan  ret->id_loc = input_location;
7268169699Skan  return ret;
7269132730Skan}
7270132730Skan
7271169699Skan/* Return something to represent absolute declarators containing a *.
7272169699Skan   TARGET is the absolute declarator that the * contains.
7273169699Skan   TYPE_QUALS_ATTRS is a structure for type qualifiers and attributes
7274169699Skan   to apply to the pointer type.  */
7275169699Skan
7276169699Skanstruct c_declarator *
7277169699Skanmake_pointer_declarator (struct c_declspecs *type_quals_attrs,
7278169699Skan			 struct c_declarator *target)
7279132730Skan{
7280169699Skan  tree attrs;
7281169699Skan  int quals = 0;
7282169699Skan  struct c_declarator *itarget = target;
7283169699Skan  struct c_declarator *ret = XOBNEW (&parser_obstack, struct c_declarator);
7284169699Skan  if (type_quals_attrs)
7285169699Skan    {
7286169699Skan      attrs = type_quals_attrs->attrs;
7287169699Skan      quals = quals_from_declspecs (type_quals_attrs);
7288169699Skan      if (attrs != NULL_TREE)
7289169699Skan	itarget = build_attrs_declarator (attrs, target);
7290169699Skan    }
7291169699Skan  ret->kind = cdk_pointer;
7292169699Skan  ret->declarator = itarget;
7293169699Skan  ret->u.pointer_quals = quals;
7294169699Skan  return ret;
7295132730Skan}
7296132730Skan
7297169699Skan/* Return a pointer to a structure for an empty list of declaration
7298169699Skan   specifiers.  */
7299132730Skan
7300169699Skanstruct c_declspecs *
7301169699Skanbuild_null_declspecs (void)
7302132730Skan{
7303169699Skan  struct c_declspecs *ret = XOBNEW (&parser_obstack, struct c_declspecs);
7304169699Skan  ret->type = 0;
7305169699Skan  ret->decl_attr = 0;
7306169699Skan  ret->attrs = 0;
7307169699Skan  ret->typespec_word = cts_none;
7308169699Skan  ret->storage_class = csc_none;
7309169699Skan  ret->declspecs_seen_p = false;
7310169699Skan  ret->type_seen_p = false;
7311169699Skan  ret->non_sc_seen_p = false;
7312169699Skan  ret->typedef_p = false;
7313169699Skan  ret->tag_defined_p = false;
7314169699Skan  ret->explicit_signed_p = false;
7315169699Skan  ret->deprecated_p = false;
7316260919Spfg  /* APPLE LOCAL "unavailable" attribute (radar 2809697) */
7317260919Spfg  ret->unavailable_p = false;
7318169699Skan  ret->default_int_p = false;
7319169699Skan  ret->long_p = false;
7320169699Skan  ret->long_long_p = false;
7321169699Skan  ret->short_p = false;
7322169699Skan  ret->signed_p = false;
7323169699Skan  ret->unsigned_p = false;
7324169699Skan  ret->complex_p = false;
7325169699Skan  ret->inline_p = false;
7326169699Skan  ret->thread_p = false;
7327169699Skan  ret->const_p = false;
7328169699Skan  ret->volatile_p = false;
7329169699Skan  ret->restrict_p = false;
7330169699Skan  return ret;
7331169699Skan}
7332132730Skan
7333169699Skan/* Add the type qualifier QUAL to the declaration specifiers SPECS,
7334169699Skan   returning SPECS.  */
7335132730Skan
7336169699Skanstruct c_declspecs *
7337169699Skandeclspecs_add_qual (struct c_declspecs *specs, tree qual)
7338169699Skan{
7339169699Skan  enum rid i;
7340169699Skan  bool dupe = false;
7341169699Skan  specs->non_sc_seen_p = true;
7342169699Skan  specs->declspecs_seen_p = true;
7343169699Skan  gcc_assert (TREE_CODE (qual) == IDENTIFIER_NODE
7344169699Skan	      && C_IS_RESERVED_WORD (qual));
7345169699Skan  i = C_RID_CODE (qual);
7346169699Skan  switch (i)
7347169699Skan    {
7348169699Skan    case RID_CONST:
7349169699Skan      dupe = specs->const_p;
7350169699Skan      specs->const_p = true;
7351169699Skan      break;
7352169699Skan    case RID_VOLATILE:
7353169699Skan      dupe = specs->volatile_p;
7354169699Skan      specs->volatile_p = true;
7355169699Skan      break;
7356169699Skan    case RID_RESTRICT:
7357169699Skan      dupe = specs->restrict_p;
7358169699Skan      specs->restrict_p = true;
7359169699Skan      break;
7360169699Skan    default:
7361169699Skan      gcc_unreachable ();
7362169699Skan    }
7363169699Skan  if (dupe && pedantic && !flag_isoc99)
7364169699Skan    pedwarn ("duplicate %qE", qual);
7365169699Skan  return specs;
7366169699Skan}
7367132730Skan
7368169699Skan/* Add the type specifier TYPE to the declaration specifiers SPECS,
7369169699Skan   returning SPECS.  */
7370132730Skan
7371169699Skanstruct c_declspecs *
7372169699Skandeclspecs_add_type (struct c_declspecs *specs, struct c_typespec spec)
7373169699Skan{
7374169699Skan  tree type = spec.spec;
7375169699Skan  specs->non_sc_seen_p = true;
7376169699Skan  specs->declspecs_seen_p = true;
7377169699Skan  specs->type_seen_p = true;
7378169699Skan  if (TREE_DEPRECATED (type))
7379169699Skan    specs->deprecated_p = true;
7380169699Skan
7381260919Spfg  /* APPLE LOCAL begin "unavailable" attribute (radar 2809697) */
7382260919Spfg  if (TREE_UNAVAILABLE (type))
7383260919Spfg    specs->unavailable_p = true;
7384260919Spfg  /* APPLE LOCAL end "unavailable" attribute (radar 2809697) */
7385260919Spfg
7386169699Skan  /* Handle type specifier keywords.  */
7387169699Skan  if (TREE_CODE (type) == IDENTIFIER_NODE && C_IS_RESERVED_WORD (type))
7388169699Skan    {
7389169699Skan      enum rid i = C_RID_CODE (type);
7390169699Skan      if (specs->type)
7391132730Skan	{
7392169699Skan	  error ("two or more data types in declaration specifiers");
7393169699Skan	  return specs;
7394169699Skan	}
7395169699Skan      if ((int) i <= (int) RID_LAST_MODIFIER)
7396169699Skan	{
7397169699Skan	  /* "long", "short", "signed", "unsigned" or "_Complex".  */
7398169699Skan	  bool dupe = false;
7399169699Skan	  switch (i)
7400132730Skan	    {
7401169699Skan	    case RID_LONG:
7402169699Skan	      if (specs->long_long_p)
7403132730Skan		{
7404169699Skan		  error ("%<long long long%> is too long for GCC");
7405169699Skan		  break;
7406132730Skan		}
7407169699Skan	      if (specs->long_p)
7408132730Skan		{
7409169699Skan		  if (specs->typespec_word == cts_double)
7410169699Skan		    {
7411169699Skan		      error ("both %<long long%> and %<double%> in "
7412169699Skan			     "declaration specifiers");
7413169699Skan		      break;
7414169699Skan		    }
7415169699Skan		  if (pedantic && !flag_isoc99 && !in_system_header
7416169699Skan		      && warn_long_long)
7417169699Skan		    pedwarn ("ISO C90 does not support %<long long%>");
7418169699Skan		  specs->long_long_p = 1;
7419169699Skan		  break;
7420132730Skan		}
7421169699Skan	      if (specs->short_p)
7422169699Skan		error ("both %<long%> and %<short%> in "
7423169699Skan		       "declaration specifiers");
7424169699Skan	      else if (specs->typespec_word == cts_void)
7425169699Skan		error ("both %<long%> and %<void%> in "
7426169699Skan		       "declaration specifiers");
7427169699Skan	      else if (specs->typespec_word == cts_bool)
7428169699Skan		error ("both %<long%> and %<_Bool%> in "
7429169699Skan		       "declaration specifiers");
7430169699Skan	      else if (specs->typespec_word == cts_char)
7431169699Skan		error ("both %<long%> and %<char%> in "
7432169699Skan		       "declaration specifiers");
7433169699Skan	      else if (specs->typespec_word == cts_float)
7434169699Skan		error ("both %<long%> and %<float%> in "
7435169699Skan		       "declaration specifiers");
7436169699Skan	      else if (specs->typespec_word == cts_dfloat32)
7437169699Skan		error ("both %<long%> and %<_Decimal32%> in "
7438169699Skan		       "declaration specifiers");
7439169699Skan	      else if (specs->typespec_word == cts_dfloat64)
7440169699Skan		error ("both %<long%> and %<_Decimal64%> in "
7441169699Skan		       "declaration specifiers");
7442169699Skan	      else if (specs->typespec_word == cts_dfloat128)
7443169699Skan		error ("both %<long%> and %<_Decimal128%> in "
7444169699Skan		       "declaration specifiers");
7445132730Skan	      else
7446169699Skan		specs->long_p = true;
7447169699Skan	      break;
7448169699Skan	    case RID_SHORT:
7449169699Skan	      dupe = specs->short_p;
7450169699Skan	      if (specs->long_p)
7451169699Skan		error ("both %<long%> and %<short%> in "
7452169699Skan		       "declaration specifiers");
7453169699Skan	      else if (specs->typespec_word == cts_void)
7454169699Skan		error ("both %<short%> and %<void%> in "
7455169699Skan		       "declaration specifiers");
7456169699Skan	      else if (specs->typespec_word == cts_bool)
7457169699Skan		error ("both %<short%> and %<_Bool%> in "
7458169699Skan		       "declaration specifiers");
7459169699Skan	      else if (specs->typespec_word == cts_char)
7460169699Skan		error ("both %<short%> and %<char%> in "
7461169699Skan		       "declaration specifiers");
7462169699Skan	      else if (specs->typespec_word == cts_float)
7463169699Skan		error ("both %<short%> and %<float%> in "
7464169699Skan		       "declaration specifiers");
7465169699Skan	      else if (specs->typespec_word == cts_double)
7466169699Skan		error ("both %<short%> and %<double%> in "
7467169699Skan		       "declaration specifiers");
7468169699Skan	      else if (specs->typespec_word == cts_dfloat32)
7469169699Skan                error ("both %<short%> and %<_Decimal32%> in "
7470169699Skan		       "declaration specifiers");
7471169699Skan	      else if (specs->typespec_word == cts_dfloat64)
7472169699Skan		error ("both %<short%> and %<_Decimal64%> in "
7473169699Skan		                        "declaration specifiers");
7474169699Skan	      else if (specs->typespec_word == cts_dfloat128)
7475169699Skan		error ("both %<short%> and %<_Decimal128%> in "
7476169699Skan		       "declaration specifiers");
7477169699Skan	      else
7478169699Skan		specs->short_p = true;
7479169699Skan	      break;
7480169699Skan	    case RID_SIGNED:
7481169699Skan	      dupe = specs->signed_p;
7482169699Skan	      if (specs->unsigned_p)
7483169699Skan		error ("both %<signed%> and %<unsigned%> in "
7484169699Skan		       "declaration specifiers");
7485169699Skan	      else if (specs->typespec_word == cts_void)
7486169699Skan		error ("both %<signed%> and %<void%> in "
7487169699Skan		       "declaration specifiers");
7488169699Skan	      else if (specs->typespec_word == cts_bool)
7489169699Skan		error ("both %<signed%> and %<_Bool%> in "
7490169699Skan		       "declaration specifiers");
7491169699Skan	      else if (specs->typespec_word == cts_float)
7492169699Skan		error ("both %<signed%> and %<float%> in "
7493169699Skan		       "declaration specifiers");
7494169699Skan	      else if (specs->typespec_word == cts_double)
7495169699Skan		error ("both %<signed%> and %<double%> in "
7496169699Skan		       "declaration specifiers");
7497169699Skan	      else if (specs->typespec_word == cts_dfloat32)
7498169699Skan		error ("both %<signed%> and %<_Decimal32%> in "
7499169699Skan		       "declaration specifiers");
7500169699Skan	      else if (specs->typespec_word == cts_dfloat64)
7501169699Skan		error ("both %<signed%> and %<_Decimal64%> in "
7502169699Skan		       "declaration specifiers");
7503169699Skan	      else if (specs->typespec_word == cts_dfloat128)
7504169699Skan		error ("both %<signed%> and %<_Decimal128%> in "
7505169699Skan		       "declaration specifiers");
7506169699Skan	      else
7507169699Skan		specs->signed_p = true;
7508169699Skan	      break;
7509169699Skan	    case RID_UNSIGNED:
7510169699Skan	      dupe = specs->unsigned_p;
7511169699Skan	      if (specs->signed_p)
7512169699Skan		error ("both %<signed%> and %<unsigned%> in "
7513169699Skan		       "declaration specifiers");
7514169699Skan	      else if (specs->typespec_word == cts_void)
7515169699Skan		error ("both %<unsigned%> and %<void%> in "
7516169699Skan		       "declaration specifiers");
7517169699Skan	      else if (specs->typespec_word == cts_bool)
7518169699Skan		error ("both %<unsigned%> and %<_Bool%> in "
7519169699Skan		       "declaration specifiers");
7520169699Skan	      else if (specs->typespec_word == cts_float)
7521169699Skan		error ("both %<unsigned%> and %<float%> in "
7522169699Skan		       "declaration specifiers");
7523169699Skan	      else if (specs->typespec_word == cts_double)
7524169699Skan		error ("both %<unsigned%> and %<double%> in "
7525169699Skan		       "declaration specifiers");
7526169699Skan              else if (specs->typespec_word == cts_dfloat32)
7527169699Skan		error ("both %<unsigned%> and %<_Decimal32%> in "
7528169699Skan		       "declaration specifiers");
7529169699Skan	      else if (specs->typespec_word == cts_dfloat64)
7530169699Skan		error ("both %<unsigned%> and %<_Decimal64%> in "
7531169699Skan		       "declaration specifiers");
7532169699Skan	      else if (specs->typespec_word == cts_dfloat128)
7533169699Skan		error ("both %<unsigned%> and %<_Decimal128%> in "
7534169699Skan		       "declaration specifiers");
7535169699Skan	      else
7536169699Skan		specs->unsigned_p = true;
7537169699Skan	      break;
7538169699Skan	    case RID_COMPLEX:
7539169699Skan	      dupe = specs->complex_p;
7540169699Skan	      if (pedantic && !flag_isoc99 && !in_system_header)
7541169699Skan		pedwarn ("ISO C90 does not support complex types");
7542169699Skan	      if (specs->typespec_word == cts_void)
7543169699Skan		error ("both %<complex%> and %<void%> in "
7544169699Skan		       "declaration specifiers");
7545169699Skan	      else if (specs->typespec_word == cts_bool)
7546169699Skan		error ("both %<complex%> and %<_Bool%> in "
7547169699Skan		       "declaration specifiers");
7548169699Skan              else if (specs->typespec_word == cts_dfloat32)
7549169699Skan		error ("both %<complex%> and %<_Decimal32%> in "
7550169699Skan		       "declaration specifiers");
7551169699Skan	      else if (specs->typespec_word == cts_dfloat64)
7552169699Skan		error ("both %<complex%> and %<_Decimal64%> in "
7553169699Skan		       "declaration specifiers");
7554169699Skan	      else if (specs->typespec_word == cts_dfloat128)
7555169699Skan		error ("both %<complex%> and %<_Decimal128%> in "
7556169699Skan		       "declaration specifiers");
7557169699Skan	      else
7558169699Skan		specs->complex_p = true;
7559169699Skan	      break;
7560169699Skan	    default:
7561169699Skan	      gcc_unreachable ();
7562132730Skan	    }
7563169699Skan
7564169699Skan	  if (dupe)
7565169699Skan	    error ("duplicate %qE", type);
7566169699Skan
7567169699Skan	  return specs;
7568132730Skan	}
7569169699Skan      else
7570169699Skan	{
7571169699Skan	  /* "void", "_Bool", "char", "int", "float" or "double".  */
7572169699Skan	  if (specs->typespec_word != cts_none)
7573169699Skan	    {
7574169699Skan	      error ("two or more data types in declaration specifiers");
7575169699Skan	      return specs;
7576169699Skan	    }
7577169699Skan	  switch (i)
7578169699Skan	    {
7579169699Skan	    case RID_VOID:
7580169699Skan	      if (specs->long_p)
7581169699Skan		error ("both %<long%> and %<void%> in "
7582169699Skan		       "declaration specifiers");
7583169699Skan	      else if (specs->short_p)
7584169699Skan		error ("both %<short%> and %<void%> in "
7585169699Skan		       "declaration specifiers");
7586169699Skan	      else if (specs->signed_p)
7587169699Skan		error ("both %<signed%> and %<void%> in "
7588169699Skan		       "declaration specifiers");
7589169699Skan	      else if (specs->unsigned_p)
7590169699Skan		error ("both %<unsigned%> and %<void%> in "
7591169699Skan		       "declaration specifiers");
7592169699Skan	      else if (specs->complex_p)
7593169699Skan		error ("both %<complex%> and %<void%> in "
7594169699Skan		       "declaration specifiers");
7595169699Skan	      else
7596169699Skan		specs->typespec_word = cts_void;
7597169699Skan	      return specs;
7598169699Skan	    case RID_BOOL:
7599169699Skan	      if (specs->long_p)
7600169699Skan		error ("both %<long%> and %<_Bool%> in "
7601169699Skan		       "declaration specifiers");
7602169699Skan	      else if (specs->short_p)
7603169699Skan		error ("both %<short%> and %<_Bool%> in "
7604169699Skan		       "declaration specifiers");
7605169699Skan	      else if (specs->signed_p)
7606169699Skan		error ("both %<signed%> and %<_Bool%> in "
7607169699Skan		       "declaration specifiers");
7608169699Skan	      else if (specs->unsigned_p)
7609169699Skan		error ("both %<unsigned%> and %<_Bool%> in "
7610169699Skan		       "declaration specifiers");
7611169699Skan	      else if (specs->complex_p)
7612169699Skan		error ("both %<complex%> and %<_Bool%> in "
7613169699Skan		       "declaration specifiers");
7614169699Skan	      else
7615169699Skan		specs->typespec_word = cts_bool;
7616169699Skan	      return specs;
7617169699Skan	    case RID_CHAR:
7618169699Skan	      if (specs->long_p)
7619169699Skan		error ("both %<long%> and %<char%> in "
7620169699Skan		       "declaration specifiers");
7621169699Skan	      else if (specs->short_p)
7622169699Skan		error ("both %<short%> and %<char%> in "
7623169699Skan		       "declaration specifiers");
7624169699Skan	      else
7625169699Skan		specs->typespec_word = cts_char;
7626169699Skan	      return specs;
7627169699Skan	    case RID_INT:
7628169699Skan	      specs->typespec_word = cts_int;
7629169699Skan	      return specs;
7630169699Skan	    case RID_FLOAT:
7631169699Skan	      if (specs->long_p)
7632169699Skan		error ("both %<long%> and %<float%> in "
7633169699Skan		       "declaration specifiers");
7634169699Skan	      else if (specs->short_p)
7635169699Skan		error ("both %<short%> and %<float%> in "
7636169699Skan		       "declaration specifiers");
7637169699Skan	      else if (specs->signed_p)
7638169699Skan		error ("both %<signed%> and %<float%> in "
7639169699Skan		       "declaration specifiers");
7640169699Skan	      else if (specs->unsigned_p)
7641169699Skan		error ("both %<unsigned%> and %<float%> in "
7642169699Skan		       "declaration specifiers");
7643169699Skan	      else
7644169699Skan		specs->typespec_word = cts_float;
7645169699Skan	      return specs;
7646169699Skan	    case RID_DOUBLE:
7647169699Skan	      if (specs->long_long_p)
7648169699Skan		error ("both %<long long%> and %<double%> in "
7649169699Skan		       "declaration specifiers");
7650169699Skan	      else if (specs->short_p)
7651169699Skan		error ("both %<short%> and %<double%> in "
7652169699Skan		       "declaration specifiers");
7653169699Skan	      else if (specs->signed_p)
7654169699Skan		error ("both %<signed%> and %<double%> in "
7655169699Skan		       "declaration specifiers");
7656169699Skan	      else if (specs->unsigned_p)
7657169699Skan		error ("both %<unsigned%> and %<double%> in "
7658169699Skan		       "declaration specifiers");
7659169699Skan	      else
7660169699Skan		specs->typespec_word = cts_double;
7661169699Skan	      return specs;
7662169699Skan	    case RID_DFLOAT32:
7663169699Skan	    case RID_DFLOAT64:
7664169699Skan	    case RID_DFLOAT128:
7665169699Skan	      {
7666169699Skan		const char *str;
7667169699Skan		if (i == RID_DFLOAT32)
7668169699Skan		  str = "_Decimal32";
7669169699Skan		else if (i == RID_DFLOAT64)
7670169699Skan		  str = "_Decimal64";
7671169699Skan		else
7672169699Skan		  str = "_Decimal128";
7673169699Skan		if (specs->long_long_p)
7674169699Skan		  error ("both %<long long%> and %<%s%> in "
7675169699Skan			 "declaration specifiers", str);
7676169699Skan		if (specs->long_p)
7677169699Skan		  error ("both %<long%> and %<%s%> in "
7678169699Skan			 "declaration specifiers", str);
7679169699Skan		else if (specs->short_p)
7680169699Skan		  error ("both %<short%> and %<%s%> in "
7681169699Skan			 "declaration specifiers", str);
7682169699Skan		else if (specs->signed_p)
7683169699Skan		  error ("both %<signed%> and %<%s%> in "
7684169699Skan			 "declaration specifiers", str);
7685169699Skan		else if (specs->unsigned_p)
7686169699Skan		  error ("both %<unsigned%> and %<%s%> in "
7687169699Skan			 "declaration specifiers", str);
7688169699Skan                else if (specs->complex_p)
7689169699Skan                  error ("both %<complex%> and %<%s%> in "
7690169699Skan                         "declaration specifiers", str);
7691169699Skan		else if (i == RID_DFLOAT32)
7692169699Skan		  specs->typespec_word = cts_dfloat32;
7693169699Skan		else if (i == RID_DFLOAT64)
7694169699Skan		  specs->typespec_word = cts_dfloat64;
7695169699Skan		else
7696169699Skan		  specs->typespec_word = cts_dfloat128;
7697169699Skan	      }
7698169699Skan	      if (!targetm.decimal_float_supported_p ())
7699169699Skan		error ("decimal floating point not supported for this target");
7700169699Skan	      if (pedantic)
7701169699Skan		pedwarn ("ISO C does not support decimal floating point");
7702169699Skan	      return specs;
7703169699Skan	    default:
7704169699Skan	      /* ObjC reserved word "id", handled below.  */
7705169699Skan	      break;
7706169699Skan	    }
7707169699Skan	}
7708169699Skan    }
7709132730Skan
7710169699Skan  /* Now we have a typedef (a TYPE_DECL node), an identifier (some
7711169699Skan     form of ObjC type, cases such as "int" and "long" being handled
7712169699Skan     above), a TYPE (struct, union, enum and typeof specifiers) or an
7713169699Skan     ERROR_MARK.  In none of these cases may there have previously
7714169699Skan     been any type specifiers.  */
7715169699Skan  if (specs->type || specs->typespec_word != cts_none
7716169699Skan      || specs->long_p || specs->short_p || specs->signed_p
7717169699Skan      || specs->unsigned_p || specs->complex_p)
7718169699Skan    error ("two or more data types in declaration specifiers");
7719169699Skan  else if (TREE_CODE (type) == TYPE_DECL)
7720169699Skan    {
7721169699Skan      if (TREE_TYPE (type) == error_mark_node)
7722169699Skan	; /* Allow the type to default to int to avoid cascading errors.  */
7723169699Skan      else
7724132730Skan	{
7725169699Skan	  specs->type = TREE_TYPE (type);
7726169699Skan	  specs->decl_attr = DECL_ATTRIBUTES (type);
7727169699Skan	  specs->typedef_p = true;
7728169699Skan	  specs->explicit_signed_p = C_TYPEDEF_EXPLICITLY_SIGNED (type);
7729169699Skan	}
7730169699Skan    }
7731169699Skan  else if (TREE_CODE (type) == IDENTIFIER_NODE)
7732169699Skan    {
7733169699Skan      tree t = lookup_name (type);
7734169699Skan      if (!t || TREE_CODE (t) != TYPE_DECL)
7735169699Skan	error ("%qE fails to be a typedef or built in type", type);
7736169699Skan      else if (TREE_TYPE (t) == error_mark_node)
7737169699Skan	;
7738169699Skan      else
7739169699Skan	specs->type = TREE_TYPE (t);
7740169699Skan    }
7741169699Skan  else if (TREE_CODE (type) != ERROR_MARK)
7742169699Skan    {
7743169699Skan      if (spec.kind == ctsk_tagdef || spec.kind == ctsk_tagfirstref)
7744169699Skan	specs->tag_defined_p = true;
7745169699Skan      if (spec.kind == ctsk_typeof)
7746169699Skan	specs->typedef_p = true;
7747169699Skan      specs->type = type;
7748169699Skan    }
7749132730Skan
7750169699Skan  return specs;
7751169699Skan}
7752132730Skan
7753169699Skan/* Add the storage class specifier or function specifier SCSPEC to the
7754169699Skan   declaration specifiers SPECS, returning SPECS.  */
7755169699Skan
7756169699Skanstruct c_declspecs *
7757169699Skandeclspecs_add_scspec (struct c_declspecs *specs, tree scspec)
7758169699Skan{
7759169699Skan  enum rid i;
7760169699Skan  enum c_storage_class n = csc_none;
7761169699Skan  bool dupe = false;
7762169699Skan  specs->declspecs_seen_p = true;
7763169699Skan  gcc_assert (TREE_CODE (scspec) == IDENTIFIER_NODE
7764169699Skan	      && C_IS_RESERVED_WORD (scspec));
7765169699Skan  i = C_RID_CODE (scspec);
7766169699Skan  if (extra_warnings && specs->non_sc_seen_p)
7767169699Skan    warning (OPT_Wextra, "%qE is not at beginning of declaration", scspec);
7768169699Skan  switch (i)
7769169699Skan    {
7770169699Skan    case RID_INLINE:
7771169699Skan      /* C99 permits duplicate inline.  Although of doubtful utility,
7772169699Skan	 it seems simplest to permit it in gnu89 mode as well, as
7773169699Skan	 there is also little utility in maintaining this as a
7774169699Skan	 difference between gnu89 and C99 inline.  */
7775169699Skan      dupe = false;
7776169699Skan      specs->inline_p = true;
7777169699Skan      break;
7778169699Skan    case RID_THREAD:
7779169699Skan      dupe = specs->thread_p;
7780169699Skan      if (specs->storage_class == csc_auto)
7781169699Skan	error ("%<__thread%> used with %<auto%>");
7782169699Skan      else if (specs->storage_class == csc_register)
7783169699Skan	error ("%<__thread%> used with %<register%>");
7784169699Skan      else if (specs->storage_class == csc_typedef)
7785169699Skan	error ("%<__thread%> used with %<typedef%>");
7786169699Skan      else
7787169699Skan	specs->thread_p = true;
7788169699Skan      break;
7789169699Skan    case RID_AUTO:
7790169699Skan      n = csc_auto;
7791169699Skan      break;
7792169699Skan    case RID_EXTERN:
7793169699Skan      n = csc_extern;
7794169699Skan      /* Diagnose "__thread extern".  */
7795169699Skan      if (specs->thread_p)
7796169699Skan	error ("%<__thread%> before %<extern%>");
7797169699Skan      break;
7798169699Skan    case RID_REGISTER:
7799169699Skan      n = csc_register;
7800169699Skan      break;
7801169699Skan    case RID_STATIC:
7802169699Skan      n = csc_static;
7803169699Skan      /* Diagnose "__thread static".  */
7804169699Skan      if (specs->thread_p)
7805169699Skan	error ("%<__thread%> before %<static%>");
7806169699Skan      break;
7807169699Skan    case RID_TYPEDEF:
7808169699Skan      n = csc_typedef;
7809169699Skan      break;
7810169699Skan    default:
7811169699Skan      gcc_unreachable ();
7812169699Skan    }
7813169699Skan  if (n != csc_none && n == specs->storage_class)
7814169699Skan    dupe = true;
7815169699Skan  if (dupe)
7816169699Skan    error ("duplicate %qE", scspec);
7817169699Skan  if (n != csc_none)
7818169699Skan    {
7819169699Skan      if (specs->storage_class != csc_none && n != specs->storage_class)
7820169699Skan	{
7821169699Skan	  error ("multiple storage classes in declaration specifiers");
7822132730Skan	}
7823169699Skan      else
7824169699Skan	{
7825169699Skan	  specs->storage_class = n;
7826169699Skan	  if (n != csc_extern && n != csc_static && specs->thread_p)
7827169699Skan	    {
7828169699Skan	      error ("%<__thread%> used with %qE", scspec);
7829169699Skan	      specs->thread_p = false;
7830169699Skan	    }
7831169699Skan	}
7832169699Skan    }
7833169699Skan  return specs;
7834169699Skan}
7835132730Skan
7836169699Skan/* Add the attributes ATTRS to the declaration specifiers SPECS,
7837169699Skan   returning SPECS.  */
7838169699Skan
7839169699Skanstruct c_declspecs *
7840169699Skandeclspecs_add_attrs (struct c_declspecs *specs, tree attrs)
7841169699Skan{
7842169699Skan  specs->attrs = chainon (attrs, specs->attrs);
7843169699Skan  specs->declspecs_seen_p = true;
7844169699Skan  return specs;
7845132730Skan}
7846132730Skan
7847169699Skan/* Combine "long", "short", "signed", "unsigned" and "_Complex" type
7848169699Skan   specifiers with any other type specifier to determine the resulting
7849169699Skan   type.  This is where ISO C checks on complex types are made, since
7850169699Skan   "_Complex long" is a prefix of the valid ISO C type "_Complex long
7851169699Skan   double".  */
7852132730Skan
7853169699Skanstruct c_declspecs *
7854169699Skanfinish_declspecs (struct c_declspecs *specs)
7855132730Skan{
7856169699Skan  /* If a type was specified as a whole, we have no modifiers and are
7857169699Skan     done.  */
7858169699Skan  if (specs->type != NULL_TREE)
7859169699Skan    {
7860169699Skan      gcc_assert (!specs->long_p && !specs->long_long_p && !specs->short_p
7861169699Skan		  && !specs->signed_p && !specs->unsigned_p
7862169699Skan		  && !specs->complex_p);
7863169699Skan      return specs;
7864169699Skan    }
7865132730Skan
7866169699Skan  /* If none of "void", "_Bool", "char", "int", "float" or "double"
7867169699Skan     has been specified, treat it as "int" unless "_Complex" is
7868169699Skan     present and there are no other specifiers.  If we just have
7869169699Skan     "_Complex", it is equivalent to "_Complex double", but e.g.
7870169699Skan     "_Complex short" is equivalent to "_Complex short int".  */
7871169699Skan  if (specs->typespec_word == cts_none)
7872132730Skan    {
7873169699Skan      if (specs->long_p || specs->short_p
7874169699Skan	  || specs->signed_p || specs->unsigned_p)
7875169699Skan	{
7876169699Skan	  specs->typespec_word = cts_int;
7877169699Skan	}
7878169699Skan      else if (specs->complex_p)
7879169699Skan	{
7880169699Skan	  specs->typespec_word = cts_double;
7881169699Skan	  if (pedantic)
7882169699Skan	    pedwarn ("ISO C does not support plain %<complex%> meaning "
7883169699Skan		     "%<double complex%>");
7884169699Skan	}
7885169699Skan      else
7886169699Skan	{
7887169699Skan	  specs->typespec_word = cts_int;
7888169699Skan	  specs->default_int_p = true;
7889169699Skan	  /* We don't diagnose this here because grokdeclarator will
7890169699Skan	     give more specific diagnostics according to whether it is
7891169699Skan	     a function definition.  */
7892169699Skan	}
7893169699Skan    }
7894132730Skan
7895169699Skan  /* If "signed" was specified, record this to distinguish "int" and
7896169699Skan     "signed int" in the case of a bit-field with
7897169699Skan     -funsigned-bitfields.  */
7898169699Skan  specs->explicit_signed_p = specs->signed_p;
7899132730Skan
7900169699Skan  /* Now compute the actual type.  */
7901169699Skan  switch (specs->typespec_word)
7902169699Skan    {
7903169699Skan    case cts_void:
7904169699Skan      gcc_assert (!specs->long_p && !specs->short_p
7905169699Skan		  && !specs->signed_p && !specs->unsigned_p
7906169699Skan		  && !specs->complex_p);
7907169699Skan      specs->type = void_type_node;
7908169699Skan      break;
7909169699Skan    case cts_bool:
7910169699Skan      gcc_assert (!specs->long_p && !specs->short_p
7911169699Skan		  && !specs->signed_p && !specs->unsigned_p
7912169699Skan		  && !specs->complex_p);
7913169699Skan      specs->type = boolean_type_node;
7914169699Skan      break;
7915169699Skan    case cts_char:
7916169699Skan      gcc_assert (!specs->long_p && !specs->short_p);
7917169699Skan      gcc_assert (!(specs->signed_p && specs->unsigned_p));
7918169699Skan      if (specs->signed_p)
7919169699Skan	specs->type = signed_char_type_node;
7920169699Skan      else if (specs->unsigned_p)
7921169699Skan	specs->type = unsigned_char_type_node;
7922169699Skan      else
7923169699Skan	specs->type = char_type_node;
7924169699Skan      if (specs->complex_p)
7925169699Skan	{
7926169699Skan	  if (pedantic)
7927169699Skan	    pedwarn ("ISO C does not support complex integer types");
7928169699Skan	  specs->type = build_complex_type (specs->type);
7929169699Skan	}
7930169699Skan      break;
7931169699Skan    case cts_int:
7932169699Skan      gcc_assert (!(specs->long_p && specs->short_p));
7933169699Skan      gcc_assert (!(specs->signed_p && specs->unsigned_p));
7934169699Skan      if (specs->long_long_p)
7935169699Skan	specs->type = (specs->unsigned_p
7936169699Skan		       ? long_long_unsigned_type_node
7937169699Skan		       : long_long_integer_type_node);
7938169699Skan      else if (specs->long_p)
7939169699Skan	specs->type = (specs->unsigned_p
7940169699Skan		       ? long_unsigned_type_node
7941169699Skan		       : long_integer_type_node);
7942169699Skan      else if (specs->short_p)
7943169699Skan	specs->type = (specs->unsigned_p
7944169699Skan		       ? short_unsigned_type_node
7945169699Skan		       : short_integer_type_node);
7946169699Skan      else
7947169699Skan	specs->type = (specs->unsigned_p
7948169699Skan		       ? unsigned_type_node
7949169699Skan		       : integer_type_node);
7950169699Skan      if (specs->complex_p)
7951169699Skan	{
7952169699Skan	  if (pedantic)
7953169699Skan	    pedwarn ("ISO C does not support complex integer types");
7954169699Skan	  specs->type = build_complex_type (specs->type);
7955169699Skan	}
7956169699Skan      break;
7957169699Skan    case cts_float:
7958169699Skan      gcc_assert (!specs->long_p && !specs->short_p
7959169699Skan		  && !specs->signed_p && !specs->unsigned_p);
7960169699Skan      specs->type = (specs->complex_p
7961169699Skan		     ? complex_float_type_node
7962169699Skan		     : float_type_node);
7963169699Skan      break;
7964169699Skan    case cts_double:
7965169699Skan      gcc_assert (!specs->long_long_p && !specs->short_p
7966169699Skan		  && !specs->signed_p && !specs->unsigned_p);
7967169699Skan      if (specs->long_p)
7968169699Skan	{
7969169699Skan	  specs->type = (specs->complex_p
7970169699Skan			 ? complex_long_double_type_node
7971169699Skan			 : long_double_type_node);
7972169699Skan	}
7973169699Skan      else
7974169699Skan	{
7975169699Skan	  specs->type = (specs->complex_p
7976169699Skan			 ? complex_double_type_node
7977169699Skan			 : double_type_node);
7978169699Skan	}
7979169699Skan      break;
7980169699Skan    case cts_dfloat32:
7981169699Skan    case cts_dfloat64:
7982169699Skan    case cts_dfloat128:
7983169699Skan      gcc_assert (!specs->long_p && !specs->long_long_p && !specs->short_p
7984169699Skan		  && !specs->signed_p && !specs->unsigned_p && !specs->complex_p);
7985169699Skan      if (specs->typespec_word == cts_dfloat32)
7986169699Skan	specs->type = dfloat32_type_node;
7987169699Skan      else if (specs->typespec_word == cts_dfloat64)
7988169699Skan	specs->type = dfloat64_type_node;
7989169699Skan      else
7990169699Skan	specs->type = dfloat128_type_node;
7991169699Skan      break;
7992169699Skan    default:
7993169699Skan      gcc_unreachable ();
7994169699Skan    }
7995132730Skan
7996169699Skan  return specs;
7997169699Skan}
7998132730Skan
7999169699Skan/* Synthesize a function which calls all the global ctors or global
8000169699Skan   dtors in this file.  This is only used for targets which do not
8001169699Skan   support .ctors/.dtors sections.  FIXME: Migrate into cgraph.  */
8002169699Skanstatic void
8003169699Skanbuild_cdtor (int method_type, tree cdtors)
8004169699Skan{
8005169699Skan  tree body = 0;
8006132730Skan
8007169699Skan  if (!cdtors)
8008169699Skan    return;
8009169699Skan
8010169699Skan  for (; cdtors; cdtors = TREE_CHAIN (cdtors))
8011169699Skan    append_to_statement_list (build_function_call (TREE_VALUE (cdtors), 0),
8012169699Skan			      &body);
8013169699Skan
8014169699Skan  cgraph_build_static_cdtor (method_type, body, DEFAULT_INIT_PRIORITY);
8015169699Skan}
8016169699Skan
8017169699Skan/* A subroutine of c_write_global_declarations.  Perform final processing
8018169699Skan   on one file scope's declarations (or the external scope's declarations),
8019169699Skan   GLOBALS.  */
8020169699Skan
8021169699Skanstatic void
8022169699Skanc_write_global_declarations_1 (tree globals)
8023169699Skan{
8024169699Skan  tree decl;
8025169699Skan  bool reconsider;
8026169699Skan
8027169699Skan  /* Process the decls in the order they were written.  */
8028169699Skan  for (decl = globals; decl; decl = TREE_CHAIN (decl))
8029169699Skan    {
8030169699Skan      /* Check for used but undefined static functions using the C
8031169699Skan	 standard's definition of "used", and set TREE_NO_WARNING so
8032169699Skan	 that check_global_declarations doesn't repeat the check.  */
8033169699Skan      if (TREE_CODE (decl) == FUNCTION_DECL
8034169699Skan	  && DECL_INITIAL (decl) == 0
8035169699Skan	  && DECL_EXTERNAL (decl)
8036169699Skan	  && !TREE_PUBLIC (decl)
8037169699Skan	  && C_DECL_USED (decl))
8038169699Skan	{
8039169699Skan	  pedwarn ("%q+F used but never defined", decl);
8040169699Skan	  TREE_NO_WARNING (decl) = 1;
8041169699Skan	}
8042169699Skan
8043169699Skan      wrapup_global_declaration_1 (decl);
8044132730Skan    }
8045169699Skan
8046169699Skan  do
8047169699Skan    {
8048169699Skan      reconsider = false;
8049169699Skan      for (decl = globals; decl; decl = TREE_CHAIN (decl))
8050169699Skan	reconsider |= wrapup_global_declaration_2 (decl);
8051169699Skan    }
8052169699Skan  while (reconsider);
8053169699Skan
8054169699Skan  for (decl = globals; decl; decl = TREE_CHAIN (decl))
8055169699Skan    check_global_declaration_1 (decl);
8056132730Skan}
8057132730Skan
8058169699Skan/* A subroutine of c_write_global_declarations Emit debug information for each
8059169699Skan   of the declarations in GLOBALS.  */
8060132730Skan
8061169699Skanstatic void
8062169699Skanc_write_global_declarations_2 (tree globals)
8063169699Skan{
8064169699Skan  tree decl;
8065169699Skan
8066169699Skan  for (decl = globals; decl ; decl = TREE_CHAIN (decl))
8067169699Skan    debug_hooks->global_decl (decl);
8068169699Skan}
8069169699Skan
8070169699Skan/* Preserve the external declarations scope across a garbage collect.  */
8071169699Skanstatic GTY(()) tree ext_block;
8072169699Skan
8073132730Skanvoid
8074169699Skanc_write_global_declarations (void)
8075132730Skan{
8076169699Skan  tree t;
8077132730Skan
8078169699Skan  /* We don't want to do this if generating a PCH.  */
8079169699Skan  if (pch_file)
8080169699Skan    return;
8081132730Skan
8082169699Skan  /* Don't waste time on further processing if -fsyntax-only or we've
8083169699Skan     encountered errors.  */
8084169699Skan  if (flag_syntax_only || errorcount || sorrycount || cpp_errors (parse_in))
8085169699Skan    return;
8086132730Skan
8087169699Skan  /* Close the external scope.  */
8088169699Skan  ext_block = pop_scope ();
8089169699Skan  external_scope = 0;
8090169699Skan  gcc_assert (!current_scope);
8091169699Skan
8092169699Skan  if (ext_block)
8093169699Skan    {
8094169699Skan      tree tmp = BLOCK_VARS (ext_block);
8095169699Skan      int flags;
8096169699Skan      FILE * stream = dump_begin (TDI_tu, &flags);
8097169699Skan      if (stream && tmp)
8098169699Skan	{
8099169699Skan	  dump_node (tmp, flags & ~TDF_SLIM, stream);
8100169699Skan	  dump_end (TDI_tu, stream);
8101169699Skan	}
8102169699Skan    }
8103169699Skan
8104169699Skan  /* Process all file scopes in this compilation, and the external_scope,
8105169699Skan     through wrapup_global_declarations and check_global_declarations.  */
8106169699Skan  for (t = all_translation_units; t; t = TREE_CHAIN (t))
8107169699Skan    c_write_global_declarations_1 (BLOCK_VARS (DECL_INITIAL (t)));
8108169699Skan  c_write_global_declarations_1 (BLOCK_VARS (ext_block));
8109169699Skan
8110169699Skan  /* Generate functions to call static constructors and destructors
8111169699Skan     for targets that do not support .ctors/.dtors sections.  These
8112169699Skan     functions have magic names which are detected by collect2.  */
8113169699Skan  build_cdtor ('I', static_ctors); static_ctors = 0;
8114169699Skan  build_cdtor ('D', static_dtors); static_dtors = 0;
8115169699Skan
8116169699Skan  /* We're done parsing; proceed to optimize and emit assembly.
8117169699Skan     FIXME: shouldn't be the front end's responsibility to call this.  */
8118169699Skan  cgraph_optimize ();
8119169699Skan
8120169699Skan  /* After cgraph has had a chance to emit everything that's going to
8121169699Skan     be emitted, output debug information for globals.  */
8122169699Skan  if (errorcount == 0 && sorrycount == 0)
8123169699Skan    {
8124169699Skan      timevar_push (TV_SYMOUT);
8125169699Skan      for (t = all_translation_units; t; t = TREE_CHAIN (t))
8126169699Skan	c_write_global_declarations_2 (BLOCK_VARS (DECL_INITIAL (t)));
8127169699Skan      c_write_global_declarations_2 (BLOCK_VARS (ext_block));
8128169699Skan      timevar_pop (TV_SYMOUT);
8129169699Skan    }
8130169699Skan
8131169699Skan  ext_block = NULL;
8132132730Skan}
8133132730Skan
8134117421Skan#include "gt-c-decl.h"
8135