OSDN Git Service

* cp-tree.h (struct lang_type): Added non_zero_init.
[pf3gnuchains/gcc-fork.git] / gcc / cp / tree.c
index 77973d6..9a52cc0 100644 (file)
@@ -1,6 +1,6 @@
 /* Language-dependent node constructors for parse phase of GNU compiler.
    Copyright (C) 1987, 1988, 1992, 1993, 1994, 1995, 1996, 1997, 1998,
-   1999, 2000 Free Software Foundation, Inc.
+   1999, 2000, 2001, 2002 Free Software Foundation, Inc.
    Hacked by Michael Tiemann (tiemann@cygnus.com)
 
 This file is part of GNU CC.
@@ -31,22 +31,28 @@ Boston, MA 02111-1307, USA.  */
 #include "ggc.h"
 #include "insn-config.h"
 #include "integrate.h"
+#include "tree-inline.h"
 
 static tree bot_manip PARAMS ((tree *, int *, void *));
 static tree bot_replace PARAMS ((tree *, int *, void *));
 static tree build_cplus_array_type_1 PARAMS ((tree, tree));
-static void list_hash_add PARAMS ((int, tree));
-static int list_hash PARAMS ((tree, tree, tree));
-static tree list_hash_lookup PARAMS ((int, tree, tree, tree));
+static int list_hash_eq PARAMS ((const void *, const void *));
+static hashval_t list_hash_pieces PARAMS ((tree, tree, tree));
+static hashval_t list_hash PARAMS ((const void *));
 static cp_lvalue_kind lvalue_p_1 PARAMS ((tree, int));
 static tree no_linkage_helper PARAMS ((tree *, int *, void *));
-static tree build_srcloc PARAMS ((char *, int));
-static void mark_list_hash PARAMS ((void *));
-static int statement_code_p PARAMS ((enum tree_code));
+static tree build_srcloc PARAMS ((const char *, int));
 static tree mark_local_for_remap_r PARAMS ((tree *, int *, void *));
 static tree cp_unsave_r PARAMS ((tree *, int *, void *));
-static void cp_unsave PARAMS ((tree *));
 static tree build_target_expr PARAMS ((tree, tree));
+static tree count_trees_r PARAMS ((tree *, int *, void *));
+static tree verify_stmt_tree_r PARAMS ((tree *, int *, void *));
+static tree find_tree_r PARAMS ((tree *, int *, void *));
+extern int cp_statement_code_p PARAMS ((enum tree_code));
+
+static tree handle_java_interface_attribute PARAMS ((tree *, tree, tree, int, bool *));
+static tree handle_com_interface_attribute PARAMS ((tree *, tree, tree, int, bool *));
+static tree handle_init_priority_attribute PARAMS ((tree *, tree, tree, int, bool *));
 
 /* If REF is an lvalue, returns the kind of lvalue that REF is.
    Otherwise, returns clk_none.  If TREAT_CLASS_RVALUES_AS_LVALUES is
@@ -63,7 +69,7 @@ lvalue_p_1 (ref, treat_class_rvalues_as_lvalues)
   if (TREE_CODE (TREE_TYPE (ref)) == REFERENCE_TYPE)
     return clk_ordinary;
 
-  if (ref == current_class_ptr && flag_this_is_variable <= 0)
+  if (ref == current_class_ptr)
     return clk_none;
 
   switch (TREE_CODE (ref))
@@ -78,6 +84,9 @@ lvalue_p_1 (ref, treat_class_rvalues_as_lvalues)
     case WITH_CLEANUP_EXPR:
     case REALPART_EXPR:
     case IMAGPART_EXPR:
+      /* This shouldn't be here, but there are lots of places in the compiler
+         that are sloppy about tacking on NOP_EXPRs to the same type when
+        no actual conversion is happening.  */
     case NOP_EXPR:
       return lvalue_p_1 (TREE_OPERAND (ref, 0),
                         treat_class_rvalues_as_lvalues);
@@ -117,7 +126,7 @@ lvalue_p_1 (ref, treat_class_rvalues_as_lvalues)
 
       /* A currently unresolved scope ref.  */
     case SCOPE_REF:
-      my_friendly_abort (103);
+      abort ();
     case OFFSET_REF:
       if (TREE_CODE (TREE_OPERAND (ref, 1)) == FUNCTION_DECL)
        return clk_ordinary;
@@ -225,7 +234,7 @@ build_target_expr (decl, value)
   tree t;
 
   t = build (TARGET_EXPR, TREE_TYPE (decl), decl, value, 
-            maybe_build_cleanup (decl), NULL_TREE);
+            cxx_maybe_build_cleanup (decl), NULL_TREE);
   /* We always set TREE_SIDE_EFFECTS so that expand_expr does not
      ignore the TARGET_EXPR.  If there really turn out to be no
      side-effects, then the optimizer should be able to get rid of
@@ -283,7 +292,7 @@ build_cplus_new (type, init)
   return rval;
 }
 
-/* Buidl a TARGET_EXPR using INIT to initialize a new temporary of the
+/* Build a TARGET_EXPR using INIT to initialize a new temporary of the
    indicated TYPE.  */
 
 tree
@@ -294,6 +303,9 @@ build_target_expr_with_type (init, type)
   tree slot;
   tree rval;
 
+  if (TREE_CODE (init) == TARGET_EXPR)
+    return init;
+
   slot = build (VAR_DECL, type);
   DECL_ARTIFICIAL (slot) = 1;
   DECL_CONTEXT (slot) = current_function_decl;
@@ -312,37 +324,6 @@ get_target_expr (init)
   return build_target_expr_with_type (init, TREE_TYPE (init));
 }
 
-/* Recursively search EXP for CALL_EXPRs that need cleanups and replace
-   these CALL_EXPRs with tree nodes that will perform the cleanups.  */
-
-tree
-break_out_cleanups (exp)
-     tree exp;
-{
-  tree tmp = exp;
-
-  if (TREE_CODE (tmp) == CALL_EXPR
-      && TYPE_HAS_NONTRIVIAL_DESTRUCTOR (TREE_TYPE (tmp)))
-    return build_cplus_new (TREE_TYPE (tmp), tmp);
-
-  while (TREE_CODE (tmp) == NOP_EXPR
-        || TREE_CODE (tmp) == CONVERT_EXPR
-        || TREE_CODE (tmp) == NON_LVALUE_EXPR)
-    {
-      if (TREE_CODE (TREE_OPERAND (tmp, 0)) == CALL_EXPR
-         && TYPE_HAS_NONTRIVIAL_DESTRUCTOR (TREE_TYPE (TREE_OPERAND (tmp, 0))))
-       {
-         TREE_OPERAND (tmp, 0)
-           = build_cplus_new (TREE_TYPE (TREE_OPERAND (tmp, 0)),
-                              TREE_OPERAND (tmp, 0));
-         break;
-       }
-      else
-       tmp = TREE_OPERAND (tmp, 0);
-    }
-  return exp;
-}
-
 /* Recursively perform a preorder search EXP for CALL_EXPRs, making
    copies where they are found.  Returns a deep copy all nodes transitively
    containing CALL_EXPRs.  */
@@ -402,7 +383,7 @@ break_out_calls (exp)
     case 'e':  /* an expression */
     case 'r':  /* a reference */
     case 's':  /* an expression with side effects */
