From fc378698688e76cd83c0171c493703858b822bac Mon Sep 17 00:00:00 2001
From: Mike Stump <mrs@gcc.gnu.org>
Date: Thu, 21 Mar 1996 19:46:11 +0000
Subject: [PATCH] 85th Cygnus<->FSF quick merge

From-SVN: r11587
---
 gcc/cp/ChangeLog   | 230 +++++++++++++++++++++++++++++++++++++++++++++
 gcc/cp/call.c      |  68 +++-----------
 gcc/cp/class.c     | 229 +++++++++++++++++++-------------------------
 gcc/cp/cp-tree.h   |  26 +++--
 gcc/cp/cvt.c       |  61 ++++--------
 gcc/cp/decl.c      | 192 ++++++++++++++++---------------------
 gcc/cp/decl2.c     |  77 +++++++++------
 gcc/cp/error.c     |  11 +--
 gcc/cp/except.c    |   6 +-
 gcc/cp/expr.c      |   3 +
 gcc/cp/gxxint.texi |  32 +++----
 gcc/cp/init.c      | 169 ++++++++++++++++-----------------
 gcc/cp/lex.c       |  61 +++++-------
 gcc/cp/method.c    |  27 +++++-
 gcc/cp/parse.y     |  27 +++++-
 gcc/cp/pt.c        |  63 ++++++++-----
 gcc/cp/search.c    | 110 +++++++++++++---------
 gcc/cp/spew.c      |  54 +++++------
 gcc/cp/tree.c      |  11 ++-
 gcc/cp/typeck.c    |  79 +++++++++++-----
 gcc/cp/typeck2.c   |  93 +++++-------------
 21 files changed, 893 insertions(+), 736 deletions(-)

diff --git a/gcc/cp/ChangeLog b/gcc/cp/ChangeLog
index 7e7006fdb0cb..3434665100c7 100644
--- a/gcc/cp/ChangeLog
+++ b/gcc/cp/ChangeLog
@@ -1,3 +1,233 @@
+Wed Mar 20 14:51:55 1996  Jason Merrill  <jason@yorick.cygnus.com>
+
+	* parse.y (named_complex_class_head_sans_basetype): Don't crash on
+ 	definition of nonexistent nested type.
+
+	* error.c (dump_decl, case TYPE_DECL): Fix decision for whether or
+ 	not to say 'typedef'.
+
+Wed Mar 20 00:11:47 1996  Brendan Kehoe  <brendan@lisa.cygnus.com>
+
+	* cp-tree.h (struct lang_type): Make search_slot a tree, not a char*.
+	* search.c (dfs_walk, dfs_init_vbase_pointers,
+	expand_upcast_fixups): Remove cast of CLASSTYPE_SEARCH_SLOT.
+	(dfs_find_vbases): Remove cast for CLASSTYPE_SEARCH_SLOT init.
+
+Tue Mar 19 17:56:03 1996  Jason Merrill  <jason@yorick.cygnus.com>
+
+	* except.c (build_throw): Support minimal parse.
+	* pt.c (tsubst_copy): Support THROW_EXPR.
+	* decl2.c (build_expr_from_tree): Ditto.
+
+	* pt.c (mangle_class_name_for_template): Always allocate
+ 	scratch_firstobj.
+
+Tue Mar 19 16:34:31 1996  Bob Manson  <manson@beauty.cygnus.com>
+
+	* cvt.c (cp_convert_to_pointer): Give an appropriate error
+	when trying to cast from an incomplete type.
+
+Tue Mar 19 16:00:33 1996  Jason Merrill  <jason@yorick.cygnus.com>
+
+	* pt.c (instantiate_class_template): Don't bother setting up
+ 	CLASSTYPE_TAGS explicitly, as the nested types will add
+ 	themselves.
+
+Tue Mar 19 15:48:43 1996  Bob Manson  <manson@beauty.cygnus.com>
+
+	* decl.c (shadow_tag): Remove old error check for usage of
+	an enum without a previous declaration.
+	(xref_tag): Add error message about usage of enums without a
+	previous declaration.
+
+Tue Mar 19 09:21:35 1996  Jason Merrill  <jason@yorick.cygnus.com>
+
+	* lex.c (do_identifier): Only do name consistency check if we're
+ 	parsing.
+
+	* pt.c (push_template_decl): Don't crash if we get a member defn
+	that doesn't match.
+
+	* decl.c (xref_tag_from_type): New function to do an xref without
+ 	always having to figure out code_type_node.
+	* cp-tree.h: Declare it.
+	* pt.c (instantiate_class_template): Use it for friend classes.
+  	(lookup_template_class): Use it.
+
+	* typeck2.c (build_functional_cast): Pull out a single parm before
+ 	passing it to build_c_cast.
+
+Tue Mar 19 09:07:15 1996  Bob Manson  <manson@beauty.cygnus.com>
+
+	* expr.c (do_case): Give an error message if a pointer is
+	given as a case value.
+
+Mon Mar 18 21:57:54 1996  Jason Merrill  <jason@yorick.cygnus.com>
+
+	* typeck.c (build_c_cast): Don't pull single TEMPLATE_DECL out of
+ 	an overload list.
+
+	* lex.c (cons_up_default_function): Really, now, interface hackery
+ 	does not apply to synthesized methods.
+
+Mon Mar 18 18:20:57 1996  Mike Stump  <mrs@cygnus.com>
+
+	* call.c (build_method_call): Ctors and dtors now have special names
+	with respect to lookups.
+	* class.c (add_method): Ditto.
+	(grow_method): Ditto.
+	(finish_struct_methods): Ditto.
+	(warn_hidden): Ditto.
+	(finish_struct_1): Ditto.
+	* cvt.c (convert_to_reference): Ditto.
+	(convert_to_aggr): Ditto.
+	(cp_convert): Ditto.
+	* decl2.c (check_classfn): Ditto.
+	* init.c (expand_member_init): Ditto.
+	(expand_default_init): Ditto.
+	(expand_aggr_init_1): Ditto.
+	(build_offset_ref): Ditto.
+	(build_new): Ditto.
+	(build_delete): Ditto.
+	* lex.c (do_inline_function_hair): Ditto.
+	* search.c (lookup_field_1): Ditto.
+	(lookup_fnfields_here): Ditto.
+	(lookup_field): Ditto.
+	(lookup_fnfields): Ditto.
+	(get_virtual_destructor): Ditto.
+	(dfs_debug_mark): Ditto.
+	(dfs_pushdecls): Ditto.
+	(dfs_compress_decls): Ditto.
+	* tree.c (layout_basetypes): Ditto.
+	* typeck.c (build_component_ref): Ditto.
+	(build_x_function_call): Ditto.
+	(build_modify_expr): Ditto.
+	(convert_for_initialization): Ditto.
+	(build_functional_cast): Ditto.
+	* cp-tree.h (CLASSTYPE_FIRST_CONVERSION): Ditto.
+	(CTOR_NAME): New.
+	(DTOR_NAME): New.
+	* decl.c (ctor_identifier): New.
+	(dtor_identifier): New.
+	(init_decl_processing): Set them.
+
+Mon Mar 18 18:00:51 1996  Mike Stump  <mrs@cygnus.com>
+
+	* typeck.c (build_component_ref): Don't get confused by fields whose
+	context has no type name, like pointer to member functions.
+
+Mon Mar 18 13:19:03 1996  Jason Merrill  <jason@yorick.cygnus.com>
+
+	* decl.c (grokdeclarator): Handle typedef without declarator.
+
+	* pt.c (tsubst): Handle SCOPE_REF in declarator.
+
+	* parse.y (bad_parm): Catch another case of missing `typename'.
+
+	* lex.c (yyprint): Handle TYPE_DECLs.
+
+	* decl.c (start_function): Don't try to be clever.
+
+	* lex.c: Lose compiler_error_with_decl.
+	* typeck2.c: Lose error_with_aggr_type.
+	(incomplete_type_error): Use cp_* instead of old functions.
+	(readonly_error): Ditto.
+	* typeck.c (convert_arguments): Ditto.
+	* search.c (lookup_nested_field): Ditto.
+	* method.c (make_thunk): Ditto.
+	* decl.c (grokparms): Ditto.
+	* cp-tree.h: Update.
+
+	* tree.c (min_tree_cons): Call copy_to_permanent for the purpose
+ 	and value.
+
+Mon Mar 18 11:25:52 1996  Bob Manson  <manson@beauty.cygnus.com>
+
+	* method.c (build_opfncall): When deleting a pointer to an
+	array, build a new pointer to the tree past any ARRAY_TYPE
+	nodes.
+
+Mon Mar 18 10:11:46 1996  Brendan Kehoe  <brendan@lisa.cygnus.com>
+
+	* decl.c (lookup_name_real): Initialize local var TYPE to NULL_TREE.
+
+Fri Mar 15 11:03:57 1996  Jason Merrill  <jason@yorick.cygnus.com>
+
+	* pt.c (instantiate_decl): Only call import_export_decl if at_eof
+ 	and ! DECL_INLINE.
+
+	* decl.c (finish_function): Don't set nested based on
+ 	hack_decl_function_context.
+	* parse.y (function_try_block): Check for nested function.
+	(pending_inlines): Ditto.
+
+	* decl2.c (build_expr_from_tree): If a unary op already has a
+ 	type, just return it.
+
+	* decl2.c (finish_prevtable_vardecl): Use ADJUST_VTABLE_LINKAGE.
+
+	* decl2.c (walk_vtables): vardecl_fn returns int; return 1 if it does.
+	(finish_file): Check the return value of walk_vtables.
+	(finish_prevtable_vardecl): Return int.
+	(finish_vtable_vardecl): Ditto.
+	(prune_vtable_vardecl): Ditto.
+	* lex.c (set_vardecl_interface_info): Ditto.
+	* cp-tree.h: Adjust return types.
+
+	* class.c (delete_duplicate_fields_1): Don't complain about
+ 	duplicate nested types if they're the same type.
+	(finish_struct): Remove check for duplicate.
+	* decl2.c (grokfield): Don't check for typedef of anonymous type.
+
+Thu Mar 14 10:00:19 1996  Jason Merrill  <jason@yorick.cygnus.com>
+
+	* cp-tree.h: Lose SIGNATURE_GROKKING_TYPEDEF.
+
+	* decl.c (grokdeclarator): Lose special handling of class-level
+ 	typedef.  Lose SIGNATURE_GROKKING_TYPEDEF.  Set
+ 	SIGNATURE_HAS_OPAQUE_TYPEDECLS later.
+
+	* cvt.c (convert_pointer_to_real): Retain cv-quals in conversion.
+
+	* pt.c (tsubst_copy): Strip cv-quals from destructor name types.
+
+	* search.c (compute_access): Fix handling of anonymous union
+ 	members.
+	* class.c (finish_struct_anon): Propagate TREE_{PRIVATE,PROTECTED}
+ 	from anonymous unions to their members.
+
+	* typeck.c (build_x_function_call): For static member functions,
+ 	hand off to build_member_call.
+
+Wed Mar 13 14:03:34 1996  Jason Merrill  <jason@yorick.cygnus.com>
+
+	* typeck.c (build_component_ref): Handle OFFSET_REFs.
+
+	* init.c (expand_vec_init): Fix init == 0 case.
+
+Tue Mar 12 14:36:02 1996  Jason Merrill  <jason@yorick.cygnus.com>
+
+	* init.c (build_new): Pedwarn about init and array new.
+	(expand_vec_init): Handle lists, use convert_for_initialization
+
+	* typeck.c (convert_for_initialization): Pass LOOKUP_NO_CONVERSION
+ 	when converting to an aggregate type.
+	* cvt.c (cp_convert): Pass it through.
+
+	* typeck.c (build_conditional_expr): Handle user-defined
+ 	conversions to slightly different types.
+
+	* decl.c (grokdeclarator): Force an array type in a parm to be
+ 	permanent.
+
+	* decl2.c (do_using_directive): Sorry.
+	(do_namespace_alias): Ditto.
+	* lex.c (real_yylex): Warn about using the `namespace' keyword.
+
+Sun Mar 10 22:26:09 1996  Jason Merrill  <jason@yorick.cygnus.com>
+
+	* parse.y (datadef): Move call to note_list_got_semicolon up.
+
 Fri Mar  8 11:47:26 1996  Mike Stump  <mrs@cygnus.com>
 
 	* tree.c (unsave_expr): Don't unsave, UNSAVE_EXPRs.
diff --git a/gcc/cp/call.c b/gcc/cp/call.c
index 570c02077e29..5f0560f39916 100644
--- a/gcc/cp/call.c
+++ b/gcc/cp/call.c
@@ -1745,11 +1745,15 @@ build_method_call (instance, name, parms, basetype_path, flags)
 	;
       /* call to a constructor... */
       else if (basetype_path)
-	basetype = BINFO_TYPE (basetype_path);
+	{
+	  basetype = BINFO_TYPE (basetype_path);
+	  if (name == DECL_NAME (TYPE_NAME (basetype)))
+	    name = ctor_identifier;
+	}
       else if (IDENTIFIER_HAS_TYPE_VALUE (name))
 	{
 	  basetype = IDENTIFIER_TYPE_VALUE (name);
-	  name = constructor_name (basetype);
+	  name = ctor_identifier;
 	}
       else
 	{
@@ -1758,7 +1762,7 @@ build_method_call (instance, name, parms, basetype_path, flags)
 	    {
 	      /* Canonicalize the typedef name.  */
 	      basetype = TREE_TYPE (typedef_name);
-	      name = TYPE_IDENTIFIER (basetype);
+	      name = ctor_identifier;
 	    }
 	  else
 	    {
@@ -2046,14 +2050,17 @@ build_method_call (instance, name, parms, basetype_path, flags)
 
   /* Look up function name in the structure type definition.  */
 
+  /* FIXME Axe most of this now?  */
   if ((IDENTIFIER_HAS_TYPE_VALUE (name)
        && ! IDENTIFIER_OPNAME_P (name)
        && IS_AGGR_TYPE (IDENTIFIER_TYPE_VALUE (name)))
-      || name == constructor_name (basetype))
+      || name == constructor_name (basetype)
+      || name == ctor_identifier)
     {
       tree tmp = NULL_TREE;
       if (IDENTIFIER_TYPE_VALUE (name) == basetype
-	  || name == constructor_name (basetype))
+	  || name == constructor_name (basetype)
+	  || name == ctor_identifier)
 	tmp = TYPE_BINFO (basetype);
       else
 	tmp = get_binfo (IDENTIFIER_TYPE_VALUE (name), basetype, 0);
@@ -2092,19 +2099,6 @@ build_method_call (instance, name, parms, basetype_path, flags)
   if (result == error_mark_node)
     return error_mark_node;
 
-
-#if 0
-  /* Now, go look for this method name.  We do not find destructors here.
-
-     Putting `void_list_node' on the end of the parmtypes
-     fakes out `build_decl_overload' into doing the right thing.  */
-  TREE_CHAIN (last) = void_list_node;
-  method_name = build_decl_overload (name, parmtypes,
-				     1 + (name == constructor_name (save_basetype)
-					  || name == constructor_name_full (save_basetype)));
-  TREE_CHAIN (last) = NULL_TREE;
-#endif
-
   for (pass = 0; pass < 2; pass++)
     {
       struct candidate *candidates;
@@ -2112,10 +2106,6 @@ build_method_call (instance, name, parms, basetype_path, flags)
       int len;
       unsigned best = 1;
 
-      /* This increments every time we go up the type hierarchy.
-	 The idea is to prefer a function of the derived class if possible. */
-      int b_or_d = 0;
-
       baselink = result;
 
       if (pass > 0)
@@ -2167,7 +2157,7 @@ build_method_call (instance, name, parms, basetype_path, flags)
 	    }
 	}
 
-      while (baselink)
+      if (baselink)
 	{
 	  /* We have a hit (of sorts). If the parameter list is
 	     "error_mark_node", or some variant thereof, it won't
@@ -2183,30 +2173,6 @@ build_method_call (instance, name, parms, basetype_path, flags)
 	    basetype_path = TREE_VALUE (basetype_path);
 	  basetype = BINFO_TYPE (basetype_path);
 
-#if 0
-	  /* Cast the instance variable if necessary.  */
-	  if (basetype != TYPE_MAIN_VARIANT
-	      (TREE_TYPE (TREE_TYPE (TREE_VALUE (parms)))))
-	    {
-	      if (basetype == save_basetype)
-		TREE_VALUE (parms) = instance_ptr;
-	      else
-		{
-		  tree type = build_pointer_type
-		    (build_type_variant (basetype, constp, volatilep));
-		  TREE_VALUE (parms) = convert_force (type, instance_ptr, 0);
-		}
-	    }
-
-	  /* FIXME: this is the wrong place to get an error.  Hopefully
-	     the access-control rewrite will make this change more cleanly.  */
-	  if (TREE_VALUE (parms) == error_mark_node)
-	    return error_mark_node;
-#endif
-
-	  if (DESTRUCTOR_NAME_P (DECL_ASSEMBLER_NAME (function)))
-	    function = DECL_CHAIN (function);
-
 	  for (; function; function = DECL_CHAIN (function))
 	    {
 #ifdef GATHER_STATISTICS
@@ -2263,14 +2229,8 @@ build_method_call (instance, name, parms, basetype_path, flags)
 		    }
 		}
 	    }
-	  /* Now we have run through one link's member functions.
-	     arrange to head-insert this link's links.  */
-	  baselink = next_baselink (baselink);
-	  b_or_d += 1;
-	  /* Don't grab functions from base classes.  lookup_fnfield will
-	     do the work to get us down into the right place.  */
-	  baselink = NULL_TREE;
 	}
+
       if (pass == 0)
 	{
 	  tree igv = lookup_name_nonclass (name);
diff --git a/gcc/cp/class.c b/gcc/cp/class.c
index 1628d65565b1..ffe0104656e0 100644
--- a/gcc/cp/class.c
+++ b/gcc/cp/class.c
@@ -932,8 +932,16 @@ add_method (type, fields, method)
       tree method_vec = make_node (TREE_VEC);
       if (TYPE_IDENTIFIER (type) == DECL_NAME (decl))
 	{
-	  TREE_VEC_ELT (method_vec, 0) = decl;
-	  TREE_VEC_LENGTH (method_vec) = 1;
+	  /* ??? Is it possible for there to have been enough room in the
+	     current chunk for the tree_vec structure but not a tree_vec
+	     plus a tree*?  Will this work in that case?  */
+	  obstack_free (current_obstack, method_vec);
+	  obstack_blank (current_obstack, sizeof (struct tree_vec) + sizeof (tree *));
+	  if (DESTRUCTOR_NAME_P (DECL_ASSEMBLER_NAME (decl)))
+	    TREE_VEC_ELT (method_vec, 1) = decl;
+	  else
+	    TREE_VEC_ELT (method_vec, 0) = decl;
+	  TREE_VEC_LENGTH (method_vec) = 2;
 	}
       else
 	{
@@ -941,9 +949,9 @@ add_method (type, fields, method)
 	     current chunk for the tree_vec structure but not a tree_vec
 	     plus a tree*?  Will this work in that case?  */
 	  obstack_free (current_obstack, method_vec);
-	  obstack_blank (current_obstack, sizeof (struct tree_vec) + sizeof (tree *));
-	  TREE_VEC_ELT (method_vec, 1) = decl;
-	  TREE_VEC_LENGTH (method_vec) = 2;
+	  obstack_blank (current_obstack, sizeof (struct tree_vec) + 2*sizeof (tree *));
+	  TREE_VEC_ELT (method_vec, 2) = decl;
+	  TREE_VEC_LENGTH (method_vec) = 3;
 	  obstack_finish (current_obstack);
 	}
       CLASSTYPE_METHOD_VEC (type) = method_vec;
@@ -957,11 +965,12 @@ add_method (type, fields, method)
          METHOD_VEC always has a slot for such entries.  */
       if (TYPE_IDENTIFIER (type) == DECL_NAME (decl))
 	{
-	  /* TREE_VEC_ELT (method_vec, 0) = decl; */
-	  if (decl != TREE_VEC_ELT (method_vec, 0))
+	  int index = !!DESTRUCTOR_NAME_P (DECL_ASSEMBLER_NAME (decl));
+	  /* TREE_VEC_ELT (method_vec, index) = decl; */
+	  if (decl != TREE_VEC_ELT (method_vec, index))
 	    {
-	      DECL_CHAIN (decl) = TREE_VEC_ELT (method_vec, 0);
-	      TREE_VEC_ELT (method_vec, 0) = decl;
+	      DECL_CHAIN (decl) = TREE_VEC_ELT (method_vec, index);
+	      TREE_VEC_ELT (method_vec, index) = decl;
 	    }
 	}
       else
@@ -1085,7 +1094,11 @@ delete_duplicate_fields_1 (field, fields)
 				x);
 		  else if (TREE_CODE (field) == TYPE_DECL
 			   && TREE_CODE (x) == TYPE_DECL)
