118334Speter/* Language-dependent node constructors for parse phase of GNU compiler.
290075Sobrien   Copyright (C) 1987, 1988, 1992, 1993, 1994, 1995, 1996, 1997, 1998,
3146895Skan   1999, 2000, 2001, 2002, 2003, 2004, 2005 Free Software Foundation, Inc.
418334Speter   Hacked by Michael Tiemann (tiemann@cygnus.com)
518334Speter
6132718SkanThis file is part of GCC.
718334Speter
8132718SkanGCC is free software; you can redistribute it and/or modify
918334Speterit under the terms of the GNU General Public License as published by
1018334Speterthe Free Software Foundation; either version 2, or (at your option)
1118334Speterany later version.
1218334Speter
13132718SkanGCC is distributed in the hope that it will be useful,
1418334Speterbut WITHOUT ANY WARRANTY; without even the implied warranty of
1518334SpeterMERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
1618334SpeterGNU General Public License for more details.
1718334Speter
1818334SpeterYou should have received a copy of the GNU General Public License
19132718Skanalong with GCC; see the file COPYING.  If not, write to
20169689Skanthe Free Software Foundation, 51 Franklin Street, Fifth Floor,
21169689SkanBoston, MA 02110-1301, USA.  */
2218334Speter
2318334Speter#include "config.h"
2450397Sobrien#include "system.h"
25132718Skan#include "coretypes.h"
26132718Skan#include "tm.h"
2718334Speter#include "tree.h"
2818334Speter#include "cp-tree.h"
2918334Speter#include "flags.h"
30117395Skan#include "real.h"
3118334Speter#include "rtl.h"
3250397Sobrien#include "toplev.h"
3390075Sobrien#include "insn-config.h"
3490075Sobrien#include "integrate.h"
3590075Sobrien#include "tree-inline.h"
36169689Skan#include "debug.h"
37117395Skan#include "target.h"
38169689Skan#include "convert.h"
3918334Speter
40132718Skanstatic tree bot_manip (tree *, int *, void *);
41132718Skanstatic tree bot_replace (tree *, int *, void *);
42132718Skanstatic tree build_cplus_array_type_1 (tree, tree);
43132718Skanstatic int list_hash_eq (const void *, const void *);
44132718Skanstatic hashval_t list_hash_pieces (tree, tree, tree);
45132718Skanstatic hashval_t list_hash (const void *);
46132718Skanstatic cp_lvalue_kind lvalue_p_1 (tree, int);
47132718Skanstatic tree build_target_expr (tree, tree);
48132718Skanstatic tree count_trees_r (tree *, int *, void *);
49132718Skanstatic tree verify_stmt_tree_r (tree *, int *, void *);
50132718Skanstatic tree build_local_temp (tree);
5150397Sobrien
52132718Skanstatic tree handle_java_interface_attribute (tree *, tree, tree, int, bool *);
53132718Skanstatic tree handle_com_interface_attribute (tree *, tree, tree, int, bool *);
54132718Skanstatic tree handle_init_priority_attribute (tree *, tree, tree, int, bool *);
5518334Speter
5690075Sobrien/* If REF is an lvalue, returns the kind of lvalue that REF is.
5790075Sobrien   Otherwise, returns clk_none.  If TREAT_CLASS_RVALUES_AS_LVALUES is
58117395Skan   nonzero, rvalues of class type are considered lvalues.  */
5918334Speter
6090075Sobrienstatic cp_lvalue_kind
61169689Skanlvalue_p_1 (tree ref,
62169689Skan	    int treat_class_rvalues_as_lvalues)
6318334Speter{
6490075Sobrien  cp_lvalue_kind op1_lvalue_kind = clk_none;
6590075Sobrien  cp_lvalue_kind op2_lvalue_kind = clk_none;
6690075Sobrien
6718334Speter  if (TREE_CODE (TREE_TYPE (ref)) == REFERENCE_TYPE)
6890075Sobrien    return clk_ordinary;
6918334Speter
7090075Sobrien  if (ref == current_class_ptr)
7190075Sobrien    return clk_none;
7218334Speter
7318334Speter  switch (TREE_CODE (ref))
7418334Speter    {
7518334Speter      /* preincrements and predecrements are valid lvals, provided
7650397Sobrien	 what they refer to are valid lvals.  */
7718334Speter    case PREINCREMENT_EXPR:
7818334Speter    case PREDECREMENT_EXPR:
7918334Speter    case SAVE_EXPR:
8050397Sobrien    case TRY_CATCH_EXPR:
8150397Sobrien    case WITH_CLEANUP_EXPR:
8252284Sobrien    case REALPART_EXPR:
8352284Sobrien    case IMAGPART_EXPR:
8452284Sobrien      return lvalue_p_1 (TREE_OPERAND (ref, 0),
85132718Skan			 treat_class_rvalues_as_lvalues);
8618334Speter
8790075Sobrien    case COMPONENT_REF:
8890075Sobrien      op1_lvalue_kind = lvalue_p_1 (TREE_OPERAND (ref, 0),
89132718Skan				    treat_class_rvalues_as_lvalues);
90132718Skan      /* Look at the member designator.  */
91169689Skan      if (!op1_lvalue_kind
92169689Skan	  /* The "field" can be a FUNCTION_DECL or an OVERLOAD in some
93169689Skan	     situations.  */
94169689Skan	  || TREE_CODE (TREE_OPERAND (ref, 1)) != FIELD_DECL)
95169689Skan	;
96132718Skan      else if (DECL_C_BIT_FIELD (TREE_OPERAND (ref, 1)))
9790075Sobrien	{
9890075Sobrien	  /* Clear the ordinary bit.  If this object was a class
9990075Sobrien	     rvalue we want to preserve that information.  */
10090075Sobrien	  op1_lvalue_kind &= ~clk_ordinary;
101132718Skan	  /* The lvalue is for a bitfield.  */
10290075Sobrien	  op1_lvalue_kind |= clk_bitfield;
10390075Sobrien	}
104132718Skan      else if (DECL_PACKED (TREE_OPERAND (ref, 1)))
105132718Skan	op1_lvalue_kind |= clk_packed;
106169689Skan
10790075Sobrien      return op1_lvalue_kind;
10890075Sobrien
10918334Speter    case STRING_CST:
11090075Sobrien      return clk_ordinary;
11118334Speter
112169689Skan    case CONST_DECL:
11318334Speter    case VAR_DECL:
11418334Speter      if (TREE_READONLY (ref) && ! TREE_STATIC (ref)
11518334Speter	  && DECL_LANG_SPECIFIC (ref)
11618334Speter	  && DECL_IN_AGGR_P (ref))
11790075Sobrien	return clk_none;
11818334Speter    case INDIRECT_REF:
11918334Speter    case ARRAY_REF:
12018334Speter    case PARM_DECL:
12118334Speter    case RESULT_DECL:
12252284Sobrien      if (TREE_CODE (TREE_TYPE (ref)) != METHOD_TYPE)
12390075Sobrien	return clk_ordinary;
12418334Speter      break;
12518334Speter
12618334Speter      /* A currently unresolved scope ref.  */
12718334Speter    case SCOPE_REF:
128169689Skan      gcc_unreachable ();
12990075Sobrien    case MAX_EXPR:
13090075Sobrien    case MIN_EXPR:
131169689Skan      /* Disallow <? and >? as lvalues if either argument side-effects.  */
132169689Skan      if (TREE_SIDE_EFFECTS (TREE_OPERAND (ref, 0))
133169689Skan	  || TREE_SIDE_EFFECTS (TREE_OPERAND (ref, 1)))
134169689Skan	return clk_none;
13590075Sobrien      op1_lvalue_kind = lvalue_p_1 (TREE_OPERAND (ref, 0),
136132718Skan				    treat_class_rvalues_as_lvalues);
13790075Sobrien      op2_lvalue_kind = lvalue_p_1 (TREE_OPERAND (ref, 1),
138132718Skan				    treat_class_rvalues_as_lvalues);
13918334Speter      break;
14018334Speter
14118334Speter    case COND_EXPR:
14290075Sobrien      op1_lvalue_kind = lvalue_p_1 (TREE_OPERAND (ref, 1),
143132718Skan				    treat_class_rvalues_as_lvalues);
14490075Sobrien      op2_lvalue_kind = lvalue_p_1 (TREE_OPERAND (ref, 2),
145132718Skan				    treat_class_rvalues_as_lvalues);
14690075Sobrien      break;
14718334Speter
14818334Speter    case MODIFY_EXPR:
14990075Sobrien      return clk_ordinary;
15018334Speter
15118334Speter    case COMPOUND_EXPR:
15252284Sobrien      return lvalue_p_1 (TREE_OPERAND (ref, 1),
153132718Skan			 treat_class_rvalues_as_lvalues);
15418334Speter
15552284Sobrien    case TARGET_EXPR:
15690075Sobrien      return treat_class_rvalues_as_lvalues ? clk_class : clk_none;
15752284Sobrien
158169689Skan    case VA_ARG_EXPR:
159169689Skan      return (treat_class_rvalues_as_lvalues
160169689Skan	      && CLASS_TYPE_P (TREE_TYPE (ref))
161169689Skan	      ? clk_class : clk_none);
162169689Skan
16352284Sobrien    case CALL_EXPR:
164132718Skan      /* Any class-valued call would be wrapped in a TARGET_EXPR.  */
165132718Skan      return clk_none;
16652284Sobrien
16752284Sobrien    case FUNCTION_DECL:
16852284Sobrien      /* All functions (except non-static-member functions) are
16952284Sobrien	 lvalues.  */
170169689Skan      return (DECL_NONSTATIC_MEMBER_FUNCTION_P (ref)
17190075Sobrien	      ? clk_none : clk_ordinary);
17252284Sobrien
173132718Skan    case NON_DEPENDENT_EXPR:
174132718Skan      /* We must consider NON_DEPENDENT_EXPRs to be lvalues so that
175132718Skan	 things like "&E" where "E" is an expression with a
176132718Skan	 non-dependent type work. It is safe to be lenient because an
177132718Skan	 error will be issued when the template is instantiated if "E"
178132718Skan	 is not an lvalue.  */
179132718Skan      return clk_ordinary;
180132718Skan
18150397Sobrien    default:
18250397Sobrien      break;
18318334Speter    }
18418334Speter
18590075Sobrien  /* If one operand is not an lvalue at all, then this expression is
18690075Sobrien     not an lvalue.  */
18790075Sobrien  if (!op1_lvalue_kind || !op2_lvalue_kind)
18890075Sobrien    return clk_none;
18990075Sobrien
19090075Sobrien  /* Otherwise, it's an lvalue, and it has all the odd properties
19190075Sobrien     contributed by either operand.  */
19290075Sobrien  op1_lvalue_kind = op1_lvalue_kind | op2_lvalue_kind;
19390075Sobrien  /* It's not an ordinary lvalue if it involves either a bit-field or
19490075Sobrien     a class rvalue.  */
19590075Sobrien  if ((op1_lvalue_kind & ~clk_ordinary) != clk_none)
19690075Sobrien    op1_lvalue_kind &= ~clk_ordinary;
19790075Sobrien  return op1_lvalue_kind;
19818334Speter}
19918334Speter
200117395Skan/* Returns the kind of lvalue that REF is, in the sense of
201117395Skan   [basic.lval].  This function should really be named lvalue_p; it
202117395Skan   computes the C++ definition of lvalue.  */
203117395Skan
204117395Skancp_lvalue_kind
205132718Skanreal_lvalue_p (tree ref)
206117395Skan{
207169689Skan  return lvalue_p_1 (ref,
208132718Skan		     /*treat_class_rvalues_as_lvalues=*/0);
209117395Skan}
210117395Skan
21190075Sobrien/* This differs from real_lvalue_p in that class rvalues are
21290075Sobrien   considered lvalues.  */
21352284Sobrien
21418334Speterint
215132718Skanlvalue_p (tree ref)
21618334Speter{
217169689Skan  return
218132718Skan    (lvalue_p_1 (ref, /*class rvalue ok*/ 1) != clk_none);
21918334Speter}
22018334Speter
221169689Skan/* Test whether DECL is a builtin that may appear in a
222169689Skan   constant-expression. */
22318334Speter
224169689Skanbool
225169689Skanbuiltin_valid_in_constant_expr_p (tree decl)
22618334Speter{
227169689Skan  /* At present BUILT_IN_CONSTANT_P is the only builtin we're allowing
228169689Skan     in constant-expressions.  We may want to add other builtins later. */
229169689Skan  return DECL_IS_BUILTIN_CONSTANT_P (decl);
23018334Speter}
23118334Speter
23290075Sobrien/* Build a TARGET_EXPR, initializing the DECL with the VALUE.  */
23390075Sobrien
23490075Sobrienstatic tree
235132718Skanbuild_target_expr (tree decl, tree value)
23690075Sobrien{
23790075Sobrien  tree t;
23890075Sobrien
239169689Skan  t = build4 (TARGET_EXPR, TREE_TYPE (decl), decl, value,
240169689Skan	      cxx_maybe_build_cleanup (decl), NULL_TREE);
24190075Sobrien  /* We always set TREE_SIDE_EFFECTS so that expand_expr does not
24290075Sobrien     ignore the TARGET_EXPR.  If there really turn out to be no
24390075Sobrien     side-effects, then the optimizer should be able to get rid of
24490075Sobrien     whatever code is generated anyhow.  */
24590075Sobrien  TREE_SIDE_EFFECTS (t) = 1;
24690075Sobrien
24790075Sobrien  return t;
24890075Sobrien}
24990075Sobrien
250132718Skan/* Return an undeclared local temporary of type TYPE for use in building a
251132718Skan   TARGET_EXPR.  */
252132718Skan
253132718Skanstatic tree
254132718Skanbuild_local_temp (tree type)
255132718Skan{
256132718Skan  tree slot = build_decl (VAR_DECL, NULL_TREE, type);
257132718Skan  DECL_ARTIFICIAL (slot) = 1;
258169689Skan  DECL_IGNORED_P (slot) = 1;
259132718Skan  DECL_CONTEXT (slot) = current_function_decl;
260132718Skan  layout_decl (slot, 0);
261132718Skan  return slot;
262132718Skan}
263132718Skan
26418334Speter/* INIT is a CALL_EXPR which needs info about its target.
26518334Speter   TYPE is the type that this initialization should appear to have.
26618334Speter
26718334Speter   Build an encapsulation of the initialization to perform
26818334Speter   and return it so that it can be processed by language-independent
26950397Sobrien   and language-specific expression expanders.  */
27018334Speter
27118334Spetertree
272132718Skanbuild_cplus_new (tree type, tree init)
27318334Speter{
27490075Sobrien  tree fn;
27518334Speter  tree slot;
27618334Speter  tree rval;
277132718Skan  int is_ctor;
27818334Speter
27990075Sobrien  /* Make sure that we're not trying to create an instance of an
28090075Sobrien     abstract class.  */
28190075Sobrien  abstract_virtuals_error (NULL_TREE, type);
28290075Sobrien
28350397Sobrien  if (TREE_CODE (init) != CALL_EXPR && TREE_CODE (init) != AGGR_INIT_EXPR)
28452284Sobrien    return convert (type, init);
28550397Sobrien
286132718Skan  fn = TREE_OPERAND (init, 0);
287132718Skan  is_ctor = (TREE_CODE (fn) == ADDR_EXPR
288132718Skan	     && TREE_CODE (TREE_OPERAND (fn, 0)) == FUNCTION_DECL
289132718Skan	     && DECL_CONSTRUCTOR_P (TREE_OPERAND (fn, 0)));
29090075Sobrien
291132718Skan  slot = build_local_temp (type);
292132718Skan
29390075Sobrien  /* We split the CALL_EXPR into its function and its arguments here.
29490075Sobrien     Then, in expand_expr, we put them back together.  The reason for
29590075Sobrien     this is that this expression might be a default argument
29690075Sobrien     expression.  In that case, we need a new temporary every time the
29790075Sobrien     expression is used.  That's what break_out_target_exprs does; it
29890075Sobrien     replaces every AGGR_INIT_EXPR with a copy that uses a fresh
29990075Sobrien     temporary slot.  Then, expand_expr builds up a call-expression
30090075Sobrien     using the new slot.  */
301132718Skan
302132718Skan  /* If we don't need to use a constructor to create an object of this
303132718Skan     type, don't mess with AGGR_INIT_EXPR.  */
304132718Skan  if (is_ctor || TREE_ADDRESSABLE (type))
305132718Skan    {
306169689Skan      rval = build3 (AGGR_INIT_EXPR, void_type_node, fn,
307169689Skan		     TREE_OPERAND (init, 1), slot);
308132718Skan      TREE_SIDE_EFFECTS (rval) = 1;
309132718Skan      AGGR_INIT_VIA_CTOR_P (rval) = is_ctor;
310132718Skan    }
311132718Skan  else
312132718Skan    rval = init;
313132718Skan
31490075Sobrien  rval = build_target_expr (slot, rval);
315169689Skan  TARGET_EXPR_IMPLICIT_P (rval) = 1;
31618334Speter
31718334Speter  return rval;
31818334Speter}
31918334Speter
320117395Skan/* Build a TARGET_EXPR using INIT to initialize a new temporary of the
32190075Sobrien   indicated TYPE.  */
32250397Sobrien
32350397Sobrientree
324132718Skanbuild_target_expr_with_type (tree init, tree type)
32550397Sobrien{
326169689Skan  gcc_assert (!VOID_TYPE_P (type));
32750397Sobrien
32890075Sobrien  if (TREE_CODE (init) == TARGET_EXPR)
32990075Sobrien    return init;
330122180Skan  else if (CLASS_TYPE_P (type) && !TYPE_HAS_TRIVIAL_INIT_REF (type)
331122180Skan	   && TREE_CODE (init) != COND_EXPR
332132718Skan	   && TREE_CODE (init) != CONSTRUCTOR
333132718Skan	   && TREE_CODE (init) != VA_ARG_EXPR)
334122180Skan    /* We need to build up a copy constructor call.  COND_EXPR is a special
335122180Skan       case because we already have copies on the arms and we don't want
336122180Skan       another one here.  A CONSTRUCTOR is aggregate initialization, which
337132718Skan       is handled separately.  A VA_ARG_EXPR is magic creation of an
338132718Skan       aggregate; there's no additional work to be done.  */
339122180Skan    return force_rvalue (init);
34090075Sobrien
341169689Skan  return force_target_expr (type, init);
34250397Sobrien}
34350397Sobrien
344132718Skan/* Like the above function, but without the checking.  This function should
345132718Skan   only be used by code which is deliberately trying to subvert the type
346132718Skan   system, such as call_builtin_trap.  */
34718334Speter
34818334Spetertree
349132718Skanforce_target_expr (tree type, tree init)
35018334Speter{
351169689Skan  tree slot;
352169689Skan
353169689Skan  gcc_assert (!VOID_TYPE_P (type));
354169689Skan
355169689Skan  slot = build_local_temp (type);
356132718Skan  return build_target_expr (slot, init);
35718334Speter}
35850397Sobrien
359132718Skan/* Like build_target_expr_with_type, but use the type of INIT.  */
360132718Skan
36118334Spetertree
362132718Skanget_target_expr (tree init)
36318334Speter{
364132718Skan  return build_target_expr_with_type (init, TREE_TYPE (init));
36518334Speter}
36618334Speter
367169689Skan/* If EXPR is a bitfield reference, convert it to the declared type of
368169689Skan   the bitfield, and return the resulting expression.  Otherwise,
369169689Skan   return EXPR itself.  */
370169689Skan
371169689Skantree
372169689Skanconvert_bitfield_to_declared_type (tree expr)
373169689Skan{
374169689Skan  tree bitfield_type;
375169689Skan
376169689Skan  bitfield_type = is_bitfield_expr_with_lowered_type (expr);
377169689Skan  if (bitfield_type)
378169689Skan    expr = convert_to_integer (TYPE_MAIN_VARIANT (bitfield_type),
379169689Skan			       expr);
380169689Skan  return expr;
381169689Skan}
382169689Skan
383169689Skan/* EXPR is being used in an rvalue context.  Return a version of EXPR
384169689Skan   that is marked as an rvalue.  */
385169689Skan
386169689Skantree
387169689Skanrvalue (tree expr)
388169689Skan{
389169689Skan  tree type;
390169689Skan
391169689Skan  if (error_operand_p (expr))
392169689Skan    return expr;
393169689Skan
394169689Skan  /* [basic.lval]
395169689Skan
396169689Skan     Non-class rvalues always have cv-unqualified types.  */
397169689Skan  type = TREE_TYPE (expr);
398169689Skan  if (!CLASS_TYPE_P (type) && cp_type_quals (type))
399169689Skan    type = TYPE_MAIN_VARIANT (type);
400169689Skan
401169689Skan  if (!processing_template_decl && real_lvalue_p (expr))
402169689Skan    expr = build1 (NON_LVALUE_EXPR, type, expr);
403169689Skan  else if (type != TREE_TYPE (expr))
404169689Skan    expr = build_nop (type, expr);
405169689Skan
406169689Skan  return expr;
407169689Skan}
408169689Skan
409132718Skan
41050397Sobrienstatic tree
411132718Skanbuild_cplus_array_type_1 (tree elt_type, tree index_type)
41218334Speter{
41318334Speter  tree t;
41418334Speter
41590075Sobrien  if (elt_type == error_mark_node || index_type == error_mark_node)
41690075Sobrien    return error_mark_node;
41718334Speter
418132718Skan  if (dependent_type_p (elt_type)
419132718Skan      || (index_type
420132718Skan	  && value_dependent_expression_p (TYPE_MAX_VALUE (index_type))))
42150397Sobrien    {
42250397Sobrien      t = make_node (ARRAY_TYPE);
42350397Sobrien      TREE_TYPE (t) = elt_type;
42450397Sobrien      TYPE_DOMAIN (t) = index_type;
42550397Sobrien    }
42650397Sobrien  else
42750397Sobrien    t = build_array_type (elt_type, index_type);
42818334Speter
42918334Speter  /* Push these needs up so that initialization takes place
43018334Speter     more easily.  */
431169689Skan  TYPE_NEEDS_CONSTRUCTING (t)
43290075Sobrien    = TYPE_NEEDS_CONSTRUCTING (TYPE_MAIN_VARIANT (elt_type));
433169689Skan  TYPE_HAS_NONTRIVIAL_DESTRUCTOR (t)
43490075Sobrien    = TYPE_HAS_NONTRIVIAL_DESTRUCTOR (TYPE_MAIN_VARIANT (elt_type));
43518334Speter  return t;
43618334Speter}
43750397Sobrien
43850397Sobrientree
439132718Skanbuild_cplus_array_type (tree elt_type, tree index_type)
44050397Sobrien{
44150397Sobrien  tree t;
44290075Sobrien  int type_quals = cp_type_quals (elt_type);
44352284Sobrien
444132718Skan  if (type_quals != TYPE_UNQUALIFIED)
445132718Skan    elt_type = cp_build_qualified_type (elt_type, TYPE_UNQUALIFIED);
44650397Sobrien
44750397Sobrien  t = build_cplus_array_type_1 (elt_type, index_type);
44850397Sobrien
449132718Skan  if (type_quals != TYPE_UNQUALIFIED)
450132718Skan    t = cp_build_qualified_type (t, type_quals);
45150397Sobrien
45250397Sobrien  return t;
45350397Sobrien}
45418334Speter
45590075Sobrien/* Make a variant of TYPE, qualified with the TYPE_QUALS.  Handles
45690075Sobrien   arrays correctly.  In particular, if TYPE is an array of T's, and
45796263Sobrien   TYPE_QUALS is non-empty, returns an array of qualified T's.
458169689Skan
45996263Sobrien   FLAGS determines how to deal with illformed qualifications. If
46096263Sobrien   tf_ignore_bad_quals is set, then bad qualifications are dropped
46196263Sobrien   (this is permitted if TYPE was introduced via a typedef or template
46296263Sobrien   type parameter). If bad qualifications are dropped and tf_warning
46396263Sobrien   is set, then a warning is issued for non-const qualifications.  If
46496263Sobrien   tf_ignore_bad_quals is not set and tf_error is not set, we
46596263Sobrien   return error_mark_node. Otherwise, we issue an error, and ignore
46696263Sobrien   the qualifications.
46718334Speter
46896263Sobrien   Qualification of a reference type is valid when the reference came
46996263Sobrien   via a typedef or template type argument. [dcl.ref] No such
47096263Sobrien   dispensation is provided for qualifying a function type.  [dcl.fct]
47196263Sobrien   DR 295 queries this and the proposed resolution brings it into line
472132718Skan   with qualifying a reference.  We implement the DR.  We also behave
47396263Sobrien   in a similar manner for restricting non-pointer types.  */
474169689Skan
47518334Spetertree
476169689Skancp_build_qualified_type_real (tree type,
477169689Skan			      int type_quals,
478169689Skan			      tsubst_flags_t complain)
47918334Speter{
48090075Sobrien  tree result;
48196263Sobrien  int bad_quals = TYPE_UNQUALIFIED;
48290075Sobrien
48350397Sobrien  if (type == error_mark_node)
48450397Sobrien    return type;
48590075Sobrien
48690075Sobrien  if (type_quals == cp_type_quals (type))
48790075Sobrien    return type;
48890075Sobrien
48996263Sobrien  if (TREE_CODE (type) == ARRAY_TYPE)
49090075Sobrien    {
49190075Sobrien      /* In C++, the qualification really applies to the array element
49290075Sobrien	 type.  Obtain the appropriately qualified element type.  */
49390075Sobrien      tree t;
494169689Skan      tree element_type
495169689Skan	= cp_build_qualified_type_real (TREE_TYPE (type),
49690075Sobrien					type_quals,
49790075Sobrien					complain);
49818334Speter
49990075Sobrien      if (element_type == error_mark_node)
50090075Sobrien	return error_mark_node;
50118334Speter
50290075Sobrien      /* See if we already have an identically qualified type.  */
503117395Skan      for (t = TYPE_MAIN_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
504169689Skan	if (cp_type_quals (t) == type_quals
505117395Skan	    && TYPE_NAME (t) == TYPE_NAME (type)
506117395Skan	    && TYPE_CONTEXT (t) == TYPE_CONTEXT (type))
507117395Skan	  break;
508169689Skan
50990075Sobrien      if (!t)
51018334Speter	{
51190075Sobrien	  /* Make a new array type, just like the old one, but with the
51290075Sobrien	     appropriately qualified element type.  */
513169689Skan	  t = build_variant_type_copy (type);
51490075Sobrien	  TREE_TYPE (t) = element_type;
51518334Speter	}
51618334Speter
51790075Sobrien      /* Even if we already had this variant, we update
51890075Sobrien	 TYPE_NEEDS_CONSTRUCTING and TYPE_HAS_NONTRIVIAL_DESTRUCTOR in case
519169689Skan	 they changed since the variant was originally created.
520169689Skan
52190075Sobrien	 This seems hokey; if there is some way to use a previous
52290075Sobrien	 variant *without* coming through here,
52390075Sobrien	 TYPE_NEEDS_CONSTRUCTING will never be updated.  */
524169689Skan      TYPE_NEEDS_CONSTRUCTING (t)
52590075Sobrien	= TYPE_NEEDS_CONSTRUCTING (TYPE_MAIN_VARIANT (element_type));
526169689Skan      TYPE_HAS_NONTRIVIAL_DESTRUCTOR (t)
52790075Sobrien	= TYPE_HAS_NONTRIVIAL_DESTRUCTOR (TYPE_MAIN_VARIANT (element_type));
52890075Sobrien      return t;
52918334Speter    }
53090075Sobrien  else if (TYPE_PTRMEMFUNC_P (type))
53190075Sobrien    {
53290075Sobrien      /* For a pointer-to-member type, we can't just return a
53390075Sobrien	 cv-qualified version of the RECORD_TYPE.  If we do, we
53496263Sobrien	 haven't changed the field that contains the actual pointer to
53590075Sobrien	 a method, and so TYPE_PTRMEMFUNC_FN_TYPE will be wrong.  */
53690075Sobrien      tree t;
53790075Sobrien
53890075Sobrien      t = TYPE_PTRMEMFUNC_FN_TYPE (type);
53990075Sobrien      t = cp_build_qualified_type_real (t, type_quals, complain);
54090075Sobrien      return build_ptrmemfunc_type (t);
54190075Sobrien    }
542169689Skan
543169689Skan  /* A reference or method type shall not be cv qualified.
544132718Skan     [dcl.ref], [dct.fct]  */
545132718Skan  if (type_quals & (TYPE_QUAL_CONST | TYPE_QUAL_VOLATILE)
546132718Skan      && (TREE_CODE (type) == REFERENCE_TYPE
547132718Skan	  || TREE_CODE (type) == METHOD_TYPE))
548132718Skan    {
549132718Skan      bad_quals |= type_quals & (TYPE_QUAL_CONST | TYPE_QUAL_VOLATILE);
550132718Skan      type_quals &= ~(TYPE_QUAL_CONST | TYPE_QUAL_VOLATILE);
551132718Skan    }
552169689Skan
553132718Skan  /* A restrict-qualified type must be a pointer (or reference)
554169689Skan     to object or incomplete type, or a function type. */
555132718Skan  if ((type_quals & TYPE_QUAL_RESTRICT)
556132718Skan      && TREE_CODE (type) != TEMPLATE_TYPE_PARM
557132718Skan      && TREE_CODE (type) != TYPENAME_TYPE
558169689Skan      && TREE_CODE (type) != FUNCTION_TYPE
559132718Skan      && !POINTER_TYPE_P (type))
560132718Skan    {
561132718Skan      bad_quals |= TYPE_QUAL_RESTRICT;
562132718Skan      type_quals &= ~TYPE_QUAL_RESTRICT;
563132718Skan    }
564132718Skan
565132718Skan  if (bad_quals == TYPE_UNQUALIFIED)
566132718Skan    /*OK*/;
567132718Skan  else if (!(complain & (tf_error | tf_ignore_bad_quals)))
568132718Skan    return error_mark_node;
569132718Skan  else
570132718Skan    {
571132718Skan      if (complain & tf_ignore_bad_quals)
572169689Skan	/* We're not going to warn about constifying things that can't
573169689Skan	   be constified.  */
574169689Skan	bad_quals &= ~TYPE_QUAL_CONST;
575132718Skan      if (bad_quals)
576169689Skan	{
577169689Skan	  tree bad_type = build_qualified_type (ptr_type_node, bad_quals);
578169689Skan
579169689Skan	  if (!(complain & tf_ignore_bad_quals))
580169689Skan	    error ("%qV qualifiers cannot be applied to %qT",
581132718Skan		   bad_type, type);
582169689Skan	}
583132718Skan    }
584169689Skan
58590075Sobrien  /* Retrieve (or create) the appropriately qualified variant.  */
58690075Sobrien  result = build_qualified_type (type, type_quals);
58790075Sobrien
58890075Sobrien  /* If this was a pointer-to-method type, and we just made a copy,
589117395Skan     then we need to unshare the record that holds the cached
590117395Skan     pointer-to-member-function type, because these will be distinct
591117395Skan     between the unqualified and qualified types.  */
592169689Skan  if (result != type
59390075Sobrien      && TREE_CODE (type) == POINTER_TYPE
59490075Sobrien      && TREE_CODE (TREE_TYPE (type)) == METHOD_TYPE)
595117395Skan    TYPE_LANG_SPECIFIC (result) = NULL;
59690075Sobrien
59790075Sobrien  return result;
59818334Speter}
59950397Sobrien
60050397Sobrien/* Returns the canonical version of TYPE.  In other words, if TYPE is
60150397Sobrien   a typedef, returns the underlying type.  The cv-qualification of
60250397Sobrien   the type returned matches the type input; they will always be
60350397Sobrien   compatible types.  */
60450397Sobrien
60550397Sobrientree
606132718Skancanonical_type_variant (tree t)
60750397Sobrien{
60890075Sobrien  return cp_build_qualified_type (TYPE_MAIN_VARIANT (t), cp_type_quals (t));
60950397Sobrien}
61018334Speter
611169689Skan/* Makes a copy of BINFO and TYPE, which is to be inherited into a
612169689Skan   graph dominated by T.  If BINFO is NULL, TYPE is a dependent base,
613169689Skan   and we do a shallow copy.  If BINFO is non-NULL, we do a deep copy.
614169689Skan   VIRT indicates whether TYPE is inherited virtually or not.
615169689Skan   IGO_PREV points at the previous binfo of the inheritance graph
616169689Skan   order chain.  The newly copied binfo's TREE_CHAIN forms this
617169689Skan   ordering.
61818334Speter
619169689Skan   The CLASSTYPE_VBASECLASSES vector of T is constructed in the
620169689Skan   correct order. That is in the order the bases themselves should be
621169689Skan   constructed in.
622132718Skan
623132718Skan   The BINFO_INHERITANCE of a virtual base class points to the binfo
624169689Skan   of the most derived type. ??? We could probably change this so that
625169689Skan   BINFO_INHERITANCE becomes synonymous with BINFO_PRIMARY, and hence
626169689Skan   remove a field.  They currently can only differ for primary virtual
627169689Skan   virtual bases.  */
628132718Skan
629132718Skantree
630169689Skancopy_binfo (tree binfo, tree type, tree t, tree *igo_prev, int virt)
63150397Sobrien{
632169689Skan  tree new_binfo;
63350397Sobrien
634169689Skan  if (virt)
635169689Skan    {
636169689Skan      /* See if we've already made this virtual base.  */
637169689Skan      new_binfo = binfo_for_vbase (type, t);
638169689Skan      if (new_binfo)
639169689Skan	return new_binfo;
640169689Skan    }
64150397Sobrien
642169689Skan  new_binfo = make_tree_binfo (binfo ? BINFO_N_BASE_BINFOS (binfo) : 0);
643169689Skan  BINFO_TYPE (new_binfo) = type;
644169689Skan
645169689Skan  /* Chain it into the inheritance graph.  */
646169689Skan  TREE_CHAIN (*igo_prev) = new_binfo;
647169689Skan  *igo_prev = new_binfo;
648169689Skan
649169689Skan  if (binfo)
65052284Sobrien    {
651169689Skan      int ix;
652169689Skan      tree base_binfo;
653132718Skan
654169689Skan      gcc_assert (!BINFO_DEPENDENT_BASE_P (binfo));
655169689Skan      gcc_assert (SAME_BINFO_TYPE_P (BINFO_TYPE (binfo), type));
656169689Skan
657169689Skan      BINFO_OFFSET (new_binfo) = BINFO_OFFSET (binfo);
658169689Skan      BINFO_VIRTUALS (new_binfo) = BINFO_VIRTUALS (binfo);
659169689Skan
660169689Skan      /* We do not need to copy the accesses, as they are read only.  */
661169689Skan      BINFO_BASE_ACCESSES (new_binfo) = BINFO_BASE_ACCESSES (binfo);
662169689Skan
663169689Skan      /* Recursively copy base binfos of BINFO.  */
664169689Skan      for (ix = 0; BINFO_BASE_ITERATE (binfo, ix, base_binfo); ix++)
665132718Skan	{
666169689Skan	  tree new_base_binfo;
667169689Skan
668169689Skan	  gcc_assert (!BINFO_DEPENDENT_BASE_P (base_binfo));
669169689Skan	  new_base_binfo = copy_binfo (base_binfo, BINFO_TYPE (base_binfo),
670169689Skan				       t, igo_prev,
671169689Skan				       BINFO_VIRTUAL_P (base_binfo));
672169689Skan
673169689Skan	  if (!BINFO_INHERITANCE_CHAIN (new_base_binfo))
674169689Skan	    BINFO_INHERITANCE_CHAIN (new_base_binfo) = new_binfo;
675169689Skan	  BINFO_BASE_APPEND (new_binfo, new_base_binfo);
676132718Skan	}
67750397Sobrien    }
678169689Skan  else
679169689Skan    BINFO_DEPENDENT_BASE_P (new_binfo) = 1;
680132718Skan
681169689Skan  if (virt)
682169689Skan    {
683169689Skan      /* Push it onto the list after any virtual bases it contains
684169689Skan	 will have been pushed.  */
685169689Skan      VEC_quick_push (tree, CLASSTYPE_VBASECLASSES (t), new_binfo);
686169689Skan      BINFO_VIRTUAL_P (new_binfo) = 1;
687169689Skan      BINFO_INHERITANCE_CHAIN (new_binfo) = TYPE_BINFO (t);
688169689Skan    }
689169689Skan
690169689Skan  return new_binfo;
69150397Sobrien}
69218334Speter
69318334Speter/* Hashing of lists so that we don't make duplicates.
69418334Speter   The entry point is `list_hash_canon'.  */
69518334Speter
69618334Speter/* Now here is the hash table.  When recording a list, it is added
69718334Speter   to the slot whose index is the hash code mod the table size.
69818334Speter   Note that the hash table is used for several kinds of lists.
69918334Speter   While all these live in the same table, they are completely independent,
70018334Speter   and the hash code is computed differently for each of these.  */
70118334Speter
702117395Skanstatic GTY ((param_is (union tree_node))) htab_t list_hash_table;
70318334Speter
704169689Skanstruct list_proxy
70590075Sobrien{
70690075Sobrien  tree purpose;
70790075Sobrien  tree value;
70890075Sobrien  tree chain;
70990075Sobrien};
71090075Sobrien
71190075Sobrien/* Compare ENTRY (an entry in the hash table) with DATA (a list_proxy
71290075Sobrien   for a node we are thinking about adding).  */
71390075Sobrien
71490075Sobrienstatic int
715132718Skanlist_hash_eq (const void* entry, const void* data)
71690075Sobrien{
71790075Sobrien  tree t = (tree) entry;
71890075Sobrien  struct list_proxy *proxy = (struct list_proxy *) data;
71990075Sobrien
72090075Sobrien  return (TREE_VALUE (t) == proxy->value
72190075Sobrien	  && TREE_PURPOSE (t) == proxy->purpose
72290075Sobrien	  && TREE_CHAIN (t) == proxy->chain);
72390075Sobrien}
72490075Sobrien
72518334Speter/* Compute a hash code for a list (chain of TREE_LIST nodes
72618334Speter   with goodies in the TREE_PURPOSE, TREE_VALUE, and bits of the
72718334Speter   TREE_COMMON slots), by adding the hash codes of the individual entries.  */
72818334Speter
72990075Sobrienstatic hashval_t
730132718Skanlist_hash_pieces (tree purpose, tree value, tree chain)
73118334Speter{
73290075Sobrien  hashval_t hashcode = 0;
733169689Skan
73450397Sobrien  if (chain)
735169689Skan    hashcode += TREE_HASH (chain);
736169689Skan
73750397Sobrien  if (value)
738169689Skan    hashcode += TREE_HASH (value);
73918334Speter  else
74018334Speter    hashcode += 1007;
74150397Sobrien  if (purpose)
742169689Skan    hashcode += TREE_HASH (purpose);
74318334Speter  else
74418334Speter    hashcode += 1009;
74518334Speter  return hashcode;
74618334Speter}
74718334Speter
74890075Sobrien/* Hash an already existing TREE_LIST.  */
74918334Speter
75090075Sobrienstatic hashval_t
751132718Skanlist_hash (const void* p)
75218334Speter{
75390075Sobrien  tree t = (tree) p;
754169689Skan  return list_hash_pieces (TREE_PURPOSE (t),
755169689Skan			   TREE_VALUE (t),
75690075Sobrien			   TREE_CHAIN (t));
75718334Speter}
75818334Speter
75952284Sobrien/* Given list components PURPOSE, VALUE, AND CHAIN, return the canonical
76052284Sobrien   object for an identical list if one already exists.  Otherwise, build a
76152284Sobrien   new one, and record it as the canonical object.  */
76218334Speter
76318334Spetertree
764132718Skanhash_tree_cons (tree purpose, tree value, tree chain)
76518334Speter{
76650397Sobrien  int hashcode = 0;
767132718Skan  void **slot;
76890075Sobrien  struct list_proxy proxy;
76918334Speter
77090075Sobrien  /* Hash the list node.  */
77190075Sobrien  hashcode = list_hash_pieces (purpose, value, chain);
77290075Sobrien  /* Create a proxy for the TREE_LIST we would like to create.  We
77390075Sobrien     don't actually create it so as to avoid creating garbage.  */
77490075Sobrien  proxy.purpose = purpose;
77590075Sobrien  proxy.value = value;
77690075Sobrien  proxy.chain = chain;
77790075Sobrien  /* See if it is already in the table.  */
77890075Sobrien  slot = htab_find_slot_with_hash (list_hash_table, &proxy, hashcode,
77990075Sobrien				   INSERT);
78090075Sobrien  /* If not, create a new node.  */
78190075Sobrien  if (!*slot)
782132718Skan    *slot = tree_cons (purpose, value, chain);
783169689Skan  return (tree) *slot;
78418334Speter}
78518334Speter
78618334Speter/* Constructor for hashed lists.  */
78750397Sobrien
78818334Spetertree
789132718Skanhash_tree_chain (tree value, tree chain)
79018334Speter{
79152284Sobrien  return hash_tree_cons (NULL_TREE, value, chain);
79218334Speter}
79318334Speter
79418334Spetervoid
795132718Skandebug_binfo (tree elem)
79618334Speter{
79790075Sobrien  HOST_WIDE_INT n;
79818334Speter  tree virtuals;
79918334Speter
800132718Skan  fprintf (stderr, "type \"%s\", offset = " HOST_WIDE_INT_PRINT_DEC
801132718Skan	   "\nvtable type:\n",
802132718Skan	   TYPE_NAME_STRING (BINFO_TYPE (elem)),
80390075Sobrien	   TREE_INT_CST_LOW (BINFO_OFFSET (elem)));
80418334Speter  debug_tree (BINFO_TYPE (elem));
80518334Speter  if (BINFO_VTABLE (elem))
80690075Sobrien    fprintf (stderr, "vtable decl \"%s\"\n",
80790075Sobrien	     IDENTIFIER_POINTER (DECL_NAME (get_vtbl_decl_for_binfo (elem))));
80818334Speter  else
80918334Speter    fprintf (stderr, "no vtable decl yet\n");
81018334Speter  fprintf (stderr, "virtuals:\n");
81118334Speter  virtuals = BINFO_VIRTUALS (elem);
81290075Sobrien  n = 0;
81318334Speter
81418334Speter  while (virtuals)
81518334Speter    {
81690075Sobrien      tree fndecl = TREE_VALUE (virtuals);
81750397Sobrien      fprintf (stderr, "%s [%ld =? %ld]\n",
81818334Speter	       IDENTIFIER_POINTER (DECL_ASSEMBLER_NAME (fndecl)),
81950397Sobrien	       (long) n, (long) TREE_INT_CST_LOW (DECL_VINDEX (fndecl)));
82018334Speter      ++n;
82118334Speter      virtuals = TREE_CHAIN (virtuals);
82218334Speter    }
82318334Speter}
82418334Speter
825169689Skan/* Build a representation for the qualified name SCOPE::NAME.  TYPE is
826169689Skan   the type of the result expression, if known, or NULL_TREE if the
827169689Skan   resulting expression is type-dependent.  If TEMPLATE_P is true,
828169689Skan   NAME is known to be a template because the user explicitly used the
829169689Skan   "template" keyword after the "::".
830169689Skan
831169689Skan   All SCOPE_REFs should be built by use of this function.  */
832169689Skan
833169689Skantree
834169689Skanbuild_qualified_name (tree type, tree scope, tree name, bool template_p)
83518334Speter{
836169689Skan  tree t;
837169689Skan  if (type == error_mark_node
838169689Skan      || scope == error_mark_node
839169689Skan      || name == error_mark_node)
840169689Skan    return error_mark_node;
841169689Skan  t = build2 (SCOPE_REF, type, scope, name);
842169689Skan  QUALIFIED_NAME_IS_TEMPLATE (t) = template_p;
843169689Skan  return t;
84418334Speter}
84518334Speter
846169689Skan/* Returns non-zero if X is an expression for a (possibly overloaded)
847169689Skan   function.  If "f" is a function or function template, "f", "c->f",
848169689Skan   "c.f", "C::f", and "f<int>" will all be considered possibly
849169689Skan   overloaded functions.  Returns 2 if the function is actually
850169689Skan   overloaded, i.e., if it is impossible to know the the type of the
851169689Skan   function without performing overload resolution.  */
852169689Skan
85318334Speterint
854132718Skanis_overloaded_fn (tree x)
85518334Speter{
85652284Sobrien  /* A baselink is also considered an overloaded function.  */
857169689Skan  if (TREE_CODE (x) == OFFSET_REF
858169689Skan      || TREE_CODE (x) == COMPONENT_REF)
85952284Sobrien    x = TREE_OPERAND (x, 1);
86052284Sobrien  if (BASELINK_P (x))
861117395Skan    x = BASELINK_FUNCTIONS (x);
862169689Skan  if (TREE_CODE (x) == TEMPLATE_ID_EXPR
863169689Skan      || DECL_FUNCTION_TEMPLATE_P (OVL_CURRENT (x))
864169689Skan      || (TREE_CODE (x) == OVERLOAD && OVL_CHAIN (x)))
865169689Skan    return 2;
866169689Skan  return  (TREE_CODE (x) == FUNCTION_DECL
867169689Skan	   || TREE_CODE (x) == OVERLOAD);
86818334Speter}
86918334Speter
870169689Skan/* Returns true iff X is an expression for an overloaded function
871169689Skan   whose type cannot be known without performing overload
872169689Skan   resolution.  */
873169689Skan
874169689Skanbool
875132718Skanreally_overloaded_fn (tree x)
876169689Skan{
877169689Skan  return is_overloaded_fn (x) == 2;
87818334Speter}
87918334Speter
88018334Spetertree
881132718Skanget_first_fn (tree from)
882117395Skan{
883169689Skan  gcc_assert (is_overloaded_fn (from));
884117395Skan  /* A baselink is also considered an overloaded function.  */
885169689Skan  if (TREE_CODE (from) == COMPONENT_REF)
886169689Skan    from = TREE_OPERAND (from, 1);
88752284Sobrien  if (BASELINK_P (from))
888117395Skan    from = BASELINK_FUNCTIONS (from);
88950397Sobrien  return OVL_CURRENT (from);
89050397Sobrien}
89118334Speter
892117395Skan/* Return a new OVL node, concatenating it with the old one.  */
89350397Sobrien
89450397Sobrientree
895132718Skanovl_cons (tree decl, tree chain)
89650397Sobrien{
89750397Sobrien  tree result = make_node (OVERLOAD);
89850397Sobrien  TREE_TYPE (result) = unknown_type_node;
89950397Sobrien  OVL_FUNCTION (result) = decl;
90050397Sobrien  TREE_CHAIN (result) = chain;
901169689Skan
90250397Sobrien  return result;
90318334Speter}
90418334Speter
90550397Sobrien/* Build a new overloaded function. If this is the first one,
90650397Sobrien   just return it; otherwise, ovl_cons the _DECLs */
90750397Sobrien
90850397Sobrientree
909132718Skanbuild_overload (tree decl, tree chain)
91018334Speter{
91152284Sobrien  if (! chain && TREE_CODE (decl) != TEMPLATE_DECL)
91250397Sobrien    return decl;
91352284Sobrien  if (chain && TREE_CODE (chain) != OVERLOAD)
91450397Sobrien    chain = ovl_cons (chain, NULL_TREE);
91550397Sobrien  return ovl_cons (decl, chain);
91618334Speter}
91718334Speter
91818334Speter
91918334Speter#define PRINT_RING_SIZE 4
92018334Speter
92190075Sobrienconst char *
922132718Skancxx_printable_name (tree decl, int v)
92318334Speter{
92418334Speter  static tree decl_ring[PRINT_RING_SIZE];
92518334Speter  static char *print_ring[PRINT_RING_SIZE];
92618334Speter  static int ring_counter;
92718334Speter  int i;
92818334Speter
92918334Speter  /* Only cache functions.  */
93050397Sobrien  if (v < 2
93150397Sobrien      || TREE_CODE (decl) != FUNCTION_DECL
93218334Speter      || DECL_LANG_SPECIFIC (decl) == 0)
93350397Sobrien    return lang_decl_name (decl, v);
93418334Speter
93518334Speter  /* See if this print name is lying around.  */
93618334Speter  for (i = 0; i < PRINT_RING_SIZE; i++)
93718334Speter    if (decl_ring[i] == decl)
93818334Speter      /* yes, so return it.  */
93918334Speter      return print_ring[i];
94018334Speter
94118334Speter  if (++ring_counter == PRINT_RING_SIZE)
94218334Speter    ring_counter = 0;
94318334Speter
94418334Speter  if (current_function_decl != NULL_TREE)
94518334Speter    {
94618334Speter      if (decl_ring[ring_counter] == current_function_decl)
94718334Speter	ring_counter += 1;
94818334Speter      if (ring_counter == PRINT_RING_SIZE)
94918334Speter	ring_counter = 0;
950169689Skan      gcc_assert (decl_ring[ring_counter] != current_function_decl);
95118334Speter    }
95218334Speter
95318334Speter  if (print_ring[ring_counter])
95418334Speter    free (print_ring[ring_counter]);
95518334Speter
95650397Sobrien  print_ring[ring_counter] = xstrdup (lang_decl_name (decl, v));
95750397Sobrien  decl_ring[ring_counter] = decl;
95818334Speter  return print_ring[ring_counter];
95918334Speter}
96018334Speter
96118334Speter/* Build the FUNCTION_TYPE or METHOD_TYPE which may throw exceptions
96218334Speter   listed in RAISES.  */
96350397Sobrien
96418334Spetertree
965132718Skanbuild_exception_variant (tree type, tree raises)
96618334Speter{
96718334Speter  tree v = TYPE_MAIN_VARIANT (type);
96852284Sobrien  int type_quals = TYPE_QUALS (type);
96918334Speter
97050397Sobrien  for (; v; v = TYPE_NEXT_VARIANT (v))
971169689Skan    if (check_qualified_type (v, type, type_quals)
972169689Skan	&& comp_except_specs (raises, TYPE_RAISES_EXCEPTIONS (v), 1))
97390075Sobrien      return v;
97452284Sobrien
97518334Speter  /* Need to build a new variant.  */
976169689Skan  v = build_variant_type_copy (type);
97718334Speter  TYPE_RAISES_EXCEPTIONS (v) = raises;
97818334Speter  return v;
97918334Speter}
98018334Speter
98190075Sobrien/* Given a TEMPLATE_TEMPLATE_PARM node T, create a new
98290075Sobrien   BOUND_TEMPLATE_TEMPLATE_PARM bound with NEWARGS as its template
98390075Sobrien   arguments.  */
98450397Sobrien
98550397Sobrientree
986132718Skanbind_template_template_parm (tree t, tree newargs)
98750397Sobrien{
98890075Sobrien  tree decl = TYPE_NAME (t);
98952284Sobrien  tree t2;
99052284Sobrien
99190075Sobrien  t2 = make_aggr_type (BOUND_TEMPLATE_TEMPLATE_PARM);
99290075Sobrien  decl = build_decl (TYPE_DECL, DECL_NAME (decl), NULL_TREE);
99352284Sobrien
99490075Sobrien  /* These nodes have to be created to reflect new TYPE_DECL and template
99590075Sobrien     arguments.  */
99690075Sobrien  TEMPLATE_TYPE_PARM_INDEX (t2) = copy_node (TEMPLATE_TYPE_PARM_INDEX (t));
99790075Sobrien  TEMPLATE_PARM_DECL (TEMPLATE_TYPE_PARM_INDEX (t2)) = decl;
99890075Sobrien  TEMPLATE_TEMPLATE_PARM_TEMPLATE_INFO (t2)
999169689Skan    = tree_cons (TEMPLATE_TEMPLATE_PARM_TEMPLATE_DECL (t),
100090075Sobrien		 newargs, NULL_TREE);
100152284Sobrien
100290075Sobrien  TREE_TYPE (decl) = t2;
100390075Sobrien  TYPE_NAME (t2) = decl;
100490075Sobrien  TYPE_STUB_DECL (t2) = decl;
100590075Sobrien  TYPE_SIZE (t2) = 0;
100650397Sobrien
100750397Sobrien  return t2;
100850397Sobrien}
100950397Sobrien
101090075Sobrien/* Called from count_trees via walk_tree.  */
101118334Speter
101290075Sobrienstatic tree
1013169689Skancount_trees_r (tree *tp, int *walk_subtrees, void *data)
101418334Speter{
1015169689Skan  ++*((int *) data);
1016169689Skan
1017169689Skan  if (TYPE_P (*tp))
1018169689Skan    *walk_subtrees = 0;
1019169689Skan
102090075Sobrien  return NULL_TREE;
102190075Sobrien}
102252284Sobrien
102390075Sobrien/* Debugging function for measuring the rough complexity of a tree
102490075Sobrien   representation.  */
102518334Speter
102690075Sobrienint
1027132718Skancount_trees (tree t)
102890075Sobrien{
102990075Sobrien  int n_trees = 0;
103090075Sobrien  walk_tree_without_duplicates (&t, count_trees_r, &n_trees);
103190075Sobrien  return n_trees;
1032169689Skan}
103318334Speter
103490075Sobrien/* Called from verify_stmt_tree via walk_tree.  */
103518334Speter
103690075Sobrienstatic tree
1037169689Skanverify_stmt_tree_r (tree* tp,
1038169689Skan		    int* walk_subtrees ATTRIBUTE_UNUSED ,
1039169689Skan		    void* data)
104090075Sobrien{
104190075Sobrien  tree t = *tp;
104290075Sobrien  htab_t *statements = (htab_t *) data;
104390075Sobrien  void **slot;
104452284Sobrien
1045132718Skan  if (!STATEMENT_CODE_P (TREE_CODE (t)))
104690075Sobrien    return NULL_TREE;
104752284Sobrien
104890075Sobrien  /* If this statement is already present in the hash table, then
104990075Sobrien     there is a circularity in the statement tree.  */
1050169689Skan  gcc_assert (!htab_find (*statements, t));
1051169689Skan
105290075Sobrien  slot = htab_find_slot (*statements, t, INSERT);
105390075Sobrien  *slot = t;
105452284Sobrien
105552284Sobrien  return NULL_TREE;
105652284Sobrien}
105752284Sobrien
105890075Sobrien/* Debugging function to check that the statement T has not been
105990075Sobrien   corrupted.  For now, this function simply checks that T contains no
106090075Sobrien   circularities.  */
106152284Sobrien
106290075Sobrienvoid
1063132718Skanverify_stmt_tree (tree t)
106452284Sobrien{
106590075Sobrien  htab_t statements;
106690075Sobrien  statements = htab_create (37, htab_hash_pointer, htab_eq_pointer, NULL);
106790075Sobrien  walk_tree (&t, verify_stmt_tree_r, &statements, NULL);
106890075Sobrien  htab_delete (statements);
106952284Sobrien}
107052284Sobrien
1071169689Skan/* Check if the type T depends on a type with no linkage and if so, return
1072169689Skan   it.  If RELAXED_P then do not consider a class type declared within
1073169689Skan   a TREE_PUBLIC function to have no linkage.  */
107452284Sobrien
1075169689Skantree
1076169689Skanno_linkage_check (tree t, bool relaxed_p)
107752284Sobrien{
1078169689Skan  tree r;
107990075Sobrien
1080169689Skan  /* There's no point in checking linkage on template functions; we
1081169689Skan     can't know their complete types.  */
1082169689Skan  if (processing_template_decl)
1083169689Skan    return NULL_TREE;
108452284Sobrien
1085169689Skan  switch (TREE_CODE (t))
1086169689Skan    {
1087169689Skan      tree fn;
108852284Sobrien
1089169689Skan    case RECORD_TYPE:
1090169689Skan      if (TYPE_PTRMEMFUNC_P (t))
1091169689Skan	goto ptrmem;
1092169689Skan      /* Fall through.  */
1093169689Skan    case UNION_TYPE:
1094169689Skan      if (!CLASS_TYPE_P (t))
1095169689Skan	return NULL_TREE;
1096169689Skan      /* Fall through.  */
1097169689Skan    case ENUMERAL_TYPE:
1098169689Skan      if (TYPE_ANONYMOUS_P (t))
1099169689Skan	return t;
1100169689Skan      fn = decl_function_context (TYPE_MAIN_DECL (t));
1101169689Skan      if (fn && (!relaxed_p || !TREE_PUBLIC (fn)))
1102169689Skan	return t;
1103169689Skan      return NULL_TREE;
110418334Speter
1105169689Skan    case ARRAY_TYPE:
1106169689Skan    case POINTER_TYPE:
1107169689Skan    case REFERENCE_TYPE:
1108169689Skan      return no_linkage_check (TREE_TYPE (t), relaxed_p);
110952284Sobrien
1110169689Skan    case OFFSET_TYPE:
1111169689Skan    ptrmem:
1112169689Skan      r = no_linkage_check (TYPE_PTRMEM_POINTED_TO_TYPE (t),
1113169689Skan			    relaxed_p);
1114169689Skan      if (r)
1115169689Skan	return r;
1116169689Skan      return no_linkage_check (TYPE_PTRMEM_CLASS_TYPE (t), relaxed_p);
111752284Sobrien
1118169689Skan    case METHOD_TYPE:
1119169689Skan      r = no_linkage_check (TYPE_METHOD_BASETYPE (t), relaxed_p);
1120169689Skan      if (r)
1121169689Skan	return r;
1122169689Skan      /* Fall through.  */
1123169689Skan    case FUNCTION_TYPE:
1124169689Skan      {
1125169689Skan	tree parm;
1126169689Skan	for (parm = TYPE_ARG_TYPES (t);
1127169689Skan	     parm && parm != void_list_node;
1128169689Skan	     parm = TREE_CHAIN (parm))
1129169689Skan	  {
1130169689Skan	    r = no_linkage_check (TREE_VALUE (parm), relaxed_p);
1131169689Skan	    if (r)
1132169689Skan	      return r;
1133169689Skan	  }
1134169689Skan	return no_linkage_check (TREE_TYPE (t), relaxed_p);
1135169689Skan      }
113618334Speter
1137169689Skan    default:
1138169689Skan      return NULL_TREE;
1139169689Skan    }
114018334Speter}
114118334Speter
114250397Sobrien#ifdef GATHER_STATISTICS
114350397Sobrienextern int depth_reached;
114450397Sobrien#endif
114550397Sobrien
114618334Spetervoid
1147132718Skancxx_print_statistics (void)
114818334Speter{
114918334Speter  print_search_statistics ();
115018334Speter  print_class_statistics ();
115150397Sobrien#ifdef GATHER_STATISTICS
115250397Sobrien  fprintf (stderr, "maximum template instantiation depth reached: %d\n",
115350397Sobrien	   depth_reached);
115450397Sobrien#endif
115518334Speter}
115618334Speter
115750397Sobrien/* Return, as an INTEGER_CST node, the number of elements for TYPE
115850397Sobrien   (which is an ARRAY_TYPE).  This counts only elements of the top
115950397Sobrien   array.  */
116018334Speter
116118334Spetertree
1162132718Skanarray_type_nelts_top (tree type)
116318334Speter{
1164169689Skan  return fold_build2 (PLUS_EXPR, sizetype,
116518334Speter		      array_type_nelts (type),
1166169689Skan		      integer_one_node);
116718334Speter}
116818334Speter
116950397Sobrien/* Return, as an INTEGER_CST node, the number of elements for TYPE
117050397Sobrien   (which is an ARRAY_TYPE).  This one is a recursive count of all
117150397Sobrien   ARRAY_TYPEs that are clumped together.  */
117218334Speter
117318334Spetertree
1174132718Skanarray_type_nelts_total (tree type)
117518334Speter{
117618334Speter  tree sz = array_type_nelts_top (type);
117718334Speter  type = TREE_TYPE (type);
117818334Speter  while (TREE_CODE (type) == ARRAY_TYPE)
117918334Speter    {
118018334Speter      tree n = array_type_nelts_top (type);
1181169689Skan      sz = fold_build2 (MULT_EXPR, sizetype, sz, n);
118218334Speter      type = TREE_TYPE (type);
118318334Speter    }
118418334Speter  return sz;
118518334Speter}
118618334Speter
118790075Sobrien/* Called from break_out_target_exprs via mapcar.  */
118890075Sobrien
118990075Sobrienstatic tree
1190132718Skanbot_manip (tree* tp, int* walk_subtrees, void* data)
119118334Speter{
119290075Sobrien  splay_tree target_remap = ((splay_tree) data);
119390075Sobrien  tree t = *tp;
119490075Sobrien
1195169689Skan  if (!TYPE_P (t) && TREE_CONSTANT (t))
119650397Sobrien    {
119790075Sobrien      /* There can't be any TARGET_EXPRs or their slot variables below
1198169689Skan	 this point.  We used to check !TREE_SIDE_EFFECTS, but then we
1199169689Skan	 failed to copy an ADDR_EXPR of the slot VAR_DECL.  */
120090075Sobrien      *walk_subtrees = 0;
120190075Sobrien      return NULL_TREE;
120290075Sobrien    }
120390075Sobrien  if (TREE_CODE (t) == TARGET_EXPR)
120490075Sobrien    {
120590075Sobrien      tree u;
120690075Sobrien
120750397Sobrien      if (TREE_CODE (TREE_OPERAND (t, 1)) == AGGR_INIT_EXPR)
1208169689Skan	u = build_cplus_new
1209169689Skan	  (TREE_TYPE (t), break_out_target_exprs (TREE_OPERAND (t, 1)));
1210169689Skan      else
1211169689Skan	u = build_target_expr_with_type
1212169689Skan	  (break_out_target_exprs (TREE_OPERAND (t, 1)), TREE_TYPE (t));
121390075Sobrien
121490075Sobrien      /* Map the old variable to the new one.  */
1215169689Skan      splay_tree_insert (target_remap,
1216169689Skan			 (splay_tree_key) TREE_OPERAND (t, 0),
121790075Sobrien			 (splay_tree_value) TREE_OPERAND (u, 0));
121890075Sobrien
121990075Sobrien      /* Replace the old expression with the new version.  */
122090075Sobrien      *tp = u;
122190075Sobrien      /* We don't have to go below this point; the recursive call to
122290075Sobrien	 break_out_target_exprs will have handled anything below this
122390075Sobrien	 point.  */
122490075Sobrien      *walk_subtrees = 0;
122590075Sobrien      return NULL_TREE;
122650397Sobrien    }
122750397Sobrien
122890075Sobrien  /* Make a copy of this node.  */
122990075Sobrien  return copy_tree_r (tp, walk_subtrees, NULL);
123018334Speter}
1231169689Skan
123290075Sobrien/* Replace all remapped VAR_DECLs in T with their new equivalents.
123390075Sobrien   DATA is really a splay-tree mapping old variables to new
123490075Sobrien   variables.  */
123550397Sobrien
123690075Sobrienstatic tree
1237169689Skanbot_replace (tree* t,
1238169689Skan	     int* walk_subtrees ATTRIBUTE_UNUSED ,
1239169689Skan	     void* data)
124090075Sobrien{
124190075Sobrien  splay_tree target_remap = ((splay_tree) data);
124290075Sobrien
124390075Sobrien  if (TREE_CODE (*t) == VAR_DECL)
124490075Sobrien    {
124590075Sobrien      splay_tree_node n = splay_tree_lookup (target_remap,
124690075Sobrien					     (splay_tree_key) *t);
124790075Sobrien      if (n)
124890075Sobrien	*t = (tree) n->value;
124990075Sobrien    }
125090075Sobrien
125190075Sobrien  return NULL_TREE;
125290075Sobrien}
1253169689Skan
125490075Sobrien/* When we parse a default argument expression, we may create
125590075Sobrien   temporary variables via TARGET_EXPRs.  When we actually use the
125690075Sobrien   default-argument expression, we make a copy of the expression, but
125790075Sobrien   we must replace the temporaries with appropriate local versions.  */
125890075Sobrien
125918334Spetertree
1260132718Skanbreak_out_target_exprs (tree t)
126118334Speter{
126290075Sobrien  static int target_remap_count;
126390075Sobrien  static splay_tree target_remap;
126490075Sobrien
126590075Sobrien  if (!target_remap_count++)
1266169689Skan    target_remap = splay_tree_new (splay_tree_compare_pointers,
1267169689Skan				   /*splay_tree_delete_key_fn=*/NULL,
126890075Sobrien				   /*splay_tree_delete_value_fn=*/NULL);
126990075Sobrien  walk_tree (&t, bot_manip, target_remap, NULL);
127090075Sobrien  walk_tree (&t, bot_replace, target_remap, NULL);
127190075Sobrien
127290075Sobrien  if (!--target_remap_count)
127390075Sobrien    {
127490075Sobrien      splay_tree_delete (target_remap);
127590075Sobrien      target_remap = NULL;
127690075Sobrien    }
127790075Sobrien
127890075Sobrien  return t;
127918334Speter}
128018334Speter
1281132718Skan/* Similar to `build_nt', but for template definitions of dependent
1282132718Skan   expressions  */
128350397Sobrien
128418334Spetertree
1285132718Skanbuild_min_nt (enum tree_code code, ...)
128618334Speter{
1287132718Skan  tree t;
1288132718Skan  int length;
1289132718Skan  int i;
1290132718Skan  va_list p;
129118334Speter
1292132718Skan  va_start (p, code);
129350397Sobrien
129450397Sobrien  t = make_node (code);
129590075Sobrien  length = TREE_CODE_LENGTH (code);
129650397Sobrien
129750397Sobrien  for (i = 0; i < length; i++)
129850397Sobrien    {
129950397Sobrien      tree x = va_arg (p, tree);
130090075Sobrien      TREE_OPERAND (t, i) = x;
130150397Sobrien    }
130250397Sobrien
1303132718Skan  va_end (p);
130418334Speter  return t;
130518334Speter}
130618334Speter
1307132718Skan/* Similar to `build', but for template definitions.  */
130850397Sobrien
130918334Spetertree
1310132718Skanbuild_min (enum tree_code code, tree tt, ...)
131118334Speter{
1312132718Skan  tree t;
1313132718Skan  int length;
1314132718Skan  int i;
1315132718Skan  va_list p;
131618334Speter
1317132718Skan  va_start (p, tt);
131818334Speter
131950397Sobrien  t = make_node (code);
132090075Sobrien  length = TREE_CODE_LENGTH (code);
132190075Sobrien  TREE_TYPE (t) = tt;
132250397Sobrien
132350397Sobrien  for (i = 0; i < length; i++)
132418334Speter    {
132550397Sobrien      tree x = va_arg (p, tree);
132690075Sobrien      TREE_OPERAND (t, i) = x;
1327169689Skan      if (x && !TYPE_P (x) && TREE_SIDE_EFFECTS (x))
1328132718Skan	TREE_SIDE_EFFECTS (t) = 1;
132950397Sobrien    }
133050397Sobrien
1331132718Skan  va_end (p);
133250397Sobrien  return t;
133350397Sobrien}
133450397Sobrien
1335132718Skan/* Similar to `build', but for template definitions of non-dependent
1336132718Skan   expressions. NON_DEP is the non-dependent expression that has been
1337132718Skan   built.  */
1338132718Skan
1339132718Skantree
1340132718Skanbuild_min_non_dep (enum tree_code code, tree non_dep, ...)
1341132718Skan{
1342132718Skan  tree t;
1343132718Skan  int length;
1344132718Skan  int i;
1345132718Skan  va_list p;
1346132718Skan
1347132718Skan  va_start (p, non_dep);
1348132718Skan
1349132718Skan  t = make_node (code);
1350132718Skan  length = TREE_CODE_LENGTH (code);
1351132718Skan  TREE_TYPE (t) = TREE_TYPE (non_dep);
1352132718Skan  TREE_SIDE_EFFECTS (t) = TREE_SIDE_EFFECTS (non_dep);
1353132718Skan
1354132718Skan  for (i = 0; i < length; i++)
1355132718Skan    {
1356132718Skan      tree x = va_arg (p, tree);
1357132718Skan      TREE_OPERAND (t, i) = x;
1358132718Skan    }
1359132718Skan
1360132718Skan  if (code == COMPOUND_EXPR && TREE_CODE (non_dep) != COMPOUND_EXPR)
1361132718Skan    /* This should not be considered a COMPOUND_EXPR, because it
1362132718Skan       resolves to an overload.  */
1363132718Skan    COMPOUND_EXPR_OVERLOADED (t) = 1;
1364169689Skan
1365132718Skan  va_end (p);
1366132718Skan  return t;
1367132718Skan}
1368132718Skan
136950397Sobrientree
1370132718Skanget_type_decl (tree t)
137150397Sobrien{
137250397Sobrien  if (TREE_CODE (t) == TYPE_DECL)
137350397Sobrien    return t;
137490075Sobrien  if (TYPE_P (t))
137550397Sobrien    return TYPE_STUB_DECL (t);
1376169689Skan  gcc_assert (t == error_mark_node);
1377169689Skan  return t;
137850397Sobrien}
137950397Sobrien
138052284Sobrien/* Returns the namespace that contains DECL, whether directly or
138152284Sobrien   indirectly.  */
138252284Sobrien
138352284Sobrientree
1384132718Skandecl_namespace_context (tree decl)
138552284Sobrien{
138652284Sobrien  while (1)
138752284Sobrien    {
138852284Sobrien      if (TREE_CODE (decl) == NAMESPACE_DECL)
138952284Sobrien	return decl;
139052284Sobrien      else if (TYPE_P (decl))
139152284Sobrien	decl = CP_DECL_CONTEXT (TYPE_MAIN_DECL (decl));
139252284Sobrien      else
139352284Sobrien	decl = CP_DECL_CONTEXT (decl);
139452284Sobrien    }
139552284Sobrien}
139652284Sobrien
1397169689Skan/* Returns true if decl is within an anonymous namespace, however deeply
1398169689Skan   nested, or false otherwise.  */
1399169689Skan
1400169689Skanbool
1401169689Skandecl_anon_ns_mem_p (tree decl)
1402169689Skan{
1403169689Skan  while (1)
1404169689Skan    {
1405169689Skan      if (decl == NULL_TREE || decl == error_mark_node)
1406169689Skan	return false;
1407169689Skan      if (TREE_CODE (decl) == NAMESPACE_DECL
1408169689Skan	  && DECL_NAME (decl) == NULL_TREE)
1409169689Skan	return true;
1410169689Skan      /* Classes and namespaces inside anonymous namespaces have
1411169689Skan         TREE_PUBLIC == 0, so we can shortcut the search.  */
1412169689Skan      else if (TYPE_P (decl))
1413169689Skan	return (TREE_PUBLIC (TYPE_NAME (decl)) == 0);
1414169689Skan      else if (TREE_CODE (decl) == NAMESPACE_DECL)
1415169689Skan	return (TREE_PUBLIC (decl) == 0);
1416169689Skan      else
1417169689Skan	decl = DECL_CONTEXT (decl);
1418169689Skan    }
1419169689Skan}
1420169689Skan
142150397Sobrien/* Return truthvalue of whether T1 is the same tree structure as T2.
1422132718Skan   Return 1 if they are the same. Return 0 if they are different.  */
142350397Sobrien
1424132718Skanbool
1425132718Skancp_tree_equal (tree t1, tree t2)
142650397Sobrien{
1427132718Skan  enum tree_code code1, code2;
142850397Sobrien
142950397Sobrien  if (t1 == t2)
1430132718Skan    return true;
1431132718Skan  if (!t1 || !t2)
1432132718Skan    return false;
143350397Sobrien
1434132718Skan  for (code1 = TREE_CODE (t1);
1435132718Skan       code1 == NOP_EXPR || code1 == CONVERT_EXPR
1436132718Skan	 || code1 == NON_LVALUE_EXPR;
1437132718Skan       code1 = TREE_CODE (t1))
1438132718Skan    t1 = TREE_OPERAND (t1, 0);
1439132718Skan  for (code2 = TREE_CODE (t2);
1440132718Skan       code2 == NOP_EXPR || code2 == CONVERT_EXPR
1441132718Skan	 || code1 == NON_LVALUE_EXPR;
1442132718Skan       code2 = TREE_CODE (t2))
1443132718Skan    t2 = TREE_OPERAND (t2, 0);
144450397Sobrien
1445132718Skan  /* They might have become equal now.  */
1446132718Skan  if (t1 == t2)
1447132718Skan    return true;
1448169689Skan
144950397Sobrien  if (code1 != code2)
1450132718Skan    return false;
145150397Sobrien
145250397Sobrien  switch (code1)
145350397Sobrien    {
145450397Sobrien    case INTEGER_CST:
145550397Sobrien      return TREE_INT_CST_LOW (t1) == TREE_INT_CST_LOW (t2)
145650397Sobrien	&& TREE_INT_CST_HIGH (t1) == TREE_INT_CST_HIGH (t2);
145750397Sobrien
145850397Sobrien    case REAL_CST:
145950397Sobrien      return REAL_VALUES_EQUAL (TREE_REAL_CST (t1), TREE_REAL_CST (t2));
146050397Sobrien
146150397Sobrien    case STRING_CST:
146250397Sobrien      return TREE_STRING_LENGTH (t1) == TREE_STRING_LENGTH (t2)
146390075Sobrien	&& !memcmp (TREE_STRING_POINTER (t1), TREE_STRING_POINTER (t2),
1464132718Skan		    TREE_STRING_LENGTH (t1));
146550397Sobrien
1466169689Skan    case COMPLEX_CST:
1467169689Skan      return cp_tree_equal (TREE_REALPART (t1), TREE_REALPART (t2))
1468169689Skan	&& cp_tree_equal (TREE_IMAGPART (t1), TREE_IMAGPART (t2));
1469169689Skan
147050397Sobrien    case CONSTRUCTOR:
147150397Sobrien      /* We need to do this when determining whether or not two
147250397Sobrien	 non-type pointer to member function template arguments
147350397Sobrien	 are the same.  */
147452284Sobrien      if (!(same_type_p (TREE_TYPE (t1), TREE_TYPE (t2))
147550397Sobrien	    /* The first operand is RTL.  */
147650397Sobrien	    && TREE_OPERAND (t1, 0) == TREE_OPERAND (t2, 0)))
1477132718Skan	return false;
147850397Sobrien      return cp_tree_equal (TREE_OPERAND (t1, 1), TREE_OPERAND (t2, 1));
147950397Sobrien
148050397Sobrien    case TREE_LIST:
1481132718Skan      if (!cp_tree_equal (TREE_PURPOSE (t1), TREE_PURPOSE (t2)))
1482132718Skan	return false;
1483132718Skan      if (!cp_tree_equal (TREE_VALUE (t1), TREE_VALUE (t2)))
1484132718Skan	return false;
148550397Sobrien      return cp_tree_equal (TREE_CHAIN (t1), TREE_CHAIN (t2));
148650397Sobrien
148718334Speter    case SAVE_EXPR:
148850397Sobrien      return cp_tree_equal (TREE_OPERAND (t1, 0), TREE_OPERAND (t2, 0));
148918334Speter
149050397Sobrien    case CALL_EXPR:
1491132718Skan      if (!cp_tree_equal (TREE_OPERAND (t1, 0), TREE_OPERAND (t2, 0)))
1492132718Skan	return false;
1493132718Skan      return cp_tree_equal (TREE_OPERAND (t1, 1), TREE_OPERAND (t2, 1));
149450397Sobrien
149518334Speter    case TARGET_EXPR:
1496132718Skan      {
1497132718Skan	tree o1 = TREE_OPERAND (t1, 0);
1498132718Skan	tree o2 = TREE_OPERAND (t2, 0);
1499169689Skan
1500132718Skan	/* Special case: if either target is an unallocated VAR_DECL,
1501132718Skan	   it means that it's going to be unified with whatever the
1502132718Skan	   TARGET_EXPR is really supposed to initialize, so treat it
1503132718Skan	   as being equivalent to anything.  */
1504132718Skan	if (TREE_CODE (o1) == VAR_DECL && DECL_NAME (o1) == NULL_TREE
1505132718Skan	    && !DECL_RTL_SET_P (o1))
1506132718Skan	  /*Nop*/;
1507132718Skan	else if (TREE_CODE (o2) == VAR_DECL && DECL_NAME (o2) == NULL_TREE
1508132718Skan		 && !DECL_RTL_SET_P (o2))
1509132718Skan	  /*Nop*/;
1510132718Skan	else if (!cp_tree_equal (o1, o2))
1511132718Skan	  return false;
1512169689Skan
1513132718Skan	return cp_tree_equal (TREE_OPERAND (t1, 1), TREE_OPERAND (t2, 1));
1514132718Skan      }
1515169689Skan
151650397Sobrien    case WITH_CLEANUP_EXPR:
1517132718Skan      if (!cp_tree_equal (TREE_OPERAND (t1, 0), TREE_OPERAND (t2, 0)))
1518132718Skan	return false;
151990075Sobrien      return cp_tree_equal (TREE_OPERAND (t1, 1), TREE_OPERAND (t1, 1));
152050397Sobrien
152150397Sobrien    case COMPONENT_REF:
1522132718Skan      if (TREE_OPERAND (t1, 1) != TREE_OPERAND (t2, 1))
1523132718Skan	return false;
1524132718Skan      return cp_tree_equal (TREE_OPERAND (t1, 0), TREE_OPERAND (t2, 0));
152550397Sobrien
152650397Sobrien    case VAR_DECL:
152750397Sobrien    case PARM_DECL:
152850397Sobrien    case CONST_DECL:
152950397Sobrien    case FUNCTION_DECL:
1530132718Skan    case TEMPLATE_DECL:
1531132718Skan    case IDENTIFIER_NODE:
1532169689Skan    case SSA_NAME:
1533132718Skan      return false;
153450397Sobrien
1535146895Skan    case BASELINK:
1536146895Skan      return (BASELINK_BINFO (t1) == BASELINK_BINFO (t2)
1537146895Skan	      && BASELINK_ACCESS_BINFO (t1) == BASELINK_ACCESS_BINFO (t2)
1538146895Skan	      && cp_tree_equal (BASELINK_FUNCTIONS (t1),
1539146895Skan				BASELINK_FUNCTIONS (t2)));
1540146895Skan
154150397Sobrien    case TEMPLATE_PARM_INDEX:
1542117395Skan      return (TEMPLATE_PARM_IDX (t1) == TEMPLATE_PARM_IDX (t2)
1543117395Skan	      && TEMPLATE_PARM_LEVEL (t1) == TEMPLATE_PARM_LEVEL (t2)
1544117395Skan	      && same_type_p (TREE_TYPE (TEMPLATE_PARM_DECL (t1)),
1545117395Skan			      TREE_TYPE (TEMPLATE_PARM_DECL (t2))));
154650397Sobrien
1547132718Skan    case TEMPLATE_ID_EXPR:
1548132718Skan      {
1549132718Skan	unsigned ix;
1550132718Skan	tree vec1, vec2;
1551169689Skan
1552132718Skan	if (!cp_tree_equal (TREE_OPERAND (t1, 0), TREE_OPERAND (t2, 0)))
1553132718Skan	  return false;
1554132718Skan	vec1 = TREE_OPERAND (t1, 1);
1555132718Skan	vec2 = TREE_OPERAND (t2, 1);
1556132718Skan
1557132718Skan	if (!vec1 || !vec2)
1558132718Skan	  return !vec1 && !vec2;
1559169689Skan
1560132718Skan	if (TREE_VEC_LENGTH (vec1) != TREE_VEC_LENGTH (vec2))
1561132718Skan	  return false;
1562132718Skan
1563132718Skan	for (ix = TREE_VEC_LENGTH (vec1); ix--;)
1564132718Skan	  if (!cp_tree_equal (TREE_VEC_ELT (vec1, ix),
1565132718Skan			      TREE_VEC_ELT (vec2, ix)))
1566132718Skan	    return false;
1567169689Skan
1568132718Skan	return true;
1569132718Skan      }
1570169689Skan
157150397Sobrien    case SIZEOF_EXPR:
157250397Sobrien    case ALIGNOF_EXPR:
1573132718Skan      {
1574132718Skan	tree o1 = TREE_OPERAND (t1, 0);
1575132718Skan	tree o2 = TREE_OPERAND (t2, 0);
1576169689Skan
1577132718Skan	if (TREE_CODE (o1) != TREE_CODE (o2))
1578132718Skan	  return false;
1579132718Skan	if (TYPE_P (o1))
1580132718Skan	  return same_type_p (o1, o2);
1581132718Skan	else
1582132718Skan	  return cp_tree_equal (o1, o2);
1583132718Skan      }
1584169689Skan
158552284Sobrien    case PTRMEM_CST:
158652284Sobrien      /* Two pointer-to-members are the same if they point to the same
158752284Sobrien	 field or function in the same class.  */
1588132718Skan      if (PTRMEM_CST_MEMBER (t1) != PTRMEM_CST_MEMBER (t2))
1589132718Skan	return false;
159052284Sobrien
1591132718Skan      return same_type_p (PTRMEM_CST_CLASS (t1), PTRMEM_CST_CLASS (t2));
1592132718Skan
1593146895Skan    case OVERLOAD:
1594146895Skan      if (OVL_FUNCTION (t1) != OVL_FUNCTION (t2))
1595146895Skan	return false;
1596146895Skan      return cp_tree_equal (OVL_CHAIN (t1), OVL_CHAIN (t2));
1597146895Skan
159850397Sobrien    default:
159918334Speter      break;
160050397Sobrien    }
160118334Speter
160250397Sobrien  switch (TREE_CODE_CLASS (code1))
160350397Sobrien    {
1604169689Skan    case tcc_unary:
1605169689Skan    case tcc_binary:
1606169689Skan    case tcc_comparison:
1607169689Skan    case tcc_expression:
1608169689Skan    case tcc_reference:
1609169689Skan    case tcc_statement:
161090075Sobrien      {
161190075Sobrien	int i;
1612169689Skan
161390075Sobrien	for (i = 0; i < TREE_CODE_LENGTH (code1); ++i)
1614132718Skan	  if (!cp_tree_equal (TREE_OPERAND (t1, i), TREE_OPERAND (t2, i)))
1615132718Skan	    return false;
1616169689Skan
1617132718Skan	return true;
161890075Sobrien      }
1619169689Skan
1620169689Skan    case tcc_type:
1621132718Skan      return same_type_p (t1, t2);
1622169689Skan    default:
1623169689Skan      gcc_unreachable ();
162418334Speter    }
1625169689Skan  /* We can get here with --disable-checking.  */
1626132718Skan  return false;
162750397Sobrien}
162818334Speter
162950397Sobrien/* The type of ARG when used as an lvalue.  */
163050397Sobrien
163150397Sobrientree
1632132718Skanlvalue_type (tree arg)
163350397Sobrien{
163450397Sobrien  tree type = TREE_TYPE (arg);
163552284Sobrien  return type;
163650397Sobrien}
163750397Sobrien
163850397Sobrien/* The type of ARG for printing error messages; denote lvalues with
163950397Sobrien   reference types.  */
164050397Sobrien
164150397Sobrientree
1642132718Skanerror_type (tree arg)
164350397Sobrien{
164450397Sobrien  tree type = TREE_TYPE (arg);
1645169689Skan
164650397Sobrien  if (TREE_CODE (type) == ARRAY_TYPE)
164750397Sobrien    ;
1648132718Skan  else if (TREE_CODE (type) == ERROR_MARK)
1649132718Skan    ;
165050397Sobrien  else if (real_lvalue_p (arg))
165150397Sobrien    type = build_reference_type (lvalue_type (arg));
165250397Sobrien  else if (IS_AGGR_TYPE (type))
165350397Sobrien    type = lvalue_type (arg);
165450397Sobrien
165550397Sobrien  return type;
165650397Sobrien}
165750397Sobrien
165850397Sobrien/* Does FUNCTION use a variable-length argument list?  */
165950397Sobrien
166018334Speterint
1661132718Skanvarargs_function_p (tree function)
166218334Speter{
166350397Sobrien  tree parm = TYPE_ARG_TYPES (TREE_TYPE (function));
166450397Sobrien  for (; parm; parm = TREE_CHAIN (parm))
166550397Sobrien    if (TREE_VALUE (parm) == void_type_node)
166650397Sobrien      return 0;
166750397Sobrien  return 1;
166818334Speter}
166950397Sobrien
167050397Sobrien/* Returns 1 if decl is a member of a class.  */
167150397Sobrien
167250397Sobrienint
1673132718Skanmember_p (tree decl)
167450397Sobrien{
167590075Sobrien  const tree ctx = DECL_CONTEXT (decl);
167690075Sobrien  return (ctx && TYPE_P (ctx));
167750397Sobrien}
167852284Sobrien
167952284Sobrien/* Create a placeholder for member access where we don't actually have an
168052284Sobrien   object that the access is against.  */
168152284Sobrien
168252284Sobrientree
1683132718Skanbuild_dummy_object (tree type)
168452284Sobrien{
168552284Sobrien  tree decl = build1 (NOP_EXPR, build_pointer_type (type), void_zero_node);
168690075Sobrien  return build_indirect_ref (decl, NULL);
168752284Sobrien}
168852284Sobrien
168952284Sobrien/* We've gotten a reference to a member of TYPE.  Return *this if appropriate,
169052284Sobrien   or a dummy object otherwise.  If BINFOP is non-0, it is filled with the
169152284Sobrien   binfo path from current_class_type to TYPE, or 0.  */
169252284Sobrien
169352284Sobrientree
1694132718Skanmaybe_dummy_object (tree type, tree* binfop)
169552284Sobrien{
169652284Sobrien  tree decl, context;
169790075Sobrien  tree binfo;
1698169689Skan
169952284Sobrien  if (current_class_type
170090075Sobrien      && (binfo = lookup_base (current_class_type, type,
1701169689Skan			       ba_unique | ba_quiet, NULL)))
170252284Sobrien    context = current_class_type;
170352284Sobrien  else
170452284Sobrien    {
170552284Sobrien      /* Reference from a nested class member function.  */
170652284Sobrien      context = type;
170790075Sobrien      binfo = TYPE_BINFO (type);
170852284Sobrien    }
170952284Sobrien
171090075Sobrien  if (binfop)
171190075Sobrien    *binfop = binfo;
1712169689Skan
1713117395Skan  if (current_class_ref && context == current_class_type
1714117395Skan      /* Kludge: Make sure that current_class_type is actually
1715169689Skan	 correct.  It might not be if we're in the middle of
1716169689Skan	 tsubst_default_argument.  */
1717117395Skan      && same_type_p (TYPE_MAIN_VARIANT (TREE_TYPE (current_class_ref)),
1718117395Skan		      current_class_type))
171952284Sobrien    decl = current_class_ref;
1720261188Spfg  /* APPLE LOCAL begin radar 6154598 */
1721261188Spfg    else if (cur_block)
1722261188Spfg    {
1723261188Spfg      tree this_copiedin_var = lookup_name (this_identifier);
1724261188Spfg      gcc_assert (!current_class_ref);
1725261188Spfg      gcc_assert (this_copiedin_var);
1726261188Spfg      decl = build_x_arrow (this_copiedin_var);
1727261188Spfg    }
1728261188Spfg  /* APPLE LOCAL end radar 6154598 */
172952284Sobrien  else
173052284Sobrien    decl = build_dummy_object (context);
173152284Sobrien
173252284Sobrien  return decl;
173352284Sobrien}
173452284Sobrien
173552284Sobrien/* Returns 1 if OB is a placeholder object, or a pointer to one.  */
173652284Sobrien
173752284Sobrienint
1738132718Skanis_dummy_object (tree ob)
173952284Sobrien{
174052284Sobrien  if (TREE_CODE (ob) == INDIRECT_REF)
174152284Sobrien    ob = TREE_OPERAND (ob, 0);
174252284Sobrien  return (TREE_CODE (ob) == NOP_EXPR
174352284Sobrien	  && TREE_OPERAND (ob, 0) == void_zero_node);
174452284Sobrien}
174552284Sobrien
174652284Sobrien/* Returns 1 iff type T is a POD type, as defined in [basic.types].  */
174752284Sobrien
174852284Sobrienint
1749132718Skanpod_type_p (tree t)
175052284Sobrien{
175190075Sobrien  t = strip_array_types (t);
175252284Sobrien
1753117395Skan  if (t == error_mark_node)
1754117395Skan    return 1;
175590075Sobrien  if (INTEGRAL_TYPE_P (t))
175690075Sobrien    return 1;  /* integral, character or enumeral type */
175790075Sobrien  if (FLOAT_TYPE_P (t))
175852284Sobrien    return 1;
175990075Sobrien  if (TYPE_PTR_P (t))
176090075Sobrien    return 1; /* pointer to non-member */
1761132718Skan  if (TYPE_PTR_TO_MEMBER_P (t))
1762132718Skan    return 1; /* pointer to member */
1763169689Skan
1764146895Skan  if (TREE_CODE (t) == VECTOR_TYPE)
1765146895Skan    return 1; /* vectors are (small) arrays of scalars */
1766169689Skan
176790075Sobrien  if (! CLASS_TYPE_P (t))
176890075Sobrien    return 0; /* other non-class type (reference or function) */
176990075Sobrien  if (CLASSTYPE_NON_POD_P (t))
177052284Sobrien    return 0;
177190075Sobrien  return 1;
177290075Sobrien}
177352284Sobrien
1774259268Spfg/* Nonzero iff type T is a class template implicit specialization.  */
1775259268Spfg
1776259268Spfgbool
1777259268Spfgclass_tmpl_impl_spec_p (tree t)
1778259268Spfg{
1779259268Spfg  return CLASS_TYPE_P (t) && CLASSTYPE_TEMPLATE_INSTANTIATION (t);
1780259268Spfg}
1781259268Spfg
1782102780Skan/* Returns 1 iff zero initialization of type T means actually storing
1783102780Skan   zeros in it.  */
1784102780Skan
1785102780Skanint
1786132718Skanzero_init_p (tree t)
1787102780Skan{
1788117395Skan  t = strip_array_types (t);
1789102780Skan
1790117395Skan  if (t == error_mark_node)
1791117395Skan    return 1;
1792102780Skan
1793117395Skan  /* NULL pointers to data members are initialized with -1.  */
1794117395Skan  if (TYPE_PTRMEM_P (t))
1795117395Skan    return 0;
1796117395Skan
1797117395Skan  /* Classes that contain types that can't be zero-initialized, cannot
1798117395Skan     be zero-initialized themselves.  */
1799117395Skan  if (CLASS_TYPE_P (t) && CLASSTYPE_NON_ZERO_INIT_P (t))
1800117395Skan    return 0;
1801117395Skan
1802102780Skan  return 1;
1803102780Skan}
1804102780Skan
180590075Sobrien/* Table of valid C++ attributes.  */
1806117395Skanconst struct attribute_spec cxx_attribute_table[] =
180790075Sobrien{
180890075Sobrien  /* { name, min_len, max_len, decl_req, type_req, fn_type_req, handler } */
180990075Sobrien  { "java_interface", 0, 0, false, false, false, handle_java_interface_attribute },
181090075Sobrien  { "com_interface",  0, 0, false, false, false, handle_com_interface_attribute },
181190075Sobrien  { "init_priority",  1, 1, true,  false, false, handle_init_priority_attribute },
1812169689Skan  { NULL,	      0, 0, false, false, false, NULL }
181390075Sobrien};
181490075Sobrien
181590075Sobrien/* Handle a "java_interface" attribute; arguments as in
181690075Sobrien   struct attribute_spec.handler.  */
181790075Sobrienstatic tree
1818169689Skanhandle_java_interface_attribute (tree* node,
1819169689Skan				 tree name,
1820169689Skan				 tree args ATTRIBUTE_UNUSED ,
1821169689Skan				 int flags,
1822169689Skan				 bool* no_add_attrs)
182390075Sobrien{
182490075Sobrien  if (DECL_P (*node)
182590075Sobrien      || !CLASS_TYPE_P (*node)
182690075Sobrien      || !TYPE_FOR_JAVA (*node))
182752284Sobrien    {
1828169689Skan      error ("%qE attribute can only be applied to Java class definitions",
1829169689Skan	     name);
183090075Sobrien      *no_add_attrs = true;
183190075Sobrien      return NULL_TREE;
183252284Sobrien    }
183390075Sobrien  if (!(flags & (int) ATTR_FLAG_TYPE_IN_PLACE))
1834169689Skan    *node = build_variant_type_copy (*node);
183590075Sobrien  TYPE_JAVA_INTERFACE (*node) = 1;
183652284Sobrien
183790075Sobrien  return NULL_TREE;
183852284Sobrien}
183952284Sobrien
184090075Sobrien/* Handle a "com_interface" attribute; arguments as in
184190075Sobrien   struct attribute_spec.handler.  */
184290075Sobrienstatic tree
1843169689Skanhandle_com_interface_attribute (tree* node,
1844169689Skan				tree name,
1845169689Skan				tree args ATTRIBUTE_UNUSED ,
1846169689Skan				int flags ATTRIBUTE_UNUSED ,
1847169689Skan				bool* no_add_attrs)
184852284Sobrien{
184990075Sobrien  static int warned;
185052284Sobrien
185190075Sobrien  *no_add_attrs = true;
185252284Sobrien
185390075Sobrien  if (DECL_P (*node)
185490075Sobrien      || !CLASS_TYPE_P (*node)
185590075Sobrien      || *node != TYPE_MAIN_VARIANT (*node))
185690075Sobrien    {
1857169689Skan      warning (OPT_Wattributes, "%qE attribute can only be applied "
1858169689Skan	       "to class definitions", name);
185990075Sobrien      return NULL_TREE;
186052284Sobrien    }
186152284Sobrien
186290075Sobrien  if (!warned++)
1863169689Skan    warning (0, "%qE is obsolete; g++ vtables are now COM-compatible by default",
1864169689Skan	     name);
186590075Sobrien
186690075Sobrien  return NULL_TREE;
186790075Sobrien}
186890075Sobrien
186990075Sobrien/* Handle an "init_priority" attribute; arguments as in
187090075Sobrien   struct attribute_spec.handler.  */
187190075Sobrienstatic tree
1872169689Skanhandle_init_priority_attribute (tree* node,
1873169689Skan				tree name,
1874169689Skan				tree args,
1875169689Skan				int flags ATTRIBUTE_UNUSED ,
1876169689Skan				bool* no_add_attrs)
187790075Sobrien{
187890075Sobrien  tree initp_expr = TREE_VALUE (args);
187990075Sobrien  tree decl = *node;
188090075Sobrien  tree type = TREE_TYPE (decl);
188190075Sobrien  int pri;
188290075Sobrien
188390075Sobrien  STRIP_NOPS (initp_expr);
1884169689Skan
188590075Sobrien  if (!initp_expr || TREE_CODE (initp_expr) != INTEGER_CST)
188690075Sobrien    {
188790075Sobrien      error ("requested init_priority is not an integer constant");
188890075Sobrien      *no_add_attrs = true;
188990075Sobrien      return NULL_TREE;
189090075Sobrien    }
189152284Sobrien
189290075Sobrien  pri = TREE_INT_CST_LOW (initp_expr);
1893169689Skan
189490075Sobrien  type = strip_array_types (type);
189552284Sobrien
189690075Sobrien  if (decl == NULL_TREE
189790075Sobrien      || TREE_CODE (decl) != VAR_DECL
189890075Sobrien      || !TREE_STATIC (decl)
189990075Sobrien      || DECL_EXTERNAL (decl)
190090075Sobrien      || (TREE_CODE (type) != RECORD_TYPE
190190075Sobrien	  && TREE_CODE (type) != UNION_TYPE)
190290075Sobrien      /* Static objects in functions are initialized the
190390075Sobrien	 first time control passes through that
190490075Sobrien	 function. This is not precise enough to pin down an
1905117395Skan	 init_priority value, so don't allow it.  */
1906169689Skan      || current_function_decl)
190790075Sobrien    {
1908169689Skan      error ("can only use %qE attribute on file-scope definitions "
1909169689Skan	     "of objects of class type", name);
191090075Sobrien      *no_add_attrs = true;
191190075Sobrien      return NULL_TREE;
191290075Sobrien    }
191352284Sobrien
191490075Sobrien  if (pri > MAX_INIT_PRIORITY || pri <= 0)
191590075Sobrien    {
191690075Sobrien      error ("requested init_priority is out of range");
191790075Sobrien      *no_add_attrs = true;
191890075Sobrien      return NULL_TREE;
191990075Sobrien    }
192052284Sobrien
192190075Sobrien  /* Check for init_priorities that are reserved for
192290075Sobrien     language and runtime support implementations.*/
192390075Sobrien  if (pri <= MAX_RESERVED_INIT_PRIORITY)
192490075Sobrien    {
1925169689Skan      warning
1926169689Skan	(0, "requested init_priority is reserved for internal use");
192790075Sobrien    }
192852284Sobrien
192990075Sobrien  if (SUPPORTS_INIT_PRIORITY)
193090075Sobrien    {
1931169689Skan      SET_DECL_INIT_PRIORITY (decl, pri);
1932169689Skan      DECL_HAS_INIT_PRIORITY_P (decl) = 1;
193390075Sobrien      return NULL_TREE;
193452284Sobrien    }
193590075Sobrien  else
193690075Sobrien    {
1937169689Skan      error ("%qE attribute is not supported on this platform", name);
193890075Sobrien      *no_add_attrs = true;
193990075Sobrien      return NULL_TREE;
194090075Sobrien    }
194152284Sobrien}
194252284Sobrien
194352284Sobrien/* Return a new PTRMEM_CST of the indicated TYPE.  The MEMBER is the
194452284Sobrien   thing pointed to by the constant.  */
194552284Sobrien
194652284Sobrientree
1947132718Skanmake_ptrmem_cst (tree type, tree member)
194852284Sobrien{
194952284Sobrien  tree ptrmem_cst = make_node (PTRMEM_CST);
195052284Sobrien  TREE_TYPE (ptrmem_cst) = type;
195152284Sobrien  PTRMEM_CST_MEMBER (ptrmem_cst) = member;
195252284Sobrien  return ptrmem_cst;
195352284Sobrien}
195452284Sobrien
1955132718Skan/* Build a variant of TYPE that has the indicated ATTRIBUTES.  May
1956132718Skan   return an existing type of an appropriate type already exists.  */
1957132718Skan
1958132718Skantree
1959132718Skancp_build_type_attribute_variant (tree type, tree attributes)
1960132718Skan{
1961132718Skan  tree new_type;
1962132718Skan
1963132718Skan  new_type = build_type_attribute_variant (type, attributes);
1964132718Skan  if (TREE_CODE (new_type) == FUNCTION_TYPE
1965169689Skan      && (TYPE_RAISES_EXCEPTIONS (new_type)
1966132718Skan	  != TYPE_RAISES_EXCEPTIONS (type)))
1967132718Skan    new_type = build_exception_variant (new_type,
1968132718Skan					TYPE_RAISES_EXCEPTIONS (type));
1969169689Skan
1970169689Skan  /* Making a new main variant of a class type is broken.  */
1971169689Skan  gcc_assert (!CLASS_TYPE_P (type) || new_type == type);
1972169689Skan
1973132718Skan  return new_type;
1974132718Skan}
1975132718Skan
197690075Sobrien/* Apply FUNC to all language-specific sub-trees of TP in a pre-order
1977169689Skan   traversal.  Called from walk_tree.  */
197890075Sobrien
1979169689Skantree
1980169689Skancp_walk_subtrees (tree *tp, int *walk_subtrees_p, walk_tree_fn func,
1981169689Skan		  void *data, struct pointer_set_t *pset)
198290075Sobrien{
198390075Sobrien  enum tree_code code = TREE_CODE (*tp);
1984169689Skan  location_t save_locus;
198590075Sobrien  tree result;
1986169689Skan
198790075Sobrien#define WALK_SUBTREE(NODE)				\
198890075Sobrien  do							\
198990075Sobrien    {							\
1990169689Skan      result = walk_tree (&(NODE), func, data, pset);	\
1991169689Skan      if (result) goto out;				\
199290075Sobrien    }							\
199390075Sobrien  while (0)
199490075Sobrien
1995169689Skan  /* Set input_location here so we get the right instantiation context
1996169689Skan     if we call instantiate_decl from inlinable_function_p.  */
1997169689Skan  save_locus = input_location;
1998169689Skan  if (EXPR_HAS_LOCATION (*tp))
1999169689Skan    input_location = EXPR_LOCATION (*tp);
2000169689Skan
200190075Sobrien  /* Not one of the easy cases.  We must explicitly go through the
200290075Sobrien     children.  */
2003169689Skan  result = NULL_TREE;
200490075Sobrien  switch (code)
200590075Sobrien    {
200690075Sobrien    case DEFAULT_ARG:
200790075Sobrien    case TEMPLATE_TEMPLATE_PARM:
200890075Sobrien    case BOUND_TEMPLATE_TEMPLATE_PARM:
200990075Sobrien    case UNBOUND_CLASS_TEMPLATE:
201090075Sobrien    case TEMPLATE_PARM_INDEX:
201190075Sobrien    case TEMPLATE_TYPE_PARM:
201290075Sobrien    case TYPENAME_TYPE:
201390075Sobrien    case TYPEOF_TYPE:
2014132718Skan    case BASELINK:
2015132718Skan      /* None of these have subtrees other than those already walked
2016169689Skan	 above.  */
201790075Sobrien      *walk_subtrees_p = 0;
201890075Sobrien      break;
201990075Sobrien
2020169689Skan    case TINST_LEVEL:
2021169689Skan      WALK_SUBTREE (TINST_DECL (*tp));
2022169689Skan      *walk_subtrees_p = 0;
2023169689Skan      break;
2024169689Skan
202590075Sobrien    case PTRMEM_CST:
202690075Sobrien      WALK_SUBTREE (TREE_TYPE (*tp));
202790075Sobrien      *walk_subtrees_p = 0;
202890075Sobrien      break;
202990075Sobrien
203090075Sobrien    case TREE_LIST:
2031132718Skan      WALK_SUBTREE (TREE_PURPOSE (*tp));
203290075Sobrien      break;
203390075Sobrien
203490075Sobrien    case OVERLOAD:
203590075Sobrien      WALK_SUBTREE (OVL_FUNCTION (*tp));
203690075Sobrien      WALK_SUBTREE (OVL_CHAIN (*tp));
203790075Sobrien      *walk_subtrees_p = 0;
203890075Sobrien      break;
203990075Sobrien
204090075Sobrien    case RECORD_TYPE:
204190075Sobrien      if (TYPE_PTRMEMFUNC_P (*tp))
204290075Sobrien	WALK_SUBTREE (TYPE_PTRMEMFUNC_FN_TYPE (*tp));
204390075Sobrien      break;
204490075Sobrien
204590075Sobrien    default:
2046169689Skan      input_location = save_locus;
2047169689Skan      return NULL_TREE;
204890075Sobrien    }
204990075Sobrien
205090075Sobrien  /* We didn't find what we were looking for.  */
2051169689Skan out:
2052169689Skan  input_location = save_locus;
2053169689Skan  return result;
205490075Sobrien
205590075Sobrien#undef WALK_SUBTREE
205690075Sobrien}
205790075Sobrien
205890075Sobrien/* Decide whether there are language-specific reasons to not inline a
205990075Sobrien   function as a tree.  */
206090075Sobrien
206190075Sobrienint
2062132718Skancp_cannot_inline_tree_fn (tree* fnp)
206390075Sobrien{
206490075Sobrien  tree fn = *fnp;
206590075Sobrien
206690075Sobrien  /* We can inline a template instantiation only if it's fully
206790075Sobrien     instantiated.  */
206890075Sobrien  if (DECL_TEMPLATE_INFO (fn)
206990075Sobrien      && TI_PENDING_TEMPLATE_FLAG (DECL_TEMPLATE_INFO (fn)))
207090075Sobrien    {
2071132718Skan      /* Don't instantiate functions that are not going to be
2072132718Skan	 inlined.  */
2073169689Skan      if (!DECL_INLINE (DECL_TEMPLATE_RESULT
2074132718Skan			(template_for_substitution (fn))))
2075132718Skan	return 1;
2076132718Skan
2077169689Skan      fn = *fnp = instantiate_decl (fn, /*defer_ok=*/0, /*undefined_ok=*/0);
2078132718Skan
2079102780Skan      if (TI_PENDING_TEMPLATE_FLAG (DECL_TEMPLATE_INFO (fn)))
2080102780Skan	return 1;
208190075Sobrien    }
208290075Sobrien
2083132718Skan  if (flag_really_no_inline
2084132718Skan      && lookup_attribute ("always_inline", DECL_ATTRIBUTES (fn)) == NULL)
2085132718Skan    return 1;
2086132718Skan
2087169689Skan  /* Don't auto-inline functions that might be replaced at link-time
2088169689Skan     with an alternative definition.  */
2089169689Skan  if (!DECL_DECLARED_INLINE_P (fn) && DECL_REPLACEABLE_P (fn))
2090117395Skan    {
2091117395Skan      DECL_UNINLINABLE (fn) = 1;
2092117395Skan      return 1;
2093117395Skan    }
2094117395Skan
209590075Sobrien  if (varargs_function_p (fn))
209690075Sobrien    {
209790075Sobrien      DECL_UNINLINABLE (fn) = 1;
209890075Sobrien      return 1;
209990075Sobrien    }
210090075Sobrien
210190075Sobrien  if (! function_attribute_inlinable_p (fn))
210290075Sobrien    {
210390075Sobrien      DECL_UNINLINABLE (fn) = 1;
210490075Sobrien      return 1;
210590075Sobrien    }
210690075Sobrien
210790075Sobrien  return 0;
210890075Sobrien}
210990075Sobrien
211090075Sobrien/* Add any pending functions other than the current function (already
211190075Sobrien   handled by the caller), that thus cannot be inlined, to FNS_P, then
211290075Sobrien   return the latest function added to the array, PREV_FN.  */
211390075Sobrien
211490075Sobrientree
2115132718Skancp_add_pending_fn_decls (void* fns_p, tree prev_fn)
211690075Sobrien{
211790075Sobrien  varray_type *fnsp = (varray_type *)fns_p;
211890075Sobrien  struct saved_scope *s;
211990075Sobrien
212090075Sobrien  for (s = scope_chain; s; s = s->prev)
212190075Sobrien    if (s->function_decl && s->function_decl != prev_fn)
212290075Sobrien      {
212390075Sobrien	VARRAY_PUSH_TREE (*fnsp, s->function_decl);
212490075Sobrien	prev_fn = s->function_decl;
212590075Sobrien      }
212690075Sobrien
212790075Sobrien  return prev_fn;
212890075Sobrien}
212990075Sobrien
213090075Sobrien/* Determine whether VAR is a declaration of an automatic variable in
213190075Sobrien   function FN.  */
213290075Sobrien
213390075Sobrienint
2134132718Skancp_auto_var_in_fn_p (tree var, tree fn)
213590075Sobrien{
213690075Sobrien  return (DECL_P (var) && DECL_CONTEXT (var) == fn
213790075Sobrien	  && nonstatic_local_decl_p (var));
213890075Sobrien}
213990075Sobrien
2140169689Skan/* Like save_expr, but for C++.  */
214190075Sobrien
214290075Sobrientree
2143169689Skancp_save_expr (tree expr)
214490075Sobrien{
2145169689Skan  /* There is no reason to create a SAVE_EXPR within a template; if
2146169689Skan     needed, we can create the SAVE_EXPR when instantiating the
2147169689Skan     template.  Furthermore, the middle-end cannot handle C++-specific
2148169689Skan     tree codes.  */
2149169689Skan  if (processing_template_decl)
2150169689Skan    return expr;
2151169689Skan  return save_expr (expr);
215290075Sobrien}
215390075Sobrien
215490075Sobrien/* Initialize tree.c.  */
215590075Sobrien
215690075Sobrienvoid
2157132718Skaninit_tree (void)
215890075Sobrien{
2159117395Skan  list_hash_table = htab_create_ggc (31, list_hash, list_hash_eq, NULL);
216090075Sobrien}
216190075Sobrien
216290075Sobrien/* Returns the kind of special function that DECL (a FUNCTION_DECL)
2163117395Skan   is.  Note that sfk_none is zero, so this function can be used as a
2164117395Skan   predicate to test whether or not DECL is a special function.  */
216590075Sobrien
216690075Sobrienspecial_function_kind
2167132718Skanspecial_function_p (tree decl)
216890075Sobrien{
216990075Sobrien  /* Rather than doing all this stuff with magic names, we should
217090075Sobrien     probably have a field of type `special_function_kind' in
217190075Sobrien     DECL_LANG_SPECIFIC.  */
217290075Sobrien  if (DECL_COPY_CONSTRUCTOR_P (decl))
217390075Sobrien    return sfk_copy_constructor;
217490075Sobrien  if (DECL_CONSTRUCTOR_P (decl))
217590075Sobrien    return sfk_constructor;
217690075Sobrien  if (DECL_OVERLOADED_OPERATOR_P (decl) == NOP_EXPR)
217790075Sobrien    return sfk_assignment_operator;
217890075Sobrien  if (DECL_MAYBE_IN_CHARGE_DESTRUCTOR_P (decl))
217990075Sobrien    return sfk_destructor;
218090075Sobrien  if (DECL_COMPLETE_DESTRUCTOR_P (decl))
218190075Sobrien    return sfk_complete_destructor;
218290075Sobrien  if (DECL_BASE_DESTRUCTOR_P (decl))
218390075Sobrien    return sfk_base_destructor;
218490075Sobrien  if (DECL_DELETING_DESTRUCTOR_P (decl))
218590075Sobrien    return sfk_deleting_destructor;
218690075Sobrien  if (DECL_CONV_FN_P (decl))
218790075Sobrien    return sfk_conversion;
218890075Sobrien
218990075Sobrien  return sfk_none;
219090075Sobrien}
219190075Sobrien
2192117395Skan/* Returns nonzero if TYPE is a character type, including wchar_t.  */
2193117395Skan
219490075Sobrienint
2195132718Skanchar_type_p (tree type)
219690075Sobrien{
219790075Sobrien  return (same_type_p (type, char_type_node)
219890075Sobrien	  || same_type_p (type, unsigned_char_type_node)
219990075Sobrien	  || same_type_p (type, signed_char_type_node)
220090075Sobrien	  || same_type_p (type, wchar_type_node));
220190075Sobrien}
220290075Sobrien
220390075Sobrien/* Returns the kind of linkage associated with the indicated DECL.  Th
220490075Sobrien   value returned is as specified by the language standard; it is
220590075Sobrien   independent of implementation details regarding template
220690075Sobrien   instantiation, etc.  For example, it is possible that a declaration
220790075Sobrien   to which this function assigns external linkage would not show up
220890075Sobrien   as a global symbol when you run `nm' on the resulting object file.  */
220990075Sobrien
221090075Sobrienlinkage_kind
2211132718Skandecl_linkage (tree decl)
221290075Sobrien{
221390075Sobrien  /* This function doesn't attempt to calculate the linkage from first
221490075Sobrien     principles as given in [basic.link].  Instead, it makes use of
221590075Sobrien     the fact that we have already set TREE_PUBLIC appropriately, and
221690075Sobrien     then handles a few special cases.  Ideally, we would calculate
221790075Sobrien     linkage first, and then transform that into a concrete
221890075Sobrien     implementation.  */
221990075Sobrien
222090075Sobrien  /* Things that don't have names have no linkage.  */
222190075Sobrien  if (!DECL_NAME (decl))
222290075Sobrien    return lk_none;
222390075Sobrien
222490075Sobrien  /* Things that are TREE_PUBLIC have external linkage.  */
222590075Sobrien  if (TREE_PUBLIC (decl))
222690075Sobrien    return lk_external;
222790075Sobrien
2228169689Skan  if (TREE_CODE (decl) == NAMESPACE_DECL)
2229169689Skan    return lk_external;
2230169689Skan
2231169689Skan  /* Linkage of a CONST_DECL depends on the linkage of the enumeration
2232169689Skan     type.  */
2233169689Skan  if (TREE_CODE (decl) == CONST_DECL)
2234169689Skan    return decl_linkage (TYPE_NAME (TREE_TYPE (decl)));
2235169689Skan
223690075Sobrien  /* Some things that are not TREE_PUBLIC have external linkage, too.
223790075Sobrien     For example, on targets that don't have weak symbols, we make all
223890075Sobrien     template instantiations have internal linkage (in the object
223990075Sobrien     file), but the symbols should still be treated as having external
224090075Sobrien     linkage from the point of view of the language.  */
2241169689Skan  if (TREE_CODE (decl) != TYPE_DECL && DECL_LANG_SPECIFIC (decl)
2242169689Skan      && DECL_COMDAT (decl))
224390075Sobrien    return lk_external;
224490075Sobrien
224590075Sobrien  /* Things in local scope do not have linkage, if they don't have
224690075Sobrien     TREE_PUBLIC set.  */
224790075Sobrien  if (decl_function_context (decl))
224890075Sobrien    return lk_none;
224990075Sobrien
2250169689Skan  /* Members of the anonymous namespace also have TREE_PUBLIC unset, but
2251169689Skan     are considered to have external linkage for language purposes.  DECLs
2252169689Skan     really meant to have internal linkage have DECL_THIS_STATIC set.  */
2253169689Skan  if (TREE_CODE (decl) == TYPE_DECL
2254169689Skan      || ((TREE_CODE (decl) == VAR_DECL || TREE_CODE (decl) == FUNCTION_DECL)
2255169689Skan	  && !DECL_THIS_STATIC (decl)))
2256169689Skan    return lk_external;
2257169689Skan
225890075Sobrien  /* Everything else has internal linkage.  */
225990075Sobrien  return lk_internal;
226090075Sobrien}
2261117395Skan
2262169689Skan/* EXP is an expression that we want to pre-evaluate.  Returns (in
2263169689Skan   *INITP) an expression that will perform the pre-evaluation.  The
2264169689Skan   value returned by this function is a side-effect free expression
2265169689Skan   equivalent to the pre-evaluated expression.  Callers must ensure
2266169689Skan   that *INITP is evaluated before EXP.  */
2267117395Skan
2268117395Skantree
2269132718Skanstabilize_expr (tree exp, tree* initp)
2270117395Skan{
2271117395Skan  tree init_expr;
2272117395Skan
2273117395Skan  if (!TREE_SIDE_EFFECTS (exp))
2274169689Skan    init_expr = NULL_TREE;
2275117395Skan  else if (!real_lvalue_p (exp)
2276117395Skan	   || !TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (exp)))
2277117395Skan    {
2278117395Skan      init_expr = get_target_expr (exp);
2279117395Skan      exp = TARGET_EXPR_SLOT (init_expr);
2280117395Skan    }
2281117395Skan  else
2282117395Skan    {
2283117395Skan      exp = build_unary_op (ADDR_EXPR, exp, 1);
2284117395Skan      init_expr = get_target_expr (exp);
2285117395Skan      exp = TARGET_EXPR_SLOT (init_expr);
2286117395Skan      exp = build_indirect_ref (exp, 0);
2287117395Skan    }
2288169689Skan  *initp = init_expr;
2289117395Skan
2290169689Skan  gcc_assert (!TREE_SIDE_EFFECTS (exp));
2291117395Skan  return exp;
2292117395Skan}
2293132718Skan
2294169689Skan/* Add NEW, an expression whose value we don't care about, after the
2295169689Skan   similar expression ORIG.  */
2296132718Skan
2297169689Skantree
2298169689Skanadd_stmt_to_compound (tree orig, tree new)
2299169689Skan{
2300169689Skan  if (!new || !TREE_SIDE_EFFECTS (new))
2301169689Skan    return orig;
2302169689Skan  if (!orig || !TREE_SIDE_EFFECTS (orig))
2303169689Skan    return new;
2304169689Skan  return build2 (COMPOUND_EXPR, void_type_node, orig, new);
2305169689Skan}
2306169689Skan
2307169689Skan/* Like stabilize_expr, but for a call whose arguments we want to
2308169689Skan   pre-evaluate.  CALL is modified in place to use the pre-evaluated
2309169689Skan   arguments, while, upon return, *INITP contains an expression to
2310169689Skan   compute the arguments.  */
2311169689Skan
2312132718Skanvoid
2313132718Skanstabilize_call (tree call, tree *initp)
2314132718Skan{
2315132718Skan  tree inits = NULL_TREE;
2316132718Skan  tree t;
2317132718Skan
2318132718Skan  if (call == error_mark_node)
2319132718Skan    return;
2320132718Skan
2321169689Skan  gcc_assert (TREE_CODE (call) == CALL_EXPR
2322169689Skan	      || TREE_CODE (call) == AGGR_INIT_EXPR);
2323132718Skan
2324132718Skan  for (t = TREE_OPERAND (call, 1); t; t = TREE_CHAIN (t))
2325132718Skan    if (TREE_SIDE_EFFECTS (TREE_VALUE (t)))
2326132718Skan      {
2327132718Skan	tree init;
2328132718Skan	TREE_VALUE (t) = stabilize_expr (TREE_VALUE (t), &init);
2329169689Skan	inits = add_stmt_to_compound (inits, init);
2330132718Skan      }
2331132718Skan
2332132718Skan  *initp = inits;
2333132718Skan}
2334132718Skan
2335169689Skan/* Like stabilize_expr, but for an initialization.
2336132718Skan
2337169689Skan   If the initialization is for an object of class type, this function
2338169689Skan   takes care not to introduce additional temporaries.
2339169689Skan
2340169689Skan   Returns TRUE iff the expression was successfully pre-evaluated,
2341169689Skan   i.e., if INIT is now side-effect free, except for, possible, a
2342169689Skan   single call to a constructor.  */
2343169689Skan
2344132718Skanbool
2345132718Skanstabilize_init (tree init, tree *initp)
2346132718Skan{
2347132718Skan  tree t = init;
2348132718Skan
2349169689Skan  *initp = NULL_TREE;
2350169689Skan
2351132718Skan  if (t == error_mark_node)
2352132718Skan    return true;
2353132718Skan
2354132718Skan  if (TREE_CODE (t) == INIT_EXPR
2355132718Skan      && TREE_CODE (TREE_OPERAND (t, 1)) != TARGET_EXPR)
2356132718Skan    {
2357169689Skan      TREE_OPERAND (t, 1) = stabilize_expr (TREE_OPERAND (t, 1), initp);
2358169689Skan      return true;
2359169689Skan    }
2360132718Skan
2361169689Skan  if (TREE_CODE (t) == INIT_EXPR)
2362169689Skan    t = TREE_OPERAND (t, 1);
2363169689Skan  if (TREE_CODE (t) == TARGET_EXPR)
2364169689Skan    t = TARGET_EXPR_INITIAL (t);
2365169689Skan  if (TREE_CODE (t) == COMPOUND_EXPR)
2366169689Skan    t = expr_last (t);
2367169689Skan  if (TREE_CODE (t) == CONSTRUCTOR
2368169689Skan      && EMPTY_CONSTRUCTOR_P (t))
2369169689Skan    /* Default-initialization.  */
2370169689Skan    return true;
2371132718Skan
2372169689Skan  /* If the initializer is a COND_EXPR, we can't preevaluate
2373169689Skan     anything.  */
2374169689Skan  if (TREE_CODE (t) == COND_EXPR)
2375169689Skan    return false;
2376169689Skan
2377169689Skan  if (TREE_CODE (t) == CALL_EXPR
2378169689Skan      || TREE_CODE (t) == AGGR_INIT_EXPR)
2379169689Skan    {
2380169689Skan      stabilize_call (t, initp);
2381169689Skan      return true;
2382132718Skan    }
2383132718Skan
2384169689Skan  /* The initialization is being performed via a bitwise copy -- and
2385169689Skan     the item copied may have side effects.  */
2386169689Skan  return TREE_SIDE_EFFECTS (init);
2387132718Skan}
2388132718Skan
2389146895Skan/* Like "fold", but should be used whenever we might be processing the
2390146895Skan   body of a template.  */
2391146895Skan
2392146895Skantree
2393146895Skanfold_if_not_in_template (tree expr)
2394146895Skan{
2395146895Skan  /* In the body of a template, there is never any need to call
2396146895Skan     "fold".  We will call fold later when actually instantiating the
2397146895Skan     template.  Integral constant expressions in templates will be
2398146895Skan     evaluated via fold_non_dependent_expr, as necessary.  */
2399169689Skan  if (processing_template_decl)
2400169689Skan    return expr;
2401169689Skan
2402169689Skan  /* Fold C++ front-end specific tree codes.  */
2403169689Skan  if (TREE_CODE (expr) == UNARY_PLUS_EXPR)
2404169689Skan    return fold_convert (TREE_TYPE (expr), TREE_OPERAND (expr, 0));
2405169689Skan
2406169689Skan  return fold (expr);
2407146895Skan}
2408146895Skan
2409169689Skan/* Returns true if a cast to TYPE may appear in an integral constant
2410169689Skan   expression.  */
2411169689Skan
2412169689Skanbool
2413169689Skancast_valid_in_integral_constant_expression_p (tree type)
2414169689Skan{
2415169689Skan  return (INTEGRAL_OR_ENUMERATION_TYPE_P (type)
2416169689Skan	  || dependent_type_p (type)
2417169689Skan	  || type == error_mark_node);
2418169689Skan}
2419169689Skan
2420117395Skan
2421117395Skan#if defined ENABLE_TREE_CHECKING && (GCC_VERSION >= 2007)
2422117395Skan/* Complain that some language-specific thing hanging off a tree
2423117395Skan   node has been accessed improperly.  */
2424117395Skan
2425117395Skanvoid
2426132718Skanlang_check_failed (const char* file, int line, const char* function)
2427117395Skan{
2428117395Skan  internal_error ("lang_* check: failed in %s, at %s:%d",
2429117395Skan		  function, trim_filename (file), line);
2430117395Skan}
2431117395Skan#endif /* ENABLE_TREE_CHECKING */
2432117395Skan
2433117395Skan#include "gt-cp-tree.h"
2434