-      for (i = tree_code_length[(int) code] - 1; i >= 0; i--)
+      for (i = TREE_CODE_LENGTH (code) - 1; i >= 0; i--)
        {
          t1 = break_out_calls (TREE_OPERAND (exp, i));
          if (t1 != TREE_OPERAND (exp, i))
@@ -424,7 +405,7 @@ break_out_calls (exp)
        changed = 1;
       if (changed)
        {
-         if (tree_code_length[(int) code] == 1)
+         if (TREE_CODE_LENGTH (code) == 1)
            return build1 (code, TREE_TYPE (exp), t1);
          else
            return build (code, TREE_TYPE (exp), t1, t2);
@@ -434,12 +415,6 @@ break_out_calls (exp)
 
 }
 \f
-extern struct obstack permanent_obstack;
-
-/* Here is how primitive or already-canonicalized types' hash
-   codes are made.  MUST BE CONSISTENT WITH tree.c !!! */
-#define TYPE_HASH(TYPE) ((HOST_WIDE_INT) (TYPE) & 0777777)
-
 /* Construct, lay out and return the type of methods belonging to class
    BASETYPE and whose arguments are described by ARGTYPES and whose values
    are described by RETTYPE.  If each type exists already, reuse it.  */
@@ -488,7 +463,12 @@ build_cplus_array_type_1 (elt_type, index_type)
   if (elt_type == error_mark_node || index_type == error_mark_node)
     return error_mark_node;
 
-  if (processing_template_decl 
+  /* Don't do the minimal thing just because processing_template_decl is
+     set; we want to give string constants the right type immediately, so
+     we don't have to fix them up at instantiation time.  */
+  if ((processing_template_decl
+       && index_type && TYPE_MAX_VALUE (index_type)
+       && TREE_CODE (TYPE_MAX_VALUE (index_type)) != INTEGER_CST)
       || uses_template_parms (elt_type) 
       || uses_template_parms (index_type))
     {
@@ -514,65 +494,101 @@ build_cplus_array_type (elt_type, index_type)
      tree index_type;
 {
   tree t;
-  int type_quals = CP_TYPE_QUALS (elt_type);
+  int type_quals = cp_type_quals (elt_type);
+  int cv_quals = type_quals & (TYPE_QUAL_CONST|TYPE_QUAL_VOLATILE);
+  int other_quals = type_quals & ~(TYPE_QUAL_CONST|TYPE_QUAL_VOLATILE);
 
-  elt_type = TYPE_MAIN_VARIANT (elt_type);
+  if (cv_quals)
+    elt_type = cp_build_qualified_type (elt_type, other_quals);
 
   t = build_cplus_array_type_1 (elt_type, index_type);
 
-  if (type_quals != TYPE_UNQUALIFIED)
-    t = cp_build_qualified_type (t, type_quals);
+  if (cv_quals)
+    t = cp_build_qualified_type (t, cv_quals);
 
   return t;
 }
 \f
 /* Make a variant of TYPE, qualified with the TYPE_QUALS.  Handles
    arrays correctly.  In particular, if TYPE is an array of T's, and
-   TYPE_QUALS is non-empty, returns an array of qualified T's.  If
-   at attempt is made to qualify a type illegally, and COMPLAIN is
-   non-zero, an error is issued.  If COMPLAIN is zero, error_mark_node
-   is returned.  */
-
+   TYPE_QUALS is non-empty, returns an array of qualified T's.
+  
+   FLAGS determines how to deal with illformed qualifications. If
+   tf_ignore_bad_quals is set, then bad qualifications are dropped
+   (this is permitted if TYPE was introduced via a typedef or template
+   type parameter). If bad qualifications are dropped and tf_warning
+   is set, then a warning is issued for non-const qualifications.  If
+   tf_ignore_bad_quals is not set and tf_error is not set, we
+   return error_mark_node. Otherwise, we issue an error, and ignore
+   the qualifications.
+
+   Qualification of a reference type is valid when the reference came
+   via a typedef or template type argument. [dcl.ref] No such
+   dispensation is provided for qualifying a function type.  [dcl.fct]
+   DR 295 queries this and the proposed resolution brings it into line
+   with qualifiying a reference.  We implement the DR.  We also behave
+   in a similar manner for restricting non-pointer types.  */
 tree
 cp_build_qualified_type_real (type, type_quals, complain)
      tree type;
      int type_quals;
-     int complain;
+     tsubst_flags_t complain;
 {
   tree result;
+  int bad_quals = TYPE_UNQUALIFIED;
 
   if (type == error_mark_node)
     return type;
 
-  if (type_quals == TYPE_QUALS (type))
+  if (type_quals == cp_type_quals (type))
     return type;
 
-  /* A restrict-qualified pointer type must be a pointer (or reference)
+  /* A reference, fucntion or method type shall not be cv qualified.
+     [dcl.ref], [dct.fct]  */
+  if (type_quals & (TYPE_QUAL_CONST | TYPE_QUAL_VOLATILE)
+      && (TREE_CODE (type) == REFERENCE_TYPE
+         || TREE_CODE (type) == FUNCTION_TYPE
+         || TREE_CODE (type) == METHOD_TYPE))
+    {
+      bad_quals |= type_quals & (TYPE_QUAL_CONST | TYPE_QUAL_VOLATILE);
+      type_quals &= ~(TYPE_QUAL_CONST | TYPE_QUAL_VOLATILE);
+    }
+  
+  /* A restrict-qualified type must be a pointer (or reference)
      to object or incomplete type.  */
   if ((type_quals & TYPE_QUAL_RESTRICT)
       && TREE_CODE (type) != TEMPLATE_TYPE_PARM
-      && (!POINTER_TYPE_P (type)
-         || TYPE_PTRMEM_P (type)
-         || TREE_CODE (TREE_TYPE (type)) == FUNCTION_TYPE))
+      && TREE_CODE (type) != TYPENAME_TYPE
+      && !POINTER_TYPE_P (type))
     {
-      if (complain)
-       cp_error ("`%T' cannot be `restrict'-qualified", type);
-      else
-       return error_mark_node;
-
+      bad_quals |= TYPE_QUAL_RESTRICT;
       type_quals &= ~TYPE_QUAL_RESTRICT;
     }
 
-  if (type_quals != TYPE_UNQUALIFIED
-      && TREE_CODE (type) == FUNCTION_TYPE)
+  if (bad_quals == TYPE_UNQUALIFIED)
+    /*OK*/;
+  else if (!(complain & (tf_error | tf_ignore_bad_quals)))
+    return error_mark_node;
+  else
     {
-      if (complain)
-       cp_error ("`%T' cannot be `const'-, `volatile'-, or `restrict'-qualified", type);
-      else
-       return error_mark_node;
-      type_quals = TYPE_UNQUALIFIED;
+      if (complain & tf_ignore_bad_quals)
+       /* We're not going to warn about constifying things that can't
+          be constified.  */
+       bad_quals &= ~TYPE_QUAL_CONST;
+      if (bad_quals)
+       {
+         tree bad_type = build_qualified_type (ptr_type_node, bad_quals);
+         if (!(complain & tf_ignore_bad_quals))
+           error ("`%V' qualifiers cannot be applied to `%T'",
+                  bad_type, type);
+         else if (complain & tf_warning)
+           warning ("ignoring `%V' qualifiers on `%T'", bad_type, type);
+       }
     }
-  else if (TREE_CODE (type) == ARRAY_TYPE)
+  
+  if (TREE_CODE (type) == ARRAY_TYPE)
     {
       /* In C++, the qualification really applies to the array element
         type.  Obtain the appropriately qualified element type.  */
@@ -586,9 +602,7 @@ cp_build_qualified_type_real (type, type_quals, complain)
        return error_mark_node;
 
       /* See if we already have an identically qualified type.  */
-      for (t = TYPE_MAIN_VARIANT (type); t; t = TYPE_NEXT_VARIANT (t))
-       if (CP_TYPE_QUALS (t) == type_quals)
-         break;
+      t = get_qualified_type (type, type_quals);
 
       /* If we didn't already have it, create it now.  */
       if (!t)
@@ -616,7 +630,7 @@ cp_build_qualified_type_real (type, type_quals, complain)
     {
       /* For a pointer-to-member type, we can't just return a
         cv-qualified version of the RECORD_TYPE.  If we do, we
-        haven't change the field that contains the actual pointer to
+        haven't changed the field that contains the actual pointer to
         a method, and so TYPE_PTRMEMFUNC_FN_TYPE will be wrong.  */
       tree t;
 
@@ -624,7 +638,7 @@ cp_build_qualified_type_real (type, type_quals, complain)
       t = cp_build_qualified_type_real (t, type_quals, complain);
       return build_ptrmemfunc_type (t);
     }
-
+  
   /* Retrieve (or create) the appropriately qualified variant.  */
   result = build_qualified_type (type, type_quals);
 
@@ -649,7 +663,7 @@ tree
 canonical_type_variant (t)
      tree t;
 {
-  return cp_build_qualified_type (TYPE_MAIN_VARIANT (t), CP_TYPE_QUALS (t));
+  return cp_build_qualified_type (TYPE_MAIN_VARIANT (t), cp_type_quals (t));
 }
 \f
 /* Makes new binfos for the indirect bases under BINFO, and updates
@@ -680,6 +694,7 @@ unshare_base_binfos (binfo)
       TREE_VIA_PROTECTED (new_binfo) = TREE_VIA_PROTECTED (base_binfo);
       TREE_VIA_VIRTUAL (new_binfo) = TREE_VIA_VIRTUAL (base_binfo);
       BINFO_INHERITANCE_CHAIN (new_binfo) = binfo;
+      BINFO_PRIMARY_BASE_OF (new_binfo) = NULL_TREE;
       unshare_base_binfos (new_binfo);
     }
 }
@@ -688,38 +703,52 @@ unshare_base_binfos (binfo)
 /* Hashing of lists so that we don't make duplicates.
    The entry point is `list_hash_canon'.  */
 
-/* Each hash table slot is a bucket containing a chain
-   of these structures.  */
-
-struct list_hash
-{
-  struct list_hash *next;      /* Next structure in the bucket.  */
-  int hashcode;                        /* Hash code of this list.  */
-  tree list;                   /* The list recorded here.  */
-};
-
 /* Now here is the hash table.  When recording a list, it is added
    to the slot whose index is the hash code mod the table size.
    Note that the hash table is used for several kinds of lists.
    While all these live in the same table, they are completely independent,
    and the hash code is computed differently for each of these.  */
 
-#define TYPE_HASH_SIZE 59
-static struct list_hash *list_hash_table[TYPE_HASH_SIZE];
+static htab_t list_hash_table;
+
+struct list_proxy 
+{
+  tree purpose;
+  tree value;
+  tree chain;
+};
+
+/* Compare ENTRY (an entry in the hash table) with DATA (a list_proxy
+   for a node we are thinking about adding).  */
+
+static int
+list_hash_eq (entry, data)
+     const void *entry;
+     const void *data;
+{
+  tree t = (tree) entry;
+  struct list_proxy *proxy = (struct list_proxy *) data;
+
+  return (TREE_VALUE (t) == proxy->value
+         && TREE_PURPOSE (t) == proxy->purpose
+         && TREE_CHAIN (t) == proxy->chain);
+}
 
 /* Compute a hash code for a list (chain of TREE_LIST nodes
    with goodies in the TREE_PURPOSE, TREE_VALUE, and bits of the
    TREE_COMMON slots), by adding the hash codes of the individual entries.  */
 
-static int
-list_hash (purpose, value, chain)
-     tree purpose, value, chain;
+static hashval_t
+list_hash_pieces (purpose, value, chain)
+     tree purpose;
+     tree value;
+     tree chain;
 {
-  register int hashcode = 0;
-
+  hashval_t hashcode = 0;
+  
   if (chain)
     hashcode += TYPE_HASH (chain);
-
+  
   if (value)
     hashcode += TYPE_HASH (value);
   else
@@ -731,72 +760,44 @@ list_hash (purpose, value, chain)
   return hashcode;
 }
 
-/* Look in the type hash table for a type isomorphic to TYPE.
-   If one is found, return it.  Otherwise return 0.  */
-
-static tree
-list_hash_lookup (hashcode, purpose, value, chain)
-     int hashcode;
-     tree purpose, value, chain;
-{
-  register struct list_hash *h;
-
-  for (h = list_hash_table[hashcode % TYPE_HASH_SIZE]; h; h = h->next)
-    if (h->hashcode == hashcode
-       && TREE_PURPOSE (h->list) == purpose
-       && TREE_VALUE (h->list) == value
-       && TREE_CHAIN (h->list) == chain)
-      return h->list;
-  return 0;
-}
-
-/* Add an entry to the list-hash-table
-   for a list TYPE whose hash code is HASHCODE.  */
+/* Hash an already existing TREE_LIST.  */
 
-static void
-list_hash_add (hashcode, list)
-     int hashcode;
-     tree list;
+static hashval_t
+list_hash (p)
+     const void *p;
 {
-  register struct list_hash *h;
-
-  h = (struct list_hash *) obstack_alloc (&permanent_obstack, sizeof (struct list_hash));
-  h->hashcode = hashcode;
-  h->list = list;
-  h->next = list_hash_table[hashcode % TYPE_HASH_SIZE];
-  list_hash_table[hashcode % TYPE_HASH_SIZE] = h;
+  tree t = (tree) p;
+  return list_hash_pieces (TREE_PURPOSE (t), 
+                          TREE_VALUE (t), 
+                          TREE_CHAIN (t));
 }
 
 /* Given list components PURPOSE, VALUE, AND CHAIN, return the canonical
    object for an identical list if one already exists.  Otherwise, build a
    new one, and record it as the canonical object.  */
 
-/* Set to 1 to debug without canonicalization.  Never set by program.  */
-
-static int debug_no_list_hash = 0;
-
 tree
 hash_tree_cons (purpose, value, chain)
      tree purpose, value, chain;
 {
-  tree t;
   int hashcode = 0;
-
-  if (! debug_no_list_hash)
-    {
-      hashcode = list_hash (purpose, value, chain);
-      t = list_hash_lookup (hashcode, purpose, value, chain);
-      if (t)
-       return t;
-    }
-
-  t = tree_cons (purpose, value, chain);
-
-  /* If this is a new list, record it for later reuse.  */
-  if (! debug_no_list_hash)
-    list_hash_add (hashcode, t);
-
-  return t;
+  PTR* slot;
+  struct list_proxy proxy;
+
+  /* Hash the list node.  */
+  hashcode = list_hash_pieces (purpose, value, chain);
+  /* Create a proxy for the TREE_LIST we would like to create.  We
+     don't actually create it so as to avoid creating garbage.  */
+  proxy.purpose = purpose;
+  proxy.value = value;
+  proxy.chain = chain;
+  /* See if it is already in the table.  */
+  slot = htab_find_slot_with_hash (list_hash_table, &proxy, hashcode,
+                                  INSERT);
+  /* If not, create a new node.  */
+  if (!*slot)
+    *slot = (PTR) tree_cons (purpose, value, chain);
+  return *slot;
 }
 
 /* Constructor for hashed lists.  */
@@ -844,7 +845,7 @@ make_binfo (offset, binfo, vtable, virtuals)
      tree offset, binfo;
      tree vtable, virtuals;
 {
-  tree new_binfo = make_tree_vec (8);
+  tree new_binfo = make_tree_vec (11);
   tree type;
 
   if (TREE_CODE (binfo) == TREE_VEC)
@@ -865,23 +866,6 @@ make_binfo (offset, binfo, vtable, virtuals)
   return new_binfo;
 }
 
-/* Return the binfo value for ELEM in TYPE.  */
-
-tree
-binfo_value (elem, type)
-     tree elem;
-     tree type;
-{
-  if (get_base_distance (elem, type, 0, (tree *)0) == -2)
-    compiler_error ("base class `%s' ambiguous in binfo_value",
-                   TYPE_NAME_STRING (elem));
-  if (elem == type)
-    return TYPE_BINFO (type);
-  if (TREE_CODE (elem) == RECORD_TYPE && TYPE_BINFO (elem) == type)
-    return type;
-  return get_binfo (elem, type, 0);
-}
-
 /* Return a TREE_LIST whose TREE_VALUE nodes along the
    BINFO_INHERITANCE_CHAIN for BINFO, but in the opposite order.  In
    other words, while the BINFO_INHERITANCE_CHAIN goes from base
@@ -924,7 +908,7 @@ debug_binfo (elem)
     fprintf (stderr, "no vtable decl yet\n");
   fprintf (stderr, "virtuals:\n");
   virtuals = BINFO_VIRTUALS (elem);
-  n = first_vfun_index (BINFO_TYPE (elem));
+  n = 0;
 
   while (virtuals)
     {
@@ -951,7 +935,7 @@ count_functions (t)
       return i;
     }
 
-  my_friendly_abort (359);
+  abort ();
   return 0;
 }
 
@@ -1036,23 +1020,6 @@ build_overload (decl, chain)
   return ovl_cons (decl, chain);
 }
 
-/* True if fn is in ovl. */
-
-int
-ovl_member (fn, ovl)
-     tree fn;
-     tree ovl;
-{
-  if (ovl == NULL_TREE)
-    return 0;
-  if (TREE_CODE (ovl) != OVERLOAD)
-    return ovl == fn;
-  for (; ovl; ovl = OVL_CHAIN (ovl))
-    if (OVL_FUNCTION (ovl) == fn)
-      return 1;
-  return 0;
-}
-
 int
 is_aggr_type_2 (t1, t2)
      tree t1, t2;
@@ -1064,36 +1031,19 @@ is_aggr_type_2 (t1, t2)
 
 /* Returns non-zero if CODE is the code for a statement.  */
 
-static int
-statement_code_p (code)
+int
+cp_statement_code_p (code)
      enum tree_code code;
 {
   switch (code)
     {
-    case EXPR_STMT:
-    case COMPOUND_STMT:
-    case DECL_STMT:
-    case IF_STMT:
-    case FOR_STMT:
-    case WHILE_STMT:
-    case DO_STMT:
-    case RETURN_STMT:
-    case BREAK_STMT:
-    case CONTINUE_STMT:
-    case SWITCH_STMT:
-    case GOTO_STMT:
-    case LABEL_STMT:
-    case ASM_STMT:
-    case SUBOBJECT:
-    case CLEANUP_STMT:
-    case START_CATCH_STMT:
-    case CTOR_STMT:
-    case SCOPE_STMT:
     case CTOR_INITIALIZER:
-    case CASE_LABEL:
     case RETURN_INIT:
     case TRY_BLOCK:
     case HANDLER:
+    case EH_SPEC_BLOCK:
+    case USING_STMT:
+    case TAG_DEFN:
       return 1;
 
     default:
@@ -1104,7 +1054,7 @@ statement_code_p (code)
 #define PRINT_RING_SIZE 4
 
 const char *
-lang_printable_name (decl, v)
+cxx_printable_name (decl, v)
      tree decl;
      int v;
 {
@@ -1135,7 +1085,7 @@ lang_printable_name (decl, v)
       if (ring_counter == PRINT_RING_SIZE)
        ring_counter = 0;
       if (decl_ring[ring_counter] == current_function_decl)
-       my_friendly_abort (106);
+       abort ();
     }
 
   if (print_ring[ring_counter])
@@ -1168,224 +1118,123 @@ build_exception_variant (type, raises)
   return v;
 }
 
-/* Given a TEMPLATE_TEMPLATE_PARM node T, create a new one together with its 
-   lang_specific field and its corresponding TEMPLATE_DECL node */
+/* Given a TEMPLATE_TEMPLATE_PARM node T, create a new
+   BOUND_TEMPLATE_TEMPLATE_PARM bound with NEWARGS as its template
+   arguments.  */
 
 tree
-copy_template_template_parm (t)
+bind_template_template_parm (t, newargs)
      tree t;
+     tree newargs;
 {
-  tree template = TYPE_NAME (t);
+  tree decl = TYPE_NAME (t);
   tree t2;
 
-  t2 = make_aggr_type (TEMPLATE_TEMPLATE_PARM);
-  template = copy_decl (template);
+  t2 = make_aggr_type (BOUND_TEMPLATE_TEMPLATE_PARM);
+  decl = build_decl (TYPE_DECL, DECL_NAME (decl), NULL_TREE);
 
-  TREE_TYPE (template) = t2;
-  TYPE_NAME (t2) = template;
-  TYPE_STUB_DECL (t2) = template;
+  /* These nodes have to be created to reflect new TYPE_DECL and template
+     arguments.  */
+  TEMPLATE_TYPE_PARM_INDEX (t2) = copy_node (TEMPLATE_TYPE_PARM_INDEX (t));
+  TEMPLATE_PARM_DECL (TEMPLATE_TYPE_PARM_INDEX (t2)) = decl;
+  TEMPLATE_TEMPLATE_PARM_TEMPLATE_INFO (t2)
+    = tree_cons (TEMPLATE_TEMPLATE_PARM_TEMPLATE_DECL (t), 
+                newargs, NULL_TREE);
+
+  TREE_TYPE (decl) = t2;
+  TYPE_NAME (t2) = decl;
+  TYPE_STUB_DECL (t2) = decl;
+  TYPE_SIZE (t2) = 0;
 
-  /* No need to copy these */
-  TYPE_FIELDS (t2) = TYPE_FIELDS (t);
-  TEMPLATE_TEMPLATE_PARM_TEMPLATE_INFO (t2) 
-    = TEMPLATE_TEMPLATE_PARM_TEMPLATE_INFO (t);
   return t2;
 }
 
-/* Apply FUNC to all the sub-trees of TP in a pre-order traversal.
-   FUNC is called with the DATA and the address of each sub-tree.  If
-   FUNC returns a non-NULL value, the traversal is aborted, and the
-   value returned by FUNC is returned.  */
+/* Called from count_trees via walk_tree.  */
 
-tree 
-walk_tree (tp, func, data)
-     tree *tp;
-     walk_tree_fn func;
+static tree
+count_trees_r (tp, walk_subtrees, data)
+     tree *tp ATTRIBUTE_UNUSED;
+     int *walk_subtrees ATTRIBUTE_UNUSED;
      void *data;
 {
-  enum tree_code code;
-  int walk_subtrees;
-  tree result;
-  
-#define WALK_SUBTREE(NODE)                     \
-  do                                           \
-    {                                          \
-      result = walk_tree (&(NODE), func, data);        \
-      if (result)                              \
-       return result;                          \
-    }                                          \
-  while (0)
-
-  /* Skip empty subtrees.  */
-  if (!*tp)
-    return NULL_TREE;
-
-  /* Call the function.  */
-  walk_subtrees = 1;
-  result = (*func) (tp, &walk_subtrees, data);
-
-  /* If we found something, return it.  */
-  if (result)
-    return result;
-
-  /* Even if we didn't, FUNC may have decided that there was nothing
-     interesting below this point in the tree.  */
-  if (!walk_subtrees)
-    return NULL_TREE;
-
-  code = TREE_CODE (*tp);
-
-  /* Handle common cases up front.  */
-  if (IS_EXPR_CODE_CLASS (TREE_CODE_CLASS (code))
-      || TREE_CODE_CLASS (code) == 'r'
-      || TREE_CODE_CLASS (code) == 's')
-    {
-      int i, len;
-
-      /* Walk over all the sub-trees of this operand.  */
-      len = first_rtl_op (code);
-      /* TARGET_EXPRs are peculiar: operands 1 and 3 can be the same.
-        But, we only want to walk once.  */
-      if (code == TARGET_EXPR
-         && TREE_OPERAND (*tp, 3) == TREE_OPERAND (*tp, 1))
-       --len;
-      /* Go through the subtrees.  We need to do this in forward order so
-         that the scope of a FOR_EXPR is handled properly.  */
-      for (i = 0; i < len; ++i)
-       WALK_SUBTREE (TREE_OPERAND (*tp, i));
-
-      /* For statements, we also walk the chain so that we cover the
-        entire statement tree.  */
-      if (statement_code_p (code))
-       {
-         if (code == DECL_STMT 
-             && DECL_STMT_DECL (*tp) 
-             && DECL_P (DECL_STMT_DECL (*tp)))
-           {
-             /* Walk the DECL_INITIAL and DECL_SIZE.  We don't want to walk
-                into declarations that are just mentioned, rather than
-                declared; they don't really belong to this part of the tree.
-                And, we can see cycles: the initializer for a declaration can
-                refer to the declaration itself.  */
-             WALK_SUBTREE (DECL_INITIAL (DECL_STMT_DECL (*tp)));
-             WALK_SUBTREE (DECL_SIZE (DECL_STMT_DECL (*tp)));
-             WALK_SUBTREE (DECL_SIZE_UNIT (DECL_STMT_DECL (*tp)));
-           }
-
-         WALK_SUBTREE (TREE_CHAIN (*tp));
-       }
-
-      /* We didn't find what we were looking for.  */
-      return NULL_TREE;
-    }
-  else if (TREE_CODE_CLASS (code) == 'd')
-    {
-      WALK_SUBTREE (TREE_TYPE (*tp));
-
-      /* We didn't find what we were looking for.  */
-      return NULL_TREE;
-    }
-
-  /* Not one of the easy cases.  We must explicitly go through the
-     children.  */
-  switch (code)
-    {
-    case ERROR_MARK:
-    case IDENTIFIER_NODE:
-    case INTEGER_CST:
-    case REAL_CST:
-    case STRING_CST:
-    case DEFAULT_ARG:
-    case TEMPLATE_TEMPLATE_PARM:
-    case TEMPLATE_PARM_INDEX:
-    case TEMPLATE_TYPE_PARM:
-    case REAL_TYPE:
-    case COMPLEX_TYPE:
-    case VOID_TYPE:
-    case BOOLEAN_TYPE:
-    case TYPENAME_TYPE:
-    case UNION_TYPE:
-    case ENUMERAL_TYPE:
-    case TYPEOF_TYPE:
-    case BLOCK:
-      /* None of thse have subtrees other than those already walked
-         above.  */
-      break;
-
-    case PTRMEM_CST:
-      WALK_SUBTREE (TREE_TYPE (*tp));
-      break;
-
-    case POINTER_TYPE:
-    case REFERENCE_TYPE:
-      WALK_SUBTREE (TREE_TYPE (*tp));
-      break;
+  ++ *((int*) data);
+  return NULL_TREE;
+}
 
-    case TREE_LIST:
-      WALK_SUBTREE (TREE_PURPOSE (*tp));
-      WALK_SUBTREE (TREE_VALUE (*tp));
-      WALK_SUBTREE (TREE_CHAIN (*tp));
-      break;
+/* Debugging function for measuring the rough complexity of a tree
+   representation.  */
 
-    case OVERLOAD:
-      WALK_SUBTREE (OVL_FUNCTION (*tp));
-      WALK_SUBTREE (OVL_CHAIN (*tp));
-      break;
-
-    case TREE_VEC:
-      {
-       int len = TREE_VEC_LENGTH (*tp);
-       while (len--)
-         WALK_SUBTREE (TREE_VEC_ELT (*tp, len));
-      }
-      break;
+int
+count_trees (t)
+     tree t;
+{
+  int n_trees = 0;
+  walk_tree_without_duplicates (&t, count_trees_r, &n_trees);
+  return n_trees;
+}  
 
-    case COMPLEX_CST:
-      WALK_SUBTREE (TREE_REALPART (*tp));
-      WALK_SUBTREE (TREE_IMAGPART (*tp));
-      break;
+/* Called from verify_stmt_tree via walk_tree.  */
 
-    case CONSTRUCTOR:
-      WALK_SUBTREE (CONSTRUCTOR_ELTS (*tp));
-      break;
+static tree
+verify_stmt_tree_r (tp, walk_subtrees, data)
+     tree *tp;
+     int *walk_subtrees ATTRIBUTE_UNUSED;
+     void *data;
+{
+  tree t = *tp;
+  htab_t *statements = (htab_t *) data;
+  void **slot;
 
-    case METHOD_TYPE:
-      WALK_SUBTREE (TYPE_METHOD_BASETYPE (*tp));
-      /* Fall through.  */
+  if (!statement_code_p (TREE_CODE (t)))
+    return NULL_TREE;
 
-    case FUNCTION_TYPE:
-      WALK_SUBTREE (TREE_TYPE (*tp));
-      WALK_SUBTREE (TYPE_ARG_TYPES (*tp));
-      break;
+  /* If this statement is already present in the hash table, then
+     there is a circularity in the statement tree.  */
+  if (htab_find (*statements, t))
+    abort ();
+  
+  slot = htab_find_slot (*statements, t, INSERT);
+  *slot = t;
 
-    case ARRAY_TYPE:
-      WALK_SUBTREE (TREE_TYPE (*tp));
-      WALK_SUBTREE (TYPE_DOMAIN (*tp));
-      break;
+  return NULL_TREE;
+}
 
-    case INTEGER_TYPE:
-      WALK_SUBTREE (TYPE_MIN_VALUE (*tp));
-      WALK_SUBTREE (TYPE_MAX_VALUE (*tp));
-      break;
+/* Debugging function to check that the statement T has not been
+   corrupted.  For now, this function simply checks that T contains no
+   circularities.  */
 
-    case OFFSET_TYPE:
-      WALK_SUBTREE (TREE_TYPE (*tp));
-      WALK_SUBTREE (TYPE_OFFSET_BASETYPE (*tp));
-      break;
+void
+verify_stmt_tree (t)
+     tree t;
+{
+  htab_t statements;
+  statements = htab_create (37, htab_hash_pointer, htab_eq_pointer, NULL);
+  walk_tree (&t, verify_stmt_tree_r, &statements, NULL);
+  htab_delete (statements);
+}
 
-    case RECORD_TYPE:
-      if (TYPE_PTRMEMFUNC_P (*tp))
-       WALK_SUBTREE (TYPE_PTRMEMFUNC_FN_TYPE (*tp));
-      break;
+/* Called from find_tree via walk_tree.  */
 
-    default:
-      my_friendly_abort (19990803);
-    }
+static tree
+find_tree_r (tp, walk_subtrees, data)
+     tree *tp;
+     int *walk_subtrees ATTRIBUTE_UNUSED;
+     void *data;
+{
+  if (*tp == (tree) data)
+    return (tree) data;
 
-  /* We didn't find what we were looking for.  */
   return NULL_TREE;
+}
 
-#undef WALK_SUBTREE
+/* Returns X if X appears in the tree structure rooted at T.  */
+
+tree
+find_tree (t, x)
+     tree t;
+     tree x;
+{
+  return walk_tree_without_duplicates (&t, find_tree_r, x);
 }
 
 /* Passed to walk_tree.  Checks for the use of types with no linkage.  */
@@ -1399,9 +1248,9 @@ no_linkage_helper (tp, walk_subtrees, data)
   tree t = *tp;
 
   if (TYPE_P (t)
-      && (IS_AGGR_TYPE (t) || TREE_CODE (t) == ENUMERAL_TYPE)
+      && (CLASS_TYPE_P (t) || TREE_CODE (t) == ENUMERAL_TYPE)
       && (decl_function_context (TYPE_MAIN_DECL (t))
-         || ANON_AGGRNAME_P (TYPE_IDENTIFIER (t))))
+         || TYPE_ANONYMOUS_P (t)))
     return t;
   return NULL_TREE;
 }
@@ -1418,66 +1267,18 @@ no_linkage_check (t)
   if (processing_template_decl)
     return NULL_TREE;
 
-  t = walk_tree (&t, no_linkage_helper, NULL);
+  t = walk_tree_without_duplicates (&t, no_linkage_helper, NULL);
   if (t != error_mark_node)
     return t;
   return NULL_TREE;
 }
 
-/* Passed to walk_tree.  Copies the node pointed to, if appropriate.  */
-
-tree
-copy_tree_r (tp, walk_subtrees, data)
-     tree *tp;
-     int *walk_subtrees;
-     void *data ATTRIBUTE_UNUSED;
-{
-  enum tree_code code = TREE_CODE (*tp);
-
-  /* We make copies of most nodes.  */
-  if (IS_EXPR_CODE_CLASS (TREE_CODE_CLASS (code))
-      || TREE_CODE_CLASS (code) == 'r'
-      || TREE_CODE_CLASS (code) == 'c'
-      || TREE_CODE_CLASS (code) == 's'
-      || code == PARM_DECL
-      || code == TREE_LIST
-      || code == TREE_VEC
-      || code == OVERLOAD)
-    {
-      /* Because the chain gets clobbered when we make a copy, we save it
-        here.  */
-      tree chain = TREE_CHAIN (*tp);
-
-      /* Copy the node.  */
-      *tp = copy_node (*tp);
-
-      /* Now, restore the chain, if appropriate.  That will cause
-        walk_tree to walk into the chain as well.  */
-      if (code == PARM_DECL || code == TREE_LIST || code == OVERLOAD
-         || statement_code_p (code))
-       TREE_CHAIN (*tp) = chain;
-
-      /* For now, we don't update BLOCKs when we make copies.  So, we
-        have to nullify all scope-statements.  */
-      if (TREE_CODE (*tp) == SCOPE_STMT)
-       SCOPE_STMT_BLOCK (*tp) = NULL_TREE;
-    }
-  else if (code == TEMPLATE_TEMPLATE_PARM)
-    /* These must be copied specially.  */
-    *tp = copy_template_template_parm (*tp);
-  else if (TREE_CODE_CLASS (code) == 't')
-    /* There's no need to copy types, or anything beneath them.  */
-    *walk_subtrees = 0;
-
-  return NULL_TREE;
-}
-
 #ifdef GATHER_STATISTICS
 extern int depth_reached;
 #endif
 
 void
-print_lang_statistics ()
+cxx_print_statistics ()
 {
   print_search_statistics ();
   print_class_statistics ();
@@ -1530,13 +1331,15 @@ bot_manip (tp, walk_subtrees, data)
   splay_tree target_remap = ((splay_tree) data);
   tree t = *tp;
 
-  if (TREE_CODE (t) != TREE_LIST && ! TREE_SIDE_EFFECTS (t))
+  if (TREE_CONSTANT (t))
     {
-      /* There can't be any TARGET_EXPRs below this point.  */
+      /* There can't be any TARGET_EXPRs or their slot variables below
+         this point.  We used to check !TREE_SIDE_EFFECTS, but then we
+         failed to copy an ADDR_EXPR of the slot VAR_DECL.  */
       *walk_subtrees = 0;
       return NULL_TREE;
     }
-  else if (TREE_CODE (t) == TARGET_EXPR)
+  if (TREE_CODE (t) == TARGET_EXPR)
     {
       tree u;
 
@@ -1548,13 +1351,8 @@ bot_manip (tp, walk_subtrees, data)
        }
       else 
        {
-         tree var;
-
-         u = copy_node (t);
-         var = build (VAR_DECL, TREE_TYPE (t));
-         DECL_CONTEXT (var) = current_function_decl;
-         layout_decl (var, 0);
-         TREE_OPERAND (u, 0) = var;
+         u = build_target_expr_with_type
+           (break_out_target_exprs (TREE_OPERAND (t, 1)), TREE_TYPE (t));
        }
 
       /* Map the old variable to the new one.  */
@@ -1616,8 +1414,8 @@ break_out_target_exprs (t)
     target_remap = splay_tree_new (splay_tree_compare_pointers, 
                                   /*splay_tree_delete_key_fn=*/NULL, 
                                   /*splay_tree_delete_value_fn=*/NULL);
-  walk_tree (&t, bot_manip, target_remap);
-  walk_tree (&t, bot_replace, target_remap);
+  walk_tree (&t, bot_manip, target_remap, NULL);
+  walk_tree (&t, bot_replace, target_remap, NULL);
 
   if (!--target_remap_count)
     {
@@ -1637,22 +1435,15 @@ break_out_target_exprs (t)
 tree
 build_min_nt VPARAMS ((enum tree_code code, ...))
 {
-#ifndef ANSI_PROTOTYPES
-  enum tree_code code;
-#endif
-  va_list p;
   register tree t;
   register int length;
   register int i;
 
-  VA_START (p, code);
-
-#ifndef ANSI_PROTOTYPES
-  code = va_arg (p, enum tree_code);
-#endif
+  VA_OPEN (p, code);
+  VA_FIXEDARG (p, enum tree_code, code);
 
   t = make_node (code);
-  length = tree_code_length[(int) code];
+  length = TREE_CODE_LENGTH (code);
   TREE_COMPLEXITY (t) = lineno;
 
   for (i = 0; i < length; i++)
@@ -1661,7 +1452,7 @@ build_min_nt VPARAMS ((enum tree_code code, ...))
       TREE_OPERAND (t, i) = x;
     }
 
-  va_end (p);
+  VA_CLOSE (p);
   return t;
 }
 
@@ -1671,24 +1462,16 @@ build_min_nt VPARAMS ((enum tree_code code, ...))
 tree
 build_min VPARAMS ((enum tree_code code, tree tt, ...))
 {
-#ifndef ANSI_PROTOTYPES
-  enum tree_code code;
-  tree tt;
-#endif
-  va_list p;
   register tree t;
   register int length;
   register int i;
 
-  VA_START (p, tt);
-
-#ifndef ANSI_PROTOTYPES
-  code = va_arg (p, enum tree_code);
-  tt = va_arg (p, tree);
-#endif
+  VA_OPEN (p, tt);
+  VA_FIXEDARG (p, enum tree_code, code);
+  VA_FIXEDARG (p, tree, tt);
 
   t = make_node (code);
-  length = tree_code_length[(int) code];
+  length = TREE_CODE_LENGTH (code);
   TREE_TYPE (t) = tt;
   TREE_COMPLEXITY (t) = lineno;
 
@@ -1698,7 +1481,7 @@ build_min VPARAMS ((enum tree_code code, tree tt, ...))
       TREE_OPERAND (t, i) = x;
     }
 
-  va_end (p);
+  VA_CLOSE (p);
   return t;
 }
 
@@ -1730,34 +1513,15 @@ get_type_decl (t)
     return t;
   if (TYPE_P (t))
     return TYPE_STUB_DECL (t);
+  if (t == error_mark_node)
+    return t;
   
-  my_friendly_abort (42);
+  abort ();
 
   /* Stop compiler from complaining control reaches end of non-void function.  */
   return 0;
 }
 