-		    cp_error_at ("duplicate nested type `%D'", x);
+		    {
+		      if (TREE_TYPE (field) == TREE_TYPE (x))
+			continue;
+		      cp_error_at ("duplicate nested type `%D'", x);
+		    }
 		  else if (TREE_CODE (field) == TYPE_DECL
 			   || TREE_CODE (x) == TYPE_DECL)
 		    {
@@ -1756,42 +1769,41 @@ finish_struct_bits (t, max_has_virtual)
     }
 }
 
-/* Add FN to the method_vec growing on the class_obstack.  Used by
-   finish_struct_methods.  */
+/* Add FNDECL to the method_vec growing on the class_obstack.  Used by
+   finish_struct_methods.  Note, FNDECL cannot be a constructor or
+   destructor, those cases are handled by the caller.  */
 static void
-grow_method (fn, method_vec_ptr)
-     tree fn;
+grow_method (fndecl, method_vec_ptr)
+     tree fndecl;
      tree *method_vec_ptr;
 {
   tree method_vec = (tree)obstack_base (&class_obstack);
-  tree *testp = &TREE_VEC_ELT (method_vec, 0);
-  if (*testp == NULL_TREE)
-    testp++;
-  while (((HOST_WIDE_INT) testp
-	  < (HOST_WIDE_INT) obstack_next_free (&class_obstack))
-	 && DECL_NAME (*testp) != DECL_NAME (fn))
+
+  /* Start off past the constructors and destructor.  */
+  tree *testp = &TREE_VEC_ELT (method_vec, 2);
+
+  while (testp < (tree *) obstack_next_free (&class_obstack)
+	 && (*testp == NULL_TREE || DECL_NAME (*testp) != DECL_NAME (fndecl)))
     testp++;
-  if ((HOST_WIDE_INT) testp
-      < (HOST_WIDE_INT) obstack_next_free (&class_obstack))
+
+  if (testp < (tree *) obstack_next_free (&class_obstack))
     {
       tree x, prev_x;
 
       for (x = *testp; x; x = DECL_CHAIN (x))
 	{
-	  if (DECL_NAME (fn) == ansi_opname[(int) DELETE_EXPR]
-	      || DECL_NAME (fn) == ansi_opname[(int) VEC_DELETE_EXPR])
+	  if (DECL_NAME (fndecl) == ansi_opname[(int) DELETE_EXPR]
+	      || DECL_NAME (fndecl) == ansi_opname[(int) VEC_DELETE_EXPR])
 	    {
 	      /* ANSI C++ June 5 1992 WP 12.5.5.1 */
-	      cp_error_at ("`%D' overloaded", fn);
+	      cp_error_at ("`%D' overloaded", fndecl);
 	      cp_error_at ("previous declaration as `%D' here", x);
 	    }
-	  if (DECL_ASSEMBLER_NAME (fn)==DECL_ASSEMBLER_NAME (x))
+	  if (DECL_ASSEMBLER_NAME (fndecl) == DECL_ASSEMBLER_NAME (x))
 	    {
-	      /* We complain about multiple destructors on sight,
-		 so we do not repeat the warning here.  Friend-friend
-		 ambiguities are warned about outside this loop.  */
-	      if (!DESTRUCTOR_NAME_P (DECL_ASSEMBLER_NAME (fn)))
-		cp_error_at ("ambiguous method `%#D' in structure", fn);
+	      /* Friend-friend ambiguities are warned about outside
+		 this loop.  */
+	      cp_error_at ("ambiguous method `%#D' in structure", fndecl);
 	      break;
 	    }
 	  prev_x = x;
@@ -1799,14 +1811,14 @@ grow_method (fn, method_vec_ptr)
       if (x == 0)
 	{
 	  if (*testp)
-	    DECL_CHAIN (prev_x) = fn;
+	    DECL_CHAIN (prev_x) = fndecl;
 	  else
-	    *testp = fn;
+	    *testp = fndecl;
 	}
     }
   else
     {
-      obstack_ptr_grow (&class_obstack, fn);
+      obstack_ptr_grow (&class_obstack, fndecl);
       *method_vec_ptr = (tree)obstack_base (&class_obstack);
     }
 }
@@ -1842,27 +1854,27 @@ finish_struct_methods (t, fn_fields, nonprivate_method)
 {
   tree method_vec;
   tree save_fn_fields = fn_fields;
-  tree name = constructor_name (t);
+  tree ctor_name = constructor_name (t);
   int i, n_baseclasses = CLASSTYPE_N_BASECLASSES (t);
 
   /* Now prepare to gather fn_fields into vector.  */
   struct obstack *ambient_obstack = current_obstack;
   current_obstack = &class_obstack;
-  method_vec = make_node (TREE_VEC);
-  /* Room has been saved for constructors and destructors.  */
+  method_vec = make_tree_vec (2);
   current_obstack = ambient_obstack;
+
   /* Now make this a live vector.  */
   obstack_free (&class_obstack, method_vec);
-  obstack_blank (&class_obstack, sizeof (struct tree_vec));
 
-  /* First fill in entry 0 with the constructors, and the next few with
-     type conversion operators (if any).  */
+  /* Save room for constructors and destructors.  */
+  obstack_blank (&class_obstack, sizeof (struct tree_vec) + sizeof (struct tree *));
+
+  /* First fill in entry 0 with the constructors, entry 1 with destructors,
+     and the next few with type conversion operators (if any).  */
 
   for (; fn_fields; fn_fields = TREE_CHAIN (fn_fields))
     {
       tree fn_name = DECL_NAME (fn_fields);
-      if (fn_name == NULL_TREE)
-	fn_name = name;
 
       /* Clear out this flag.
 
@@ -1873,7 +1885,7 @@ finish_struct_methods (t, fn_fields, nonprivate_method)
       /* Note here that a copy ctor is private, so we don't dare generate
  	 a default copy constructor for a class that has a member
  	 of this type without making sure they have access to it.  */
-      if (fn_name == name)
+      if (fn_name == ctor_name)
  	{
  	  tree parmtypes = FUNCTION_ARG_CHAIN (fn_fields);
  	  tree parmtype = parmtypes ? TREE_VALUE (parmtypes) : void_type_node;
@@ -1891,9 +1903,18 @@ finish_struct_methods (t, fn_fields, nonprivate_method)
  		    TYPE_HAS_NONPUBLIC_CTOR (t) = 2;
  		}
  	    }
-	  /* Constructors are handled easily in search routines.  */
-	  DECL_CHAIN (fn_fields) = TREE_VEC_ELT (method_vec, 0);
-	  TREE_VEC_ELT (method_vec, 0) = fn_fields;
+	  if (DESTRUCTOR_NAME_P (DECL_ASSEMBLER_NAME (fn_fields)))
+	    {	    
+	      /* Destructors go in slot 1.  */
+	      DECL_CHAIN (fn_fields) = TREE_VEC_ELT (method_vec, 1);
+	      TREE_VEC_ELT (method_vec, 1) = fn_fields;
+	    }
+	  else
+	    {
+	      /* Constructors go in slot 0.  */
+	      DECL_CHAIN (fn_fields) = TREE_VEC_ELT (method_vec, 0);
+	      TREE_VEC_ELT (method_vec, 0) = fn_fields;
+	    }
  	}
       else if (IDENTIFIER_TYPENAME_P (fn_name))
 	{
@@ -1914,10 +1935,8 @@ finish_struct_methods (t, fn_fields, nonprivate_method)
   for (; fn_fields; fn_fields = TREE_CHAIN (fn_fields))
     {
       tree fn_name = DECL_NAME (fn_fields);
-      if (fn_name == NULL_TREE)
-	fn_name = name;
 
-      if (fn_name == name || IDENTIFIER_TYPENAME_P (fn_name))
+      if (fn_name == ctor_name || IDENTIFIER_TYPENAME_P (fn_name))
 	continue;
 
       if (fn_name == ansi_opname[(int) MODIFY_EXPR])
@@ -1957,53 +1976,35 @@ finish_struct_methods (t, fn_fields, nonprivate_method)
 	cp_warning ("all member functions in class `%T' are private", t);
     }
 
-  /* If there are constructors (and destructors), they are at the
-     front.  Place destructors at very front.  Also warn if all
-     constructors and/or destructors are private (in which case this
-     class is effectively unusable.  */
+  /* Warn if all destructors are private (in which case this class is
+     effectively unusable.  */
   if (TYPE_HAS_DESTRUCTOR (t))
     {
-      tree dtor, prev;
-
-      for (dtor = TREE_VEC_ELT (method_vec, 0);
-	   dtor;
-	   prev = dtor, dtor = DECL_CHAIN (dtor))
-	{
-	  if (DESTRUCTOR_NAME_P (DECL_ASSEMBLER_NAME (dtor)))
-	    {
-	      if (TREE_PRIVATE (dtor)
-		  && CLASSTYPE_FRIEND_CLASSES (t) == NULL_TREE
-		  && DECL_FRIENDLIST (TYPE_NAME (t)) == NULL_TREE
-		  && warn_ctor_dtor_privacy)
-		cp_warning ("`%#T' only defines a private destructor and has no friends",
-			    t);
-	      break;
-	    }
-	}
+      tree dtor = TREE_VEC_ELT (method_vec, 1);
 
       /* Wild parse errors can cause this to happen.  */
       if (dtor == NULL_TREE)
 	TYPE_HAS_DESTRUCTOR (t) = 0;
-      else if (dtor != TREE_VEC_ELT (method_vec, 0))
-	{
-	  DECL_CHAIN (prev) = DECL_CHAIN (dtor);
-	  DECL_CHAIN (dtor) = TREE_VEC_ELT (method_vec, 0);
-	  TREE_VEC_ELT (method_vec, 0) = dtor;
-	}
+      else if (TREE_PRIVATE (dtor)
+	       && CLASSTYPE_FRIEND_CLASSES (t) == NULL_TREE
+	       && DECL_FRIENDLIST (TYPE_NAME (t)) == NULL_TREE
+	       && warn_ctor_dtor_privacy)
+	cp_warning ("`%#T' only defines a private destructor and has no friends",
+		    t);
     }
 
   /* Now for each member function (except for constructors and
      destructors), compute where member functions of the same
      name reside in base classes.  */
   if (n_baseclasses != 0
-      && TREE_VEC_LENGTH (method_vec) > 1)
+      && TREE_VEC_LENGTH (method_vec) > 2)
     {
       int len = TREE_VEC_LENGTH (method_vec);
       tree baselink_vec = make_tree_vec (len);
       int any_links = 0;
       tree baselink_binfo = build_tree_list (NULL_TREE, TYPE_BINFO (t));
 
-      for (i = 1; i < len; i++)
+      for (i = 2; i < len; i++)
 	{
 	  TREE_VEC_ELT (baselink_vec, i)
 	    = get_baselinks (baselink_binfo, t, DECL_NAME (TREE_VEC_ELT (method_vec, i)));
@@ -2016,44 +2017,6 @@ finish_struct_methods (t, fn_fields, nonprivate_method)
 	obstack_free (current_obstack, baselink_vec);
     }
 
-#if 0
-  /* Now add the methods to the TYPE_METHODS of T, arranged in a chain.  */
-  {
-    tree x, last_x = NULL_TREE;
-    int limit = TREE_VEC_LENGTH (method_vec);
-
-    for (i = 1; i < limit; i++)
-      {
-	for (x = TREE_VEC_ELT (method_vec, i); x; x = DECL_CHAIN (x))
-	  {
-	    if (last_x != NULL_TREE)
-	      TREE_CHAIN (last_x) = x;
-	    last_x = x;
-	  }
-      }
-
-    /* Put ctors and dtors at the front of the list.  */
-    x = TREE_VEC_ELT (method_vec, 0);
-    if (x)
-      {
-	while (DECL_CHAIN (x))
-	  {
-	    /* Let's avoid being circular about this.  */
-	    if (x == DECL_CHAIN (x))
-	      break;
-	    TREE_CHAIN (x) = DECL_CHAIN (x);
-	    x = DECL_CHAIN (x);
-	  }
-	if (TREE_VEC_LENGTH (method_vec) > 1)
-	  TREE_CHAIN (x) = TREE_VEC_ELT (method_vec, 1);
-	else
-	  TREE_CHAIN (x) = NULL_TREE;
-      }
-  }
-
-  TYPE_METHODS (t) = method_vec;
-#endif
-
   return method_vec;
 }
 
@@ -2077,17 +2040,17 @@ duplicate_tag_error (t)
    * This used to be in finish_struct, but it turns out that the
    * TREE_CHAIN is used by dbxout_type_methods and perhaps some other things...
    */
-  if (CLASSTYPE_METHOD_VEC(t)) 
+  if (CLASSTYPE_METHOD_VEC (t)) 
     {
-      tree tv = CLASSTYPE_METHOD_VEC(t);
-      int i, len  = TREE_VEC_LENGTH (tv);
+      tree method_vec = CLASSTYPE_METHOD_VEC (t);
+      int i, len  = TREE_VEC_LENGTH (method_vec);
       for (i = 0; i < len; i++)
 	{
-	  tree unchain = TREE_VEC_ELT (tv, i);
+	  tree unchain = TREE_VEC_ELT (method_vec, i);
 	  while (unchain != NULL_TREE) 
 	    {
 	      TREE_CHAIN (unchain) = NULL_TREE;
-	      unchain = DECL_CHAIN(unchain);
+	      unchain = DECL_CHAIN (unchain);
 	    }
 	}
     }
@@ -2829,7 +2792,8 @@ check_for_override (decl, ctype)
     }
 }
 
-/* Warn about hidden virtual functions that are not overridden in t.  */
+/* Warn about hidden virtual functions that are not overridden in t.
+   We know that constructors and destructors don't apply.  */
 void
 warn_hidden (t)
      tree t;
@@ -2839,7 +2803,7 @@ warn_hidden (t)
   int i;
 
   /* We go through each separately named virtual function.  */
-  for (i = 1; i < n_methods; ++i)
+  for (i = 2; i < n_methods; ++i)
     {
       tree fndecl = TREE_VEC_ELT (method_vec, i);
 
@@ -2927,6 +2891,9 @@ finish_struct_anon (t)
 	      else if (TREE_PROTECTED (*uelt))
 		cp_pedwarn_at ("protected member `%#D' in anonymous union",
 			       *uelt);
+
+	      TREE_PRIVATE (*uelt) = TREE_PRIVATE (field);
+	      TREE_PROTECTED (*uelt) = TREE_PROTECTED (field);
 	    }
 	}
     }
@@ -3692,8 +3659,8 @@ finish_struct_1 (t, attributes, warn_anon)
 	tree fdecl = TREE_VALUE (access_decls);
 	tree flist = NULL_TREE;
 	tree name;
-	tree access = TREE_PURPOSE(access_decls);
-	int i = TREE_VEC_ELT (method_vec, 0) ? 0 : 1;
+	tree access = TREE_PURPOSE (access_decls);
+	int i = 2;
 	tree tmp;
 
 	if (TREE_CODE (fdecl) == TREE_LIST)
@@ -3811,9 +3778,11 @@ finish_struct_1 (t, attributes, warn_anon)
       for (x = fields; x; x = TREE_CHAIN (x))
 	{
 	  tree name = DECL_NAME (x);
-	  int i = /*TREE_VEC_ELT (method_vec, 0) ? 0 : */ 1;
+	  int i = 2;
+
 	  if (TREE_CODE (x) == TYPE_DECL && DECL_ARTIFICIAL (x))
 	    continue;
+
 	  for (; i < n_methods; ++i)
 	    if (DECL_NAME (TREE_VEC_ELT (method_vec, i)) == name)
 	      {
@@ -4368,14 +4337,6 @@ finish_struct (t, list_of_fieldlists, attributes, warn_anon)
 	{
 	  tree tag = TYPE_NAME (TREE_VALUE (x));
 
-	  /* Check to see if it is already there.  This will be the case if
-	     was do enum { red; } color; */
-	  if (chain_member (tag, fields))
-	      {
-		x = TREE_CHAIN (x);
-		continue;
-	      }
-
 #ifdef DWARF_DEBUGGING_INFO
 	  if (write_symbols == DWARF_DEBUG)
 	    {
diff --git a/gcc/cp/cp-tree.h b/gcc/cp/cp-tree.h
index 120948d6f660..7d9f12cf96e4 100644
--- a/gcc/cp/cp-tree.h
+++ b/gcc/cp/cp-tree.h
@@ -427,9 +427,9 @@ struct lang_type
       unsigned marked4 : 1;
       unsigned marked5 : 1;
       unsigned marked6 : 1;
+      unsigned debug_requested : 1;
 
       unsigned use_template : 2;
-      unsigned debug_requested : 1;
       unsigned has_method_call_overloaded : 1;
       unsigned private_attr : 1;
       unsigned got_semicolon : 1;
@@ -439,14 +439,13 @@ struct lang_type
 
       unsigned is_signature_reference : 1;
       unsigned has_default_implementation : 1;
-      unsigned grokking_typedef : 1;
       unsigned has_opaque_typedecls : 1;
       unsigned sigtable_has_been_generated : 1;
       unsigned was_anonymous : 1;
       unsigned has_real_assignment : 1;
       unsigned has_real_assign_ref : 1;
-
       unsigned has_const_init_ref : 1;
+
       unsigned has_complex_init_ref : 1;
       unsigned has_complex_assign_ref : 1;
       unsigned has_abstract_assign_ref : 1;
@@ -455,7 +454,7 @@ struct lang_type
       /* The MIPS compiler gets it wrong if this struct also
 	 does not fill out to a multiple of 4 bytes.  Add a
 	 member `dummy' with new bits if you go over the edge.  */
-      unsigned dummy : 19;
+      unsigned dummy : 20;
 
       unsigned n_vancestors : 16;
     } type_flags;
@@ -475,7 +474,7 @@ struct lang_type
   union tree_node *tags;
   char *memoized_table_entry;
 
-  char *search_slot;
+  union tree_node *search_slot;
 
 #ifdef ONLY_INT_FIELDS
   unsigned int mode : 8;
@@ -604,9 +603,6 @@ struct lang_type
 /* Nonzero means that this signature type has a default implementation.  */
 # define HAS_DEFAULT_IMPLEMENTATION(NODE) (TYPE_LANG_SPECIFIC(NODE)->type_flags.has_default_implementation)
 
-/* Nonzero means that grokdeclarator works on a signature-local typedef.  */
-#define SIGNATURE_GROKKING_TYPEDEF(NODE) (TYPE_LANG_SPECIFIC(NODE)->type_flags.grokking_typedef)
-
 /* Nonzero means that this signature contains opaque type declarations.  */
 #define SIGNATURE_HAS_OPAQUE_TYPEDECLS(NODE) (TYPE_LANG_SPECIFIC(NODE)->type_flags.has_opaque_typedecls)
 
@@ -664,8 +660,8 @@ struct lang_type
    searched with TREE_CHAIN), or the first non-constructor function if
    there are no type conversion operators.  */
 #define CLASSTYPE_FIRST_CONVERSION(NODE) \
-  TREE_VEC_LENGTH (CLASSTYPE_METHOD_VEC (NODE)) > 1 \
-    ? TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (NODE), 1) \
+  TREE_VEC_LENGTH (CLASSTYPE_METHOD_VEC (NODE)) > 2 \
+    ? TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (NODE), 2) \
     : NULL_TREE;
 
 /* Pointer from any member function to the head of the list of
@@ -1491,6 +1487,7 @@ extern tree __ptmf_desc_type_node, __ptmd_desc_type_node;
 extern tree type_info_type_node;
 extern tree class_star_type_node;
 extern tree this_identifier;
+extern tree ctor_identifier, dtor_identifier;
 extern tree pfn_identifier;
 extern tree index_identifier;
 extern tree delta_identifier;
@@ -1675,6 +1672,8 @@ extern int current_function_parms_stored;
 #define THIS_NAME "this"
 #define DESTRUCTOR_NAME_FORMAT "~%s"
 #define FILE_FUNCTION_PREFIX_LEN 9
+#define CTOR_NAME "__ct"
+#define DTOR_NAME "__dt"
 
 #define IN_CHARGE_NAME "__in_chrg"
 
@@ -2047,6 +2046,7 @@ extern tree build_ptrmemfunc_type		PROTO((tree));
 /* the grokdeclarator prototype is in decl.h */
 extern int parmlist_is_exprlist			PROTO((tree));
 extern tree xref_tag				PROTO((tree, tree, tree, int));
