tree.c revision 117395
1/* Language-dependent node constructors for parse phase of GNU compiler.
2   Copyright (C) 1987, 1988, 1992, 1993, 1994, 1995, 1996, 1997, 1998,
3   1999, 2000, 2001, 2002 Free Software Foundation, Inc.
4   Hacked by Michael Tiemann (tiemann@cygnus.com)
5
6This file is part of GNU CC.
7
8GNU CC is free software; you can redistribute it and/or modify
9it under the terms of the GNU General Public License as published by
10the Free Software Foundation; either version 2, or (at your option)
11any later version.
12
13GNU CC is distributed in the hope that it will be useful,
14but WITHOUT ANY WARRANTY; without even the implied warranty of
15MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16GNU General Public License for more details.
17
18You should have received a copy of the GNU General Public License
19along with GNU CC; see the file COPYING.  If not, write to
20the Free Software Foundation, 59 Temple Place - Suite 330,
21Boston, MA 02111-1307, USA.  */
22
23#include "config.h"
24#include "system.h"
25#include "tree.h"
26#include "cp-tree.h"
27#include "flags.h"
28#include "real.h"
29#include "rtl.h"
30#include "toplev.h"
31#include "ggc.h"
32#include "insn-config.h"
33#include "integrate.h"
34#include "tree-inline.h"
35#include "target.h"
36
37static tree bot_manip PARAMS ((tree *, int *, void *));
38static tree bot_replace PARAMS ((tree *, int *, void *));
39static tree build_cplus_array_type_1 PARAMS ((tree, tree));
40static int list_hash_eq PARAMS ((const void *, const void *));
41static hashval_t list_hash_pieces PARAMS ((tree, tree, tree));
42static hashval_t list_hash PARAMS ((const void *));
43static cp_lvalue_kind lvalue_p_1 PARAMS ((tree, int, int));
44static tree no_linkage_helper PARAMS ((tree *, int *, void *));
45static tree build_srcloc PARAMS ((const char *, int));
46static tree mark_local_for_remap_r PARAMS ((tree *, int *, void *));
47static tree cp_unsave_r PARAMS ((tree *, int *, void *));
48static tree build_target_expr PARAMS ((tree, tree));
49static tree count_trees_r PARAMS ((tree *, int *, void *));
50static tree verify_stmt_tree_r PARAMS ((tree *, int *, void *));
51static tree find_tree_r PARAMS ((tree *, int *, void *));
52extern int cp_statement_code_p PARAMS ((enum tree_code));
53
54static tree handle_java_interface_attribute PARAMS ((tree *, tree, tree, int, bool *));
55static tree handle_com_interface_attribute PARAMS ((tree *, tree, tree, int, bool *));
56static tree handle_init_priority_attribute PARAMS ((tree *, tree, tree, int, bool *));
57
58/* If REF is an lvalue, returns the kind of lvalue that REF is.
59   Otherwise, returns clk_none.  If TREAT_CLASS_RVALUES_AS_LVALUES is
60   nonzero, rvalues of class type are considered lvalues.  */
61
62static cp_lvalue_kind
63lvalue_p_1 (ref, treat_class_rvalues_as_lvalues, allow_cast_as_lvalue)
64     tree ref;
65     int treat_class_rvalues_as_lvalues;
66     int allow_cast_as_lvalue;
67{
68  cp_lvalue_kind op1_lvalue_kind = clk_none;
69  cp_lvalue_kind op2_lvalue_kind = clk_none;
70
71  if (TREE_CODE (TREE_TYPE (ref)) == REFERENCE_TYPE)
72    return clk_ordinary;
73
74  if (ref == current_class_ptr)
75    return clk_none;
76
77  switch (TREE_CODE (ref))
78    {
79      /* preincrements and predecrements are valid lvals, provided
80	 what they refer to are valid lvals.  */
81    case PREINCREMENT_EXPR:
82    case PREDECREMENT_EXPR:
83    case SAVE_EXPR:
84    case UNSAVE_EXPR:
85    case TRY_CATCH_EXPR:
86    case WITH_CLEANUP_EXPR:
87    case REALPART_EXPR:
88    case IMAGPART_EXPR:
89      return lvalue_p_1 (TREE_OPERAND (ref, 0),
90			 treat_class_rvalues_as_lvalues,
91			 allow_cast_as_lvalue);
92
93    case NOP_EXPR:
94      /* If expression doesn't change the type, we consider it as an
95	 lvalue even when cast_as_lvalue extension isn't selected.
96	 That's because parts of the compiler are alleged to be sloppy
97	 about sticking in NOP_EXPR node for no good reason.  */
98      if (allow_cast_as_lvalue ||
99	  same_type_p (TYPE_MAIN_VARIANT (TREE_TYPE (ref)),
100		       TYPE_MAIN_VARIANT (TREE_TYPE (TREE_OPERAND (ref, 0)))))
101	return lvalue_p_1 (TREE_OPERAND (ref, 0),
102			   treat_class_rvalues_as_lvalues,
103			   allow_cast_as_lvalue);
104      else
105	return clk_none;
106
107    case COMPONENT_REF:
108      op1_lvalue_kind = lvalue_p_1 (TREE_OPERAND (ref, 0),
109				    treat_class_rvalues_as_lvalues,
110				    allow_cast_as_lvalue);
111      if (op1_lvalue_kind
112	  /* The "field" can be a FUNCTION_DECL or an OVERLOAD in some
113	     situations.  */
114	  && TREE_CODE (TREE_OPERAND (ref, 1)) == FIELD_DECL
115	  && DECL_C_BIT_FIELD (TREE_OPERAND (ref, 1)))
116	{
117	  /* Clear the ordinary bit.  If this object was a class
118	     rvalue we want to preserve that information.  */
119	  op1_lvalue_kind &= ~clk_ordinary;
120	  /* The lvalue is for a btifield.  */
121	  op1_lvalue_kind |= clk_bitfield;
122	}
123      return op1_lvalue_kind;
124
125    case STRING_CST:
126      return clk_ordinary;
127
128    case VAR_DECL:
129      if (TREE_READONLY (ref) && ! TREE_STATIC (ref)
130	  && DECL_LANG_SPECIFIC (ref)
131	  && DECL_IN_AGGR_P (ref))
132	return clk_none;
133    case INDIRECT_REF:
134    case ARRAY_REF:
135    case PARM_DECL:
136    case RESULT_DECL:
137      if (TREE_CODE (TREE_TYPE (ref)) != METHOD_TYPE)
138	return clk_ordinary;
139      break;
140
141      /* A currently unresolved scope ref.  */
142    case SCOPE_REF:
143      abort ();
144    case OFFSET_REF:
145      if (TREE_CODE (TREE_OPERAND (ref, 1)) == FUNCTION_DECL)
146	return clk_ordinary;
147      /* Fall through.  */
148    case MAX_EXPR:
149    case MIN_EXPR:
150      op1_lvalue_kind = lvalue_p_1 (TREE_OPERAND (ref, 0),
151				    treat_class_rvalues_as_lvalues,
152				    allow_cast_as_lvalue);
153      op2_lvalue_kind = lvalue_p_1 (TREE_OPERAND (ref, 1),
154				    treat_class_rvalues_as_lvalues,
155				    allow_cast_as_lvalue);
156      break;
157
158    case COND_EXPR:
159      op1_lvalue_kind = lvalue_p_1 (TREE_OPERAND (ref, 1),
160				    treat_class_rvalues_as_lvalues,
161				    allow_cast_as_lvalue);
162      op2_lvalue_kind = lvalue_p_1 (TREE_OPERAND (ref, 2),
163				    treat_class_rvalues_as_lvalues,
164				    allow_cast_as_lvalue);
165      break;
166
167    case MODIFY_EXPR:
168      return clk_ordinary;
169
170    case COMPOUND_EXPR:
171      return lvalue_p_1 (TREE_OPERAND (ref, 1),
172			 treat_class_rvalues_as_lvalues,
173			 allow_cast_as_lvalue);
174
175    case TARGET_EXPR:
176      return treat_class_rvalues_as_lvalues ? clk_class : clk_none;
177
178    case CALL_EXPR:
179    case VA_ARG_EXPR:
180      return ((treat_class_rvalues_as_lvalues
181	       && IS_AGGR_TYPE (TREE_TYPE (ref)))
182	      ? clk_class : clk_none);
183
184    case FUNCTION_DECL:
185      /* All functions (except non-static-member functions) are
186	 lvalues.  */
187      return (DECL_NONSTATIC_MEMBER_FUNCTION_P (ref)
188	      ? clk_none : clk_ordinary);
189
190    default:
191      break;
192    }
193
194  /* If one operand is not an lvalue at all, then this expression is
195     not an lvalue.  */
196  if (!op1_lvalue_kind || !op2_lvalue_kind)
197    return clk_none;
198
199  /* Otherwise, it's an lvalue, and it has all the odd properties
200     contributed by either operand.  */
201  op1_lvalue_kind = op1_lvalue_kind | op2_lvalue_kind;
202  /* It's not an ordinary lvalue if it involves either a bit-field or
203     a class rvalue.  */
204  if ((op1_lvalue_kind & ~clk_ordinary) != clk_none)
205    op1_lvalue_kind &= ~clk_ordinary;
206  return op1_lvalue_kind;
207}
208
209/* If REF is an lvalue, returns the kind of lvalue that REF is.
210   Otherwise, returns clk_none.  Lvalues can be assigned, unless they
211   have TREE_READONLY, or unless they are FUNCTION_DECLs.  Lvalues can
212   have their address taken, unless they have DECL_REGISTER.  */
213
214cp_lvalue_kind
215real_lvalue_p (ref)
216     tree ref;
217{
218  return lvalue_p_1 (ref, /*treat_class_rvalues_as_lvalues=*/ 0, /*cast*/ 1);
219}
220
221/* Returns the kind of lvalue that REF is, in the sense of
222   [basic.lval].  This function should really be named lvalue_p; it
223   computes the C++ definition of lvalue.  */
224
225cp_lvalue_kind
226real_non_cast_lvalue_p (tree ref)
227{
228  return lvalue_p_1 (ref,
229		     /*treat_class_rvalues_as_lvalues=*/0,
230		     /*allow_cast_as_lvalue=*/0);
231}
232
233/* This differs from real_lvalue_p in that class rvalues are
234   considered lvalues.  */
235
236int
237lvalue_p (ref)
238     tree ref;
239{
240  return
241    (lvalue_p_1 (ref, /*class rvalue ok*/ 1, /*cast*/ 1) != clk_none);
242}
243
244int
245non_cast_lvalue_p (ref)
246     tree ref;
247{
248  return
249    (lvalue_p_1 (ref, /*class rvalue ok*/ 1, /*cast*/ 0) != clk_none);
250}
251
252/* Return nonzero if REF is an lvalue valid for this language;
253   otherwise, print an error message and return zero.  */
254
255int
256lvalue_or_else (ref, string)
257     tree ref;
258     const char *string;
259{
260  int ret = lvalue_p_1 (ref, /* class rvalue ok */ 1, /* cast ok */ 1);
261  int win = (ret != clk_none);
262  if (! win)
263    error ("non-lvalue in %s", string);
264  return win;
265}
266
267int
268non_cast_lvalue_or_else (ref, string)
269     tree ref;
270     const char *string;
271{
272  int ret = lvalue_p_1 (ref, /* class rvalue ok */ 1, /* cast ok */ 0);
273  int win = (ret != clk_none);
274  if (! win)
275    error ("non-lvalue in %s", string);
276  return win;
277}
278
279/* Build a TARGET_EXPR, initializing the DECL with the VALUE.  */
280
281static tree
282build_target_expr (decl, value)
283     tree decl;
284     tree value;
285{
286  tree t;
287
288  t = build (TARGET_EXPR, TREE_TYPE (decl), decl, value,
289	     cxx_maybe_build_cleanup (decl), NULL_TREE);
290  /* We always set TREE_SIDE_EFFECTS so that expand_expr does not
291     ignore the TARGET_EXPR.  If there really turn out to be no
292     side-effects, then the optimizer should be able to get rid of
293     whatever code is generated anyhow.  */
294  TREE_SIDE_EFFECTS (t) = 1;
295
296  return t;
297}
298
299/* INIT is a CALL_EXPR which needs info about its target.
300   TYPE is the type that this initialization should appear to have.
301
302   Build an encapsulation of the initialization to perform
303   and return it so that it can be processed by language-independent
304   and language-specific expression expanders.  */
305
306tree
307build_cplus_new (type, init)
308     tree type;
309     tree init;
310{
311  tree fn;
312  tree slot;
313  tree rval;
314
315  /* Make sure that we're not trying to create an instance of an
316     abstract class.  */
317  abstract_virtuals_error (NULL_TREE, type);
318
319  if (TREE_CODE (init) != CALL_EXPR && TREE_CODE (init) != AGGR_INIT_EXPR)
320    return convert (type, init);
321
322  slot = build (VAR_DECL, type);
323  DECL_ARTIFICIAL (slot) = 1;
324  DECL_CONTEXT (slot) = current_function_decl;
325  layout_decl (slot, 0);
326
327  /* We split the CALL_EXPR into its function and its arguments here.
328     Then, in expand_expr, we put them back together.  The reason for
329     this is that this expression might be a default argument
330     expression.  In that case, we need a new temporary every time the
331     expression is used.  That's what break_out_target_exprs does; it
332     replaces every AGGR_INIT_EXPR with a copy that uses a fresh
333     temporary slot.  Then, expand_expr builds up a call-expression
334     using the new slot.  */
335  fn = TREE_OPERAND (init, 0);
336  rval = build (AGGR_INIT_EXPR, type, fn, TREE_OPERAND (init, 1), slot);
337  TREE_SIDE_EFFECTS (rval) = 1;
338  AGGR_INIT_VIA_CTOR_P (rval)
339    = (TREE_CODE (fn) == ADDR_EXPR
340       && TREE_CODE (TREE_OPERAND (fn, 0)) == FUNCTION_DECL
341       && DECL_CONSTRUCTOR_P (TREE_OPERAND (fn, 0)));
342  rval = build_target_expr (slot, rval);
343
344  return rval;
345}
346
347/* Build a TARGET_EXPR using INIT to initialize a new temporary of the
348   indicated TYPE.  */
349
350tree
351build_target_expr_with_type (init, type)
352     tree init;
353     tree type;
354{
355  tree slot;
356  tree rval;
357
358  if (TREE_CODE (init) == TARGET_EXPR)
359    return init;
360
361  slot = build (VAR_DECL, type);
362  DECL_ARTIFICIAL (slot) = 1;
363  DECL_CONTEXT (slot) = current_function_decl;
364  layout_decl (slot, 0);
365  rval = build_target_expr (slot, init);
366
367  return rval;
368}
369
370/* Like build_target_expr_with_type, but use the type of INIT.  */
371
372tree
373get_target_expr (init)
374     tree init;
375{
376  return build_target_expr_with_type (init, TREE_TYPE (init));
377}
378
379/* Recursively perform a preorder search EXP for CALL_EXPRs, making
380   copies where they are found.  Returns a deep copy all nodes transitively
381   containing CALL_EXPRs.  */
382
383tree
384break_out_calls (exp)
385     tree exp;
386{
387  register tree t1, t2 = NULL_TREE;
388  register enum tree_code code;
389  register int changed = 0;
390  register int i;
391
392  if (exp == NULL_TREE)
393    return exp;
394
395  code = TREE_CODE (exp);
396
397  if (code == CALL_EXPR)
398    return copy_node (exp);
399
400  /* Don't try and defeat a save_expr, as it should only be done once.  */
401    if (code == SAVE_EXPR)
402       return exp;
403
404  switch (TREE_CODE_CLASS (code))
405    {
406    default:
407      abort ();
408
409    case 'c':  /* a constant */
410    case 't':  /* a type node */
411    case 'x':  /* something random, like an identifier or an ERROR_MARK.  */
412      return exp;
413
414    case 'd':  /* A decl node */
415#if 0                               /* This is bogus.  jason 9/21/94 */
416
417      t1 = break_out_calls (DECL_INITIAL (exp));
418      if (t1 != DECL_INITIAL (exp))
419	{
420	  exp = copy_node (exp);
421	  DECL_INITIAL (exp) = t1;
422	}
423#endif
424      return exp;
425
426    case 'b':  /* A block node */
427      {
428	/* Don't know how to handle these correctly yet.   Must do a
429	   break_out_calls on all DECL_INITIAL values for local variables,
430	   and also break_out_calls on all sub-blocks and sub-statements.  */
431	abort ();
432      }
433      return exp;
434
435    case 'e':  /* an expression */
436    case 'r':  /* a reference */
437    case 's':  /* an expression with side effects */
438      for (i = TREE_CODE_LENGTH (code) - 1; i >= 0; i--)
439	{
440	  t1 = break_out_calls (TREE_OPERAND (exp, i));
441	  if (t1 != TREE_OPERAND (exp, i))
442	    {
443	      exp = copy_node (exp);
444	      TREE_OPERAND (exp, i) = t1;
445	    }
446	}
447      return exp;
448
449    case '<':  /* a comparison expression */
450    case '2':  /* a binary arithmetic expression */
451      t2 = break_out_calls (TREE_OPERAND (exp, 1));
452      if (t2 != TREE_OPERAND (exp, 1))
453	changed = 1;
454    case '1':  /* a unary arithmetic expression */
455      t1 = break_out_calls (TREE_OPERAND (exp, 0));
456      if (t1 != TREE_OPERAND (exp, 0))
457	changed = 1;
458      if (changed)
459	{
460	  if (TREE_CODE_LENGTH (code) == 1)
461	    return build1 (code, TREE_TYPE (exp), t1);
462	  else
463	    return build (code, TREE_TYPE (exp), t1, t2);
464	}
465      return exp;
466    }
467
468}
469
470/* Construct, lay out and return the type of methods belonging to class
471   BASETYPE and whose arguments are described by ARGTYPES and whose values
472   are described by RETTYPE.  If each type exists already, reuse it.  */
473
474tree
475build_cplus_method_type (basetype, rettype, argtypes)
476     tree basetype, rettype, argtypes;
477{
478  register tree t;
479  tree ptype;
480  int hashcode;
481
482  /* Make a node of the sort we want.  */
483  t = make_node (METHOD_TYPE);
484
485  TYPE_METHOD_BASETYPE (t) = TYPE_MAIN_VARIANT (basetype);
486  TREE_TYPE (t) = rettype;
487  ptype = build_pointer_type (basetype);
488
489  /* The actual arglist for this function includes a "hidden" argument
490     which is "this".  Put it into the list of argument types.  */
491  argtypes = tree_cons (NULL_TREE, ptype, argtypes);
492  TYPE_ARG_TYPES (t) = argtypes;
493  TREE_SIDE_EFFECTS (argtypes) = 1;  /* Mark first argtype as "artificial".  */
494
495  /* If we already have such a type, use the old one and free this one.
496     Note that it also frees up the above cons cell if found.  */
497  hashcode = TYPE_HASH (basetype) + TYPE_HASH (rettype) +
498    type_hash_list (argtypes);
499
500  t = type_hash_canon (hashcode, t);
501
502  if (!COMPLETE_TYPE_P (t))
503    layout_type (t);
504
505  return t;
506}
507
508static tree
509build_cplus_array_type_1 (elt_type, index_type)
510     tree elt_type;
511     tree index_type;
512{
513  tree t;
514
515  if (elt_type == error_mark_node || index_type == error_mark_node)
516    return error_mark_node;
517
518  /* Don't do the minimal thing just because processing_template_decl is
519     set; we want to give string constants the right type immediately, so
520     we don't have to fix them up at instantiation time.  */
521  if ((processing_template_decl
522       && index_type && TYPE_MAX_VALUE (index_type)
523       && TREE_CODE (TYPE_MAX_VALUE (index_type)) != INTEGER_CST)
524      || uses_template_parms (elt_type)
525      || (index_type && uses_template_parms (index_type)))
526    {
527      t = make_node (ARRAY_TYPE);
528      TREE_TYPE (t) = elt_type;
529      TYPE_DOMAIN (t) = index_type;
530    }
531  else
532    t = build_array_type (elt_type, index_type);
533
534  /* Push these needs up so that initialization takes place
535     more easily.  */
536  TYPE_NEEDS_CONSTRUCTING (t)
537    = TYPE_NEEDS_CONSTRUCTING (TYPE_MAIN_VARIANT (elt_type));
538  TYPE_HAS_NONTRIVIAL_DESTRUCTOR (t)
539    = TYPE_HAS_NONTRIVIAL_DESTRUCTOR (TYPE_MAIN_VARIANT (elt_type));
540  return t;
541}
542
543tree
544build_cplus_array_type (elt_type, index_type)
545     tree elt_type;
546     tree index_type;
547{
548  tree t;
549  int type_quals = cp_type_quals (elt_type);
550  int cv_quals = type_quals & (TYPE_QUAL_CONST|TYPE_QUAL_VOLATILE);
551  int other_quals = type_quals & ~(TYPE_QUAL_CONST|TYPE_QUAL_VOLATILE);
552
553  if (cv_quals)
554    elt_type = cp_build_qualified_type (elt_type, other_quals);
555
556  t = build_cplus_array_type_1 (elt_type, index_type);
557
558  if (cv_quals)
559    t = cp_build_qualified_type (t, cv_quals);
560
561  return t;
562}
563
564/* Make a variant of TYPE, qualified with the TYPE_QUALS.  Handles
565   arrays correctly.  In particular, if TYPE is an array of T's, and
566   TYPE_QUALS is non-empty, returns an array of qualified T's.
567
568   FLAGS determines how to deal with illformed qualifications. If
569   tf_ignore_bad_quals is set, then bad qualifications are dropped
570   (this is permitted if TYPE was introduced via a typedef or template
571   type parameter). If bad qualifications are dropped and tf_warning
572   is set, then a warning is issued for non-const qualifications.  If
573   tf_ignore_bad_quals is not set and tf_error is not set, we
574   return error_mark_node. Otherwise, we issue an error, and ignore
575   the qualifications.
576
577   Qualification of a reference type is valid when the reference came
578   via a typedef or template type argument. [dcl.ref] No such
579   dispensation is provided for qualifying a function type.  [dcl.fct]
580   DR 295 queries this and the proposed resolution brings it into line
581   with qualifiying a reference.  We implement the DR.  We also behave
582   in a similar manner for restricting non-pointer types.  */
583
584tree
585cp_build_qualified_type_real (type, type_quals, complain)
586     tree type;
587     int type_quals;
588     tsubst_flags_t complain;
589{
590  tree result;
591  int bad_quals = TYPE_UNQUALIFIED;
592  /* We keep bad function qualifiers separate, so that we can decide
593     whether to implement DR 295 or not. DR 295 break existing code,
594     unfortunately. Remove this variable to implement the defect
595     report.  */
596  int bad_func_quals = TYPE_UNQUALIFIED;
597
598  if (type == error_mark_node)
599    return type;
600
601  if (type_quals == cp_type_quals (type))
602    return type;
603
604  /* A reference, fucntion or method type shall not be cv qualified.
605     [dcl.ref], [dct.fct]  */
606  if (type_quals & (TYPE_QUAL_CONST | TYPE_QUAL_VOLATILE)
607      && (TREE_CODE (type) == REFERENCE_TYPE
608	  || TREE_CODE (type) == FUNCTION_TYPE
609	  || TREE_CODE (type) == METHOD_TYPE))
610    {
611      bad_quals |= type_quals & (TYPE_QUAL_CONST | TYPE_QUAL_VOLATILE);
612      if (TREE_CODE (type) != REFERENCE_TYPE)
613	bad_func_quals |= type_quals & (TYPE_QUAL_CONST | TYPE_QUAL_VOLATILE);
614      type_quals &= ~(TYPE_QUAL_CONST | TYPE_QUAL_VOLATILE);
615    }
616
617  /* A restrict-qualified type must be a pointer (or reference)
618     to object or incomplete type.  */
619  if ((type_quals & TYPE_QUAL_RESTRICT)
620      && TREE_CODE (type) != TEMPLATE_TYPE_PARM
621      && TREE_CODE (type) != TYPENAME_TYPE
622      && !POINTER_TYPE_P (type))
623    {
624      bad_quals |= TYPE_QUAL_RESTRICT;
625      type_quals &= ~TYPE_QUAL_RESTRICT;
626    }
627
628  if (bad_quals == TYPE_UNQUALIFIED)
629    /*OK*/;
630  else if (!(complain & (tf_error | tf_ignore_bad_quals)))
631    return error_mark_node;
632  else if (bad_func_quals && !(complain & tf_error))
633    return error_mark_node;
634  else
635    {
636      if (complain & tf_ignore_bad_quals)
637 	/* We're not going to warn about constifying things that can't
638 	   be constified.  */
639 	bad_quals &= ~TYPE_QUAL_CONST;
640      bad_quals |= bad_func_quals;
641      if (bad_quals)
642 	{
643 	  tree bad_type = build_qualified_type (ptr_type_node, bad_quals);
644
645 	  if (!(complain & tf_ignore_bad_quals)
646	      || bad_func_quals)
647 	    error ("`%V' qualifiers cannot be applied to `%T'",
648		   bad_type, type);
649 	}
650    }
651
652  if (TREE_CODE (type) == ARRAY_TYPE)
653    {
654      /* In C++, the qualification really applies to the array element
655	 type.  Obtain the appropriately qualified element type.  */
656      tree t;
657      tree element_type
658	= cp_build_qualified_type_real (TREE_TYPE (type),
659					type_quals,
660					complain);
661
662      if (element_type == error_mark_node)
663	return error_mark_node;
664
665      /* See if we already have an identically qualified type.  */
666      for (t = TYPE_MAIN_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
667	if (cp_type_quals (t) == type_quals
668	    && TYPE_NAME (t) == TYPE_NAME (type)
669	    && TYPE_CONTEXT (t) == TYPE_CONTEXT (type))
670	  break;
671
672      if (!t)
673	{
674	  /* Make a new array type, just like the old one, but with the
675	     appropriately qualified element type.  */
676	  t = build_type_copy (type);
677	  TREE_TYPE (t) = element_type;
678	}
679
680      /* Even if we already had this variant, we update
681	 TYPE_NEEDS_CONSTRUCTING and TYPE_HAS_NONTRIVIAL_DESTRUCTOR in case
682	 they changed since the variant was originally created.
683
684	 This seems hokey; if there is some way to use a previous
685	 variant *without* coming through here,
686	 TYPE_NEEDS_CONSTRUCTING will never be updated.  */
687      TYPE_NEEDS_CONSTRUCTING (t)
688	= TYPE_NEEDS_CONSTRUCTING (TYPE_MAIN_VARIANT (element_type));
689      TYPE_HAS_NONTRIVIAL_DESTRUCTOR (t)
690	= TYPE_HAS_NONTRIVIAL_DESTRUCTOR (TYPE_MAIN_VARIANT (element_type));
691      return t;
692    }
693  else if (TYPE_PTRMEMFUNC_P (type))
694    {
695      /* For a pointer-to-member type, we can't just return a
696	 cv-qualified version of the RECORD_TYPE.  If we do, we
697	 haven't changed the field that contains the actual pointer to
698	 a method, and so TYPE_PTRMEMFUNC_FN_TYPE will be wrong.  */
699      tree t;
700
701      t = TYPE_PTRMEMFUNC_FN_TYPE (type);
702      t = cp_build_qualified_type_real (t, type_quals, complain);
703      return build_ptrmemfunc_type (t);
704    }
705
706  /* Retrieve (or create) the appropriately qualified variant.  */
707  result = build_qualified_type (type, type_quals);
708
709  /* If this was a pointer-to-method type, and we just made a copy,
710     then we need to unshare the record that holds the cached
711     pointer-to-member-function type, because these will be distinct
712     between the unqualified and qualified types.  */
713  if (result != type
714      && TREE_CODE (type) == POINTER_TYPE
715      && TREE_CODE (TREE_TYPE (type)) == METHOD_TYPE)
716    TYPE_LANG_SPECIFIC (result) = NULL;
717
718  return result;
719}
720
721/* Returns the canonical version of TYPE.  In other words, if TYPE is
722   a typedef, returns the underlying type.  The cv-qualification of
723   the type returned matches the type input; they will always be
724   compatible types.  */
725
726tree
727canonical_type_variant (t)
728     tree t;
729{
730  return cp_build_qualified_type (TYPE_MAIN_VARIANT (t), cp_type_quals (t));
731}
732
733/* Makes new binfos for the indirect bases under BINFO, and updates
734   BINFO_OFFSET for them and their bases.  */
735
736void
737unshare_base_binfos (binfo)
738     tree binfo;
739{
740  tree binfos = BINFO_BASETYPES (binfo);
741  tree new_binfo;
742  int j;
743
744  if (binfos == NULL_TREE)
745    return;
746
747  /* Now unshare the structure beneath BINFO.  */
748  for (j = TREE_VEC_LENGTH (binfos)-1;
749       j >= 0; j--)
750    {
751      tree base_binfo = TREE_VEC_ELT (binfos, j);
752      new_binfo = TREE_VEC_ELT (binfos, j)
753	= make_binfo (BINFO_OFFSET (base_binfo),
754		      base_binfo,
755		      BINFO_VTABLE (base_binfo),
756		      BINFO_VIRTUALS (base_binfo));
757      TREE_VIA_PUBLIC (new_binfo) = TREE_VIA_PUBLIC (base_binfo);
758      TREE_VIA_PROTECTED (new_binfo) = TREE_VIA_PROTECTED (base_binfo);
759      TREE_VIA_VIRTUAL (new_binfo) = TREE_VIA_VIRTUAL (base_binfo);
760      BINFO_INHERITANCE_CHAIN (new_binfo) = binfo;
761      BINFO_PRIMARY_BASE_OF (new_binfo) = NULL_TREE;
762      unshare_base_binfos (new_binfo);
763    }
764}
765
766
767/* Hashing of lists so that we don't make duplicates.
768   The entry point is `list_hash_canon'.  */
769
770/* Now here is the hash table.  When recording a list, it is added
771   to the slot whose index is the hash code mod the table size.
772   Note that the hash table is used for several kinds of lists.
773   While all these live in the same table, they are completely independent,
774   and the hash code is computed differently for each of these.  */
775
776static GTY ((param_is (union tree_node))) htab_t list_hash_table;
777
778struct list_proxy
779{
780  tree purpose;
781  tree value;
782  tree chain;
783};
784
785/* Compare ENTRY (an entry in the hash table) with DATA (a list_proxy
786   for a node we are thinking about adding).  */
787
788static int
789list_hash_eq (entry, data)
790     const void *entry;
791     const void *data;
792{
793  tree t = (tree) entry;
794  struct list_proxy *proxy = (struct list_proxy *) data;
795
796  return (TREE_VALUE (t) == proxy->value
797	  && TREE_PURPOSE (t) == proxy->purpose
798	  && TREE_CHAIN (t) == proxy->chain);
799}
800
801/* Compute a hash code for a list (chain of TREE_LIST nodes
802   with goodies in the TREE_PURPOSE, TREE_VALUE, and bits of the
803   TREE_COMMON slots), by adding the hash codes of the individual entries.  */
804
805static hashval_t
806list_hash_pieces (purpose, value, chain)
807     tree purpose;
808     tree value;
809     tree chain;
810{
811  hashval_t hashcode = 0;
812
813  if (chain)
814    hashcode += TYPE_HASH (chain);
815
816  if (value)
817    hashcode += TYPE_HASH (value);
818  else
819    hashcode += 1007;
820  if (purpose)
821    hashcode += TYPE_HASH (purpose);
822  else
823    hashcode += 1009;
824  return hashcode;
825}
826
827/* Hash an already existing TREE_LIST.  */
828
829static hashval_t
830list_hash (p)
831     const void *p;
832{
833  tree t = (tree) p;
834  return list_hash_pieces (TREE_PURPOSE (t),
835			   TREE_VALUE (t),
836			   TREE_CHAIN (t));
837}
838
839/* Given list components PURPOSE, VALUE, AND CHAIN, return the canonical
840   object for an identical list if one already exists.  Otherwise, build a
841   new one, and record it as the canonical object.  */
842
843tree
844hash_tree_cons (purpose, value, chain)
845     tree purpose, value, chain;
846{
847  int hashcode = 0;
848  PTR* slot;
849  struct list_proxy proxy;
850
851  /* Hash the list node.  */
852  hashcode = list_hash_pieces (purpose, value, chain);
853  /* Create a proxy for the TREE_LIST we would like to create.  We
854     don't actually create it so as to avoid creating garbage.  */
855  proxy.purpose = purpose;
856  proxy.value = value;
857  proxy.chain = chain;
858  /* See if it is already in the table.  */
859  slot = htab_find_slot_with_hash (list_hash_table, &proxy, hashcode,
860				   INSERT);
861  /* If not, create a new node.  */
862  if (!*slot)
863    *slot = (PTR) tree_cons (purpose, value, chain);
864  return *slot;
865}
866
867/* Constructor for hashed lists.  */
868
869tree
870hash_tree_chain (value, chain)
871     tree value, chain;
872{
873  return hash_tree_cons (NULL_TREE, value, chain);
874}
875
876/* Similar, but used for concatenating two lists.  */
877
878tree
879hash_chainon (list1, list2)
880     tree list1, list2;
881{
882  if (list2 == 0)
883    return list1;
884  if (list1 == 0)
885    return list2;
886  if (TREE_CHAIN (list1) == NULL_TREE)
887    return hash_tree_chain (TREE_VALUE (list1), list2);
888  return hash_tree_chain (TREE_VALUE (list1),
889			  hash_chainon (TREE_CHAIN (list1), list2));
890}
891
892/* Build an association between TYPE and some parameters:
893
894   OFFSET is the offset added to `this' to convert it to a pointer
895   of type `TYPE *'
896
897   BINFO is the base binfo to use, if we are deriving from one.  This
898   is necessary, as we want specialized parent binfos from base
899   classes, so that the VTABLE_NAMEs of bases are for the most derived
900   type, instead of the simple type.
901
902   VTABLE is the virtual function table with which to initialize
903   sub-objects of type TYPE.
904
905   VIRTUALS are the virtual functions sitting in VTABLE.  */
906
907tree
908make_binfo (offset, binfo, vtable, virtuals)
909     tree offset, binfo;
910     tree vtable, virtuals;
911{
912  tree new_binfo = make_tree_vec (11);
913  tree type;
914
915  if (TREE_CODE (binfo) == TREE_VEC)
916    type = BINFO_TYPE (binfo);
917  else
918    {
919      type = binfo;
920      binfo = CLASS_TYPE_P (type) ? TYPE_BINFO (binfo) : NULL_TREE;
921    }
922
923  TREE_TYPE (new_binfo) = TYPE_MAIN_VARIANT (type);
924  BINFO_OFFSET (new_binfo) = offset;
925  BINFO_VTABLE (new_binfo) = vtable;
926  BINFO_VIRTUALS (new_binfo) = virtuals;
927
928  if (binfo && BINFO_BASETYPES (binfo) != NULL_TREE)
929    BINFO_BASETYPES (new_binfo) = copy_node (BINFO_BASETYPES (binfo));
930  return new_binfo;
931}
932
933/* Return a TREE_LIST whose TREE_VALUE nodes along the
934   BINFO_INHERITANCE_CHAIN for BINFO, but in the opposite order.  In
935   other words, while the BINFO_INHERITANCE_CHAIN goes from base
936   classes to derived classes, the reversed path goes from derived
937   classes to base classes.  */
938
939tree
940reverse_path (binfo)
941     tree binfo;
942{
943  tree reversed_path;
944
945  reversed_path = NULL_TREE;
946  while (binfo)
947    {
948      reversed_path = tree_cons (NULL_TREE, binfo, reversed_path);
949      binfo = BINFO_INHERITANCE_CHAIN (binfo);
950    }
951
952  return reversed_path;
953}
954
955void
956debug_binfo (elem)
957     tree elem;
958{
959  HOST_WIDE_INT n;
960  tree virtuals;
961
962  fprintf (stderr, "type \"%s\", offset = ",
963	   TYPE_NAME_STRING (BINFO_TYPE (elem)));
964  fprintf (stderr, HOST_WIDE_INT_PRINT_DEC,
965	   TREE_INT_CST_LOW (BINFO_OFFSET (elem)));
966  fprintf (stderr, "\nvtable type:\n");
967  debug_tree (BINFO_TYPE (elem));
968  if (BINFO_VTABLE (elem))
969    fprintf (stderr, "vtable decl \"%s\"\n",
970	     IDENTIFIER_POINTER (DECL_NAME (get_vtbl_decl_for_binfo (elem))));
971  else
972    fprintf (stderr, "no vtable decl yet\n");
973  fprintf (stderr, "virtuals:\n");
974  virtuals = BINFO_VIRTUALS (elem);
975  n = 0;
976
977  while (virtuals)
978    {
979      tree fndecl = TREE_VALUE (virtuals);
980      fprintf (stderr, "%s [%ld =? %ld]\n",
981	       IDENTIFIER_POINTER (DECL_ASSEMBLER_NAME (fndecl)),
982	       (long) n, (long) TREE_INT_CST_LOW (DECL_VINDEX (fndecl)));
983      ++n;
984      virtuals = TREE_CHAIN (virtuals);
985    }
986}
987
988int
989count_functions (t)
990     tree t;
991{
992  int i;
993  if (TREE_CODE (t) == FUNCTION_DECL)
994    return 1;
995  else if (TREE_CODE (t) == OVERLOAD)
996    {
997      for (i=0; t; t = OVL_CHAIN (t))
998	i++;
999      return i;
1000    }
1001
1002  abort ();
1003  return 0;
1004}
1005
1006int
1007is_overloaded_fn (x)
1008     tree x;
1009{
1010  /* A baselink is also considered an overloaded function.  */
1011  if (TREE_CODE (x) == OFFSET_REF)
1012    x = TREE_OPERAND (x, 1);
1013  if (BASELINK_P (x))
1014    x = BASELINK_FUNCTIONS (x);
1015  return (TREE_CODE (x) == FUNCTION_DECL
1016	  || TREE_CODE (x) == TEMPLATE_ID_EXPR
1017	  || DECL_FUNCTION_TEMPLATE_P (x)
1018	  || TREE_CODE (x) == OVERLOAD);
1019}
1020
1021int
1022really_overloaded_fn (x)
1023     tree x;
1024{
1025  /* A baselink is also considered an overloaded function.  */
1026  if (TREE_CODE (x) == OFFSET_REF)
1027    x = TREE_OPERAND (x, 1);
1028  if (BASELINK_P (x))
1029    x = BASELINK_FUNCTIONS (x);
1030
1031  return ((TREE_CODE (x) == OVERLOAD && OVL_CHAIN (x))
1032	  || DECL_FUNCTION_TEMPLATE_P (OVL_CURRENT (x))
1033	  || TREE_CODE (x) == TEMPLATE_ID_EXPR);
1034}
1035
1036/* Return the OVERLOAD or FUNCTION_DECL inside FNS.  FNS can be an
1037   OVERLOAD, FUNCTION_DECL, TEMPLATE_ID_EXPR, or baselink.  */
1038
1039tree
1040get_overloaded_fn (fns)
1041     tree fns;
1042{
1043  if (TREE_CODE (fns) == TEMPLATE_ID_EXPR)
1044    fns = TREE_OPERAND (fns, 0);
1045  if (BASELINK_P (fns))
1046    fns = BASELINK_FUNCTIONS (fns);
1047  return fns;
1048}
1049
1050tree
1051get_first_fn (from)
1052     tree from;
1053{
1054  my_friendly_assert (is_overloaded_fn (from), 9);
1055  /* A baselink is also considered an overloaded function.  */
1056  if (BASELINK_P (from))
1057    from = BASELINK_FUNCTIONS (from);
1058  return OVL_CURRENT (from);
1059}
1060
1061/* Returns nonzero if T is a ->* or .* expression that refers to a
1062   member function.  */
1063
1064int
1065bound_pmf_p (t)
1066     tree t;
1067{
1068  return (TREE_CODE (t) == OFFSET_REF
1069	  && TYPE_PTRMEMFUNC_P (TREE_TYPE (TREE_OPERAND (t, 1))));
1070}
1071
1072/* Return a new OVL node, concatenating it with the old one.  */
1073
1074tree
1075ovl_cons (decl, chain)
1076     tree decl;
1077     tree chain;
1078{
1079  tree result = make_node (OVERLOAD);
1080  TREE_TYPE (result) = unknown_type_node;
1081  OVL_FUNCTION (result) = decl;
1082  TREE_CHAIN (result) = chain;
1083
1084  return result;
1085}
1086
1087/* Build a new overloaded function. If this is the first one,
1088   just return it; otherwise, ovl_cons the _DECLs */
1089
1090tree
1091build_overload (decl, chain)
1092     tree decl;
1093     tree chain;
1094{
1095  if (! chain && TREE_CODE (decl) != TEMPLATE_DECL)
1096    return decl;
1097  if (chain && TREE_CODE (chain) != OVERLOAD)
1098    chain = ovl_cons (chain, NULL_TREE);
1099  return ovl_cons (decl, chain);
1100}
1101
1102int
1103is_aggr_type_2 (t1, t2)
1104     tree t1, t2;
1105{
1106  if (TREE_CODE (t1) != TREE_CODE (t2))
1107    return 0;
1108  return IS_AGGR_TYPE (t1) && IS_AGGR_TYPE (t2);
1109}
1110
1111/* Returns nonzero if CODE is the code for a statement.  */
1112
1113int
1114cp_statement_code_p (code)
1115     enum tree_code code;
1116{
1117  switch (code)
1118    {
1119    case CTOR_INITIALIZER:
1120    case RETURN_INIT:
1121    case TRY_BLOCK:
1122    case HANDLER:
1123    case EH_SPEC_BLOCK:
1124    case USING_STMT:
1125    case TAG_DEFN:
1126      return 1;
1127
1128    default:
1129      return 0;
1130    }
1131}
1132
1133#define PRINT_RING_SIZE 4
1134
1135const char *
1136cxx_printable_name (decl, v)
1137     tree decl;
1138     int v;
1139{
1140  static tree decl_ring[PRINT_RING_SIZE];
1141  static char *print_ring[PRINT_RING_SIZE];
1142  static int ring_counter;
1143  int i;
1144
1145  /* Only cache functions.  */
1146  if (v < 2
1147      || TREE_CODE (decl) != FUNCTION_DECL
1148      || DECL_LANG_SPECIFIC (decl) == 0)
1149    return lang_decl_name (decl, v);
1150
1151  /* See if this print name is lying around.  */
1152  for (i = 0; i < PRINT_RING_SIZE; i++)
1153    if (decl_ring[i] == decl)
1154      /* yes, so return it.  */
1155      return print_ring[i];
1156
1157  if (++ring_counter == PRINT_RING_SIZE)
1158    ring_counter = 0;
1159
1160  if (current_function_decl != NULL_TREE)
1161    {
1162      if (decl_ring[ring_counter] == current_function_decl)
1163	ring_counter += 1;
1164      if (ring_counter == PRINT_RING_SIZE)
1165	ring_counter = 0;
1166      if (decl_ring[ring_counter] == current_function_decl)
1167	abort ();
1168    }
1169
1170  if (print_ring[ring_counter])
1171    free (print_ring[ring_counter]);
1172
1173  print_ring[ring_counter] = xstrdup (lang_decl_name (decl, v));
1174  decl_ring[ring_counter] = decl;
1175  return print_ring[ring_counter];
1176}
1177
1178/* Build the FUNCTION_TYPE or METHOD_TYPE which may throw exceptions
1179   listed in RAISES.  */
1180
1181tree
1182build_exception_variant (type, raises)
1183     tree type;
1184     tree raises;
1185{
1186  tree v = TYPE_MAIN_VARIANT (type);
1187  int type_quals = TYPE_QUALS (type);
1188
1189  for (; v; v = TYPE_NEXT_VARIANT (v))
1190    if (TYPE_QUALS (v) == type_quals
1191        && comp_except_specs (raises, TYPE_RAISES_EXCEPTIONS (v), 1))
1192      return v;
1193
1194  /* Need to build a new variant.  */
1195  v = build_type_copy (type);
1196  TYPE_RAISES_EXCEPTIONS (v) = raises;
1197  return v;
1198}
1199
1200/* Given a TEMPLATE_TEMPLATE_PARM node T, create a new
1201   BOUND_TEMPLATE_TEMPLATE_PARM bound with NEWARGS as its template
1202   arguments.  */
1203
1204tree
1205bind_template_template_parm (t, newargs)
1206     tree t;
1207     tree newargs;
1208{
1209  tree decl = TYPE_NAME (t);
1210  tree t2;
1211
1212  t2 = make_aggr_type (BOUND_TEMPLATE_TEMPLATE_PARM);
1213  decl = build_decl (TYPE_DECL, DECL_NAME (decl), NULL_TREE);
1214
1215  /* These nodes have to be created to reflect new TYPE_DECL and template
1216     arguments.  */
1217  TEMPLATE_TYPE_PARM_INDEX (t2) = copy_node (TEMPLATE_TYPE_PARM_INDEX (t));
1218  TEMPLATE_PARM_DECL (TEMPLATE_TYPE_PARM_INDEX (t2)) = decl;
1219  TEMPLATE_TEMPLATE_PARM_TEMPLATE_INFO (t2)
1220    = tree_cons (TEMPLATE_TEMPLATE_PARM_TEMPLATE_DECL (t),
1221		 newargs, NULL_TREE);
1222
1223  TREE_TYPE (decl) = t2;
1224  TYPE_NAME (t2) = decl;
1225  TYPE_STUB_DECL (t2) = decl;
1226  TYPE_SIZE (t2) = 0;
1227
1228  return t2;
1229}
1230
1231/* Called from count_trees via walk_tree.  */
1232
1233static tree
1234count_trees_r (tp, walk_subtrees, data)
1235     tree *tp ATTRIBUTE_UNUSED;
1236     int *walk_subtrees ATTRIBUTE_UNUSED;
1237     void *data;
1238{
1239  ++ *((int*) data);
1240  return NULL_TREE;
1241}
1242
1243/* Debugging function for measuring the rough complexity of a tree
1244   representation.  */
1245
1246int
1247count_trees (t)
1248     tree t;
1249{
1250  int n_trees = 0;
1251  walk_tree_without_duplicates (&t, count_trees_r, &n_trees);
1252  return n_trees;
1253}
1254
1255/* Called from verify_stmt_tree via walk_tree.  */
1256
1257static tree
1258verify_stmt_tree_r (tp, walk_subtrees, data)
1259     tree *tp;
1260     int *walk_subtrees ATTRIBUTE_UNUSED;
1261     void *data;
1262{
1263  tree t = *tp;
1264  htab_t *statements = (htab_t *) data;
1265  void **slot;
1266
1267  if (!statement_code_p (TREE_CODE (t)))
1268    return NULL_TREE;
1269
1270  /* If this statement is already present in the hash table, then
1271     there is a circularity in the statement tree.  */
1272  if (htab_find (*statements, t))
1273    abort ();
1274
1275  slot = htab_find_slot (*statements, t, INSERT);
1276  *slot = t;
1277
1278  return NULL_TREE;
1279}
1280
1281/* Debugging function to check that the statement T has not been
1282   corrupted.  For now, this function simply checks that T contains no
1283   circularities.  */
1284
1285void
1286verify_stmt_tree (t)
1287     tree t;
1288{
1289  htab_t statements;
1290  statements = htab_create (37, htab_hash_pointer, htab_eq_pointer, NULL);
1291  walk_tree (&t, verify_stmt_tree_r, &statements, NULL);
1292  htab_delete (statements);
1293}
1294
1295/* Called from find_tree via walk_tree.  */
1296
1297static tree
1298find_tree_r (tp, walk_subtrees, data)
1299     tree *tp;
1300     int *walk_subtrees ATTRIBUTE_UNUSED;
1301     void *data;
1302{
1303  if (*tp == (tree) data)
1304    return (tree) data;
1305
1306  return NULL_TREE;
1307}
1308
1309/* Returns X if X appears in the tree structure rooted at T.  */
1310
1311tree
1312find_tree (t, x)
1313     tree t;
1314     tree x;
1315{
1316  return walk_tree_without_duplicates (&t, find_tree_r, x);
1317}
1318
1319/* Passed to walk_tree.  Checks for the use of types with no linkage.  */
1320
1321static tree
1322no_linkage_helper (tp, walk_subtrees, data)
1323     tree *tp;
1324     int *walk_subtrees ATTRIBUTE_UNUSED;
1325     void *data ATTRIBUTE_UNUSED;
1326{
1327  tree t = *tp;
1328
1329  if (TYPE_P (t)
1330      && (CLASS_TYPE_P (t) || TREE_CODE (t) == ENUMERAL_TYPE)
1331      && (decl_function_context (TYPE_MAIN_DECL (t))
1332	  || TYPE_ANONYMOUS_P (t)))
1333    return t;
1334  return NULL_TREE;
1335}
1336
1337/* Check if the type T depends on a type with no linkage and if so, return
1338   it.  */
1339
1340tree
1341no_linkage_check (t)
1342     tree t;
1343{
1344  /* There's no point in checking linkage on template functions; we
1345     can't know their complete types.  */
1346  if (processing_template_decl)
1347    return NULL_TREE;
1348
1349  t = walk_tree_without_duplicates (&t, no_linkage_helper, NULL);
1350  if (t != error_mark_node)
1351    return t;
1352  return NULL_TREE;
1353}
1354
1355#ifdef GATHER_STATISTICS
1356extern int depth_reached;
1357#endif
1358
1359void
1360cxx_print_statistics ()
1361{
1362  print_search_statistics ();
1363  print_class_statistics ();
1364#ifdef GATHER_STATISTICS
1365  fprintf (stderr, "maximum template instantiation depth reached: %d\n",
1366	   depth_reached);
1367#endif
1368}
1369
1370/* Return, as an INTEGER_CST node, the number of elements for TYPE
1371   (which is an ARRAY_TYPE).  This counts only elements of the top
1372   array.  */
1373
1374tree
1375array_type_nelts_top (type)
1376     tree type;
1377{
1378  return fold (build (PLUS_EXPR, sizetype,
1379		      array_type_nelts (type),
1380		      integer_one_node));
1381}
1382
1383/* Return, as an INTEGER_CST node, the number of elements for TYPE
1384   (which is an ARRAY_TYPE).  This one is a recursive count of all
1385   ARRAY_TYPEs that are clumped together.  */
1386
1387tree
1388array_type_nelts_total (type)
1389     tree type;
1390{
1391  tree sz = array_type_nelts_top (type);
1392  type = TREE_TYPE (type);
1393  while (TREE_CODE (type) == ARRAY_TYPE)
1394    {
1395      tree n = array_type_nelts_top (type);
1396      sz = fold (build (MULT_EXPR, sizetype, sz, n));
1397      type = TREE_TYPE (type);
1398    }
1399  return sz;
1400}
1401
1402/* Called from break_out_target_exprs via mapcar.  */
1403
1404static tree
1405bot_manip (tp, walk_subtrees, data)
1406     tree *tp;
1407     int *walk_subtrees;
1408     void *data;
1409{
1410  splay_tree target_remap = ((splay_tree) data);
1411  tree t = *tp;
1412
1413  if (TREE_CONSTANT (t))
1414    {
1415      /* There can't be any TARGET_EXPRs or their slot variables below
1416         this point.  We used to check !TREE_SIDE_EFFECTS, but then we
1417         failed to copy an ADDR_EXPR of the slot VAR_DECL.  */
1418      *walk_subtrees = 0;
1419      return NULL_TREE;
1420    }
1421  if (TREE_CODE (t) == TARGET_EXPR)
1422    {
1423      tree u;
1424
1425      if (TREE_CODE (TREE_OPERAND (t, 1)) == AGGR_INIT_EXPR)
1426	{
1427	  mark_used (TREE_OPERAND (TREE_OPERAND (TREE_OPERAND (t, 1), 0), 0));
1428	  u = build_cplus_new
1429	    (TREE_TYPE (t), break_out_target_exprs (TREE_OPERAND (t, 1)));
1430	}
1431      else
1432	{
1433	  u = build_target_expr_with_type
1434	    (break_out_target_exprs (TREE_OPERAND (t, 1)), TREE_TYPE (t));
1435	}
1436
1437      /* Map the old variable to the new one.  */
1438      splay_tree_insert (target_remap,
1439			 (splay_tree_key) TREE_OPERAND (t, 0),
1440			 (splay_tree_value) TREE_OPERAND (u, 0));
1441
1442      /* Replace the old expression with the new version.  */
1443      *tp = u;
1444      /* We don't have to go below this point; the recursive call to
1445	 break_out_target_exprs will have handled anything below this
1446	 point.  */
1447      *walk_subtrees = 0;
1448      return NULL_TREE;
1449    }
1450  else if (TREE_CODE (t) == CALL_EXPR)
1451    mark_used (TREE_OPERAND (TREE_OPERAND (t, 0), 0));
1452
1453  /* Make a copy of this node.  */
1454  return copy_tree_r (tp, walk_subtrees, NULL);
1455}
1456
1457/* Replace all remapped VAR_DECLs in T with their new equivalents.
1458   DATA is really a splay-tree mapping old variables to new
1459   variables.  */
1460
1461static tree
1462bot_replace (t, walk_subtrees, data)
1463     tree *t;
1464     int *walk_subtrees ATTRIBUTE_UNUSED;
1465     void *data;
1466{
1467  splay_tree target_remap = ((splay_tree) data);
1468
1469  if (TREE_CODE (*t) == VAR_DECL)
1470    {
1471      splay_tree_node n = splay_tree_lookup (target_remap,
1472					     (splay_tree_key) *t);
1473      if (n)
1474	*t = (tree) n->value;
1475    }
1476
1477  return NULL_TREE;
1478}
1479
1480/* When we parse a default argument expression, we may create
1481   temporary variables via TARGET_EXPRs.  When we actually use the
1482   default-argument expression, we make a copy of the expression, but
1483   we must replace the temporaries with appropriate local versions.  */
1484
1485tree
1486break_out_target_exprs (t)
1487     tree t;
1488{
1489  static int target_remap_count;
1490  static splay_tree target_remap;
1491
1492  if (!target_remap_count++)
1493    target_remap = splay_tree_new (splay_tree_compare_pointers,
1494				   /*splay_tree_delete_key_fn=*/NULL,
1495				   /*splay_tree_delete_value_fn=*/NULL);
1496  walk_tree (&t, bot_manip, target_remap, NULL);
1497  walk_tree (&t, bot_replace, target_remap, NULL);
1498
1499  if (!--target_remap_count)
1500    {
1501      splay_tree_delete (target_remap);
1502      target_remap = NULL;
1503    }
1504
1505  return t;
1506}
1507
1508/* Obstack used for allocating nodes in template function and variable
1509   definitions.  */
1510
1511/* Similar to `build_nt', except that we set TREE_COMPLEXITY to be the
1512   current line number.  */
1513
1514tree
1515build_min_nt VPARAMS ((enum tree_code code, ...))
1516{
1517  register tree t;
1518  register int length;
1519  register int i;
1520
1521  VA_OPEN (p, code);
1522  VA_FIXEDARG (p, enum tree_code, code);
1523
1524  t = make_node (code);
1525  length = TREE_CODE_LENGTH (code);
1526  TREE_COMPLEXITY (t) = lineno;
1527
1528  for (i = 0; i < length; i++)
1529    {
1530      tree x = va_arg (p, tree);
1531      TREE_OPERAND (t, i) = x;
1532    }
1533
1534  VA_CLOSE (p);
1535  return t;
1536}
1537
1538/* Similar to `build', except we set TREE_COMPLEXITY to the current
1539   line-number.  */
1540
1541tree
1542build_min VPARAMS ((enum tree_code code, tree tt, ...))
1543{
1544  register tree t;
1545  register int length;
1546  register int i;
1547
1548  VA_OPEN (p, tt);
1549  VA_FIXEDARG (p, enum tree_code, code);
1550  VA_FIXEDARG (p, tree, tt);
1551
1552  t = make_node (code);
1553  length = TREE_CODE_LENGTH (code);
1554  TREE_TYPE (t) = tt;
1555  TREE_COMPLEXITY (t) = lineno;
1556
1557  for (i = 0; i < length; i++)
1558    {
1559      tree x = va_arg (p, tree);
1560      TREE_OPERAND (t, i) = x;
1561    }
1562
1563  VA_CLOSE (p);
1564  return t;
1565}
1566
1567/* Returns an INTEGER_CST (of type `int') corresponding to I.
1568   Multiple calls with the same value of I may or may not yield the
1569   same node; therefore, callers should never modify the node
1570   returned.  */
1571
1572static GTY(()) tree shared_int_cache[256];
1573
1574tree
1575build_shared_int_cst (i)
1576     int i;
1577{
1578  if (i >= 256)
1579    return build_int_2 (i, 0);
1580
1581  if (!shared_int_cache[i])
1582    shared_int_cache[i] = build_int_2 (i, 0);
1583
1584  return shared_int_cache[i];
1585}
1586
1587tree
1588get_type_decl (t)
1589     tree t;
1590{
1591  if (TREE_CODE (t) == TYPE_DECL)
1592    return t;
1593  if (TYPE_P (t))
1594    return TYPE_STUB_DECL (t);
1595  if (t == error_mark_node)
1596    return t;
1597
1598  abort ();
1599
1600  /* Stop compiler from complaining control reaches end of non-void function.  */
1601  return 0;
1602}
1603
1604/* Return first vector element whose BINFO_TYPE is ELEM.
1605   Return 0 if ELEM is not in VEC.  VEC may be NULL_TREE.  */
1606
1607tree
1608vec_binfo_member (elem, vec)
1609     tree elem, vec;
1610{
1611  int i;
1612
1613  if (vec)
1614    for (i = 0; i < TREE_VEC_LENGTH (vec); ++i)
1615      if (same_type_p (elem, BINFO_TYPE (TREE_VEC_ELT (vec, i))))
1616	return TREE_VEC_ELT (vec, i);
1617
1618  return NULL_TREE;
1619}
1620
1621/* Returns the namespace that contains DECL, whether directly or
1622   indirectly.  */
1623
1624tree
1625decl_namespace_context (decl)
1626     tree decl;
1627{
1628  while (1)
1629    {
1630      if (TREE_CODE (decl) == NAMESPACE_DECL)
1631	return decl;
1632      else if (TYPE_P (decl))
1633	decl = CP_DECL_CONTEXT (TYPE_MAIN_DECL (decl));
1634      else
1635	decl = CP_DECL_CONTEXT (decl);
1636    }
1637}
1638
1639/* Return truthvalue of whether T1 is the same tree structure as T2.
1640   Return 1 if they are the same.
1641   Return 0 if they are understandably different.
1642   Return -1 if either contains tree structure not understood by
1643   this function.  */
1644
1645int
1646cp_tree_equal (t1, t2)
1647     tree t1, t2;
1648{
1649  register enum tree_code code1, code2;
1650  int cmp;
1651
1652  if (t1 == t2)
1653    return 1;
1654  if (t1 == 0 || t2 == 0)
1655    return 0;
1656
1657  code1 = TREE_CODE (t1);
1658  code2 = TREE_CODE (t2);
1659
1660  if (code1 == NOP_EXPR || code1 == CONVERT_EXPR || code1 == NON_LVALUE_EXPR)
1661    {
1662      if (code2 == NOP_EXPR || code2 == CONVERT_EXPR || code2 == NON_LVALUE_EXPR)
1663	return cp_tree_equal (TREE_OPERAND (t1, 0), TREE_OPERAND (t2, 0));
1664      else
1665	return cp_tree_equal (TREE_OPERAND (t1, 0), t2);
1666    }
1667  else if (code2 == NOP_EXPR || code2 == CONVERT_EXPR
1668	   || code2 == NON_LVALUE_EXPR)
1669    return cp_tree_equal (t1, TREE_OPERAND (t2, 0));
1670
1671  if (code1 != code2)
1672    return 0;
1673
1674  switch (code1)
1675    {
1676    case INTEGER_CST:
1677      return TREE_INT_CST_LOW (t1) == TREE_INT_CST_LOW (t2)
1678	&& TREE_INT_CST_HIGH (t1) == TREE_INT_CST_HIGH (t2);
1679
1680    case REAL_CST:
1681      return REAL_VALUES_EQUAL (TREE_REAL_CST (t1), TREE_REAL_CST (t2));
1682
1683    case STRING_CST:
1684      return TREE_STRING_LENGTH (t1) == TREE_STRING_LENGTH (t2)
1685	&& !memcmp (TREE_STRING_POINTER (t1), TREE_STRING_POINTER (t2),
1686		  TREE_STRING_LENGTH (t1));
1687
1688    case CONSTRUCTOR:
1689      /* We need to do this when determining whether or not two
1690	 non-type pointer to member function template arguments
1691	 are the same.  */
1692      if (!(same_type_p (TREE_TYPE (t1), TREE_TYPE (t2))
1693	    /* The first operand is RTL.  */
1694	    && TREE_OPERAND (t1, 0) == TREE_OPERAND (t2, 0)))
1695	return 0;
1696      return cp_tree_equal (TREE_OPERAND (t1, 1), TREE_OPERAND (t2, 1));
1697
1698    case TREE_LIST:
1699      cmp = cp_tree_equal (TREE_PURPOSE (t1), TREE_PURPOSE (t2));
1700      if (cmp <= 0)
1701	return cmp;
1702      cmp = cp_tree_equal (TREE_VALUE (t1), TREE_VALUE (t2));
1703      if (cmp <= 0)
1704	return cmp;
1705      return cp_tree_equal (TREE_CHAIN (t1), TREE_CHAIN (t2));
1706
1707    case SAVE_EXPR:
1708      return cp_tree_equal (TREE_OPERAND (t1, 0), TREE_OPERAND (t2, 0));
1709
1710    case CALL_EXPR:
1711      cmp = cp_tree_equal (TREE_OPERAND (t1, 0), TREE_OPERAND (t2, 0));
1712      if (cmp <= 0)
1713	return cmp;
1714      return simple_cst_list_equal (TREE_OPERAND (t1, 1), TREE_OPERAND (t2, 1));
1715
1716    case TARGET_EXPR:
1717      /* Special case: if either target is an unallocated VAR_DECL,
1718	 it means that it's going to be unified with whatever the
1719	 TARGET_EXPR is really supposed to initialize, so treat it
1720	 as being equivalent to anything.  */
1721      if ((TREE_CODE (TREE_OPERAND (t1, 0)) == VAR_DECL
1722	   && DECL_NAME (TREE_OPERAND (t1, 0)) == NULL_TREE
1723	   && !DECL_RTL_SET_P (TREE_OPERAND (t1, 0)))
1724	  || (TREE_CODE (TREE_OPERAND (t2, 0)) == VAR_DECL
1725	      && DECL_NAME (TREE_OPERAND (t2, 0)) == NULL_TREE
1726	      && !DECL_RTL_SET_P (TREE_OPERAND (t2, 0))))
1727	cmp = 1;
1728      else
1729	cmp = cp_tree_equal (TREE_OPERAND (t1, 0), TREE_OPERAND (t2, 0));
1730      if (cmp <= 0)
1731	return cmp;
1732      return cp_tree_equal (TREE_OPERAND (t1, 1), TREE_OPERAND (t2, 1));
1733
1734    case WITH_CLEANUP_EXPR:
1735      cmp = cp_tree_equal (TREE_OPERAND (t1, 0), TREE_OPERAND (t2, 0));
1736      if (cmp <= 0)
1737	return cmp;
1738      return cp_tree_equal (TREE_OPERAND (t1, 1), TREE_OPERAND (t1, 1));
1739
1740    case COMPONENT_REF:
1741      if (TREE_OPERAND (t1, 1) == TREE_OPERAND (t2, 1))
1742	return cp_tree_equal (TREE_OPERAND (t1, 0), TREE_OPERAND (t2, 0));
1743      return 0;
1744
1745    case VAR_DECL:
1746    case PARM_DECL:
1747    case CONST_DECL:
1748    case FUNCTION_DECL:
1749      return 0;
1750
1751    case TEMPLATE_PARM_INDEX:
1752      return (TEMPLATE_PARM_IDX (t1) == TEMPLATE_PARM_IDX (t2)
1753	      && TEMPLATE_PARM_LEVEL (t1) == TEMPLATE_PARM_LEVEL (t2)
1754	      && same_type_p (TREE_TYPE (TEMPLATE_PARM_DECL (t1)),
1755			      TREE_TYPE (TEMPLATE_PARM_DECL (t2))));
1756
1757    case SIZEOF_EXPR:
1758    case ALIGNOF_EXPR:
1759      if (TREE_CODE (TREE_OPERAND (t1, 0)) != TREE_CODE (TREE_OPERAND (t2, 0)))
1760	return 0;
1761      if (TYPE_P (TREE_OPERAND (t1, 0)))
1762	return same_type_p (TREE_OPERAND (t1, 0), TREE_OPERAND (t2, 0));
1763      break;
1764
1765    case PTRMEM_CST:
1766      /* Two pointer-to-members are the same if they point to the same
1767	 field or function in the same class.  */
1768      return (PTRMEM_CST_MEMBER (t1) == PTRMEM_CST_MEMBER (t2)
1769	      && same_type_p (PTRMEM_CST_CLASS (t1), PTRMEM_CST_CLASS (t2)));
1770
1771    default:
1772      break;
1773    }
1774
1775  switch (TREE_CODE_CLASS (code1))
1776    {
1777    case '1':
1778    case '2':
1779    case '<':
1780    case 'e':
1781    case 'r':
1782    case 's':
1783      {
1784	int i;
1785
1786	cmp = 1;
1787	for (i = 0; i < TREE_CODE_LENGTH (code1); ++i)
1788	  {
1789	    cmp = cp_tree_equal (TREE_OPERAND (t1, i), TREE_OPERAND (t2, i));
1790	    if (cmp <= 0)
1791	      return cmp;
1792	  }
1793	return cmp;
1794      }
1795
1796      case 't':
1797	return same_type_p (t1, t2) ? 1 : 0;
1798    }
1799
1800  return -1;
1801}
1802
1803/* Build a wrapper around a 'struct z_candidate' so we can use it as a
1804   tree.  */
1805
1806tree
1807build_zc_wrapper (ptr)
1808     struct z_candidate *ptr;
1809{
1810  tree t = make_node (WRAPPER);
1811  WRAPPER_ZC (t) = ptr;
1812  return t;
1813}
1814
1815static tree
1816build_srcloc (file, line)
1817     const char *file;
1818     int line;
1819{
1820  tree t;
1821
1822  t = make_node (SRCLOC);
1823  SRCLOC_FILE (t) = file;
1824  SRCLOC_LINE (t) = line;
1825
1826  return t;
1827}
1828
1829tree
1830build_srcloc_here ()
1831{
1832  return build_srcloc (input_filename, lineno);
1833}
1834
1835/* The type of ARG when used as an lvalue.  */
1836
1837tree
1838lvalue_type (arg)
1839     tree arg;
1840{
1841  tree type = TREE_TYPE (arg);
1842  if (TREE_CODE (arg) == OVERLOAD)
1843    type = unknown_type_node;
1844  return type;
1845}
1846
1847/* The type of ARG for printing error messages; denote lvalues with
1848   reference types.  */
1849
1850tree
1851error_type (arg)
1852     tree arg;
1853{
1854  tree type = TREE_TYPE (arg);
1855  if (TREE_CODE (type) == ARRAY_TYPE)
1856    ;
1857  else if (real_lvalue_p (arg))
1858    type = build_reference_type (lvalue_type (arg));
1859  else if (IS_AGGR_TYPE (type))
1860    type = lvalue_type (arg);
1861
1862  return type;
1863}
1864
1865/* Does FUNCTION use a variable-length argument list?  */
1866
1867int
1868varargs_function_p (function)
1869     tree function;
1870{
1871  tree parm = TYPE_ARG_TYPES (TREE_TYPE (function));
1872  for (; parm; parm = TREE_CHAIN (parm))
1873    if (TREE_VALUE (parm) == void_type_node)
1874      return 0;
1875  return 1;
1876}
1877
1878/* Returns 1 if decl is a member of a class.  */
1879
1880int
1881member_p (decl)
1882     tree decl;
1883{
1884  const tree ctx = DECL_CONTEXT (decl);
1885  return (ctx && TYPE_P (ctx));
1886}
1887
1888/* Create a placeholder for member access where we don't actually have an
1889   object that the access is against.  */
1890
1891tree
1892build_dummy_object (type)
1893     tree type;
1894{
1895  tree decl = build1 (NOP_EXPR, build_pointer_type (type), void_zero_node);
1896  return build_indirect_ref (decl, NULL);
1897}
1898
1899/* We've gotten a reference to a member of TYPE.  Return *this if appropriate,
1900   or a dummy object otherwise.  If BINFOP is non-0, it is filled with the
1901   binfo path from current_class_type to TYPE, or 0.  */
1902
1903tree
1904maybe_dummy_object (type, binfop)
1905     tree type;
1906     tree *binfop;
1907{
1908  tree decl, context;
1909  tree binfo;
1910
1911  if (current_class_type
1912      && (binfo = lookup_base (current_class_type, type,
1913			       ba_ignore | ba_quiet, NULL)))
1914    context = current_class_type;
1915  else
1916    {
1917      /* Reference from a nested class member function.  */
1918      context = type;
1919      binfo = TYPE_BINFO (type);
1920    }
1921
1922  if (binfop)
1923    *binfop = binfo;
1924
1925  if (current_class_ref && context == current_class_type
1926      /* Kludge: Make sure that current_class_type is actually
1927         correct.  It might not be if we're in the middle of
1928         tsubst_default_argument.  */
1929      && same_type_p (TYPE_MAIN_VARIANT (TREE_TYPE (current_class_ref)),
1930		      current_class_type))
1931    decl = current_class_ref;
1932  else
1933    decl = build_dummy_object (context);
1934
1935  return decl;
1936}
1937
1938/* Returns 1 if OB is a placeholder object, or a pointer to one.  */
1939
1940int
1941is_dummy_object (ob)
1942     tree ob;
1943{
1944  if (TREE_CODE (ob) == INDIRECT_REF)
1945    ob = TREE_OPERAND (ob, 0);
1946  return (TREE_CODE (ob) == NOP_EXPR
1947	  && TREE_OPERAND (ob, 0) == void_zero_node);
1948}
1949
1950/* Returns 1 iff type T is a POD type, as defined in [basic.types].  */
1951
1952int
1953pod_type_p (t)
1954     tree t;
1955{
1956  t = strip_array_types (t);
1957
1958  if (t == error_mark_node)
1959    return 1;
1960  if (INTEGRAL_TYPE_P (t))
1961    return 1;  /* integral, character or enumeral type */
1962  if (FLOAT_TYPE_P (t))
1963    return 1;
1964  if (TYPE_PTR_P (t))
1965    return 1; /* pointer to non-member */
1966  if (TYPE_PTRMEM_P (t))
1967    return 1; /* pointer to member object */
1968  if (TYPE_PTRMEMFUNC_P (t))
1969    return 1; /* pointer to member function */
1970
1971  if (! CLASS_TYPE_P (t))
1972    return 0; /* other non-class type (reference or function) */
1973  if (CLASSTYPE_NON_POD_P (t))
1974    return 0;
1975  return 1;
1976}
1977
1978/* Returns 1 iff zero initialization of type T means actually storing
1979   zeros in it.  */
1980
1981int
1982zero_init_p (t)
1983     tree t;
1984{
1985  t = strip_array_types (t);
1986
1987  if (t == error_mark_node)
1988    return 1;
1989
1990  /* NULL pointers to data members are initialized with -1.  */
1991  if (TYPE_PTRMEM_P (t))
1992    return 0;
1993
1994  /* Classes that contain types that can't be zero-initialized, cannot
1995     be zero-initialized themselves.  */
1996  if (CLASS_TYPE_P (t) && CLASSTYPE_NON_ZERO_INIT_P (t))
1997    return 0;
1998
1999  return 1;
2000}
2001
2002/* Table of valid C++ attributes.  */
2003const struct attribute_spec cxx_attribute_table[] =
2004{
2005  /* { name, min_len, max_len, decl_req, type_req, fn_type_req, handler } */
2006  { "java_interface", 0, 0, false, false, false, handle_java_interface_attribute },
2007  { "com_interface",  0, 0, false, false, false, handle_com_interface_attribute },
2008  { "init_priority",  1, 1, true,  false, false, handle_init_priority_attribute },
2009  { NULL,             0, 0, false, false, false, NULL }
2010};
2011
2012/* Handle a "java_interface" attribute; arguments as in
2013   struct attribute_spec.handler.  */
2014static tree
2015handle_java_interface_attribute (node, name, args, flags, no_add_attrs)
2016     tree *node;
2017     tree name;
2018     tree args ATTRIBUTE_UNUSED;
2019     int flags;
2020     bool *no_add_attrs;
2021{
2022  if (DECL_P (*node)
2023      || !CLASS_TYPE_P (*node)
2024      || !TYPE_FOR_JAVA (*node))
2025    {
2026      error ("`%s' attribute can only be applied to Java class definitions",
2027	     IDENTIFIER_POINTER (name));
2028      *no_add_attrs = true;
2029      return NULL_TREE;
2030    }
2031  if (!(flags & (int) ATTR_FLAG_TYPE_IN_PLACE))
2032    *node = build_type_copy (*node);
2033  TYPE_JAVA_INTERFACE (*node) = 1;
2034
2035  return NULL_TREE;
2036}
2037
2038/* Handle a "com_interface" attribute; arguments as in
2039   struct attribute_spec.handler.  */
2040static tree
2041handle_com_interface_attribute (node, name, args, flags, no_add_attrs)
2042     tree *node;
2043     tree name;
2044     tree args ATTRIBUTE_UNUSED;
2045     int flags ATTRIBUTE_UNUSED;
2046     bool *no_add_attrs;
2047{
2048  static int warned;
2049
2050  *no_add_attrs = true;
2051
2052  if (DECL_P (*node)
2053      || !CLASS_TYPE_P (*node)
2054      || *node != TYPE_MAIN_VARIANT (*node))
2055    {
2056      warning ("`%s' attribute can only be applied to class definitions",
2057	       IDENTIFIER_POINTER (name));
2058      return NULL_TREE;
2059    }
2060
2061  if (!warned++)
2062    warning ("`%s' is obsolete; g++ vtables are now COM-compatible by default",
2063	     IDENTIFIER_POINTER (name));
2064
2065  return NULL_TREE;
2066}
2067
2068/* Handle an "init_priority" attribute; arguments as in
2069   struct attribute_spec.handler.  */
2070static tree
2071handle_init_priority_attribute (node, name, args, flags, no_add_attrs)
2072     tree *node;
2073     tree name;
2074     tree args;
2075     int flags ATTRIBUTE_UNUSED;
2076     bool *no_add_attrs;
2077{
2078  tree initp_expr = TREE_VALUE (args);
2079  tree decl = *node;
2080  tree type = TREE_TYPE (decl);
2081  int pri;
2082
2083  STRIP_NOPS (initp_expr);
2084
2085  if (!initp_expr || TREE_CODE (initp_expr) != INTEGER_CST)
2086    {
2087      error ("requested init_priority is not an integer constant");
2088      *no_add_attrs = true;
2089      return NULL_TREE;
2090    }
2091
2092  pri = TREE_INT_CST_LOW (initp_expr);
2093
2094  type = strip_array_types (type);
2095
2096  if (decl == NULL_TREE
2097      || TREE_CODE (decl) != VAR_DECL
2098      || !TREE_STATIC (decl)
2099      || DECL_EXTERNAL (decl)
2100      || (TREE_CODE (type) != RECORD_TYPE
2101	  && TREE_CODE (type) != UNION_TYPE)
2102      /* Static objects in functions are initialized the
2103	 first time control passes through that
2104	 function. This is not precise enough to pin down an
2105	 init_priority value, so don't allow it.  */
2106      || current_function_decl)
2107    {
2108      error ("can only use `%s' attribute on file-scope definitions of objects of class type",
2109	     IDENTIFIER_POINTER (name));
2110      *no_add_attrs = true;
2111      return NULL_TREE;
2112    }
2113
2114  if (pri > MAX_INIT_PRIORITY || pri <= 0)
2115    {
2116      error ("requested init_priority is out of range");
2117      *no_add_attrs = true;
2118      return NULL_TREE;
2119    }
2120
2121  /* Check for init_priorities that are reserved for
2122     language and runtime support implementations.*/
2123  if (pri <= MAX_RESERVED_INIT_PRIORITY)
2124    {
2125      warning
2126	("requested init_priority is reserved for internal use");
2127    }
2128
2129  if (SUPPORTS_INIT_PRIORITY)
2130    {
2131      DECL_INIT_PRIORITY (decl) = pri;
2132      return NULL_TREE;
2133    }
2134  else
2135    {
2136      error ("`%s' attribute is not supported on this platform",
2137	     IDENTIFIER_POINTER (name));
2138      *no_add_attrs = true;
2139      return NULL_TREE;
2140    }
2141}
2142
2143/* Return a new PTRMEM_CST of the indicated TYPE.  The MEMBER is the
2144   thing pointed to by the constant.  */
2145
2146tree
2147make_ptrmem_cst (type, member)
2148     tree type;
2149     tree member;
2150{
2151  tree ptrmem_cst = make_node (PTRMEM_CST);
2152  /* If would seem a great convenience if make_node would set
2153     TREE_CONSTANT for things of class `c', but it does not.  */
2154  TREE_CONSTANT (ptrmem_cst) = 1;
2155  TREE_TYPE (ptrmem_cst) = type;
2156  PTRMEM_CST_MEMBER (ptrmem_cst) = member;
2157  return ptrmem_cst;
2158}
2159
2160/* Apply FUNC to all language-specific sub-trees of TP in a pre-order
2161   traversal.  Called from walk_tree().  */
2162
2163tree
2164cp_walk_subtrees (tp, walk_subtrees_p, func, data, htab)
2165     tree *tp;
2166     int *walk_subtrees_p;
2167     walk_tree_fn func;
2168     void *data;
2169     void *htab;
2170{
2171  enum tree_code code = TREE_CODE (*tp);
2172  tree result;
2173
2174#define WALK_SUBTREE(NODE)				\
2175  do							\
2176    {							\
2177      result = walk_tree (&(NODE), func, data, htab);	\
2178      if (result)					\
2179	return result;					\
2180    }							\
2181  while (0)
2182
2183  /* Not one of the easy cases.  We must explicitly go through the
2184     children.  */
2185  switch (code)
2186    {
2187    case DEFAULT_ARG:
2188    case TEMPLATE_TEMPLATE_PARM:
2189    case BOUND_TEMPLATE_TEMPLATE_PARM:
2190    case UNBOUND_CLASS_TEMPLATE:
2191    case TEMPLATE_PARM_INDEX:
2192    case TEMPLATE_TYPE_PARM:
2193    case TYPENAME_TYPE:
2194    case TYPEOF_TYPE:
2195      /* None of thse have subtrees other than those already walked
2196         above.  */
2197      *walk_subtrees_p = 0;
2198      break;
2199
2200    case PTRMEM_CST:
2201      WALK_SUBTREE (TREE_TYPE (*tp));
2202      *walk_subtrees_p = 0;
2203      break;
2204
2205    case TREE_LIST:
2206      /* A BASELINK_P's TREE_PURPOSE is a BINFO, and hence circular.  */
2207      if (!BASELINK_P (*tp))
2208        WALK_SUBTREE (TREE_PURPOSE (*tp));
2209      break;
2210
2211    case OVERLOAD:
2212      WALK_SUBTREE (OVL_FUNCTION (*tp));
2213      WALK_SUBTREE (OVL_CHAIN (*tp));
2214      *walk_subtrees_p = 0;
2215      break;
2216
2217    case RECORD_TYPE:
2218      if (TYPE_PTRMEMFUNC_P (*tp))
2219	WALK_SUBTREE (TYPE_PTRMEMFUNC_FN_TYPE (*tp));
2220      break;
2221
2222    default:
2223      break;
2224    }
2225
2226  /* We didn't find what we were looking for.  */
2227  return NULL_TREE;
2228
2229#undef WALK_SUBTREE
2230}
2231
2232/* Decide whether there are language-specific reasons to not inline a
2233   function as a tree.  */
2234
2235int
2236cp_cannot_inline_tree_fn (fnp)
2237     tree *fnp;
2238{
2239  tree fn = *fnp;
2240
2241  if (flag_really_no_inline
2242      && lookup_attribute ("always_inline", DECL_ATTRIBUTES (fn)) == NULL)
2243    return 1;
2244
2245  /* We can inline a template instantiation only if it's fully
2246     instantiated.  */
2247  if (DECL_TEMPLATE_INFO (fn)
2248      && TI_PENDING_TEMPLATE_FLAG (DECL_TEMPLATE_INFO (fn)))
2249    {
2250      fn = *fnp = instantiate_decl (fn, /*defer_ok=*/0);
2251      if (TI_PENDING_TEMPLATE_FLAG (DECL_TEMPLATE_INFO (fn)))
2252	return 1;
2253    }
2254
2255  /* Don't auto-inline anything that might not be bound within
2256     this unit of translation.  */
2257  if (!DECL_DECLARED_INLINE_P (fn) && !(*targetm.binds_local_p) (fn))
2258    {
2259      DECL_UNINLINABLE (fn) = 1;
2260      return 1;
2261    }
2262
2263  if (varargs_function_p (fn))
2264    {
2265      DECL_UNINLINABLE (fn) = 1;
2266      return 1;
2267    }
2268
2269  if (! function_attribute_inlinable_p (fn))
2270    {
2271      DECL_UNINLINABLE (fn) = 1;
2272      return 1;
2273    }
2274
2275  return 0;
2276}
2277
2278/* Add any pending functions other than the current function (already
2279   handled by the caller), that thus cannot be inlined, to FNS_P, then
2280   return the latest function added to the array, PREV_FN.  */
2281
2282tree
2283cp_add_pending_fn_decls (fns_p, prev_fn)
2284     void *fns_p;
2285     tree prev_fn;
2286{
2287  varray_type *fnsp = (varray_type *)fns_p;
2288  struct saved_scope *s;
2289
2290  for (s = scope_chain; s; s = s->prev)
2291    if (s->function_decl && s->function_decl != prev_fn)
2292      {
2293	VARRAY_PUSH_TREE (*fnsp, s->function_decl);
2294	prev_fn = s->function_decl;
2295      }
2296
2297  return prev_fn;
2298}
2299
2300/* Determine whether a tree node is an OVERLOAD node.  Used to decide
2301   whether to copy a node or to preserve its chain when inlining a
2302   function.  */
2303
2304int
2305cp_is_overload_p (t)
2306     tree t;
2307{
2308  return TREE_CODE (t) == OVERLOAD;
2309}
2310
2311/* Determine whether VAR is a declaration of an automatic variable in
2312   function FN.  */
2313
2314int
2315cp_auto_var_in_fn_p (var, fn)
2316     tree var, fn;
2317{
2318  return (DECL_P (var) && DECL_CONTEXT (var) == fn
2319	  && nonstatic_local_decl_p (var));
2320}
2321
2322/* Tell whether a declaration is needed for the RESULT of a function
2323   FN being inlined into CALLER or if the top node of target_exprs is
2324   to be used.  */
2325
2326tree
2327cp_copy_res_decl_for_inlining (result, fn, caller, decl_map_,
2328			       need_decl, target_exprs)
2329     tree result, fn, caller;
2330     void *decl_map_;
2331     int *need_decl;
2332     void *target_exprs;
2333{
2334  splay_tree decl_map = (splay_tree)decl_map_;
2335  varray_type *texps = (varray_type *)target_exprs;
2336  tree var;
2337  int aggregate_return_p;
2338
2339  /* Figure out whether or not FN returns an aggregate.  */
2340  aggregate_return_p = IS_AGGR_TYPE (TREE_TYPE (result));
2341  *need_decl = ! aggregate_return_p;
2342
2343  /* If FN returns an aggregate then the caller will always create the
2344     temporary (using a TARGET_EXPR) and the call will be the
2345     initializing expression for the TARGET_EXPR.  If we were just to
2346     create a new VAR_DECL here, then the result of this function
2347     would be copied (bitwise) into the variable initialized by the
2348     TARGET_EXPR.  That's incorrect, so we must transform any
2349     references to the RESULT into references to the target.  */
2350  if (aggregate_return_p)
2351    {
2352      if (VARRAY_ACTIVE_SIZE (*texps) == 0)
2353	abort ();
2354      var = TREE_OPERAND (VARRAY_TOP_TREE (*texps), 0);
2355      if (! same_type_ignoring_top_level_qualifiers_p (TREE_TYPE (var),
2356						       TREE_TYPE (result)))
2357	abort ();
2358    }
2359  /* Otherwise, make an appropriate copy.  */
2360  else
2361    var = copy_decl_for_inlining (result, fn, caller);
2362
2363  if (DECL_SAVED_FUNCTION_DATA (fn))
2364    {
2365      tree nrv = DECL_SAVED_FUNCTION_DATA (fn)->x_return_value;
2366      if (nrv)
2367	{
2368	  /* We have a named return value; copy the name and source
2369	     position so we can get reasonable debugging information, and
2370	     register the return variable as its equivalent.  */
2371	  DECL_NAME (var) = DECL_NAME (nrv);
2372	  DECL_SOURCE_LOCATION (var) = DECL_SOURCE_LOCATION (nrv);
2373	  DECL_ABSTRACT_ORIGIN (var) = DECL_ORIGIN (nrv);
2374	  /* Don't lose initialization info.  */
2375	  DECL_INITIAL (var) = DECL_INITIAL (nrv);
2376	  /* Don't forget that it needs to go in the stack.  */
2377	  TREE_ADDRESSABLE (var) = TREE_ADDRESSABLE (nrv);
2378
2379	  splay_tree_insert (decl_map,
2380			     (splay_tree_key) nrv,
2381			     (splay_tree_value) var);
2382	}
2383    }
2384
2385  return var;
2386}
2387
2388/* Record that we're about to start inlining FN, and return nonzero if
2389   that's OK.  Used for lang_hooks.tree_inlining.start_inlining.  */
2390
2391int
2392cp_start_inlining (fn)
2393     tree fn;
2394{
2395  if (DECL_TEMPLATE_INSTANTIATION (fn))
2396    return push_tinst_level (fn);
2397  else
2398    return 1;
2399}
2400
2401/* Record that we're done inlining FN.  Used for
2402   lang_hooks.tree_inlining.end_inlining.  */
2403
2404void
2405cp_end_inlining (fn)
2406     tree fn ATTRIBUTE_UNUSED;
2407{
2408  if (DECL_TEMPLATE_INSTANTIATION (fn))
2409    pop_tinst_level ();
2410}
2411
2412/* Initialize tree.c.  */
2413
2414void
2415init_tree ()
2416{
2417  lang_statement_code_p = cp_statement_code_p;
2418  list_hash_table = htab_create_ggc (31, list_hash, list_hash_eq, NULL);
2419}
2420
2421/* Called via walk_tree.  If *TP points to a DECL_STMT for a local
2422   declaration, copies the declaration and enters it in the splay_tree
2423   pointed to by DATA (which is really a `splay_tree *').  */
2424
2425static tree
2426mark_local_for_remap_r (tp, walk_subtrees, data)
2427     tree *tp;
2428     int *walk_subtrees ATTRIBUTE_UNUSED;
2429     void *data;
2430{
2431  tree t = *tp;
2432  splay_tree st = (splay_tree) data;
2433  tree decl;
2434
2435
2436  if (TREE_CODE (t) == DECL_STMT
2437      && nonstatic_local_decl_p (DECL_STMT_DECL (t)))
2438    decl = DECL_STMT_DECL (t);
2439  else if (TREE_CODE (t) == LABEL_STMT)
2440    decl = LABEL_STMT_LABEL (t);
2441  else if (TREE_CODE (t) == TARGET_EXPR
2442	   && nonstatic_local_decl_p (TREE_OPERAND (t, 0)))
2443    decl = TREE_OPERAND (t, 0);
2444  else if (TREE_CODE (t) == CASE_LABEL)
2445    decl = CASE_LABEL_DECL (t);
2446  else
2447    decl = NULL_TREE;
2448
2449  if (decl)
2450    {
2451      tree copy;
2452
2453      /* Make a copy.  */
2454      copy = copy_decl_for_inlining (decl,
2455				     DECL_CONTEXT (decl),
2456				     DECL_CONTEXT (decl));
2457
2458      /* Remember the copy.  */
2459      splay_tree_insert (st,
2460			 (splay_tree_key) decl,
2461			 (splay_tree_value) copy);
2462    }
2463
2464  return NULL_TREE;
2465}
2466
2467/* Called via walk_tree when an expression is unsaved.  Using the
2468   splay_tree pointed to by ST (which is really a `splay_tree'),
2469   remaps all local declarations to appropriate replacements.  */
2470
2471static tree
2472cp_unsave_r (tp, walk_subtrees, data)
2473     tree *tp;
2474     int *walk_subtrees;
2475     void *data;
2476{
2477  splay_tree st = (splay_tree) data;
2478  splay_tree_node n;
2479
2480  /* Only a local declaration (variable or label).  */
2481  if (nonstatic_local_decl_p (*tp))
2482    {
2483      /* Lookup the declaration.  */
2484      n = splay_tree_lookup (st, (splay_tree_key) *tp);
2485
2486      /* If it's there, remap it.  */
2487      if (n)
2488	*tp = (tree) n->value;
2489    }
2490  else if (TREE_CODE (*tp) == SAVE_EXPR)
2491    remap_save_expr (tp, st, current_function_decl, walk_subtrees);
2492  else
2493    {
2494      copy_tree_r (tp, walk_subtrees, NULL);
2495
2496      /* Do whatever unsaving is required.  */
2497      unsave_expr_1 (*tp);
2498    }
2499
2500  /* Keep iterating.  */
2501  return NULL_TREE;
2502}
2503
2504/* Called whenever an expression needs to be unsaved.  */
2505
2506tree
2507cxx_unsave_expr_now (tp)
2508     tree tp;
2509{
2510  splay_tree st;
2511
2512  /* Create a splay-tree to map old local variable declarations to new
2513     ones.  */
2514  st = splay_tree_new (splay_tree_compare_pointers, NULL, NULL);
2515
2516  /* Walk the tree once figuring out what needs to be remapped.  */
2517  walk_tree (&tp, mark_local_for_remap_r, st, NULL);
2518
2519  /* Walk the tree again, copying, remapping, and unsaving.  */
2520  walk_tree (&tp, cp_unsave_r, st, NULL);
2521
2522  /* Clean up.  */
2523  splay_tree_delete (st);
2524
2525  return tp;
2526}
2527
2528/* Returns the kind of special function that DECL (a FUNCTION_DECL)
2529   is.  Note that sfk_none is zero, so this function can be used as a
2530   predicate to test whether or not DECL is a special function.  */
2531
2532special_function_kind
2533special_function_p (decl)
2534     tree decl;
2535{
2536  /* Rather than doing all this stuff with magic names, we should
2537     probably have a field of type `special_function_kind' in
2538     DECL_LANG_SPECIFIC.  */
2539  if (DECL_COPY_CONSTRUCTOR_P (decl))
2540    return sfk_copy_constructor;
2541  if (DECL_CONSTRUCTOR_P (decl))
2542    return sfk_constructor;
2543  if (DECL_OVERLOADED_OPERATOR_P (decl) == NOP_EXPR)
2544    return sfk_assignment_operator;
2545  if (DECL_MAYBE_IN_CHARGE_DESTRUCTOR_P (decl))
2546    return sfk_destructor;
2547  if (DECL_COMPLETE_DESTRUCTOR_P (decl))
2548    return sfk_complete_destructor;
2549  if (DECL_BASE_DESTRUCTOR_P (decl))
2550    return sfk_base_destructor;
2551  if (DECL_DELETING_DESTRUCTOR_P (decl))
2552    return sfk_deleting_destructor;
2553  if (DECL_CONV_FN_P (decl))
2554    return sfk_conversion;
2555
2556  return sfk_none;
2557}
2558
2559/* Returns true if and only if NODE is a name, i.e., a node created
2560   by the parser when processing an id-expression.  */
2561
2562bool
2563name_p (tree node)
2564{
2565  if (TREE_CODE (node) == TEMPLATE_ID_EXPR)
2566    node = TREE_OPERAND (node, 0);
2567  return (/* An ordinary unqualified name.  */
2568	  TREE_CODE (node) == IDENTIFIER_NODE
2569	  /* A destructor name.  */
2570	  || TREE_CODE (node) == BIT_NOT_EXPR
2571	  /* A qualified name.  */
2572	  || TREE_CODE (node) == SCOPE_REF);
2573}
2574
2575/* Returns nonzero if TYPE is a character type, including wchar_t.  */
2576
2577int
2578char_type_p (type)
2579     tree type;
2580{
2581  return (same_type_p (type, char_type_node)
2582	  || same_type_p (type, unsigned_char_type_node)
2583	  || same_type_p (type, signed_char_type_node)
2584	  || same_type_p (type, wchar_type_node));
2585}
2586
2587/* Returns the kind of linkage associated with the indicated DECL.  Th
2588   value returned is as specified by the language standard; it is
2589   independent of implementation details regarding template
2590   instantiation, etc.  For example, it is possible that a declaration
2591   to which this function assigns external linkage would not show up
2592   as a global symbol when you run `nm' on the resulting object file.  */
2593
2594linkage_kind
2595decl_linkage (decl)
2596     tree decl;
2597{
2598  /* This function doesn't attempt to calculate the linkage from first
2599     principles as given in [basic.link].  Instead, it makes use of
2600     the fact that we have already set TREE_PUBLIC appropriately, and
2601     then handles a few special cases.  Ideally, we would calculate
2602     linkage first, and then transform that into a concrete
2603     implementation.  */
2604
2605  /* Things that don't have names have no linkage.  */
2606  if (!DECL_NAME (decl))
2607    return lk_none;
2608
2609  /* Things that are TREE_PUBLIC have external linkage.  */
2610  if (TREE_PUBLIC (decl))
2611    return lk_external;
2612
2613  /* Some things that are not TREE_PUBLIC have external linkage, too.
2614     For example, on targets that don't have weak symbols, we make all
2615     template instantiations have internal linkage (in the object
2616     file), but the symbols should still be treated as having external
2617     linkage from the point of view of the language.  */
2618  if (DECL_LANG_SPECIFIC (decl) && DECL_COMDAT (decl))
2619    return lk_external;
2620
2621  /* Things in local scope do not have linkage, if they don't have
2622     TREE_PUBLIC set.  */
2623  if (decl_function_context (decl))
2624    return lk_none;
2625
2626  /* Everything else has internal linkage.  */
2627  return lk_internal;
2628}
2629
2630/* EXP is an expression that we want to pre-evaluate.  Returns via INITP an
2631   expression to perform the pre-evaluation, and returns directly an
2632   expression to use the precalculated result.  */
2633
2634tree
2635stabilize_expr (exp, initp)
2636     tree exp;
2637     tree *initp;
2638{
2639  tree init_expr;
2640
2641  if (!TREE_SIDE_EFFECTS (exp))
2642    {
2643      init_expr = void_zero_node;
2644    }
2645  else if (!real_lvalue_p (exp)
2646	   || !TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (exp)))
2647    {
2648      init_expr = get_target_expr (exp);
2649      exp = TARGET_EXPR_SLOT (init_expr);
2650    }
2651  else
2652    {
2653      exp = build_unary_op (ADDR_EXPR, exp, 1);
2654      init_expr = get_target_expr (exp);
2655      exp = TARGET_EXPR_SLOT (init_expr);
2656      exp = build_indirect_ref (exp, 0);
2657    }
2658
2659  *initp = init_expr;
2660  return exp;
2661}
2662
2663#if defined ENABLE_TREE_CHECKING && (GCC_VERSION >= 2007)
2664/* Complain that some language-specific thing hanging off a tree
2665   node has been accessed improperly.  */
2666
2667void
2668lang_check_failed (file, line, function)
2669     const char *file;
2670     int line;
2671     const char *function;
2672{
2673  internal_error ("lang_* check: failed in %s, at %s:%d",
2674		  function, trim_filename (file), line);
2675}
2676#endif /* ENABLE_TREE_CHECKING */
2677
2678#include "gt-cp-tree.h"
2679