-int
-can_free (obstack, t)
-     struct obstack *obstack;
-     tree t;
-{
-  int size = 0;
-
-  if (TREE_CODE (t) == TREE_VEC)
-    size = (TREE_VEC_LENGTH (t)-1) * sizeof (tree) + sizeof (struct tree_vec);
-  else
-    my_friendly_abort (42);
-
-#define ROUND(x) ((x + obstack_alignment_mask (obstack)) \
-                 & ~ obstack_alignment_mask (obstack))
-  if ((char *)t + ROUND (size) == obstack_next_free (obstack))
-    return 1;
-#undef ROUND
-
-  return 0;
-}
-
 /* Return first vector element whose BINFO_TYPE is ELEM.
    Return 0 if ELEM is not in VEC.  VEC may be NULL_TREE.  */
 
@@ -1839,7 +1603,7 @@ cp_tree_equal (t1, t2)
 
     case STRING_CST:
       return TREE_STRING_LENGTH (t1) == TREE_STRING_LENGTH (t2)
-       && !bcmp (TREE_STRING_POINTER (t1), TREE_STRING_POINTER (t2),
+       && !memcmp (TREE_STRING_POINTER (t1), TREE_STRING_POINTER (t2),
                  TREE_STRING_LENGTH (t1));
 
     case CONSTRUCTOR:
@@ -1877,10 +1641,10 @@ cp_tree_equal (t1, t2)
         as being equivalent to anything.  */
       if ((TREE_CODE (TREE_OPERAND (t1, 0)) == VAR_DECL
           && DECL_NAME (TREE_OPERAND (t1, 0)) == NULL_TREE
-          && DECL_RTL (TREE_OPERAND (t1, 0)) == 0)
+          && !DECL_RTL_SET_P (TREE_OPERAND (t1, 0)))
          || (TREE_CODE (TREE_OPERAND (t2, 0)) == VAR_DECL
              && DECL_NAME (TREE_OPERAND (t2, 0)) == NULL_TREE
-             && DECL_RTL (TREE_OPERAND (t2, 0)) == 0))
+             && !DECL_RTL_SET_P (TREE_OPERAND (t2, 0))))
        cmp = 1;
       else
        cmp = cp_tree_equal (TREE_OPERAND (t1, 0), TREE_OPERAND (t2, 0));