+extern tree xref_tag_from_type			PROTO((tree, tree, int));
 extern void xref_basetypes			PROTO((tree, tree, tree, tree));
 extern tree start_enum				PROTO((tree));
 extern tree finish_enum				PROTO((tree, tree));
@@ -2099,7 +2099,7 @@ extern void finish_builtin_type			PROTO((tree, char *, tree *, int, tree));
 extern tree coerce_new_type			PROTO((tree));
 extern tree coerce_delete_type			PROTO((tree));
 extern void import_export_vtable		PROTO((tree, tree, int));
-extern void walk_vtables			PROTO((void (*)(), void (*)()));
+extern int walk_vtables				PROTO((void (*)(), int (*)()));
 extern void walk_sigtables			PROTO((void (*)(), void (*)()));
 extern void finish_file				PROTO((void));
 extern void warn_if_unknown_interface		PROTO((tree));
@@ -2203,7 +2203,7 @@ extern void reinit_parse_for_function		PROTO((void));
 extern int *init_parse				PROTO((void));
 extern void print_parse_statistics		PROTO((void));
 extern void extract_interface_info		PROTO((void));
-extern void set_vardecl_interface_info		PROTO((tree, tree));
+extern int set_vardecl_interface_info		PROTO((tree, tree));
 extern void do_pending_inlines			PROTO((void));
 extern void process_next_inline			PROTO((tree));
 /* skip restore_pending_input */
@@ -2231,7 +2231,6 @@ extern tree make_lang_type			PROTO((enum tree_code));
 extern void copy_decl_lang_specific		PROTO((tree));
 extern void dump_time_statistics		PROTO((void));
 /* extern void compiler_error			PROTO((char *, HOST_WIDE_INT, HOST_WIDE_INT)); */
-extern void compiler_error_with_decl		PROTO((tree, char *));
 extern void yyerror				PROTO((char *));
 
 /* in errfn.c */
@@ -2472,7 +2471,6 @@ extern tree build_ptrmemfunc			PROTO((tree, tree, int));
 /* in typeck2.c */
 extern tree error_not_base_type			PROTO((tree, tree));
 extern tree binfo_or_else			PROTO((tree, tree));
-extern void error_with_aggr_type		(); /* PROTO((tree, char *, HOST_WIDE_INT)); */
 extern void readonly_error			PROTO((tree, char *, int));
 extern void abstract_virtuals_error		PROTO((tree, tree));
 extern void signature_error			PROTO((tree, tree));
diff --git a/gcc/cp/cvt.c b/gcc/cp/cvt.c
index e6a047a988f4..f9f3dfc8e3b4 100644
--- a/gcc/cp/cvt.c
+++ b/gcc/cp/cvt.c
@@ -201,6 +201,14 @@ cp_convert_to_pointer (type, expr)
   if (IS_AGGR_TYPE (intype))
     {
       tree rval;
+
+      if (TYPE_SIZE (complete_type (intype)) == NULL_TREE)
+	{
+	  cp_error ("can't convert from incomplete type `%T' to `%T'",
+		    intype, type);
+	  return error_mark_node;
+	}
+
       rval = build_type_conversion (CONVERT_EXPR, type, expr, 1);
       if (rval)
 	{
@@ -774,7 +782,7 @@ convert_to_reference (reftype, expr, convtype, flags, decl)
       if (TYPE_HAS_CONSTRUCTOR (type)
 	  && ! CLASSTYPE_ABSTRACT_VIRTUALS (type)
 	  && (rval = build_method_call
-	      (NULL_TREE, constructor_name_full (type),
+	      (NULL_TREE, ctor_identifier,
 	       build_tree_list (NULL_TREE, expr), TYPE_BINFO (type),
 	       LOOKUP_NO_CONVERSION|LOOKUP_SPECULATIVELY
 	       | LOOKUP_ONLYCONVERTING)))
@@ -785,7 +793,7 @@ convert_to_reference (reftype, expr, convtype, flags, decl)
 	    {
 	      extern tree static_aggregates;
 	      tree t = get_temp_name (type, toplevel_bindings_p ());
-	      init = build_method_call (t, constructor_name_full (type),
+	      init = build_method_call (t, ctor_identifier,
 					build_tree_list (NULL_TREE, expr),
 					TYPE_BINFO (type),
 					LOOKUP_NORMAL|LOOKUP_NO_CONVERSION
@@ -800,7 +808,7 @@ convert_to_reference (reftype, expr, convtype, flags, decl)
 	    }
 	  else
 	    {
-	      init = build_method_call (NULL_TREE, constructor_name_full (type),
+	      init = build_method_call (NULL_TREE, ctor_identifier,
 					build_tree_list (NULL_TREE, expr),
 					TYPE_BINFO (type),
 					LOOKUP_NORMAL|LOOKUP_NO_CONVERSION
@@ -919,47 +927,9 @@ convert_to_aggr (type, expr, msgp, protect)
   parmlist = tree_cons (NULL_TREE, integer_zero_node, parmlist);
   parmtypes = tree_cons (NULL_TREE, build_pointer_type (basetype), parmtypes);
 
-#if 0
-  method_name = build_decl_overload (name, parmtypes, 1);
-
-  /* constructors are up front.  */
-  fndecl = TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (basetype), 0);
-  if (TYPE_HAS_DESTRUCTOR (basetype))
-    fndecl = DECL_CHAIN (fndecl);
-
-  while (fndecl)
-    {
-      if (DECL_ASSEMBLER_NAME (fndecl) == method_name)
-	{
-	  function = fndecl;
-	  if (protect)
-	    {
-	      if (TREE_PRIVATE (fndecl))
-		{
-		  can_be_private =
-		    (basetype == current_class_type
-		     || is_friend (basetype, current_function_decl)
-		     || purpose_member (basetype, DECL_ACCESS (fndecl)));
-		  if (! can_be_private)
-		    goto found;
-		}
-	      else if (TREE_PROTECTED (fndecl))
-		{
-		  if (! can_be_protected)
-		    goto found;
-		}
-	    }
-	  goto found_and_ok;
-	}
-      fndecl = DECL_CHAIN (fndecl);
-    }
-#endif
-
   /* No exact conversion was found.  See if an approximate
      one will do.  */
   fndecl = TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (basetype), 0);
-  if (TYPE_HAS_DESTRUCTOR (basetype))
-    fndecl = DECL_CHAIN (fndecl);
 
   {
     int saw_private = 0;
@@ -1119,7 +1089,9 @@ convert_pointer_to_real (binfo, expr)
       binfo = NULL_TREE;
     }
 
-  ptr_type = build_pointer_type (type);
+  ptr_type = cp_build_type_variant (type, TYPE_READONLY (TREE_TYPE (intype)),
+				    TYPE_VOLATILE (TREE_TYPE (intype)));
+  ptr_type = build_pointer_type (ptr_type);
   if (ptr_type == TYPE_MAIN_VARIANT (intype))
     return expr;
 
@@ -1338,11 +1310,12 @@ cp_convert (type, expr, convtype, flags)
 	}
 
       if (TYPE_HAS_CONSTRUCTOR (complete_type (type)))
-	ctor = build_method_call (NULL_TREE, constructor_name_full (type),
+	ctor = build_method_call (NULL_TREE, ctor_identifier,
 				  build_tree_list (NULL_TREE, e),
 				  TYPE_BINFO (type),
 				  (flags & LOOKUP_NORMAL) | LOOKUP_SPECULATIVELY
-				  | (convtype&CONV_NONCONVERTING ? 0 : LOOKUP_ONLYCONVERTING)
+				  | (convtype & CONV_NONCONVERTING ? 0 : LOOKUP_ONLYCONVERTING)
+				  | (flags & LOOKUP_NO_CONVERSION)
 				  | (conversion ? LOOKUP_NO_CONVERSION : 0));
 
       if (ctor == error_mark_node)
diff --git a/gcc/cp/decl.c b/gcc/cp/decl.c
index eb7e17e98838..9855baca0056 100644
--- a/gcc/cp/decl.c
+++ b/gcc/cp/decl.c
@@ -294,6 +294,7 @@ tree base_init_expr;
    Identifiers for `this' in member functions and the auto-delete
    parameter for destructors.  */
 tree this_identifier, in_charge_identifier;
+tree ctor_identifier, dtor_identifier;
 /* Used in pointer to member functions, in vtables, and in sigtables. */
 tree pfn_identifier, index_identifier, delta_identifier, delta2_identifier;
 tree pfn_or_delta2_identifier, tag_identifier;
@@ -1461,11 +1462,11 @@ print_binding_level (lvl)
       /* We can probably fit 3 names to a line?  */
       for (t = lvl->names; t; t = TREE_CHAIN (t))
 	{
-	  if (no_print_functions && (TREE_CODE(t) == FUNCTION_DECL)) 
+	  if (no_print_functions && (TREE_CODE (t) == FUNCTION_DECL)) 
 	    continue;
 	  if (no_print_builtins
-	      && (TREE_CODE(t) == TYPE_DECL)
-	      && (!strcmp(DECL_SOURCE_FILE(t),"<built-in>")))
+	      && (TREE_CODE (t) == TYPE_DECL)
+	      && (!strcmp (DECL_SOURCE_FILE (t),"<built-in>")))
 	    continue;
 
 	  /* Function decls tend to have longer names.  */
@@ -4298,16 +4299,25 @@ lookup_namespace_name (namespace, name)
      tree namespace, name;
 {
   struct binding_level *b = (struct binding_level *)NAMESPACE_LEVEL (namespace);
-  tree x;
+  tree x = NULL_TREE;
 
-  for (x = NULL_TREE; b && !x; b = b->level_chain)
+#if 1
+  /* This searches just one level.  */
+  if (b)
     {
       for (x = b->names; x; x = TREE_CHAIN (x))
 	if (DECL_NAME (x) == name || DECL_ASSEMBLER_NAME (x) == name)
 	  break;
-      /* Must find directly in the namespace.  */
-      break;
     }
+#else
+  /* This searches all levels.  */
+  for (; b && !x; b = b->level_chain)
+    {
+      for (x = b->names; x; x = TREE_CHAIN (x))
+	if (DECL_NAME (x) == name || DECL_ASSEMBLER_NAME (x) == name)
+	  break;
+    }
+#endif
   return x;
 }
 
@@ -4370,7 +4380,7 @@ lookup_name_real (name, prefer_type, nonclass)
   if (prefer_type == -2)
     {
       extern int looking_for_typename;
-      tree type;
+      tree type = NULL_TREE;
 
       yylex = 1;
       prefer_type = looking_for_typename;
@@ -4773,6 +4783,8 @@ init_decl_processing ()
 
   this_identifier = get_identifier (THIS_NAME);
   in_charge_identifier = get_identifier (IN_CHARGE_NAME);
+  ctor_identifier = get_identifier (CTOR_NAME);
+  dtor_identifier = get_identifier (DTOR_NAME);
   pfn_identifier = get_identifier (VTABLE_PFN_NAME);
   index_identifier = get_identifier (VTABLE_INDEX_NAME);
   delta_identifier = get_identifier (VTABLE_DELTA_NAME);
@@ -5525,7 +5537,7 @@ init_type_desc()
   tdecl = lookup_name (get_identifier ("type_info"), 0);
   if (tdecl == NULL_TREE)
     return 0;
-  __t_desc_type_node = TREE_TYPE(tdecl);
+  __t_desc_type_node = TREE_TYPE (tdecl);
 #if 0
   __tp_desc_type_node = build_pointer_type (__t_desc_type_node);
 #endif
@@ -5651,10 +5663,7 @@ shadow_tag (declspecs)
 	{
 	  my_friendly_assert (TYPE_NAME (value) != NULL_TREE, 261);
 
-	  if (code == ENUMERAL_TYPE && TYPE_SIZE (value) == 0)
-	    cp_error ("forward declaration of `%#T'", value);
-
-	  else if (IS_AGGR_TYPE (value) && CLASSTYPE_USE_TEMPLATE (value))
+	  if (IS_AGGR_TYPE (value) && CLASSTYPE_USE_TEMPLATE (value))
 	    {
 	      if (CLASSTYPE_IMPLICIT_INSTANTIATION (value)
 		  && TYPE_SIZE (value) == NULL_TREE)
@@ -7916,8 +7925,7 @@ grokdeclarator (declarator, declspecs, decl_context, initialized, raises, attrli
 	type = ctor_return_type;
       else if (current_class_type
 	       && IS_SIGNATURE (current_class_type)
-	       && (RIDBIT_SETP (RID_TYPEDEF, specbits)
-		   || SIGNATURE_GROKKING_TYPEDEF (current_class_type))
+	       && RIDBIT_SETP (RID_TYPEDEF, specbits)
 	       && (decl_context == FIELD || decl_context == NORMAL))
 	{
 	  explicit_int = 0;
@@ -8147,8 +8155,7 @@ grokdeclarator (declarator, declspecs, decl_context, initialized, raises, attrli
      is used in a signature member function declaration.  */
   if (decl_context == FIELD
       && IS_SIGNATURE (current_class_type)
-      && RIDBIT_NOTSETP(RID_TYPEDEF, specbits)
-      && !SIGNATURE_GROKKING_TYPEDEF (current_class_type))
+      && RIDBIT_NOTSETP (RID_TYPEDEF, specbits))
     {
       if (constp)
 	{
@@ -8192,82 +8199,10 @@ grokdeclarator (declarator, declspecs, decl_context, initialized, raises, attrli
 	  && (RIDBIT_SETP (RID_REGISTER, specbits)
 	      || RIDBIT_SETP (RID_AUTO, specbits)))
 	;
+      else if (RIDBIT_SETP (RID_TYPEDEF, specbits))
+	;
       else if (decl_context == FIELD
-	       && RIDBIT_SETP (RID_TYPEDEF, specbits))
-	{
-	  /* Processing a typedef declaration nested within a class type
-	     definition.  */
-	  register tree scanner;
-	  register tree previous_declspec;
-  	  tree loc_typedecl;
-  
-	  if (initialized)
-	    error ("typedef declaration includes an initializer");
-  
-	  /* To process a class-local typedef declaration, we descend down
-	     the chain of declspecs looking for the `typedef' spec.  When
-	     we find it, we replace it with `static', and then recursively
-	     call `grokdeclarator' with the original declarator and with
-	     the newly adjusted declspecs.  This call should return a
-	     FIELD_DECL node with the TREE_TYPE (and other parts) set
-	     appropriately.  We can then just change the TREE_CODE on that
-	     from FIELD_DECL to TYPE_DECL and we're done.  */
-
-	  for (previous_declspec = NULL_TREE, scanner = declspecs;
-	       scanner;
-	       previous_declspec = scanner, scanner = TREE_CHAIN (scanner))
-  	    {
-	      if (TREE_VALUE (scanner) == ridpointers[(int) RID_TYPEDEF])
-		break;
-  	    }
-
-	  if (previous_declspec)
-	    TREE_CHAIN (previous_declspec) = TREE_CHAIN (scanner);
-	  else
-	    declspecs = TREE_CHAIN (scanner);
-
-	  declspecs = tree_cons (NULL_TREE, ridpointers[(int) RID_STATIC],
-				 declspecs);
-
-	  /* In the recursive call to grokdeclarator we need to know
-	     whether we are working on a signature-local typedef.  */
-	  if (IS_SIGNATURE (current_class_type))
-	    SIGNATURE_GROKKING_TYPEDEF (current_class_type) = 1;
-  
-	  loc_typedecl =
-	    grokdeclarator (declarator, declspecs, FIELD, 0, NULL_TREE, NULL_TREE);
-
-	  if (previous_declspec)
-	    TREE_CHAIN (previous_declspec) = scanner;
-  
-	  if (loc_typedecl != error_mark_node)
-  	    {
-	      register int i = sizeof (struct lang_decl_flags) / sizeof (int);
-	      register int *pi;
-  
-	      TREE_SET_CODE (loc_typedecl, TYPE_DECL);
-	      /* This is the same field as DECL_ARGUMENTS, which is set for
-		 function typedefs by the above grokdeclarator.  */
-	      DECL_NESTED_TYPENAME (loc_typedecl) = 0;
-  
-	      pi = (int *) permalloc (sizeof (struct lang_decl_flags));
-	      while (i > 0)
-	        pi[--i] = 0;
-	      DECL_LANG_SPECIFIC (loc_typedecl) = (struct lang_decl *) pi;
-	    }
-  
-	  if (IS_SIGNATURE (current_class_type))
-	    {
-	      SIGNATURE_GROKKING_TYPEDEF (current_class_type) = 0;
-	      if (loc_typedecl != error_mark_node && opaque_typedef)
-		SIGNATURE_HAS_OPAQUE_TYPEDECLS (current_class_type) = 1;
-	    }
-
-  	  return loc_typedecl;
-	}
-      else if (decl_context == FIELD
-	       && (! IS_SIGNATURE (current_class_type)
-		   || SIGNATURE_GROKKING_TYPEDEF (current_class_type))
+	       && ! IS_SIGNATURE (current_class_type)
  	       /* C++ allows static class elements  */
  	       && RIDBIT_SETP (RID_STATIC, specbits))
  	/* C++ also allows inlines and signed and unsigned elements,
@@ -8511,7 +8446,21 @@ grokdeclarator (declarator, declspecs, decl_context, initialized, raises, attrli
 						  integer_one_node), 1));
 		if (! TREE_CONSTANT (itype))
 		  itype = variable_size (itype);
-		itype = build_index_type (itype);
+
+		/* If we're a parm, we need to have a permanent type so
+                   mangling checks for re-use will work right.  If both the
+                   element and index types are permanent, the array type
+                   will be, too.  */
+		if (decl_context == PARM
+		    && allocation_temporary_p () && TREE_PERMANENT (type))
+		  {
+		    push_obstacks (&permanent_obstack, &permanent_obstack);
+		    itype = build_index_type (itype);
+		    pop_obstacks ();
+		  }
+		else
+		  itype = build_index_type (itype);
+
 	      dont_grok_size:
 		resume_momentary (yes);
 	      }
@@ -8636,7 +8585,7 @@ grokdeclarator (declarator, declspecs, decl_context, initialized, raises, attrli
  		      }
 		    {
 		      RID_BIT_TYPE tmp_bits;
-		      bcopy ((void*)&specbits, (void*)&tmp_bits, sizeof(RID_BIT_TYPE));
+		      bcopy ((void*)&specbits, (void*)&tmp_bits, sizeof (RID_BIT_TYPE));
 		      RIDBIT_RESET (RID_INLINE, tmp_bits);
 		      RIDBIT_RESET (RID_STATIC, tmp_bits);
 		      if (RIDBIT_ANY_SET (tmp_bits))
@@ -9034,7 +8983,7 @@ grokdeclarator (declarator, declspecs, decl_context, initialized, raises, attrli
 	}
     }
 
-  if (RIDBIT_SETP (RID_TYPEDEF, specbits))
+  if (RIDBIT_SETP (RID_TYPEDEF, specbits) && decl_context != TYPENAME)
     {
       tree decl;
 
@@ -9076,7 +9025,15 @@ grokdeclarator (declarator, declspecs, decl_context, initialized, raises, attrli
 	  }
 	}
 
-      decl = build_decl (TYPE_DECL, declarator, type);
+      if (decl_context == FIELD)
+	{
+	  decl = build_lang_decl (TYPE_DECL, declarator, type);
+	  if (IS_SIGNATURE (current_class_type) && opaque_typedef)
+	    SIGNATURE_HAS_OPAQUE_TYPEDECLS (current_class_type) = 1;
+	}
+      else
+	decl = build_decl (TYPE_DECL, declarator, type);
+
       if (TREE_CODE (type) == OFFSET_TYPE || TREE_CODE (type) == METHOD_TYPE)
 	{
 	  cp_error_at ("typedef name may not be class-qualified", decl);
@@ -9802,8 +9759,7 @@ grokparms (first_parm, funcdef_flag)
 		{
 		  /* Give various messages as the need arises.  */
 		  if (TREE_CODE (decl) == STRING_CST)
-		    error ("invalid string constant `%s'",
-			   TREE_STRING_POINTER (decl));
+		    cp_error ("invalid string constant `%E'", decl);
 		  else if (TREE_CODE (decl) == INTEGER_CST)
 		    error ("invalid integer constant in parameter list, did you forget to give parameter name?");
 		  continue;
@@ -9824,10 +9780,10 @@ grokparms (first_parm, funcdef_flag)
 		  else if (TREE_CODE (type) == METHOD_TYPE)
 		    {
 		      if (DECL_NAME (decl))
-			/* Cannot use `error_with_decl' here because
+			/* Cannot use the decl here because
 			   we don't have DECL_CONTEXT set up yet.  */
-			error ("parameter `%s' invalidly declared method type",
-			       IDENTIFIER_POINTER (DECL_NAME (decl)));
+			cp_error ("parameter `%D' invalidly declared method type",
+				  DECL_NAME (decl));
 		      else
 			error ("parameter invalidly declared method type");
 		      type = build_pointer_type (type);
@@ -9836,8 +9792,8 @@ grokparms (first_parm, funcdef_flag)
 		  else if (TREE_CODE (type) == OFFSET_TYPE)
 		    {
 		      if (DECL_NAME (decl))
-			error ("parameter `%s' invalidly declared offset type",
-			       IDENTIFIER_POINTER (DECL_NAME (decl)));
+			cp_error ("parameter `%D' invalidly declared offset type",
+				  DECL_NAME (decl));
 		      else
 			error ("parameter invalidly declared offset type");
 		      type = build_pointer_type (type);
@@ -10345,7 +10301,7 @@ xref_tag (code_type_node, name, binfo, globalize)
 	}
       /* If we know we are defining this tag, only look it up in this scope
        * and don't try to find it as a type. */
-      if (t && TYPE_CONTEXT(t) && TREE_MANGLED (name))
+      if (t && TYPE_CONTEXT (t) && TREE_MANGLED (name))
 	ref = t;
       else
       	ref = lookup_tag (code, name, b, 1);
@@ -10387,6 +10343,8 @@ xref_tag (code_type_node, name, binfo, globalize)
 
       if (code == ENUMERAL_TYPE)
 	{
+	  cp_error ("use of enum `%#D' without previous declaration", name);
+
 	  ref = make_node (ENUMERAL_TYPE);
 
 	  /* Give the type a default layout like unsigned int
@@ -10462,6 +10420,25 @@ xref_tag (code_type_node, name, binfo, globalize)
   return ref;
 }
 
+tree
+xref_tag_from_type (old, id, globalize)
+     tree old, id;
+     int globalize;
+{
+  tree code_type_node;
+
+  if (TREE_CODE (old) == RECORD_TYPE)
+    code_type_node = (CLASSTYPE_DECLARED_CLASS (old)
+		      ? class_type_node : record_type_node);
+  else
+    code_type_node = union_type_node;
+
+  if (id == NULL_TREE)
+    id = TYPE_IDENTIFIER (old);
+
+  return xref_tag (code_type_node, id, NULL_TREE, globalize);
+}
+
 void
 xref_basetypes (code_type_node, name, ref, binfo)
      tree code_type_node;
@@ -11048,7 +11025,7 @@ start_function (declspecs, declarator, raises, attrs, pre_parsed_p)
 
   announce_function (decl1);
 
-  if (! current_template_parms || ! uses_template_parms (TREE_TYPE (fntype)))
+  if (! current_template_parms)
     {
       if (TYPE_SIZE (complete_type (TREE_TYPE (fntype))) == NULL_TREE)
 	{
@@ -11533,9 +11510,6 @@ finish_function (lineno, call_poplevel, nested)
   if (fndecl == NULL_TREE)
     return;
 
-  if (! nested && hack_decl_function_context (fndecl) != NULL_TREE)
-    nested = 1;
-
   fntype = TREE_TYPE (fndecl);
 
 /*  TREE_READONLY (fndecl) = 1;
@@ -11715,7 +11689,7 @@ finish_function (lineno, call_poplevel, nested)
 	    }
 
 	  /* End of destructor.  */
-	  expand_end_bindings (NULL_TREE, getdecls() != NULL_TREE, 0);
+	  expand_end_bindings (NULL_TREE, getdecls () != NULL_TREE, 0);
 	  poplevel (2, 0, 0);	/* XXX change to 1 */
 
 	  /* Back to the top of destructor.  */
diff --git a/gcc/cp/decl2.c b/gcc/cp/decl2.c
index fae800e82054..a902a4f473f8 100644
--- a/gcc/cp/decl2.c
+++ b/gcc/cp/decl2.c
@@ -757,27 +757,27 @@ grok_x_components (specs, components)
 	  /* This code may be needed for UNION_TYPEs as
 	     well.  */
 	  tcode = record_type_node;
-	  if (CLASSTYPE_DECLARED_CLASS(t))
+	  if (CLASSTYPE_DECLARED_CLASS (t))
 	    tcode = class_type_node;
-	  else if (IS_SIGNATURE(t))
+	  else if (IS_SIGNATURE (t))
 	    tcode = signature_type_node;
 	  
 	  t = xref_tag (tcode, TYPE_IDENTIFIER (t), NULL_TREE, 0);
-	  if (TYPE_CONTEXT(t))
-	    CLASSTYPE_NO_GLOBALIZE(t) = 1;
+	  if (TYPE_CONTEXT (t))
+	    CLASSTYPE_NO_GLOBALIZE (t) = 1;
 	  return NULL_TREE;
 	  break;
 
 	case UNION_TYPE:
 	case ENUMERAL_TYPE:
-	  if (TREE_CODE(t) == UNION_TYPE)
+	  if (TREE_CODE (t) == UNION_TYPE)
 	    tcode = union_type_node;
 	  else
 	    tcode = enum_type_node;
 
 	  t = xref_tag (tcode, TYPE_IDENTIFIER (t), NULL_TREE, 0);
-	  if (TREE_CODE(t) == UNION_TYPE && TYPE_CONTEXT(t))
-	    CLASSTYPE_NO_GLOBALIZE(t) = 1;
+	  if (TREE_CODE (t) == UNION_TYPE && TYPE_CONTEXT (t))
+	    CLASSTYPE_NO_GLOBALIZE (t) = 1;
 	  if (TREE_CODE (t) == UNION_TYPE
 	      && ANON_AGGRNAME_P (TYPE_IDENTIFIER (t)))
 	    {
@@ -1233,7 +1233,11 @@ check_classfn (ctype, function)
       end = TREE_VEC_END (method_vec);
 
       /* First suss out ctors and dtors.  */
-      if (*methods && fn_name == DECL_NAME (*methods))
+      if (*methods && fn_name == DECL_NAME (*methods)
+	  && DECL_CONSTRUCTOR_P (function))
+	goto got_it;
+      if (*++methods && fn_name == DECL_NAME (*methods)
+	  && DESTRUCTOR_NAME_P (DECL_ASSEMBLER_NAME (function)))
 	goto got_it;
 
       while (++methods != end)
@@ -1295,8 +1299,8 @@ check_classfn (ctype, function)
 		function, ctype);
     }
 
-  /* If we did not find the method in the class, add it to
-     avoid spurious errors.  */
+  /* If we did not find the method in the class, add it to avoid
+     spurious errors.  */
   add_method (ctype, methods, function);
   return NULL_TREE;
 }
@@ -1381,16 +1385,6 @@ grokfield (declarator, declspecs, raises, init, asmspec_tree, attrlist)
       DECL_CLASS_CONTEXT (value) = current_class_type;
       CLASSTYPE_LOCAL_TYPEDECLS (current_class_type) = 1;
 
-      /* If we declare a typedef name for something that has no name,
-	 the typedef name is used for linkage.  See 7.1.3 p4 94/0158. */
-      if (TYPE_NAME (TREE_TYPE (value))
-	  && TREE_CODE (TYPE_NAME (TREE_TYPE (value))) == TYPE_DECL
-	  && ANON_AGGRNAME_P (TYPE_IDENTIFIER (TREE_TYPE (value))))
-	{
-	  TYPE_NAME (TREE_TYPE (value)) = value;
-	  TYPE_STUB_DECL (TREE_TYPE (value)) = value;
-	}
-
       pushdecl_class_level (value);
       return value;
     }
@@ -2094,6 +2088,7 @@ get_temp_name (type, staticp)
     }
   TREE_USED (decl) = 1;
   TREE_STATIC (decl) = staticp;
+  DECL_ARTIFICIAL (decl) = 1;
 
   /* If this is a local variable, then lay out its rtl now.
      Otherwise, callers of this function are responsible for dealing
@@ -2529,7 +2524,7 @@ import_export_template (type)
     }
 }
     
-static void
+static int
 finish_prevtable_vardecl (prev, vars)
      tree prev, vars;
 {
@@ -2550,6 +2545,9 @@ finish_prevtable_vardecl (prev, vars)
 	      SET_CLASSTYPE_INTERFACE_KNOWN (ctype);
 	      CLASSTYPE_VTABLE_NEEDS_WRITING (ctype) = ! DECL_EXTERNAL (method);
 	      CLASSTYPE_INTERFACE_ONLY (ctype) = DECL_EXTERNAL (method);
+#ifdef ADJUST_VTABLE_LINKAGE
+	      ADJUST_VTABLE_LINKAGE (vars, method);
+#endif
 	      break;
 	    }
 	}
@@ -2570,14 +2568,17 @@ finish_prevtable_vardecl (prev, vars)
 	 at the top level.  */
       build_t_desc (ctype, 1);
     }
+
+  return 1;
 }
     
-static void
+static int
 finish_vtable_vardecl (prev, vars)
      tree prev, vars;
 {
   if (write_virtuals >= 0
-      && ! DECL_EXTERNAL (vars) && (TREE_PUBLIC (vars) || TREE_USED (vars)))
+      && ! DECL_EXTERNAL (vars) && (TREE_PUBLIC (vars) || TREE_USED (vars))
+      && ! TREE_ASM_WRITTEN (vars))
     {
 #if 0
       /* The long term plan it to make the TD entries statically initialized,
@@ -2622,29 +2623,33 @@ finish_vtable_vardecl (prev, vars)
 #endif /* DWARF_DEBUGGING_INFO */
 
       rest_of_decl_compilation (vars, NULL_PTR, 1, 1);
+      return 1;
     }
   else if (! TREE_USED (vars))
     /* We don't know what to do with this one yet.  */
-    return;
+    return 0;
 
   /* We know that PREV must be non-zero here.  */
   TREE_CHAIN (prev) = TREE_CHAIN (vars);
+  return 0;
 }
 
-static void
+static int
 prune_vtable_vardecl (prev, vars)
      tree prev, vars;
 {
   /* We know that PREV must be non-zero here.  */
   TREE_CHAIN (prev) = TREE_CHAIN (vars);
+  return 1;
 }
 
-void
+int
 walk_vtables (typedecl_fn, vardecl_fn)
      register void (*typedecl_fn)();
-     register void (*vardecl_fn)();
+     register int (*vardecl_fn)();
 {
   tree prev, vars;
+  int flag = 0;
 
   for (prev = 0, vars = getdecls (); vars; vars = TREE_CHAIN (vars))
     {
@@ -2652,7 +2657,8 @@ walk_vtables (typedecl_fn, vardecl_fn)
 
       if (TREE_CODE (vars) == VAR_DECL && DECL_VIRTUAL_P (vars))
 	{
-	  if (vardecl_fn) (*vardecl_fn) (prev, vars);
+	  if (vardecl_fn)
+	    flag |= (*vardecl_fn) (prev, vars);
 
 	  if (prev && TREE_CHAIN (prev) != vars)
 	    continue;
@@ -2667,6 +2673,8 @@ walk_vtables (typedecl_fn, vardecl_fn)
 
       prev = vars;
     }
+
+  return flag;
 }
 
 static void
@@ -2910,7 +2918,7 @@ finish_file ()
     expand_expr_stmt (build_function_call (TREE_VALUE (static_dtors),
 					   NULL_TREE));
       
-  expand_end_bindings (getdecls(), 1, 0);
+  expand_end_bindings (getdecls (), 1, 0);
   poplevel (1, 0, 0);
   pop_momentary ();
 
@@ -3027,7 +3035,7 @@ finish_file ()
 	expand_expr_stmt (build_function_call (TREE_VALUE (static_ctors),
 					       NULL_TREE));
       
-      expand_end_bindings (getdecls(), 1, 0);
+      expand_end_bindings (getdecls (), 1, 0);
       poplevel (1, 0, 0);
       pop_momentary ();
 
@@ -3107,7 +3115,7 @@ finish_file ()
 	SET_DECL_ARTIFICIAL (vars);
 	pushdecl (vars);
 
-	walk_vtables ((void (*)())0, finish_vtable_vardecl);
+	reconsider |= walk_vtables ((void (*)())0, finish_vtable_vardecl);
 
 	while (*p)
 	  {
@@ -3314,6 +3322,8 @@ build_expr_from_tree (t)
     case TRUTH_NOT_EXPR:
     case ADDR_EXPR:
     case CONVERT_EXPR:      /* Unary + */
+      if (TREE_TYPE (t))
+	return t;
       return build_x_unary_op (TREE_CODE (t),
 			       build_expr_from_tree (TREE_OPERAND (t, 0)));
 
@@ -3472,6 +3482,9 @@ build_expr_from_tree (t)
 	(build_expr_from_tree (TREE_OPERAND (t, 0)),
 	 TREE_OPERAND (t, 1), NULL_TREE, 1);
 
+    case THROW_EXPR:
+      return build_throw (build_expr_from_tree (TREE_OPERAND (t, 0)));
+
     default:
       return t;
     }
@@ -3599,6 +3612,7 @@ void
 do_namespace_alias (alias, namespace)
      tree alias, namespace;
 {
+  sorry ("namespace alias");
 }
 
 tree
@@ -3651,6 +3665,7 @@ void
 do_using_directive (namespace)
      tree namespace;
 {
+  sorry ("using directive");
 }
 
 void
diff --git a/gcc/cp/error.c b/gcc/cp/error.c
index ccce90f5fedd..bb93dd4a17c7 100644
--- a/gcc/cp/error.c
+++ b/gcc/cp/error.c
@@ -543,7 +543,7 @@ ident_fndecl (t)
 #endif
 
 #define GLOBAL_IORD_P(NODE) \
-  !strncmp(IDENTIFIER_POINTER(NODE),GLOBAL_THING,sizeof(GLOBAL_THING)-1)
+  ! strncmp (IDENTIFIER_POINTER(NODE), GLOBAL_THING, sizeof (GLOBAL_THING) - 1)
 
 void
 dump_global_iord (t)
@@ -581,12 +581,9 @@ dump_decl (t, v)
     case TYPE_DECL:
       {
 	/* Don't say 'typedef class A' */
-	tree type = TREE_TYPE (t);
-        if (((IS_AGGR_TYPE (type) && ! TYPE_PTRMEMFUNC_P (type))
-	     || TREE_CODE (type) == ENUMERAL_TYPE)
-	    && type == TYPE_MAIN_VARIANT (type))
+        if (DECL_ARTIFICIAL (t))
 	  {
-	    dump_type (type, v);
+	    dump_type (TREE_TYPE (t), v);
 	    break;
 	  }
       }
@@ -1087,7 +1084,7 @@ dump_expr (t, nop)
 	    args = TREE_CHAIN (args);
 	  }
 	dump_expr (fn, 0);
-	OB_PUTC('(');
+	OB_PUTC ('(');
 	dump_expr_list (args);
 	OB_PUTC (')');
       }
diff --git a/gcc/cp/except.c b/gcc/cp/except.c
index 71421ccc8fae..41742a732513 100644
--- a/gcc/cp/except.c
+++ b/gcc/cp/except.c
@@ -1398,7 +1398,7 @@ expand_builtin_throw ()
     /* Fall into epilogue to unwind prologue. */
   }
 
-  expand_end_bindings (getdecls(), 1, 0);
+  expand_end_bindings (getdecls (), 1, 0);
   poplevel (1, 0, 0);
   pop_momentary ();
 
@@ -1626,7 +1626,7 @@ start_anon_func ()
 void
 end_anon_func ()
 {
-  expand_end_bindings (getdecls(), 1, 0);
+  expand_end_bindings (getdecls (), 1, 0);
   poplevel (1, 0, 0);
   pop_momentary ();
 
@@ -1809,6 +1809,8 @@ build_throw (e)
 {
   if (e != error_mark_node)
     {
+      if (current_template_parms)
+	return build_min (THROW_EXPR, void_type_node, e);
       e = build1 (THROW_EXPR, void_type_node, e);
       TREE_SIDE_EFFECTS (e) = 1;
       TREE_USED (e) = 1;
diff --git a/gcc/cp/expr.c b/gcc/cp/expr.c
index fc59cb6cfa21..9986698d20fc 100644
--- a/gcc/cp/expr.c
+++ b/gcc/cp/expr.c
@@ -366,6 +366,9 @@ do_case (start, end)
 {
   tree value1 = NULL_TREE, value2 = NULL_TREE, label;
 
+  if (start && POINTER_TYPE_P (TREE_TYPE (start)))
+    error ("pointers are not permitted as case values");
+
   if (end && pedantic)
     pedwarn ("ANSI C++ forbids range expressions in switch statement");
 
diff --git a/gcc/cp/gxxint.texi b/gcc/cp/gxxint.texi
index 64ffb84068ae..64d9776cac23 100644
--- a/gcc/cp/gxxint.texi
+++ b/gcc/cp/gxxint.texi
@@ -1226,22 +1226,22 @@ stands.
 
 Only exact type matching or reference matching of throw types works when
 -fno-rtti is used.  Only works on a SPARC (like Suns), i386, arm,
-rs6000, PowerPC, Alpha, mips and VAX machines.  Partial support is in
-for all other machines, but a stack unwinder called __unwind_function
-has to be written, and added to libgcc2 for them.  The new EH code
-doesn't rely upon the __unwind_function for C++ code, instead it creates
-per function unwinders right inside the function, unfortunately, on many
-platforms the definition of RETURN_ADDR_RTX in the tm.h file for the
-machine port is wrong.  The HPPA has a brain dead abi that prevents
-exception handling from just working.  See below for details on
-__unwind_function.  Don't expect exception handling to work right if you
-optimize, in fact the compiler will probably core dump.  RTL_EXPRs for
-EH cond variables for && and || exprs should probably be wrapped in
-UNSAVE_EXPRs, and RTL_EXPRs tweaked so that they can be unsaved, and the
-UNSAVE_EXPR code should be in the backend, or alternatively, UNSAVE_EXPR
-should be ripped out and exactly one finalization allowed to be expanded
-by the backend.  I talked with kenner about this, and we have to allow
-multiple expansions.
+rs6000, PowerPC, Alpha, mips, VAX, and m68k machines.  Partial support
+is in for all other machines, but a stack unwinder called
+__unwind_function has to be written, and added to libgcc2 for them.  The
+new EH code doesn't rely upon the __unwind_function for C++ code,
+instead it creates per function unwinders right inside the function,
+unfortunately, on many platforms the definition of RETURN_ADDR_RTX in
+the tm.h file for the machine port is wrong.  The HPPA has a brain dead
+abi that prevents exception handling from just working.  See below for
+details on __unwind_function.  Don't expect exception handling to work
+right if you optimize, in fact the compiler will probably core dump.
+RTL_EXPRs for EH cond variables for && and || exprs should probably be
+wrapped in UNSAVE_EXPRs, and RTL_EXPRs tweaked so that they can be
+unsaved, and the UNSAVE_EXPR code should be in the backend, or
+alternatively, UNSAVE_EXPR should be ripped out and exactly one
+finalization allowed to be expanded by the backend.  I talked with
+kenner about this, and we have to allow multiple expansions.
 
 We only do pointer conversions on exception matching a la 15.3 p2 case
 3: `A handler with type T, const T, T&, or const T& is a match for a
diff --git a/gcc/cp/init.c b/gcc/cp/init.c
index 2858f653e1fa..289cef8e117d 100644
--- a/gcc/cp/init.c
+++ b/gcc/cp/init.c
@@ -596,7 +596,7 @@ emit_base_init (t, immediately)
 	  target_temp_slot_level = temp_slot_level;
 
 	  member = convert_pointer_to_real (base_binfo, current_class_decl);
-	  expand_aggr_init_1 (base_binfo, 0,
+	  expand_aggr_init_1 (base_binfo, NULL_TREE,
 			      build_indirect_ref (member, NULL_PTR), init,
 			      BINFO_OFFSET_ZEROP (base_binfo), LOOKUP_NORMAL);
 	  expand_cleanups_to (old_cleanups);
@@ -935,7 +935,6 @@ expand_member_init (exp, name, init)
   tree basetype = NULL_TREE, field;
   tree parm;
   tree rval, type;
-  tree actual_name;
 
   if (exp == NULL_TREE)
     return;			/* complain about this later */
@@ -1071,14 +1070,10 @@ expand_member_init (exp, name, init)
 	  TREE_USED (exp) = 1;
 	}
       type = TYPE_MAIN_VARIANT (TREE_TYPE (field));
-      actual_name = TYPE_IDENTIFIER (type);
       parm = build_component_ref (exp, name, 0, 0);
 
-      /* Now get to the constructor.  */
+      /* Now get to the constructors.  */
       fndecl = TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (type), 0);
-      /* Get past destructor, if any.  */
-      if (TYPE_HAS_DESTRUCTOR (type))
-	fndecl = DECL_CHAIN (fndecl);
 
       if (fndecl)
 	my_friendly_assert (TREE_CODE (fndecl) == FUNCTION_DECL, 209);
@@ -1102,7 +1097,8 @@ expand_member_init (exp, name, init)
 
       init = convert_arguments (parm, parmtypes, NULL_TREE, fndecl, LOOKUP_NORMAL);
       if (init == NULL_TREE || TREE_TYPE (init) != error_mark_node)
-	rval = build_method_call (NULL_TREE, actual_name, init, NULL_TREE, LOOKUP_NORMAL);
+	rval = build_method_call (NULL_TREE, ctor_identifier, init,
+				  TYPE_BINFO (type), LOOKUP_NORMAL);
       else
 	return;
 
@@ -1245,14 +1241,15 @@ expand_aggr_init (exp, init, alias_this, flags)
 }
 
 static void
-expand_default_init (binfo, true_exp, exp, type, init, alias_this, flags)
+expand_default_init (binfo, true_exp, exp, init, alias_this, flags)
      tree binfo;
      tree true_exp, exp;
-     tree type;
      tree init;
      int alias_this;
      int flags;
 {
+  tree type = TREE_TYPE (exp);
+
   /* It fails because there may not be a constructor which takes
      its own type as the first (or only parameter), but which does
      take other types via a conversion.  So, if the thing initializing
@@ -1301,7 +1298,7 @@ expand_default_init (binfo, true_exp, exp, type, init, alias_this, flags)
     {
       if (flags & LOOKUP_ONLYCONVERTING)
 	flags |= LOOKUP_NO_CONVERSION;
-      rval = build_method_call (exp, constructor_name_full (type),
+      rval = build_method_call (exp, ctor_identifier,
 				parms, binfo, flags);
 
       /* Private, protected, or otherwise unavailable.  */
@@ -1534,7 +1531,7 @@ expand_aggr_init_1 (binfo, true_exp, exp, init, alias_this, flags)
 		  tree parms = build_tree_list (NULL_TREE, init);
 		  tree as_cons = NULL_TREE;
 		  if (TYPE_HAS_CONSTRUCTOR (type))
-		    as_cons = build_method_call (exp, constructor_name_full (type),
+		    as_cons = build_method_call (exp, ctor_identifier,
 						 parms, binfo,
 						 LOOKUP_SPECULATIVELY|LOOKUP_NO_CONVERSION);
 		  if (as_cons != NULL_TREE && as_cons != error_mark_node)
@@ -1551,7 +1548,7 @@ expand_aggr_init_1 (binfo, true_exp, exp, init, alias_this, flags)
 
   /* We know that expand_default_init can handle everything we want
      at this point.  */
-  expand_default_init (binfo, true_exp, exp, type, init, alias_this, flags);
+  expand_default_init (binfo, true_exp, exp, init, alias_this, flags);
 }
 
 /* Report an error if NAME is not the name of a user-defined,
@@ -1781,7 +1778,7 @@ build_offset_ref (type, name)
      tree type, name;
 {
   tree decl, fnfields, fields, t = error_mark_node;
-  tree basetypes = NULL_TREE;
+  tree basebinfo = NULL_TREE;
   int dtor = 0;
 
   if (current_template_parms)
@@ -1843,9 +1840,9 @@ build_offset_ref (type, name)
     }
 
   if (current_class_type == 0
-      || get_base_distance (type, current_class_type, 0, &basetypes) == -1)
+      || get_base_distance (type, current_class_type, 0, &basebinfo) == -1)
     {
-      basetypes = TYPE_BINFO (type);
+      basebinfo = TYPE_BINFO (type);
       decl = build1 (NOP_EXPR, type, error_mark_node);
     }
   else if (current_class_decl == 0)
@@ -1853,8 +1850,18 @@ build_offset_ref (type, name)
   else
     decl = C_C_D;
 
-  fnfields = lookup_fnfields (basetypes, name, 1);
-  fields = lookup_field (basetypes, name, 0, 0);
+  if (constructor_name (BINFO_TYPE (basebinfo)) == name)
+    if (dtor)
+      name = dtor_identifier;
+    else
+      name = ctor_identifier;
+  else
+    if (dtor)
+      my_friendly_abort (999);
+
+    
+  fnfields = lookup_fnfields (basebinfo, name, 1);
+  fields = lookup_field (basebinfo, name, 0, 0);
 
   if (fields == error_mark_node || fnfields == error_mark_node)
     return error_mark_node;
@@ -1863,91 +1870,58 @@ build_offset_ref (type, name)
      lookup_fnfield. */
   if (fnfields)
     {
-      basetypes = TREE_PURPOSE (fnfields);
+      extern int flag_save_memoized_contexts;
+      basebinfo = TREE_PURPOSE (fnfields);
 
       /* Go from the TREE_BASELINK to the member function info.  */
       t = TREE_VALUE (fnfields);
 
-      if (fields)
+      if (DECL_CHAIN (t) == NULL_TREE)
 	{
-	  if (DECL_FIELD_CONTEXT (fields) == DECL_FIELD_CONTEXT (t))
+	  tree access;
+
+	  /* unique functions are handled easily.  */
+	unique:
+	  access = compute_access (basebinfo, t);
+	  if (access == access_protected_node)
 	    {
-	      error ("ambiguous member reference: member `%s' defined as both field and function",
-		     IDENTIFIER_POINTER (name));
+	      cp_error_at ("member function `%#D' is protected", t);
+	      error ("in this context");
 	      return error_mark_node;
 	    }
-	  if (UNIQUELY_DERIVED_FROM_P (DECL_FIELD_CONTEXT (fields), DECL_FIELD_CONTEXT (t)))
-	    ;
-	  else if (UNIQUELY_DERIVED_FROM_P (DECL_FIELD_CONTEXT (t), DECL_FIELD_CONTEXT (fields)))
-	    t = fields;
-	  else
+	  if (access == access_private_node)
 	    {
-	      error ("ambiguous member reference: member `%s' derives from distinct classes in multiple inheritance lattice");
+	      cp_error_at ("member function `%#D' is private", t);
+	      error ("in this context");
 	      return error_mark_node;
 	    }
+	  mark_used (t);
+	  return build (OFFSET_REF, TREE_TYPE (t), decl, t);
 	}
 
-      if (t == TREE_VALUE (fnfields))
-	{
-	  extern int flag_save_memoized_contexts;
+      /* FNFIELDS is most likely allocated on the search_obstack,
+	 which will go away after this class scope.  If we need
+	 to save this value for later (either for memoization
+	 or for use as an initializer for a static variable), then
+	 do so here.
 
-	  if (DECL_CHAIN (t) == NULL_TREE || dtor)
-	    {
-	      tree access;
-
-	      /* unique functions are handled easily.  */
-	    unique:
-	      access = compute_access (basetypes, t);
-	      if (access == access_protected_node)
-		{
-		  cp_error_at ("member function `%#D' is protected", t);
-		  error ("in this context");
-		  return error_mark_node;
-		}
-	      if (access == access_private_node)
-		{
-		  cp_error_at ("member function `%#D' is private", t);
-		  error ("in this context");
-		  return error_mark_node;
-		}
-	      mark_used (t);
-	      return build (OFFSET_REF, TREE_TYPE (t), decl, t);
-	    }
+	 ??? The smart thing to do for the case of saving initializers
+	 is to resolve them before we're done with this scope.  */
+      if (!TREE_PERMANENT (fnfields)
+	  && ((flag_save_memoized_contexts && global_bindings_p ())
+	      || ! allocation_temporary_p ()))
+	fnfields = copy_list (fnfields);
 
-	  /* overloaded functions may need more work.  */
-	  if (name == constructor_name (type))
-	    {
-	      if (TYPE_HAS_DESTRUCTOR (type)
-		  && DECL_CHAIN (DECL_CHAIN (t)) == NULL_TREE)
-		{
-		  t = DECL_CHAIN (t);
-		  goto unique;
-		}
-	    }
-	  /* FNFIELDS is most likely allocated on the search_obstack,
-	     which will go away after this class scope.  If we need
-	     to save this value for later (either for memoization
-	     or for use as an initializer for a static variable), then
-	     do so here.
-
-	     ??? The smart thing to do for the case of saving initializers
-	     is to resolve them before we're done with this scope.  */
-	  if (!TREE_PERMANENT (fnfields)
-	      && ((flag_save_memoized_contexts && global_bindings_p ())
-		  || ! allocation_temporary_p ()))
-	    fnfields = copy_list (fnfields);
-
-	  t = build_tree_list (error_mark_node, fnfields);
-	  TREE_TYPE (t) = build_offset_type (type, unknown_type_node);
-	  return t;
-	}
+      t = build_tree_list (error_mark_node, fnfields);
+      TREE_TYPE (t) = build_offset_type (type, unknown_type_node);
+      return t;
     }
 
   /* Now that we know we are looking for a field, see if we
      have access to that field.  Lookup_field will give us the
      error message.  */
 
-  t = lookup_field (basetypes, name, 1, 0);
+  t = lookup_field (basebinfo, name, 1, 0);
 
   if (t == error_mark_node)
     return error_mark_node;
@@ -2802,7 +2776,12 @@ build_new (placement, decl, init, use_global_new)
     }
 
   if (has_array)
-    code = VEC_NEW_EXPR;
+    {
+      code = VEC_NEW_EXPR;
+
+      if (init && pedantic)
+	cp_pedwarn ("initialization in array new");
+    }
 
   /* Allocate the object. */
   if (! use_global_new && TYPE_LANG_SPECIFIC (true_type)
@@ -2930,8 +2909,8 @@ build_new (placement, decl, init, use_global_new)
 	  if (newrval && TREE_CODE (TREE_TYPE (newrval)) == POINTER_TYPE)
 	    newrval = build_indirect_ref (newrval, NULL_PTR);
 
-	  newrval = build_method_call (newrval, constructor_name_full (true_type),
-				       init, NULL_TREE, flags);
+	  newrval = build_method_call (newrval, ctor_identifier,
+				       init, TYPE_BINFO (true_type), flags);
 
 	  if (newrval)
 	    {
@@ -3272,6 +3251,9 @@ expand_vec_init (decl, base, maxindex, init, from_array)
   expand_assignment (rval, base, 0, 0);
   base = get_temp_regvar (build_pointer_type (type), base);
 
+  if (init != NULL_TREE && TREE_CODE (init) == TREE_LIST)
+    init = build_compound_expr (init);
+
   if (init != NULL_TREE
       && TREE_CODE (init) == CONSTRUCTOR
       && TREE_TYPE (init) == TREE_TYPE (decl))
@@ -3387,7 +3369,18 @@ expand_vec_init (decl, base, maxindex, init, from_array)
 			   array_type_nelts (type), 0, 0);
 	}
       else
-	expand_aggr_init (build1 (INDIRECT_REF, type, base), init, 0, 0);
+	{
+	  tree targ = build1 (INDIRECT_REF, type, base);
+	  tree rhs;
+
+	  if (init)
+	    rhs = convert_for_initialization (targ, type, init, LOOKUP_NORMAL,
+					      "initialization", NULL_TREE, 0);
+	  else
+	    rhs = NULL_TREE;
+
+	  expand_aggr_init (targ, rhs, 0, 0);
+	}
 
       expand_assignment (base,
 			 build (PLUS_EXPR, build_pointer_type (type), base, size),
@@ -3578,7 +3571,7 @@ build_delete (type, addr, auto_delete, flags, use_global_delete)
      of the base classes; otherwise, we must do that here.  */
   if (TYPE_HAS_DESTRUCTOR (type))
     {
-      tree dtor = DECL_MAIN_VARIANT (TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (type), 0));
+      tree dtor = DECL_MAIN_VARIANT (TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (type), 1));
       tree basetypes = TYPE_BINFO (type);
       tree passed_auto_delete;
       tree do_delete = NULL_TREE;
@@ -3631,7 +3624,7 @@ build_delete (type, addr, auto_delete, flags, use_global_delete)
 	     complete right way to do this. this offsets may not be right
 	     in the below.  (mrs) */
 	  /* This destructor must be called via virtual function table.  */
-	  dtor = TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (DECL_CONTEXT (dtor)), 0);
+	  dtor = TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (DECL_CONTEXT (dtor)), 1);
 	  basetype = DECL_CLASS_CONTEXT (dtor);
 	  binfo = get_binfo (basetype,
 			     TREE_TYPE (TREE_TYPE (TREE_VALUE (parms))),
diff --git a/gcc/cp/lex.c b/gcc/cp/lex.c
index a1a335525a6c..a1b841bf4672 100644
--- a/gcc/cp/lex.c
+++ b/gcc/cp/lex.c
@@ -837,6 +837,11 @@ yyprint (file, yychar, yylval)
     case SCSPEC:
     case PRE_PARSED_CLASS_DECL:
       t = yylval.ttype;
+      if (TREE_CODE (t) == TYPE_DECL)
+	{
+	  fprintf (file, " `%s'", DECL_NAME (t));
+	  break;
+	}
       my_friendly_assert (TREE_CODE (t) == IDENTIFIER_NODE, 224);
       if (IDENTIFIER_POINTER (t))
 	  fprintf (file, " `%s'", IDENTIFIER_POINTER (t));
@@ -1076,7 +1081,7 @@ set_typedecl_interface_info (prev, vars)
     = interface_strcmp (FILE_NAME_NONDIRECTORY (DECL_SOURCE_FILE (vars)));
 }
 
-void
+int
 set_vardecl_interface_info (prev, vars)
      tree prev, vars;
 {
@@ -1090,7 +1095,9 @@ set_vardecl_interface_info (prev, vars)
 	CLASSTYPE_VTABLE_NEEDS_WRITING (type) = 1;
       DECL_EXTERNAL (vars) = CLASSTYPE_INTERFACE_ONLY (type);
       TREE_PUBLIC (vars) = 1;
+      return 1;
     }
+  return 0;
 }
 
 /* Called from the top level: if there are any pending inlines to
@@ -1683,6 +1690,7 @@ cons_up_default_function (type, full_name, kind)
     }
 #endif
 
+#if 0
   if (CLASSTYPE_INTERFACE_KNOWN (type))
     {
       DECL_INTERFACE_KNOWN (fn) = 1;
@@ -1690,6 +1698,7 @@ cons_up_default_function (type, full_name, kind)
 				     && flag_implement_inlines);
     }
   else
+#endif
     DECL_NOT_REALLY_EXTERN (fn) = 1;
 
   mark_inline_for_output (fn);
@@ -1986,7 +1995,7 @@ check_newline ()
 			      goto skipline;
 			    }
 			  main_filename = TREE_STRING_POINTER (yylval.ttype);
-			  c = getch();
+			  c = getch ();
 			  put_back (c);
 			}
 
@@ -2063,7 +2072,7 @@ check_newline ()
 			      goto skipline;
 			    }
 			  main_filename = TREE_STRING_POINTER (yylval.ttype);
-			  c = getch();
+			  c = getch ();
 			  put_back (c);
 			}
 
@@ -2683,7 +2692,7 @@ see_typename ()
 {
   looking_for_typename = 1;
   if (yychar < 0)
-    if ((yychar = yylex()) < 0) yychar = 0;
+    if ((yychar = yylex ()) < 0) yychar = 0;
   looking_for_typename = 0;
   if (yychar == IDENTIFIER)
     {
@@ -2742,7 +2751,7 @@ do_identifier (token, parsing)
 
   /* Remember that this name has been used in the class definition, as per
      [class.scope0] */