@@ -1892,7 +1656,7 @@ cp_tree_equal (t1, t2)
       cmp = cp_tree_equal (TREE_OPERAND (t1, 0), TREE_OPERAND (t2, 0));
       if (cmp <= 0)
        return cmp;
-      return cp_tree_equal (TREE_OPERAND (t1, 2), TREE_OPERAND (t1, 2));
+      return cp_tree_equal (TREE_OPERAND (t1, 1), TREE_OPERAND (t1, 1));
 
     case COMPONENT_REF:
       if (TREE_OPERAND (t1, 1) == TREE_OPERAND (t2, 1))
@@ -1929,21 +1693,27 @@ cp_tree_equal (t1, t2)
 
   switch (TREE_CODE_CLASS (code1))
     {
-      int i;
     case '1':
     case '2':
     case '<':
     case 'e':
     case 'r':
     case 's':
-      cmp = 1;
-      for (i=0; i<tree_code_length[(int) code1]; ++i)
-       {
-         cmp = cp_tree_equal (TREE_OPERAND (t1, i), TREE_OPERAND (t2, i));
-         if (cmp <= 0)
-           return cmp;
-       }
-      return cmp;
+      {
+       int i;
+       
+       cmp = 1;
+       for (i = 0; i < TREE_CODE_LENGTH (code1); ++i)
+         {
+           cmp = cp_tree_equal (TREE_OPERAND (t1, i), TREE_OPERAND (t2, i));
+           if (cmp <= 0)
+             return cmp;
+         }
+       return cmp;
+      }
+    
+      case 't':
+       return same_type_p (t1, t2) ? 1 : 0;
     }
 
   return -1;