-  if (id && current_class_type
+  if (id && current_class_type && parsing
       && TYPE_BEING_DEFINED (current_class_type)
       && ! IDENTIFIER_CLASS_VALUE (token))
     pushdecl_class_level (id);
@@ -3238,6 +3247,14 @@ real_yylex ()
 		  token_buffer[0] = '^';
 		  token_buffer[1] = 0;
 		}
+	      else if (ptr->token == NAMESPACE)
+		{
+		  static int warned;
+		  if (! warned)
+		    warning ("namespaces are mostly broken in this version of g++");
+
+		  warned = 1;
+		}
 
 	      value = (int) ptr->token;
 	    }
@@ -4037,7 +4054,7 @@ real_yylex ()
 	  skipnewline:
 	    c = getch ();
 	    if (c == EOF) {
-		error("Unterminated string");
+		error ("Unterminated string");
 		break;
 	    }
 	  }
@@ -4383,7 +4400,7 @@ build_lang_decl (code, name, type)
 #endif
 #ifdef GATHER_STATISTICS
   tree_node_counts[(int)lang_decl] += 1;
-  tree_node_sizes[(int)lang_decl] += sizeof(struct lang_decl);
+  tree_node_sizes[(int)lang_decl] += sizeof (struct lang_decl);
 #endif
 
   return t;