@@ -1960,15 +1730,6 @@ build_ptr_wrapper (ptr)
   return t;
 }
 
-/* Same, but on the expression_obstack.  */
-
-tree
-build_expr_ptr_wrapper (ptr)
-     void *ptr;
-{
-  return build_ptr_wrapper (ptr);
-}
-
 /* Build a wrapper around some integer I so we can use it as a tree.  */
 
 tree
@@ -1982,7 +1743,7 @@ build_int_wrapper (i)
 
 static tree
 build_srcloc (file, line)
-     char *file;
+     const char *file;
      int line;
 {
   tree t;
@@ -2061,7 +1822,7 @@ build_dummy_object (type)
      tree type;
 {
   tree decl = build1 (NOP_EXPR, build_pointer_type (type), void_zero_node);
-  return build_indirect_ref (decl, NULL_PTR);
+  return build_indirect_ref (decl, NULL);
 }
 
 /* We've gotten a reference to a member of TYPE.  Return *this if appropriate,
@@ -2074,19 +1835,27 @@ maybe_dummy_object (type, binfop)
      tree *binfop;
 {
   tree decl, context;
-
+  tree binfo;
+  
   if (current_class_type
-      && get_base_distance (type, current_class_type, 0, binfop) != -1)
+      && (binfo = lookup_base (current_class_type, type,
+                              ba_ignore | ba_quiet, NULL)))
     context = current_class_type;
   else
     {
       /* Reference from a nested class member function.  */
       context = type;
-      if (binfop)
-       *binfop = TYPE_BINFO (type);
+      binfo = TYPE_BINFO (type);
     }
 