@@ -4480,7 +4497,7 @@ make_lang_type (code)
 
 #ifdef GATHER_STATISTICS
   tree_node_counts[(int)lang_type] += 1;
-  tree_node_sizes[(int)lang_type] += sizeof(struct lang_type);
+  tree_node_sizes[(int)lang_type] += sizeof (struct lang_type);
 #endif
 
   return t;
@@ -4509,7 +4526,7 @@ copy_decl_lang_specific (decl)
 
 #ifdef GATHER_STATISTICS
   tree_node_counts[(int)lang_decl] += 1;
-  tree_node_sizes[(int)lang_decl] += sizeof(struct lang_decl);
+  tree_node_sizes[(int)lang_decl] += sizeof (struct lang_decl);
 #endif
 }
 
@@ -4549,32 +4566,6 @@ compiler_error (s, v, v2)
   sprintf (buf, s, v, v2);
   error_with_file_and_line (input_filename, lineno, "%s (compiler error)", buf);
 }
-
-void
-compiler_error_with_decl (decl, s)
-     tree decl;
-     char *s;
-{
-  char *name;
-  count_error (0);
-
-  report_error_function (0);
-
-  if (TREE_CODE (decl) == PARM_DECL)
-    fprintf (stderr, "%s:%d: ",
-	     DECL_SOURCE_FILE (DECL_CONTEXT (decl)),
-	     DECL_SOURCE_LINE (DECL_CONTEXT (decl)));
-  else
-    fprintf (stderr, "%s:%d: ",
-	     DECL_SOURCE_FILE (decl), DECL_SOURCE_LINE (decl));
-
-  name = lang_printable_name (decl);
-  if (name)
-    fprintf (stderr, s, name);
-  else
-    fprintf (stderr, s, "((anonymous))");
-  fprintf (stderr, " (compiler error)\n");
-}
 
 void
 yyerror (string)
diff --git a/gcc/cp/method.c b/gcc/cp/method.c
index f5f3bbe4e1dc..c8732072d0a1 100644
--- a/gcc/cp/method.c
+++ b/gcc/cp/method.c
@@ -91,10 +91,12 @@ do_inline_function_hair (type, friend_list)
 
   if (method && TREE_CODE (method) == TREE_VEC)
     {
-      if (TREE_VEC_ELT (method, 0))
+      if (TREE_VEC_ELT (method, 1))
+	method = TREE_VEC_ELT (method, 1);
+      else if (TREE_VEC_ELT (method, 0))
 	method = TREE_VEC_ELT (method, 0);
       else
-	method = TREE_VEC_ELT (method, 1);
+	method = TREE_VEC_ELT (method, 2);
     }
 
   while (method)
@@ -1277,9 +1279,26 @@ build_opfncall (code, flags, xarg1, xarg2, arg3)
 				      build_tree_list (NULL_TREE, xarg1),
 				      flags & LOOKUP_COMPLAIN,
 				      (struct candidate *)0);
+	arg1 = TREE_TYPE (xarg1);
+
+	/* This handles the case where we're trying to delete
+	   X (*a)[10];
+	   a=new X[5][10];
+	   delete[] a; */
+	   
+	if (TREE_CODE (TREE_TYPE (arg1)) == ARRAY_TYPE)
+	  {
+	    /* Strip off the pointer and the array. */
+	    arg1 = TREE_TYPE (TREE_TYPE (arg1));
+
+	    while (TREE_CODE (arg1) == ARRAY_TYPE)
+		arg1 = (TREE_TYPE (arg1));
+
+	    arg1 = build_pointer_type (arg1);
+	  }
 
 	rval = build_method_call
-	  (build_indirect_ref (build1 (NOP_EXPR, TREE_TYPE (xarg1),
+	  (build_indirect_ref (build1 (NOP_EXPR, arg1,
 				       error_mark_node),
 			       NULL_PTR),
 	   fnname, tree_cons (NULL_TREE, xarg1,
@@ -1826,7 +1845,7 @@ make_thunk (function, delta)
   thunk = IDENTIFIER_GLOBAL_VALUE (thunk_id);
   if (thunk && TREE_CODE (thunk) != THUNK_DECL)
     {
-      error_with_decl ("implementation-reserved name `%s' used");
+      cp_error ("implementation-reserved name `%D' used", thunk_id);
       IDENTIFIER_GLOBAL_VALUE (thunk_id) = thunk = NULL_TREE;
     }
   if (thunk == NULL_TREE)
diff --git a/gcc/cp/parse.y b/gcc/cp/parse.y
index 5c7b53c71128..d2b6f95e202e 100644
--- a/gcc/cp/parse.y
+++ b/gcc/cp/parse.y
@@ -499,10 +499,10 @@ datadef:
 	| typed_declspecs declarator ';'
 		{ tree d, specs, attrs;
 		  split_specs_attrs ($1, &specs, &attrs);
+		  note_list_got_semicolon (specs);
 		  d = start_decl ($<ttype>2, specs, 0, NULL_TREE);
 		  cplus_decl_attributes (d, NULL_TREE, attrs);
 		  cp_finish_decl (d, NULL_TREE, NULL_TREE, 1, 0);
-		  note_list_got_semicolon ($<ttype>$);
 		}
         | declmods ';'
 	  { pedwarn ("empty declaration"); }
@@ -1990,7 +1990,9 @@ pending_inlines:
 	| pending_inlines fn.defpen maybe_return_init ctor_initializer_opt
 	  compstmt_or_error
 		{
-		  finish_function (lineno, (int)$4, 0);
+		  int nested = (hack_decl_function_context
+				(current_function_decl) != NULL_TREE);
+		  finish_function (lineno, (int)$4, nested);
 		  process_next_inline ($2);
 		}
 	| pending_inlines fn.defpen maybe_return_init function_try_block
@@ -2108,7 +2110,19 @@ named_class_head_sans_basetype_defn:
 
 named_complex_class_head_sans_basetype:
 	  aggr nested_name_specifier identifier
-		{ current_aggr = $$; $$ = $3; }
+		{
+		  current_aggr = $1;
+		  if (TREE_CODE ($3) == TYPE_DECL)
+		    $$ = $3;
+		  else
+		    {
+		      cp_error ("`%T' does not have a nested type named `%D'",
+				$2, $3);
+		      $$ = xref_tag
+			(current_aggr, make_anon_name (), NULL_TREE, 1);
+		      $$ = TYPE_MAIN_DECL ($$);
+		    }
+		}
 	| aggr template_type
 		{ current_aggr = $$; $$ = $2; }
 	| aggr nested_name_specifier template_type
@@ -3519,8 +3533,10 @@ function_try_block:
 		  expand_start_all_catch (); }
 	  handler_seq
 		{
+		  int nested = (hack_decl_function_context
+				(current_function_decl) != NULL_TREE);
 		  expand_end_all_catch ();
-		  finish_function (lineno, (int)$3, 0);
+		  finish_function (lineno, (int)$3, nested);
 		}
 	;
 
@@ -3820,6 +3836,9 @@ bad_parm:
 	| notype_declarator
 		{
 		  error ("type specifier omitted for parameter");
+		  if (TREE_CODE ($$) == SCOPE_REF
+		      && TREE_CODE (TREE_OPERAND ($$, 0)) == TEMPLATE_TYPE_PARM)
+		    cp_error ("  perhaps you want `typename %E' to make it a type", $$);
 		  $$ = build_tree_list (integer_type_node, $$);
 		}
 	;
diff --git a/gcc/cp/pt.c b/gcc/cp/pt.c
index 54efe9f7f20d..0ecc40018b0c 100644
--- a/gcc/cp/pt.c
+++ b/gcc/cp/pt.c
@@ -1,6 +1,7 @@
 /* Handle parameterized types (templates) for GNU C++.
    Copyright (C) 1992, 93, 94, 95, 1996 Free Software Foundation, Inc.
    Written by Ken Raeburn (raeburn@cygnus.com) while at Watchmaker Computing.
+   Rewritten by Jason Merrill (jason@cygnus.com).
 
 This file is part of GNU CC.
 
@@ -233,6 +234,9 @@ push_template_decl (decl)
     {
       if (TREE_CODE (decl) == TYPE_DECL)
 	tmpl = CLASSTYPE_TI_TEMPLATE (TREE_TYPE (decl));
+      else if (! DECL_TEMPLATE_INFO (decl))
+	/* A member definition that doesn't match anything in the class.  */
+	return;
       else
 	tmpl = DECL_TI_TEMPLATE (decl);
     }
@@ -475,12 +479,10 @@ mangle_class_name_for_template (name, parms, arglist)
   int i, nparms;
 
   if (!scratch_firstobj)
-    {
-      gcc_obstack_init (&scratch_obstack);
-      scratch_firstobj = obstack_alloc (&scratch_obstack, 1);
-    }
+    gcc_obstack_init (&scratch_obstack);
   else
     obstack_free (&scratch_obstack, scratch_firstobj);
+  scratch_firstobj = obstack_alloc (&scratch_obstack, 1);
 
 #if 0
 #define buflen	sizeof(buf)
@@ -629,12 +631,6 @@ lookup_template_class (d1, arglist, in_decl)
       return error_mark_node;
     }
 
-  if (TREE_CODE (TREE_TYPE (template)) == RECORD_TYPE)
-    code_type_node = (CLASSTYPE_DECLARED_CLASS (TREE_TYPE (template))
-		      ? class_type_node : record_type_node);
-  else
-    code_type_node = union_type_node;
-
   if (PRIMARY_TEMPLATE_P (template))
     {
       parmlist = DECL_TEMPLATE_PARMS (template);
@@ -675,7 +671,7 @@ lookup_template_class (d1, arglist, in_decl)
       IDENTIFIER_TEMPLATE (id) = d1;
 
       maybe_push_to_top_level (uses_template_parms (arglist));
-      t = xref_tag (code_type_node, id, NULL_TREE, 1);
+      t = xref_tag_from_type (TREE_TYPE (template), id, 1);
       pop_from_top_level ();
     }
   else
@@ -689,7 +685,7 @@ lookup_template_class (d1, arglist, in_decl)
 	{
 	  tree save_parms = current_template_parms;
 	  current_template_parms = NULL_TREE;
-	  t = xref_tag (code_type_node, id, NULL_TREE, 0);
+	  t = xref_tag_from_type (TREE_TYPE (template), id, 0);
 	  current_template_parms = save_parms;
 	}
       else
@@ -978,7 +974,7 @@ tree
 instantiate_class_template (type)
      tree type;
 {
-  tree template, template_info, args, pattern, t, *field_chain, *tag_chain;
+  tree template, template_info, args, pattern, t, *field_chain;
 
   if (type == error_mark_node)
     return error_mark_node;
@@ -1060,7 +1056,6 @@ instantiate_class_template (type)
   CLASSTYPE_LOCAL_TYPEDECLS (type) = CLASSTYPE_LOCAL_TYPEDECLS (pattern);
 
   field_chain = &TYPE_FIELDS (type);
-  tag_chain = &CLASSTYPE_TAGS (type);
 
   for (t = CLASSTYPE_TAGS (pattern); t; t = TREE_CHAIN (t))
     {
@@ -1068,15 +1063,13 @@ instantiate_class_template (type)
       tree tag = TREE_VALUE (t);
       tree newtag;
 
+      /* These will add themselves to CLASSTYPE_TAGS for the new type.  */
       if (TREE_CODE (tag) == ENUMERAL_TYPE)
 	newtag = start_enum (name);
       else
 	newtag = tsubst (tag, &TREE_VEC_ELT (args, 0),
 			 TREE_VEC_LENGTH (args), NULL_TREE);
 
-      *tag_chain = build_tree_list (name, newtag);
-      tag_chain = &TREE_CHAIN (*tag_chain);
-
       if (TREE_CODE (tag) == ENUMERAL_TYPE)
 	{
 	  tree e, values = NULL_TREE, *last = &values;
@@ -1124,16 +1117,30 @@ instantiate_class_template (type)
   TYPE_METHODS (type) = tsubst_chain (TYPE_METHODS (pattern), args);
 
   DECL_FRIENDLIST (TYPE_MAIN_DECL (type))
-    = tsubst_chain (DECL_FRIENDLIST (TYPE_MAIN_DECL (pattern)), args);
-  CLASSTYPE_FRIEND_CLASSES (type)
-    = tsubst_chain (CLASSTYPE_FRIEND_CLASSES (pattern), args);
+    = tsubst (DECL_FRIENDLIST (TYPE_MAIN_DECL (pattern)),
+	      &TREE_VEC_ELT (args, 0), TREE_VEC_LENGTH (args), NULL_TREE);
 
   {
-    tree d = tsubst (DECL_TEMPLATE_INJECT (template), &TREE_VEC_ELT (args, 0),
+    tree d = CLASSTYPE_FRIEND_CLASSES (type) =
+      tsubst (CLASSTYPE_FRIEND_CLASSES (pattern), &TREE_VEC_ELT (args, 0),
+	      TREE_VEC_LENGTH (args), NULL_TREE);
+
+    /* This does injection for friend classes.  */
+    for (; d; d = TREE_CHAIN (d))
+      TREE_VALUE (d) = xref_tag_from_type (TREE_VALUE (d), NULL_TREE, 1);
+
+    d = tsubst (DECL_TEMPLATE_INJECT (template), &TREE_VEC_ELT (args, 0),
 		     TREE_VEC_LENGTH (args), NULL_TREE);
 
     for (; d; d = TREE_CHAIN (d))
-      pushdecl (TREE_VALUE (d));
+      {
+	tree t = TREE_VALUE (d);
+
+	if (TREE_CODE (t) == TYPE_DECL)
+	  /* Already injected.  */;
+	else
+	  pushdecl (t);
+      }
   }
 
   TYPE_HAS_CONSTRUCTOR (type) = TYPE_HAS_CONSTRUCTOR (pattern);
@@ -1781,6 +1788,11 @@ tsubst (t, args, nargs, in_decl)
 	(CALL_EXPR, tsubst (TREE_OPERAND (t, 0), args, nargs, in_decl),
 	 tsubst (TREE_OPERAND (t, 1), args, nargs, in_decl), 0);
 
+    case SCOPE_REF:
+      return build_parse_node
+	(TREE_CODE (t), tsubst (TREE_OPERAND (t, 0), args, nargs, in_decl),
+	 tsubst (TREE_OPERAND (t, 1), args, nargs, in_decl));
+
     default:
       sorry ("use of `%s' in template",
 	     tree_code_name [(int) TREE_CODE (t)]);
@@ -1866,6 +1878,7 @@ tsubst_copy (t, args, nargs, in_decl)
     case CONVERT_EXPR:      /* Unary + */
     case SIZEOF_EXPR:
     case ARROW_EXPR:
+    case THROW_EXPR:
       return build1
 	(code, NULL_TREE,
 	 tsubst_copy (TREE_OPERAND (t, 0), args, nargs, in_decl));
@@ -1928,7 +1941,7 @@ tsubst_copy (t, args, nargs, in_decl)
 	if (TREE_CODE (name) == BIT_NOT_EXPR)
 	  {
 	    name = tsubst_copy (TREE_OPERAND (name, 0), args, nargs, in_decl);
-	    name = build1 (BIT_NOT_EXPR, NULL_TREE, name);
+	    name = build1 (BIT_NOT_EXPR, NULL_TREE, TYPE_MAIN_VARIANT (name));
 	  }
 	else if (TREE_CODE (name) == SCOPE_REF
 		 && TREE_CODE (TREE_OPERAND (name, 1)) == BIT_NOT_EXPR)
@@ -1936,7 +1949,7 @@ tsubst_copy (t, args, nargs, in_decl)
 	    tree base = tsubst_copy (TREE_OPERAND (name, 0), args, nargs, in_decl);
 	    name = TREE_OPERAND (name, 1);
 	    name = tsubst_copy (TREE_OPERAND (name, 0), args, nargs, in_decl);
-	    name = build1 (BIT_NOT_EXPR, NULL_TREE, name);
+	    name = build1 (BIT_NOT_EXPR, NULL_TREE, TYPE_MAIN_VARIANT (name));
 	    name = build_nt (SCOPE_REF, base, name);
 	  }
 	else
@@ -2915,7 +2928,7 @@ instantiate_decl (d)
 	    warn_if_unknown_interface (pattern);
 	}
 
-      if (at_eof)
+      if (at_eof && ! DECL_INLINE (d))
 	import_export_decl (d);
     }
 
diff --git a/gcc/cp/search.c b/gcc/cp/search.c
index bd46eb79c25d..588d8231f094 100644
--- a/gcc/cp/search.c
+++ b/gcc/cp/search.c
@@ -146,7 +146,7 @@ static int n_calls_lookup_fnfields, n_calls_lookup_fnfields_1;
 static int n_calls_get_base_type;
 static int n_outer_fields_searched;
 static int n_contexts_saved;
-#endif
+#endif /* GATHER_STATISTICS */
 
 /* Local variables to help save memoization contexts.  */
 static tree prev_type_memoized;
@@ -323,7 +323,7 @@ push_memoized_context (type, use_old)
 	{
 #ifdef GATHER_STATISTICS
 	  n_contexts_saved++;
-#endif
+#endif /* GATHER_STATISTICS */
 	  type_stack = prev_type_stack;
 	  prev_type_stack = 0;
 
@@ -694,12 +694,12 @@ lookup_field_1 (type, name)
 
 #ifdef GATHER_STATISTICS
   n_calls_lookup_field_1++;
-#endif
+#endif /* GATHER_STATISTICS */
   while (field)
     {
 #ifdef GATHER_STATISTICS
       n_fields_searched++;
-#endif
+#endif /* GATHER_STATISTICS */
       if (DECL_NAME (field) == NULL_TREE
 	  && TREE_CODE (TREE_TYPE (field)) == UNION_TYPE)
 	{
@@ -724,8 +724,6 @@ lookup_field_1 (type, name)
       if (TYPE_VIRTUAL_P (type))
 	return CLASSTYPE_VFIELD (type);
     }
-  if (name == constructor_name (type))
-    return TYPE_STUB_DECL (type);
   return NULL_TREE;
 }
 
@@ -845,10 +843,10 @@ compute_access (basetype_path, field)
 
   /* Fields coming from nested anonymous unions have their DECL_CLASS_CONTEXT
      slot set to the union type rather than the record type containing
-     the anonymous union.  In this case, DECL_FIELD_CONTEXT is correct.  */
+     the anonymous union.  */
   if (context && TREE_CODE (context) == UNION_TYPE
       && ANON_AGGRNAME_P (TYPE_IDENTIFIER (context)))
-    context = DECL_FIELD_CONTEXT (field);
+    context = TYPE_CONTEXT (context);
 
   /* Virtual function tables are never private.  But we should know that
      we are looking for this, and not even try to hide it.  */
@@ -1020,7 +1018,8 @@ lookup_fnfields_here (type, name)
   int index = lookup_fnfields_1 (type, name);
   tree fndecls;
 
-  if (index <= 0)
+  /* ctors and dtors are always only in the right class.  */
+  if (index <= 1)
     return index;
   fndecls = TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (type), index);
   while (fndecls)
@@ -1074,10 +1073,14 @@ lookup_field (xbasetype, name, protect, want_type)
      accurate error messages for access control.  */
   int index = MEMOIZED_HASH_FN (name);
 
+#if 0
+  /* We cannot search for constructor/destructor names like this.  */
+  /* This can't go here, but where should it go?  */
   /* If we are looking for a constructor in a templated type, use the
      unspecialized name, as that is how we store it.  */
   if (IDENTIFIER_TEMPLATE (name))
     name = constructor_name (name);
+#endif
 
   if (TREE_CODE (xbasetype) == TREE_VEC)
     {
@@ -1121,7 +1124,7 @@ lookup_field (xbasetype, name, protect, want_type)
 
 #ifdef GATHER_STATISTICS
   n_calls_lookup_field++;
-#endif
+#endif /* GATHER_STATISTICS */
   if (protect && flag_memoize_lookups && ! global_bindings_p ())
     entry = make_memoized_table_entry (type, name, 0);
   else
@@ -1137,10 +1140,7 @@ lookup_field (xbasetype, name, protect, want_type)
 	    {
 	      if (TREE_CODE (rval) != TYPE_DECL)
 		{
-		  if (name == constructor_name (type))
-		    rval = type;
-		  else
-		    rval = purpose_member (name, CLASSTYPE_TAGS (type));
+		  rval = purpose_member (name, CLASSTYPE_TAGS (type));
 		  if (rval)
 		    rval = TYPE_MAIN_DECL (TREE_VALUE (rval));
 		}
@@ -1322,10 +1322,7 @@ lookup_field (xbasetype, name, protect, want_type)
 	      {
 		if (TREE_CODE (rval) != TYPE_DECL)
 		  {
-		    if (name == constructor_name (type))
-		      rval = type;
-		    else
-		      rval = purpose_member (name, CLASSTYPE_TAGS (type));
+		    rval = purpose_member (name, CLASSTYPE_TAGS (type));
 		    if (rval)
 		      rval = TYPE_MAIN_DECL (TREE_VALUE (rval));
 		  }
@@ -1468,10 +1465,8 @@ lookup_nested_field (name, complain)
 			 enums in nested classes) when we do need to call
 			 this fn at parse time.  So, in those cases, we pass
 			 complain as a 0 and just return a NULL_TREE.  */
-		      error ("assignment to non-static member `%s' of enclosing class `%s'",
-			     lang_printable_name (id),
-			     IDENTIFIER_POINTER (TYPE_IDENTIFIER
-						 (DECL_CONTEXT (t))));
+		      cp_error ("assignment to non-static member `%D' of enclosing class `%T'",
+				id, DECL_CONTEXT (t));
 		      /* Mark this for do_identifier().  It would otherwise
 			 claim that the variable was undeclared.  */
 		      TREE_TYPE (id) = error_mark_node;
@@ -1505,15 +1500,21 @@ lookup_fnfields_1 (type, name)
 
 #ifdef GATHER_STATISTICS
       n_calls_lookup_fnfields_1++;
-#endif
-      if (*methods && name == constructor_name (type))
+#endif /* GATHER_STATISTICS */
+
+      /* Constructors are first...  */
+      if (*methods && name == ctor_identifier)
 	return 0;
 
+      /* and destructors are second.  */
+      if (*++methods && name == dtor_identifier)
+	return 1;
+
       while (++methods != end)
 	{
 #ifdef GATHER_STATISTICS
 	  n_outer_fields_searched++;
-#endif
+#endif /* GATHER_STATISTICS */
 	  if (DECL_NAME (*methods) == name)
 	    break;
 	}
@@ -1581,10 +1582,14 @@ lookup_fnfields (basetype_path, name, complain)
       protect = complain = 0;
     }
 
+#if 0
+  /* We cannot search for constructor/destructor names like this.  */
+  /* This can't go here, but where should it go?  */
   /* If we are looking for a constructor in a templated type, use the
      unspecialized name, as that is how we store it.  */
   if (IDENTIFIER_TEMPLATE (name))
     name = constructor_name (name);
+#endif
 
   binfo = basetype_path;
   binfo_h = binfo;
@@ -1644,7 +1649,7 @@ lookup_fnfields (basetype_path, name, complain)
 
 #ifdef GATHER_STATISTICS
   n_calls_lookup_fnfields++;
-#endif
+#endif /* GATHER_STATISTICS */
   if (protect && flag_memoize_lookups && ! global_bindings_p ())
     entry = make_memoized_table_entry (type, name, 1);
   else
@@ -1674,6 +1679,16 @@ lookup_fnfields (basetype_path, name, complain)
     }
   rval = NULL_TREE;
 
+  if (name == ctor_identifier || name == dtor_identifier)
+    {
+      /* Don't allow lookups of constructors and destructors to go
+ 	 deeper than the first place we look.  */
+      if (entry)
+ 	TREE_TYPE (entry) = TREE_VALUE (entry) = NULL_TREE;
+
+      return NULL_TREE;
+    }
+
   if (basetype_path == TYPE_BINFO (type))
     {
       basetype_chain = CLASSTYPE_BINFO_AS_LIST (type);
@@ -1930,7 +1945,8 @@ get_virtuals_named_this (binfo)
   return NULL_TREE;
 }
 
-static tree get_virtual_destructor (binfo, i)
+static tree
+get_virtual_destructor (binfo, i)
      tree binfo;
      int i;
 {
@@ -1938,8 +1954,8 @@ static tree get_virtual_destructor (binfo, i)
   if (i >= 0)
     type = BINFO_TYPE (TREE_VEC_ELT (BINFO_BASETYPES (binfo), i));
   if (TYPE_HAS_DESTRUCTOR (type)
-      && DECL_VINDEX (TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (type), 0)))
-    return TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (type), 0);
+      && DECL_VINDEX (TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (type), 1)))
+    return TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (type), 1);
   return 0;
 }
 