-  if (current_class_ref && context == current_class_type)
+  if (binfop)
+    *binfop = binfo;
+  
+  if (current_class_ref && context == current_class_type
+      // Kludge: Make sure that current_class_type is actually correct.
+      // It might not be if we're in the middle of tsubst_default_argument.
+      && same_type_p (TYPE_MAIN_VARIANT (TREE_TYPE (current_class_ref)),
+                     current_class_type))
     decl = current_class_ref;
   else
     decl = build_dummy_object (context);
@@ -2112,8 +1881,7 @@ int
 pod_type_p (t)
      tree t;
 {
-  while (TREE_CODE (t) == ARRAY_TYPE)
-    t = TREE_TYPE (t);
+  t = strip_array_types (t);
 
   if (INTEGRAL_TYPE_P (t))
     return 1;  /* integral, character or enumeral type */
@@ -2133,91 +1901,166 @@ pod_type_p (t)
   return 1;
 }
 
-/* Return a 1 if ATTR_NAME and ATTR_ARGS denote a valid C++-specific
-   attribute for either declaration DECL or type TYPE and 0 otherwise.
-   Plugged into valid_lang_attribute.  */
+/* Returns 1 iff zero initialization of type T means actually storing
+   zeros in it.  */
 
 int
-cp_valid_lang_attribute (attr_name, attr_args, decl, type)
-  tree attr_name;
-  tree attr_args ATTRIBUTE_UNUSED;
-  tree decl ATTRIBUTE_UNUSED;
-  tree type ATTRIBUTE_UNUSED;
+zero_init_p (t)
+     tree t;
 {
-  if (is_attribute_p ("com_interface", attr_name))
-    {
-      if (! flag_vtable_thunks)
-       {
-         error ("`com_interface' only supported with -fvtable-thunks");
-         return 0;
-       }
+  t = strip_array_types (t);
 
-      if (attr_args != NULL_TREE
-         || decl != NULL_TREE
-         || ! CLASS_TYPE_P (type)
-         || type != TYPE_MAIN_VARIANT (type))
-       {
-         warning ("`com_interface' attribute can only be applied to class definitions");
-         return 0;
-       }
+  /* NULL pointers to data members are initialized with -1.  */
+  if (TYPE_PTRMEM_P (t))
+    return 0;
 
-      CLASSTYPE_COM_INTERFACE (type) = 1;
-      return 1;
+  /* Classes that contain types that can't be zero-initialized, cannot
+     be zero-initialized themselves.  */
+  if (CLASS_TYPE_P (t) && CLASSTYPE_NON_ZERO_INIT_P (t))
+    return 0;
+
+  return 1;
+}
+
+/* Table of valid C++ attributes.  */
+const struct attribute_spec cxx_attribute_table[] =
+{
+  /* { name, min_len, max_len, decl_req, type_req, fn_type_req, handler } */
+  { "java_interface", 0, 0, false, false, false, handle_java_interface_attribute },
+  { "com_interface",  0, 0, false, false, false, handle_com_interface_attribute },
+  { "init_priority",  1, 1, true,  false, false, handle_init_priority_attribute },
+  { NULL,             0, 0, false, false, false, NULL }
+};
+
+/* Handle a "java_interface" attribute; arguments as in
+   struct attribute_spec.handler.  */
+static tree
+handle_java_interface_attribute (node, name, args, flags, no_add_attrs)
+     tree *node;
+     tree name;
+     tree args ATTRIBUTE_UNUSED;
+     int flags;
+     bool *no_add_attrs;
+{
+  if (DECL_P (*node)
+      || !CLASS_TYPE_P (*node)
+      || !TYPE_FOR_JAVA (*node))
+    {
+      error ("`%s' attribute can only be applied to Java class definitions",
+            IDENTIFIER_POINTER (name));
+      *no_add_attrs = true;
+      return NULL_TREE;
     }
-  else if (is_attribute_p ("init_priority", attr_name))
+  if (!(flags & (int) ATTR_FLAG_TYPE_IN_PLACE))
+    *node = build_type_copy (*node);
+  TYPE_JAVA_INTERFACE (*node) = 1;
+
+  return NULL_TREE;
+}
+
+/* Handle a "com_interface" attribute; arguments as in
+   struct attribute_spec.handler.  */
+static tree
+handle_com_interface_attribute (node, name, args, flags, no_add_attrs)
+     tree *node;
+     tree name;
+     tree args ATTRIBUTE_UNUSED;
+     int flags ATTRIBUTE_UNUSED;
+     bool *no_add_attrs;
+{
+  static int warned;
+
+  *no_add_attrs = true;
+
+  if (DECL_P (*node)
+      || !CLASS_TYPE_P (*node)
+      || *node != TYPE_MAIN_VARIANT (*node))
     {
-      tree initp_expr = (attr_args ? TREE_VALUE (attr_args): NULL_TREE);
-      int pri;
+      warning ("`%s' attribute can only be applied to class definitions",
+              IDENTIFIER_POINTER (name));
+      return NULL_TREE;
+    }
 
-      if (initp_expr)
-       STRIP_NOPS (initp_expr);
+  if (!warned++)
+    warning ("`%s' is obsolete; g++ vtables are now COM-compatible by default",
+            IDENTIFIER_POINTER (name));
+
+  return NULL_TREE;
+}
+
+/* Handle an "init_priority" attribute; arguments as in
+   struct attribute_spec.handler.  */
+static tree
+handle_init_priority_attribute (node, name, args, flags, no_add_attrs)
+     tree *node;
+     tree name;
+     tree args;
+     int flags ATTRIBUTE_UNUSED;
+     bool *no_add_attrs;
+{
+  tree initp_expr = TREE_VALUE (args);
+  tree decl = *node;
+  tree type = TREE_TYPE (decl);
+  int pri;
+
+  STRIP_NOPS (initp_expr);
          
-      if (!initp_expr || TREE_CODE (initp_expr) != INTEGER_CST)
-       {
-         error ("requested init_priority is not an integer constant");
-         return 0;
-       }
+  if (!initp_expr || TREE_CODE (initp_expr) != INTEGER_CST)
+    {
+      error ("requested init_priority is not an integer constant");
+      *no_add_attrs = true;
+      return NULL_TREE;
+    }
 
-      pri = TREE_INT_CST_LOW (initp_expr);
+  pri = TREE_INT_CST_LOW (initp_expr);
        
-      while (TREE_CODE (type) == ARRAY_TYPE)
-       type = TREE_TYPE (type);
-
-      if (decl == NULL_TREE
-         || TREE_CODE (decl) != VAR_DECL
-         || ! TREE_STATIC (decl)
-         || DECL_EXTERNAL (decl)
-         || (TREE_CODE (type) != RECORD_TYPE
-             && TREE_CODE (type) != UNION_TYPE)
-         /* Static objects in functions are initialized the
-            first time control passes through that
-            function. This is not precise enough to pin down an
-            init_priority value, so don't allow it. */
-         || current_function_decl) 
-       {
-         error ("can only use init_priority attribute on file-scope definitions of objects of class type");
-         return 0;
-       }
+  type = strip_array_types (type);
+
+  if (decl == NULL_TREE
+      || TREE_CODE (decl) != VAR_DECL
+      || !TREE_STATIC (decl)
+      || DECL_EXTERNAL (decl)
+      || (TREE_CODE (type) != RECORD_TYPE
+         && TREE_CODE (type) != UNION_TYPE)
+      /* Static objects in functions are initialized the
+        first time control passes through that
+        function. This is not precise enough to pin down an
+        init_priority value, so don't allow it. */
+      || current_function_decl) 
+    {
+      error ("can only use `%s' attribute on file-scope definitions of objects of class type",
+            IDENTIFIER_POINTER (name));
+      *no_add_attrs = true;
+      return NULL_TREE;
+    }
 
-      if (pri > MAX_INIT_PRIORITY || pri <= 0)
-       {
-         error ("requested init_priority is out of range");
-         return 0;
-       }
+  if (pri > MAX_INIT_PRIORITY || pri <= 0)
+    {
+      error ("requested init_priority is out of range");
+      *no_add_attrs = true;
+      return NULL_TREE;
+    }
 
-      /* Check for init_priorities that are reserved for
-        language and runtime support implementations.*/
-      if (pri <= MAX_RESERVED_INIT_PRIORITY)
-       {
-         warning 
-           ("requested init_priority is reserved for internal use");
-       }
+  /* Check for init_priorities that are reserved for
+     language and runtime support implementations.*/
+  if (pri <= MAX_RESERVED_INIT_PRIORITY)
+    {
+      warning 
+       ("requested init_priority is reserved for internal use");
+    }
 
+  if (SUPPORTS_INIT_PRIORITY)
+    {
       DECL_INIT_PRIORITY (decl) = pri;
-      return 1;
+      return NULL_TREE;
+    }
+  else
+    {
+      error ("`%s' attribute is not supported on this platform",
+            IDENTIFIER_POINTER (name));
+      *no_add_attrs = true;
+      return NULL_TREE;
     }
-
-  return 0;
 }
 
 /* Return a new PTRMEM_CST of the indicated TYPE.  The MEMBER is the
@@ -2237,70 +2080,255 @@ make_ptrmem_cst (type, member)
   return ptrmem_cst;
 }
 
-/* Mark ARG (which is really a list_hash_table **) for GC.  */
+/* Apply FUNC to all language-specific sub-trees of TP in a pre-order
+   traversal.  Called from walk_tree().  */
+
+tree 
+cp_walk_subtrees (tp, walk_subtrees_p, func, data, htab)
+     tree *tp;
+     int *walk_subtrees_p;
+     walk_tree_fn func;
+     void *data;
+     void *htab;
+{
+  enum tree_code code = TREE_CODE (*tp);
+  tree result;
+  
+#define WALK_SUBTREE(NODE)                             \
+  do                                                   \
+    {                                                  \
+      result = walk_tree (&(NODE), func, data, htab);  \
+      if (result)                                      \
+       return result;                                  \
+    }                                                  \
+  while (0)
+
+  /* Not one of the easy cases.  We must explicitly go through the
+     children.  */
+  switch (code)
+    {
+    case DEFAULT_ARG:
+    case TEMPLATE_TEMPLATE_PARM:
+    case BOUND_TEMPLATE_TEMPLATE_PARM:
+    case UNBOUND_CLASS_TEMPLATE:
+    case TEMPLATE_PARM_INDEX:
+    case TEMPLATE_TYPE_PARM:
+    case TYPENAME_TYPE:
+    case TYPEOF_TYPE:
+      /* None of thse have subtrees other than those already walked
+         above.  */
+      *walk_subtrees_p = 0;
+      break;
+
+    case PTRMEM_CST:
+      WALK_SUBTREE (TREE_TYPE (*tp));
+      *walk_subtrees_p = 0;
+      break;
+
+    case TREE_LIST:
+      /* A BASELINK_P's TREE_PURPOSE is a BINFO, and hence circular.  */
+      if (!BASELINK_P (*tp))
+        WALK_SUBTREE (TREE_PURPOSE (*tp));
+      break;
+
+    case OVERLOAD:
+      WALK_SUBTREE (OVL_FUNCTION (*tp));
+      WALK_SUBTREE (OVL_CHAIN (*tp));
+      *walk_subtrees_p = 0;
+      break;
+
+    case RECORD_TYPE:
+      if (TYPE_PTRMEMFUNC_P (*tp))
+       WALK_SUBTREE (TYPE_PTRMEMFUNC_FN_TYPE (*tp));
+      break;
+
+    default:
+      break;
+    }
+
+  /* We didn't find what we were looking for.  */
+  return NULL_TREE;
+
+#undef WALK_SUBTREE
+}
+
+/* Decide whether there are language-specific reasons to not inline a
+   function as a tree.  */
 
-static void
-mark_list_hash (arg)
-     void *arg;
+int
+cp_cannot_inline_tree_fn (fnp)
+     tree *fnp;
 {
-  struct list_hash *lh;
+  tree fn = *fnp;
+
+  if (flag_really_no_inline
+      && lookup_attribute ("always_inline", DECL_ATTRIBUTES (fn)) == NULL)
+    return 1;
 
-  for (lh = * ((struct list_hash **) arg); lh; lh = lh->next)
-    ggc_mark_tree (lh->list);
+  /* We can inline a template instantiation only if it's fully
+     instantiated.  */
+  if (DECL_TEMPLATE_INFO (fn)
+      && TI_PENDING_TEMPLATE_FLAG (DECL_TEMPLATE_INFO (fn)))
+    {
+      fn = *fnp = instantiate_decl (fn, /*defer_ok=*/0);
+      return TI_PENDING_TEMPLATE_FLAG (DECL_TEMPLATE_INFO (fn));
+    }
+
+  if (varargs_function_p (fn))
+    {
+      DECL_UNINLINABLE (fn) = 1;
+      return 1;
+    }
+
+  if (! function_attribute_inlinable_p (fn))
+    {
+      DECL_UNINLINABLE (fn) = 1;
+      return 1;
+    }
+
+  return 0;
 }
 
-/* Initialize tree.c.  */
+/* Add any pending functions other than the current function (already
+   handled by the caller), that thus cannot be inlined, to FNS_P, then
+   return the latest function added to the array, PREV_FN.  */
 
-void
-init_tree ()
+tree
+cp_add_pending_fn_decls (fns_p, prev_fn)
+     void *fns_p;
+     tree prev_fn;
 {
-  make_lang_type_fn = cp_make_lang_type;
-  lang_unsave = cp_unsave;
-  ggc_add_root (list_hash_table, 
-               sizeof (list_hash_table) / sizeof (struct list_hash *),
-               sizeof (struct list_hash *),
-               mark_list_hash);
+  varray_type *fnsp = (varray_type *)fns_p;
+  struct saved_scope *s;
+
+  for (s = scope_chain; s; s = s->prev)
+    if (s->function_decl && s->function_decl != prev_fn)
+      {
+       VARRAY_PUSH_TREE (*fnsp, s->function_decl);
+       prev_fn = s->function_decl;
+      }
+
+  return prev_fn;
 }
 
-/* The SAVE_EXPR pointed to by TP is being copied.  If ST contains
-   information indicating to what new SAVE_EXPR this one should be
-   mapped, use that one.  Otherwise, create a new node and enter it in
-   ST.  FN is the function into which the copy will be placed.  */
+/* Determine whether a tree node is an OVERLOAD node.  Used to decide
+   whether to copy a node or to preserve its chain when inlining a
+   function.  */
 
-void
-remap_save_expr (tp, st, fn, walk_subtrees)
-     tree *tp;
-     splay_tree st;
-     tree fn;
-     int *walk_subtrees;
+int
+cp_is_overload_p (t)
+     tree t;
 {
-  splay_tree_node n;
+  return TREE_CODE (t) == OVERLOAD;
+}
 
-  /* See if we already encountered this SAVE_EXPR.  */
-  n = splay_tree_lookup (st, (splay_tree_key) *tp);
-      
-  /* If we didn't already remap this SAVE_EXPR, do so now.  */
-  if (!n)
+/* Determine whether VAR is a declaration of an automatic variable in
+   function FN.  */
+
+int
+cp_auto_var_in_fn_p (var, fn)
+     tree var, fn;
+{
+  return (DECL_P (var) && DECL_CONTEXT (var) == fn
+         && nonstatic_local_decl_p (var));
+}
+
+/* Tell whether a declaration is needed for the RESULT of a function
+   FN being inlined into CALLER or if the top node of target_exprs is
+   to be used.  */
+
+tree
+cp_copy_res_decl_for_inlining (result, fn, caller, decl_map_,
+                              need_decl, target_exprs)
+     tree result, fn, caller;
+     void *decl_map_;
+     int *need_decl;
+     void *target_exprs;
+{
+  splay_tree decl_map = (splay_tree)decl_map_;
+  varray_type *texps = (varray_type *)target_exprs;
+  tree var;
+  int aggregate_return_p;
+
+  /* Figure out whether or not FN returns an aggregate.  */
+  aggregate_return_p = IS_AGGR_TYPE (TREE_TYPE (result));
+  *need_decl = ! aggregate_return_p;
+
+  /* If FN returns an aggregate then the caller will always create the
+     temporary (using a TARGET_EXPR) and the call will be the
+     initializing expression for the TARGET_EXPR.  If we were just to
+     create a new VAR_DECL here, then the result of this function
+     would be copied (bitwise) into the variable initialized by the
+     TARGET_EXPR.  That's incorrect, so we must transform any
+     references to the RESULT into references to the target.  */
+  if (aggregate_return_p)
+    {
+      if (VARRAY_ACTIVE_SIZE (*texps) == 0)
+       abort ();
+      var = TREE_OPERAND (VARRAY_TOP_TREE (*texps), 0);
+      if (! same_type_ignoring_top_level_qualifiers_p (TREE_TYPE (var),
+                                                      TREE_TYPE (result)))
+       abort ();
+    }
+  /* Otherwise, make an appropriate copy.  */
+  else
+    var = copy_decl_for_inlining (result, fn, caller);
+
+  if (DECL_SAVED_FUNCTION_DATA (fn))
     {
-      tree t = copy_node (*tp);
-
-      /* The SAVE_EXPR is now part of the function into which we
-        are inlining this body.  */
-      SAVE_EXPR_CONTEXT (t) = fn;
-      /* And we haven't evaluated it yet.  */
-      SAVE_EXPR_RTL (t) = NULL_RTX;
-      /* Remember this SAVE_EXPR.  */
-      n = splay_tree_insert (st,
-                            (splay_tree_key) *tp,
-                            (splay_tree_value) t);
+      tree nrv = DECL_SAVED_FUNCTION_DATA (fn)->x_return_value;
+      if (nrv)
+       {
+         /* We have a named return value; copy the name and source
+            position so we can get reasonable debugging information, and
+            register the return variable as its equivalent.  */
+         DECL_NAME (var) = DECL_NAME (nrv);
+         DECL_SOURCE_FILE (var) = DECL_SOURCE_FILE (nrv);
+         DECL_SOURCE_LINE (var) = DECL_SOURCE_LINE (nrv);
+         DECL_ABSTRACT_ORIGIN (var) = DECL_ORIGIN (nrv);
+         splay_tree_insert (decl_map,
+                            (splay_tree_key) nrv,
+                            (splay_tree_value) var);
+       }
     }
+
+  return var;
+}
+
+/* Record that we're about to start inlining FN, and return non-zero if
+   that's OK.  Used for lang_hooks.tree_inlining.start_inlining.  */
+
+int
+cp_start_inlining (fn)
+     tree fn;
+{
+  if (DECL_TEMPLATE_INSTANTIATION (fn))
+    return push_tinst_level (fn);
   else
-    /* We've already walked into this SAVE_EXPR, so we needn't do it
-       again.  */
-    *walk_subtrees = 0;
+    return 1;
+}
+
+/* Record that we're done inlining FN.  Used for
+   lang_hooks.tree_inlining.end_inlining.  */
 
-  /* Replace this SAVE_EXPR with the copy.  */
-  *tp = (tree) n->value;
+void
+cp_end_inlining (fn)
+     tree fn ATTRIBUTE_UNUSED;
+{
+  if (DECL_TEMPLATE_INSTANTIATION (fn))
+    pop_tinst_level ();
+}
+
+/* Initialize tree.c.  */
+
+void
+init_tree ()
+{
+  lang_statement_code_p = cp_statement_code_p;
+  list_hash_table = htab_create (31, list_hash, list_hash_eq, NULL);
+  ggc_add_root (&list_hash_table, 1, 
+               sizeof (list_hash_table),
+               mark_tree_hashtable);
 }
 
 /* Called via walk_tree.  If *TP points to a DECL_STMT for a local
@@ -2326,6 +2354,8 @@ mark_local_for_remap_r (tp, walk_subtrees, data)
   else if (TREE_CODE (t) == TARGET_EXPR
           && nonstatic_local_decl_p (TREE_OPERAND (t, 0)))
     decl = TREE_OPERAND (t, 0);
+  else if (TREE_CODE (t) == CASE_LABEL)
+    decl = CASE_LABEL_DECL (t);
   else
     decl = NULL_TREE;
 
@@ -2384,12 +2414,11 @@ cp_unsave_r (tp, walk_subtrees, data)
   return NULL_TREE;
 }
 
-/* Called by unsave_expr_now whenever an expression (*TP) needs to be
-   unsaved.  */
+/* Called whenever an expression needs to be unsaved.  */
 
-static void
-cp_unsave (tp)
-     tree *tp;
+tree
+cxx_unsave_expr_now (tp)
+     tree tp;
 {
   splay_tree st;
 
@@ -2398,11 +2427,132 @@ cp_unsave (tp)
   st = splay_tree_new (splay_tree_compare_pointers, NULL, NULL);
 
   /* Walk the tree once figuring out what needs to be remapped.  */
-  walk_tree (tp, mark_local_for_remap_r, st);
+  walk_tree (&tp, mark_local_for_remap_r, st, NULL);
 
   /* Walk the tree again, copying, remapping, and unsaving.  */
-  walk_tree (tp, cp_unsave_r, st);
+  walk_tree (&tp, cp_unsave_r, st, NULL);
 
   /* Clean up.  */
   splay_tree_delete (st);
+
+  return tp;
+}
+
+/* Returns the kind of special function that DECL (a FUNCTION_DECL)
+   is.  Note that this sfk_none is zero, so this function can be used
+   as a predicate to test whether or not DECL is a special function.  */
+
+special_function_kind
+special_function_p (decl)
+     tree decl;
+{
+  /* Rather than doing all this stuff with magic names, we should
+     probably have a field of type `special_function_kind' in
+     DECL_LANG_SPECIFIC.  */
+  if (DECL_COPY_CONSTRUCTOR_P (decl))
+    return sfk_copy_constructor;
+  if (DECL_CONSTRUCTOR_P (decl))
+    return sfk_constructor;
+  if (DECL_OVERLOADED_OPERATOR_P (decl) == NOP_EXPR)
+    return sfk_assignment_operator;
+  if (DECL_MAYBE_IN_CHARGE_DESTRUCTOR_P (decl))
+    return sfk_destructor;
+  if (DECL_COMPLETE_DESTRUCTOR_P (decl))
+    return sfk_complete_destructor;
+  if (DECL_BASE_DESTRUCTOR_P (decl))
+    return sfk_base_destructor;
+  if (DECL_DELETING_DESTRUCTOR_P (decl))
+    return sfk_deleting_destructor;
+  if (DECL_CONV_FN_P (decl))
+    return sfk_conversion;
+
+  return sfk_none;
+}
+
+/* Returns non-zero if TYPE is a character type, including wchar_t.  */
+
+int
+char_type_p (type)
+     tree type;
+{
+  return (same_type_p (type, char_type_node)
+         || same_type_p (type, unsigned_char_type_node)
+         || same_type_p (type, signed_char_type_node)
+         || same_type_p (type, wchar_type_node));
+}
+
+/* Returns the kind of linkage associated with the indicated DECL.  Th
+   value returned is as specified by the language standard; it is
+   independent of implementation details regarding template
+   instantiation, etc.  For example, it is possible that a declaration
+   to which this function assigns external linkage would not show up
+   as a global symbol when you run `nm' on the resulting object file.  */
+
+linkage_kind
+decl_linkage (decl)
+     tree decl;
+{
+  /* This function doesn't attempt to calculate the linkage from first
+     principles as given in [basic.link].  Instead, it makes use of
+     the fact that we have already set TREE_PUBLIC appropriately, and
+     then handles a few special cases.  Ideally, we would calculate
+     linkage first, and then transform that into a concrete
+     implementation.  */
+
+  /* Things that don't have names have no linkage.  */
+  if (!DECL_NAME (decl))
+    return lk_none;
+
+  /* Things that are TREE_PUBLIC have external linkage.  */
+  if (TREE_PUBLIC (decl))
+    return lk_external;
+
+  /* Some things that are not TREE_PUBLIC have external linkage, too.
+     For example, on targets that don't have weak symbols, we make all
+     template instantiations have internal linkage (in the object
+     file), but the symbols should still be treated as having external
+     linkage from the point of view of the language.  */
+  if (DECL_LANG_SPECIFIC (decl) && DECL_COMDAT (decl))
+    return lk_external;
+
+  /* Things in local scope do not have linkage, if they don't have
+     TREE_PUBLIC set.  */
+  if (decl_function_context (decl))
+    return lk_none;
+
+  /* Everything else has internal linkage.  */
+  return lk_internal;
+}
+\f
+/* EXP is an expression that we want to pre-evaluate.  Returns via INITP an
+   expression to perform the pre-evaluation, and returns directly an
+   expression to use the precalculated result.  */
+
+tree
+stabilize_expr (exp, initp)
+     tree exp;
+     tree *initp;
+{
+  tree init_expr;
+
+  if (!TREE_SIDE_EFFECTS (exp))
+    {
+      init_expr = void_zero_node;
+    }
+  else if (!real_lvalue_p (exp)
+          || !TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (exp)))
+    {
+      init_expr = get_target_expr (exp);
+      exp = TARGET_EXPR_SLOT (init_expr);
+    }
+  else
+    {
+      exp = build_unary_op (ADDR_EXPR, exp, 1);
+      init_expr = get_target_expr (exp);
+      exp = TARGET_EXPR_SLOT (init_expr);
+      exp = build_indirect_ref (exp, 0);
+    }
+
+  *initp = init_expr;
+  return exp;
 }