@@ -2336,7 +2352,7 @@ dfs_walk (binfo, fn, qfn)
 		  /* No need for the conversion here, as we know it is the
 		     right type.  */
 		  vbase_decl_ptr_intermediate
-		    = (tree)CLASSTYPE_SEARCH_SLOT (BINFO_TYPE (base_binfo));
+		    = CLASSTYPE_SEARCH_SLOT (BINFO_TYPE (base_binfo));
 		}
 	      else
 		{
@@ -2477,10 +2493,12 @@ dfs_debug_mark (binfo)
   if (current_function_decl == NULL_TREE
       || DECL_CLASS_CONTEXT (current_function_decl) != t)
     {
-      if (TREE_VEC_ELT (methods, 0))
+      if (TREE_VEC_ELT (methods, 1))
+	methods = TREE_VEC_ELT (methods, 1);
+      else if (TREE_VEC_ELT (methods, 0))
 	methods = TREE_VEC_ELT (methods, 0);
       else
-	methods = TREE_VEC_ELT (methods, 1);
+	methods = TREE_VEC_ELT (methods, 2);
       while (methods)
 	{
 	  if (DECL_VINDEX (methods)
@@ -2523,8 +2541,8 @@ dfs_find_vbases (binfo)
 	  tree binfo = binfo_member (vbase, vbase_types);
 
 	  CLASSTYPE_SEARCH_SLOT (vbase)
-	    = (char *) build (PLUS_EXPR, build_pointer_type (vbase),
-			      vbase_decl_ptr, BINFO_OFFSET (binfo));
+	    = build (PLUS_EXPR, build_pointer_type (vbase),
+		     vbase_decl_ptr, BINFO_OFFSET (binfo));
 	}
     }
   SET_BINFO_VTABLE_PATH_MARKED (binfo);
@@ -2563,7 +2581,7 @@ dfs_init_vbase_pointers (binfo)
     {
       tree ref = build (COMPONENT_REF, TREE_TYPE (fields),
 			build_indirect_ref (this_vbase_ptr, NULL_PTR), fields);
-      tree init = (tree)CLASSTYPE_SEARCH_SLOT (TREE_TYPE (TREE_TYPE (fields)));
+      tree init = CLASSTYPE_SEARCH_SLOT (TREE_TYPE (TREE_TYPE (fields)));
       vbase_init_result = tree_cons (binfo_member (TREE_TYPE (TREE_TYPE (fields)),
 						   vbase_types),
 				     build_modify_expr (ref, NOP_EXPR, init),
@@ -2682,7 +2700,7 @@ expand_upcast_fixups (binfo, addr, orig_addr, vbase, vbase_addr, t,
   delta = purpose_member (vbase, *vbase_offsets);
   if (! delta)
     {
-      delta = (tree)CLASSTYPE_SEARCH_SLOT (BINFO_TYPE (vbase));
+      delta = CLASSTYPE_SEARCH_SLOT (BINFO_TYPE (vbase));
       delta = build (MINUS_EXPR, ptrdiff_type_node, delta, vbase_addr);
       delta = save_expr (delta);
       delta = tree_cons (vbase, delta, *vbase_offsets);
@@ -2751,7 +2769,7 @@ expand_upcast_fixups (binfo, addr, orig_addr, vbase, vbase_addr, t,
 	      if (! vc_delta)
 		{
 		  tree vc_addr = convert_pointer_to_real (vc, orig_addr);
-		  vc_delta = (tree)CLASSTYPE_SEARCH_SLOT (BINFO_TYPE (vc));
+		  vc_delta = CLASSTYPE_SEARCH_SLOT (BINFO_TYPE (vc));
 		  vc_delta = build (MINUS_EXPR, ptrdiff_type_node,
 				    vc_delta, vc_addr);
 		  vc_delta = save_expr (vc_delta);
@@ -3207,10 +3225,10 @@ dfs_pushdecls (binfo)
     }
 
   method_vec = CLASSTYPE_METHOD_VEC (type);
-  if (method_vec != 0)
+  if (method_vec)
     {
       /* Farm out constructors and destructors.  */
-      methods = &TREE_VEC_ELT (method_vec, 1);
+      methods = &TREE_VEC_ELT (method_vec, 2);
       end = TREE_VEC_END (method_vec);
 
       while (methods != end)
@@ -3257,7 +3275,7 @@ dfs_compress_decls (binfo)
   if (method_vec != 0)
     {
       /* Farm out constructors and destructors.  */
-      tree *methods = &TREE_VEC_ELT (method_vec, 1);
+      tree *methods = &TREE_VEC_ELT (method_vec, 2);
       tree *end = TREE_VEC_END (method_vec);
 
       for (; methods != end; methods++)
@@ -3404,9 +3422,9 @@ print_search_statistics ()
   fprintf (stderr, "%d fnfields searched in %d calls to lookup_fnfields\n",
 	   n_outer_fields_searched, n_calls_lookup_fnfields);
   fprintf (stderr, "%d calls to get_base_type\n", n_calls_get_base_type);
-#else
+#else /* GATHER_STATISTICS */
   fprintf (stderr, "no search statistics\n");
-#endif
+#endif /* GATHER_STATISTICS */
 }
 
 void
@@ -3441,7 +3459,7 @@ reinit_search_statistics ()
   n_calls_get_base_type = 0;
   n_outer_fields_searched = 0;
   n_contexts_saved = 0;
-#endif
+#endif /* GATHER_STATISTICS */
 }
 
 static tree conversions;
@@ -3450,11 +3468,11 @@ add_conversions (binfo)
      tree binfo;
 {
   int i;
-  tree vec = CLASSTYPE_METHOD_VEC (BINFO_TYPE (binfo));
+  tree method_vec = CLASSTYPE_METHOD_VEC (BINFO_TYPE (binfo));
 
-  for (i = 1; i < TREE_VEC_LENGTH (vec); ++i)
+  for (i = 2; i < TREE_VEC_LENGTH (method_vec); ++i)
     {
-      tree tmp = TREE_VEC_ELT (vec, i);
+      tree tmp = TREE_VEC_ELT (method_vec, i);
       if (! IDENTIFIER_TYPENAME_P (DECL_NAME (tmp)))
 	break;
       conversions = tree_cons (DECL_NAME (tmp), TREE_TYPE (TREE_TYPE (tmp)),
diff --git a/gcc/cp/spew.c b/gcc/cp/spew.c
index 6564cab2e633..ace8c8f56c4d 100644
--- a/gcc/cp/spew.c
+++ b/gcc/cp/spew.c
@@ -71,7 +71,7 @@ static int debug_yychar ();
 void
 init_spew ()
 {
-  gcc_obstack_init(&token_obstack);
+  gcc_obstack_init (&token_obstack);
 }
 
 #ifdef SPEW_DEBUG
@@ -81,7 +81,7 @@ init_spew ()
 static int
 num_tokens ()
 {
-  return (obstack_object_size(&token_obstack)/sizeof(struct token))
+  return (obstack_object_size (&token_obstack) / sizeof (struct token))
     - first_token;
 }
 
@@ -92,8 +92,8 @@ nth_token (n)
 {
   /* could just have this do slurp_ implicitly, but this way is easier
    * to debug... */
-  my_friendly_assert (n < num_tokens(), 298);
-  return ((struct token*)obstack_base(&token_obstack))+n+first_token;
+  my_friendly_assert (n < num_tokens (), 298);
+  return ((struct token*)obstack_base (&token_obstack)) + n + first_token;
 }
 
 /* Add a token to the token fifo. */
@@ -101,16 +101,16 @@ static void
 add_token (t)
      struct token* t;
 {
-  obstack_grow(&token_obstack,t,sizeof (struct token));
+  obstack_grow (&token_obstack, t, sizeof (struct token));
 }
 
 /* Consume the next token out of the fifo.  */
 static void
-consume_token()
+consume_token ()
 {
-  if (num_tokens() == 1)
+  if (num_tokens () == 1)
     {
-      obstack_free(&token_obstack, obstack_base (&token_obstack));
+      obstack_free (&token_obstack, obstack_base (&token_obstack));
       first_token = 0;
     }
   else
@@ -121,15 +121,15 @@ consume_token()
 /* ...otherwise use macros.  */
 
 #define num_tokens() \
-  ((obstack_object_size(&token_obstack)/sizeof(struct token)) - first_token)
+  ((obstack_object_size (&token_obstack) / sizeof (struct token)) - first_token)
 
 #define nth_token(N) \
-  (((struct token*)obstack_base(&token_obstack))+(N)+first_token)
+  (((struct token*)obstack_base (&token_obstack))+(N)+first_token)
 
-#define add_token(T) obstack_grow(&token_obstack, (T), sizeof (struct token))
+#define add_token(T) obstack_grow (&token_obstack, (T), sizeof (struct token))
 
 #define consume_token() \
-  (num_tokens() == 1							\
+  (num_tokens () == 1							\
    ? (obstack_free (&token_obstack, obstack_base (&token_obstack)),	\
       (first_token = 0))						\
    : first_token++)
@@ -158,11 +158,11 @@ scan_tokens (n)
 	goto pad_tokens;
     }
 
-  while (num_tokens() <= n)
+  while (num_tokens () <= n)
     {
-      obstack_blank(&token_obstack,sizeof (struct token));
+      obstack_blank (&token_obstack, sizeof (struct token));
       tmp = ((struct token *)obstack_next_free (&token_obstack))-1;
-      tmp->yychar = real_yylex();
+      tmp->yychar = real_yylex ();
       tmp->end_of_file = end_of_file;
       tmp->yylval = yylval;
       end_of_file = 0;
@@ -173,7 +173,7 @@ scan_tokens (n)
 	pad_tokens:
 	  while (num_tokens () <= n)
 	    {
-	      obstack_blank(&token_obstack,sizeof (struct token));
+	      obstack_blank (&token_obstack, sizeof (struct token));
 	      tmp = ((struct token *)obstack_next_free (&token_obstack))-1;
 	      tmp->yychar = EMPTY;
 	      tmp->end_of_file = 0;
@@ -216,14 +216,14 @@ tree got_scope;
 tree got_object;
 
 int
-peekyylex()
+peekyylex ()
 {
   scan_tokens (0);
   return nth_token (0)->yychar;
 }
 
 int
-yylex()
+yylex ()
 {
   struct token tmp_token;
   tree trrr;
@@ -233,14 +233,14 @@ yylex()
   if (spew_debug)
   {
     yylex_ctr ++;
-    fprintf(stderr, "\t\t## %d ##",yylex_ctr);
+    fprintf (stderr, "\t\t## %d ##", yylex_ctr);
   }
 #endif
 
   /* if we've got tokens, send them */
-  if (num_tokens())
+  if (num_tokens ())
     {
-      tmp_token= *nth_token(0);
+      tmp_token= *nth_token (0);
 
       /* TMP_TOKEN.YYLVAL.TTYPE may have been allocated on the wrong obstack.
 	 If we don't find it in CURRENT_OBSTACK's current or immediately
@@ -258,13 +258,13 @@ yylex()
       tmp_token.yychar = real_yylex ();
       tmp_token.yylval = yylval;
       tmp_token.end_of_file = end_of_file;
-      add_token(&tmp_token);
+      add_token (&tmp_token);
     }
 
   /* many tokens just need to be returned. At first glance, all we
    * have to do is send them back up, but some of them are needed to
    * figure out local context. */
-  switch(tmp_token.yychar)
+  switch (tmp_token.yychar)
     {
     case EMPTY:
       /* This is a lexical no-op.  */
@@ -341,7 +341,7 @@ yylex()
       break;
 
     case AGGR:
-      *nth_token(0) = tmp_token;
+      *nth_token (0) = tmp_token;
       do_aggr ();
       /* fall through to output... */
     case ENUM:
@@ -349,7 +349,7 @@ yylex()
       looking_for_typename = 1;
       /* fall through... */
     default:
-      consume_token();
+      consume_token ();
     }
 
   got_object = NULL_TREE;
@@ -358,7 +358,7 @@ yylex()
   end_of_file = tmp_token.end_of_file;
 #ifdef SPEW_DEBUG    
   if (spew_debug)
-    debug_yychar(yychar);
+    debug_yychar (yychar);
 #endif
   return yychar;
 }
@@ -423,7 +423,7 @@ debug_yychar (yy)
   
   int i;
   
-  if(yy<256) {
+  if (yy<256) {
     fprintf (stderr, "<%d: %c >\n", yy, yy);
     return 0;
   }
diff --git a/gcc/cp/tree.c b/gcc/cp/tree.c
index fb484e2a6909..5c8fc1ce36be 100644
--- a/gcc/cp/tree.c
+++ b/gcc/cp/tree.c
@@ -800,9 +800,9 @@ layout_basetypes (rec, binfos)
 	  vbase_decls = decl;
 
 	  if (warn_nonvdtor && TYPE_HAS_DESTRUCTOR (basetype)
-	      && DECL_VINDEX (TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (basetype), 0)) == NULL_TREE)
+	      && DECL_VINDEX (TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (basetype), 1)) == NULL_TREE)
 	    {
-	      warning_with_decl (TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (basetype), 0),
+	      warning_with_decl (TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (basetype), 1),
 				 "destructor `%s' non-virtual");
 	      warning ("in inheritance relationship `%s: virtual %s'",
 		       TYPE_NAME_STRING (rec),
@@ -827,9 +827,9 @@ layout_basetypes (rec, binfos)
 	     claim it as theirs and explain exactly what circumstances
 	     warrant the warning.  */ 
 	  if (warn_nonvdtor && TYPE_HAS_DESTRUCTOR (basetype)
-	      && DECL_VINDEX (TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (basetype), 0)) == NULL_TREE)
+	      && DECL_VINDEX (TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (basetype), 1)) == NULL_TREE)
 	    {
-	      warning_with_decl (TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (basetype), 0),
+	      warning_with_decl (TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (basetype), 1),
 				 "destructor `%s' non-virtual");
 	      warning ("in inheritance relationship `%s:%s %s'",
 		       TYPE_NAME_STRING (rec),
@@ -1950,7 +1950,8 @@ min_tree_cons (purpose, value, chain)
   register struct obstack *ambient_obstack = current_obstack;
   current_obstack = &permanent_obstack;
 
-  node = tree_cons (purpose, value, chain);
+  node = tree_cons (copy_to_permanent (purpose),
+		    copy_to_permanent (value), chain);
   current_obstack = ambient_obstack;
   return node;
 }
diff --git a/gcc/cp/typeck.c b/gcc/cp/typeck.c
index 16f7228bf887..44e05b848b1a 100644
--- a/gcc/cp/typeck.c
+++ b/gcc/cp/typeck.c
@@ -1767,6 +1767,12 @@ build_component_ref (datum, component, basetype_path, protect)
       basetype = TREE_TYPE (datum);
       code = TREE_CODE (basetype);
     }
+  if (TREE_CODE (datum) == OFFSET_REF)
+    {
+      datum = resolve_offset_ref (datum);
+      basetype = TREE_TYPE (datum);
+      code = TREE_CODE (basetype);
+    }
 
   /* First, see if there is a field or component with name COMPONENT. */
   if (TREE_CODE (component) == TREE_LIST)
@@ -1803,7 +1809,7 @@ build_component_ref (datum, component, basetype_path, protect)
 	  cp_error ("type `%T' has no destructor", basetype);
 	  return error_mark_node;
 	}
-      return TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (basetype), 0);
+      return TREE_VEC_ELT (CLASSTYPE_METHOD_VEC (basetype), 1);
     }
 
   /* Look up component name in the structure type definition.  */
@@ -1905,7 +1911,8 @@ build_component_ref (datum, component, basetype_path, protect)
     {
       tree context = DECL_FIELD_CONTEXT (field);
       tree base = context;
-      while (base != basetype && ANON_AGGRNAME_P (TYPE_IDENTIFIER (base)))
+      while (base != basetype && TYPE_NAME (base)
+	     && ANON_AGGRNAME_P (TYPE_IDENTIFIER (base)))
 	{
 	  base = TYPE_CONTEXT (base);
 	}
@@ -1935,7 +1942,7 @@ build_component_ref (datum, component, basetype_path, protect)
       basetype = base;
  
       /* Handle things from anon unions here...  */
-      if (ANON_AGGRNAME_P (TYPE_IDENTIFIER (context)))
+      if (TYPE_NAME (context) && ANON_AGGRNAME_P (TYPE_IDENTIFIER (context)))
 	{
 	  tree subfield = lookup_anon_field (basetype, context);
 	  tree subdatum = build_component_ref (datum, subfield,
@@ -2231,6 +2238,23 @@ build_x_function_call (function, params, decl)
     return build_min_nt (CALL_EXPR, function, params, 0);
 
   type = TREE_TYPE (function);
+
+  if (TREE_CODE (type) == OFFSET_TYPE
+      && TREE_TYPE (type) == unknown_type_node
+      && TREE_CODE (function) == TREE_LIST
+      && TREE_CHAIN (function) == NULL_TREE)
+    {
+      /* Undo (Foo:bar)()... */
+      type = TYPE_OFFSET_BASETYPE (type);
+      function = TREE_VALUE (function);
+      my_friendly_assert (TREE_CODE (function) == TREE_LIST, 999);
+      my_friendly_assert (TREE_CHAIN (function) == NULL_TREE, 999);
+      function = TREE_VALUE (function);
+      my_friendly_assert (TREE_CODE (function) == FUNCTION_DECL, 999);
+      function = DECL_NAME (function);
+      return build_method_call (decl, function, params, TYPE_BINFO (type), LOOKUP_NORMAL);
+    }
+    
   is_method = ((TREE_CODE (function) == TREE_LIST
 		&& current_class_type != NULL_TREE
 		&& IDENTIFIER_CLASS_VALUE (TREE_PURPOSE (function)) == function)
@@ -2238,6 +2262,11 @@ build_x_function_call (function, params, decl)
 	       || TREE_CODE (type) == METHOD_TYPE
 	       || TYPE_PTRMEMFUNC_P (type));
 
+  if (TREE_CODE (function) == FUNCTION_DECL
+      && DECL_STATIC_FUNCTION_P (function))
+    return build_member_call
+      (DECL_CONTEXT (function), DECL_NAME (function), params);
+
   /* Handle methods, friends, and overloaded functions, respectively.  */
   if (is_method)
     {
@@ -2712,9 +2741,8 @@ convert_arguments (return_loc, typelist, values, fndecl, flags)
 	{
 	  if (fndecl)
 	    {
-	      char *buf = (char *)alloca (40 + strlen (called_thing));
-	      sprintf (buf, "too many arguments to %s `%%s'", called_thing);
-	      error_with_decl (fndecl, buf);
+	      cp_error_at ("too many arguments to %s `%+D'", called_thing,
+			   fndecl);
 	      error ("at this point in file");
 	    }
 	  else
@@ -4877,30 +4905,42 @@ build_conditional_expr (ifexp, op1, op2)
 	  cp_error ("aggregate mismatch in conditional expression: `%T' vs `%T'", type1, type2);
 	  return error_mark_node;
 	}
+      /* Warning: this code assumes that conversion between cv-variants of
+         a type is done using NOP_EXPRs.  */
       if (code1 == RECORD_TYPE && TYPE_HAS_CONVERSION (type1))
 	{
-	  tree tmp = build_type_conversion (CONVERT_EXPR, type2, op1, 0);
+	  tree tmp = build_pointer_type
+	    (build_type_variant (TREE_TYPE (type2), 1, 1));
+	  tmp = build_type_conversion (CONVERT_EXPR, tmp, op1, 0);
 	  if (tmp == NULL_TREE)
 	    {
-	      cp_error ("aggregate type `%T' could not convert on lhs of `:'", type1);
+	      cp_error ("incompatible types `%T' and `%T' in `?:'",
+			type1, type2);
 	      return error_mark_node;
 	    }
 	  if (tmp == error_mark_node)
 	    error ("ambiguous pointer conversion");
-	  result_type = type2;
+	  else
+	    STRIP_NOPS (tmp);
+	  result_type = common_type (type1, TREE_TYPE (tmp));
 	  op1 = tmp;
 	}
       else if (code2 == RECORD_TYPE && TYPE_HAS_CONVERSION (type2))
 	{
-	  tree tmp = build_type_conversion (CONVERT_EXPR, type1, op2, 0);
+	  tree tmp = build_pointer_type
+	    (build_type_variant (TREE_TYPE (type1), 1, 1));
+	  tmp = build_type_conversion (CONVERT_EXPR, tmp, op2, 0);
 	  if (tmp == NULL_TREE)
 	    {
-	      cp_error ("aggregate type `%T' could not convert on rhs of `:'", type2);
+	      cp_error ("incompatible types `%T' and `%T' in `?:'",
+			type1, type2);
 	      return error_mark_node;
 	    }
 	  if (tmp == error_mark_node)
 	    error ("ambiguous pointer conversion");
-	  result_type = type1;
+	  else
+	    STRIP_NOPS (tmp);
+	  result_type = common_type (type1, TREE_TYPE (tmp));
 	  op2 = tmp;
 	}
       else if (flag_cond_mismatch)
@@ -5183,12 +5223,6 @@ build_c_cast (type, expr, allow_nonconverting)
       return error_mark_node;
     }
 
-  /* If there's only one function in the overloaded space,
-     just take it.  */
-  if (TREE_CODE (value) == TREE_LIST
-      && TREE_CHAIN (value) == NULL_TREE)
-    value = TREE_VALUE (value);
-
   if (current_template_parms)
     {
       tree t = build_min (CAST_EXPR, type,
@@ -5471,9 +5505,9 @@ build_modify_expr (lhs, modifycode, rhs)
 	/* Do the default thing */;
       else
 	{
-	  result = build_method_call (lhs, constructor_name_full (lhstype),
+	  result = build_method_call (lhs, ctor_identifier,
 				      build_tree_list (NULL_TREE, rhs),
-				      NULL_TREE, LOOKUP_NORMAL);
+				      TYPE_BINFO (lhstype), LOOKUP_NORMAL);
 	  if (result == NULL_TREE)
 	    return error_mark_node;
 	  return result;
@@ -6688,7 +6722,7 @@ convert_for_initialization (exp, type, rhs, flags, errtype, fndecl, parmnum)
 	{
 	  if (TYPE_HAS_INIT_REF (type))
 	    {
-	      tree init = build_method_call (exp, constructor_name_full (type),
+	      tree init = build_method_call (exp, ctor_identifier,
 					     build_tree_list (NULL_TREE, rhs),
 					     TYPE_BINFO (type), LOOKUP_NORMAL);
 
@@ -6721,7 +6755,8 @@ convert_for_initialization (exp, type, rhs, flags, errtype, fndecl, parmnum)
 	  return rhs;
 	}
 
-      return cp_convert (type, rhs, CONV_OLD_CONVERT, flags);
+      return cp_convert (type, rhs, CONV_OLD_CONVERT,
+			 flags | LOOKUP_NO_CONVERSION);
     }
 
   if (type == TREE_TYPE (rhs))
diff --git a/gcc/cp/typeck2.c b/gcc/cp/typeck2.c
index 891a9f70a497..76ac10402e3a 100644
--- a/gcc/cp/typeck2.c
+++ b/gcc/cp/typeck2.c
@@ -71,29 +71,6 @@ binfo_or_else (parent_or_type, type)
   return NULL_TREE;
 }
 
-/* Print an error message stemming from an invalid use of an
-   aggregate type.
-
-   TYPE is the type or binfo which draws the error.
-   MSG is the message to print.
-   ARG is an optional argument which may provide more information.  */
-void
-error_with_aggr_type (type, msg, arg)
-     tree type;
-     char *msg;
-     HOST_WIDE_INT arg;
-{
-  tree name;
-
-  if (TREE_CODE (type) == TREE_VEC)
-    type = BINFO_TYPE (type);
-
-  name = TYPE_NAME (type);
-  if (TREE_CODE (name) == TYPE_DECL)
-    name = DECL_NAME (name);
-  error (msg, IDENTIFIER_POINTER (name), arg);
-}
-
 /* According to ARM $7.1.6, "A `const' object may be initialized, but its
    value may not be changed thereafter.  Thus, we emit hard errors for these,
    rather than just pedwarns.  If `SOFT' is 1, then we just pedwarn.  (For
@@ -108,40 +85,37 @@ readonly_error (arg, string, soft)
   void (*fn)();
 
   if (soft)
-    fn = pedwarn;
+    fn = cp_pedwarn;
   else
-    fn = error;
+    fn = cp_error;
 
   if (TREE_CODE (arg) == COMPONENT_REF)
     {
       if (TYPE_READONLY (TREE_TYPE (TREE_OPERAND (arg, 0))))
-        fmt = "%s of member `%s' in read-only structure";
+        fmt = "%s of member `%D' in read-only structure";
       else
-        fmt = "%s of read-only member `%s'";
-      (*fn) (fmt, string, lang_printable_name (TREE_OPERAND (arg, 1)));
+        fmt = "%s of read-only member `%D'";
+      (*fn) (fmt, string, TREE_OPERAND (arg, 1));
     }
   else if (TREE_CODE (arg) == VAR_DECL)
     {
       if (DECL_LANG_SPECIFIC (arg)
 	  && DECL_IN_AGGR_P (arg)
 	  && !TREE_STATIC (arg))
-	fmt = "%s of constant field `%s'";
+	fmt = "%s of constant field `%D'";
       else
-	fmt = "%s of read-only variable `%s'";
-      (*fn) (fmt, string, lang_printable_name (arg));
+	fmt = "%s of read-only variable `%D'";
+      (*fn) (fmt, string, arg);
     }
   else if (TREE_CODE (arg) == PARM_DECL)
-    (*fn) ("%s of read-only parameter `%s'", string,
-	   lang_printable_name (arg));
+    (*fn) ("%s of read-only parameter `%D'", string, arg);
   else if (TREE_CODE (arg) == INDIRECT_REF
            && TREE_CODE (TREE_TYPE (TREE_OPERAND (arg, 0))) == REFERENCE_TYPE
            && (TREE_CODE (TREE_OPERAND (arg, 0)) == VAR_DECL
                || TREE_CODE (TREE_OPERAND (arg, 0)) == PARM_DECL))
-    (*fn) ("%s of read-only reference `%s'",
-	   string, lang_printable_name (TREE_OPERAND (arg, 0)));
+    (*fn) ("%s of read-only reference `%D'", string, TREE_OPERAND (arg, 0));
   else if (TREE_CODE (arg) == RESULT_DECL)
-    (*fn) ("%s of read-only named return value `%s'",
-	   string, lang_printable_name (arg));
+    (*fn) ("%s of read-only named return value `%D'", string, arg);
   else	       
     (*fn) ("%s of read-only location", string);
 }
@@ -239,8 +213,7 @@ incomplete_type_error (value, type)
 
   if (value != 0 && (TREE_CODE (value) == VAR_DECL
 		     || TREE_CODE (value) == PARM_DECL))
-    error ("`%s' has an incomplete type",
-	   IDENTIFIER_POINTER (DECL_NAME (value)));
+    cp_error ("`%D' has incomplete type", value);
   else
     {
     retry:
@@ -249,15 +222,9 @@ incomplete_type_error (value, type)
       switch (TREE_CODE (type))
 	{
 	case RECORD_TYPE:
-	  errmsg = "invalid use of undefined type `struct %s'";
-	  break;
-
 	case UNION_TYPE:
-	  errmsg = "invalid use of undefined type `union %s'";
-	  break;
-
 	case ENUMERAL_TYPE:
-	  errmsg = "invalid use of undefined type `enum %s'";
+	  errmsg = "invalid use of undefined type `%#T'";
 	  break;
 
 	case VOID_TYPE:
@@ -281,7 +248,7 @@ incomplete_type_error (value, type)
 	  my_friendly_abort (108);
 	}
 
-      error_with_aggr_type (type, errmsg);
+      cp_error (errmsg, type);
     }
 }
 
@@ -1410,28 +1377,23 @@ build_m_component_ref (datum, component)
   return build (OFFSET_REF, rettype, datum, component);
 }
 
-/* Return a tree node for the expression TYPENAME '(' PARMS ')'.
-
-   Because we cannot tell whether this construct is really a call to a
-   constructor or a request for a type conversion, we try both, and
-   report any ambiguities we find.  */
+/* Return a tree node for the expression TYPENAME '(' PARMS ')'.  */
 tree
 build_functional_cast (exp, parms)
      tree exp;
      tree parms;
 {
+  tree binfo;
+
   /* This is either a call to a constructor,
      or a C cast in C++'s `functional' notation.  */
-  tree type, name = NULL_TREE;
-  tree expr_as_ctor = NULL_TREE;
+  tree type;
 
   if (exp == error_mark_node || parms == error_mark_node)
     return error_mark_node;
 
   if (TREE_CODE (exp) == IDENTIFIER_NODE)
     {
-      name = exp;
-
       if (IDENTIFIER_HAS_TYPE_VALUE (exp))
 	/* Either an enum or an aggregate type.  */
 	type = IDENTIFIER_TYPE_VALUE (exp);
@@ -1440,7 +1402,7 @@ build_functional_cast (exp, parms)
 	  type = lookup_name (exp, 1);
 	  if (!type || TREE_CODE (type) != TYPE_DECL)
 	    {
-	      cp_error ("`%T' fails to be a typedef or built-in type", name);
+	      cp_error ("`%T' fails to be a typedef or built-in type", exp);
 	      return error_mark_node;
 	    }
 	  type = TREE_TYPE (type);
@@ -1482,13 +1444,6 @@ build_functional_cast (exp, parms)
 	 
      then the slot being initialized will be filled in.  */
 
-  if (name == NULL_TREE)
-    {
-      name = TYPE_NAME (type);
-      if (TREE_CODE (name) == TYPE_DECL)
-	name = DECL_NESTED_TYPENAME (name);
-    }
-
   if (TYPE_SIZE (complete_type (type)) == NULL_TREE)
     {
       cp_error ("type `%T' is not yet defined", type);
@@ -1496,15 +1451,15 @@ build_functional_cast (exp, parms)
     }
 
   if (parms && TREE_CHAIN (parms) == NULL_TREE)
-    return build_c_cast (type, parms, 1);
+    return build_c_cast (type, TREE_VALUE (parms), 1);
 
-  expr_as_ctor = build_method_call (NULL_TREE, name, parms,
-				    NULL_TREE, LOOKUP_NORMAL);
+  exp = build_method_call (NULL_TREE, ctor_identifier, parms,
+			   TYPE_BINFO (type), LOOKUP_NORMAL);
 
-  if (expr_as_ctor == error_mark_node)
+  if (exp == error_mark_node)
     return error_mark_node;
 
-  return build_cplus_new (type, expr_as_ctor);
+  return build_cplus_new (type, exp);
 }
 
 /* Return the character string for the name that encodes the
-- 
GitLab