From eb34af89c78f8b04af925cc272e4462c0316f54b Mon Sep 17 00:00:00 2001
From: Richard Kenner <kenner@gcc.gnu.org>
Date: Thu, 18 Mar 2004 15:58:49 -0500
Subject: [PATCH] tree.h (TREE_CHECK2, [...]): New macros.

	* tree.h (TREE_CHECK2, TREE_CHECK3, TREE_CHECK5): New macros.
	(tree_check2_failed, tree_check3_failed, tree_check5_failed): New decl.
	(FUNC_OR_METHOD_CHECK, SET_ARRAY_OR_VECTOR_CHECK): New macros.
	(REC_OR_UNION_CHECK, NUMERICAL_TYPE_CHECK): Likewise.
	(TYPE_VALUES, TYPE_DOMAIN, TYPE_FIELDS, TYPE_METHODS, TYPE_VFIELD):
	Protect with proper check.
	(TYPE_ARG_TYPES, TYPE_METHOD_BASETYPE, TYPE_OFFSET_BASETYPE): Likewise.
	(TYPE_MIN_VALUE, TYPE_MAX_VALUE): Likewise.
	* tree.c (type_hash_eq): Rewrite to access proper fields for each type.
	(tree_check2_failed, tree_check3_failed, tree_check5_failed): New.
	* c-typeck.c (build_array_ref): Use TYPE_DOMAIN, not TYPE_VALUES.
	* dwarf2out.c (gen_enumeration_type_die): Use TYPE_VALUES,
	not TYPE_FIELDS.

	* cp/class.c (finish_struct_bits): Use TYPE_VFIELD and TYPE_METHODS.
	* cp/error.c (dump_type): Use TYPEOF_TYPE_EXPR.
	* cp/pt.c (tsubst): Likewise.
	* cp/semantics.c (finish_typeof): Likewise.
	* cp/search.c (dfs_unuse_fields): Handle TYPENAME_TYPE, TYPEOF_TYPE,
	and TEMPLATE_TYPE_PARM.
	* cp/typeck.c (comptypes): Use TYPE_ORIG_SIZE_TYPE, not TYPE_DOMAIN.
	(build_array_ref): Use TYPE_DOMAIN, not TYPE_VALUES.

	* java/java-tree.h: Changes throughout to add checking to macros
	and numerous whitespace changes.
	(VAR_OR_FIELD_CHECK): New macro.
	* java/jcf-write.c (get_access_flags): Use FIELD_PUBLIC, METHOD_PUBLIC,
	FIELD_FINAL, and METHOD_FINAL instead of CLASS_PUBLIC and CLASS_FINAL.

	* ada/ada-tree.h (TYPE_LEFT_JUSTIFIED_MODULAR_P): Add checking.
	(TYPE_CONTAINS_TEMPLATE_P, TYPE_OBJECT_RECORD_TYPE): Likewise.
	(TYPE_RM_SIZE_INT): Directly use type.values.
	(TREE_LOOP_ID): Clean up check.
	* ada/decl.c (gnat_to_gnu_entity, case E_Enumeration_Type): Use
	TYPE_VALUES, not TYPE_FIELDS.
	* ada/trans.c (convert_with_check): Delay access of bounds of basetype
	until sure is numeric.

From-SVN: r79638
---
 gcc/ChangeLog        |  18 +++
 gcc/ada/ChangeLog    |  11 ++
 gcc/ada/ada-tree.h   |  19 ++-
 gcc/ada/decl.c       |   2 +-
 gcc/ada/trans.c      |   8 +-
 gcc/c-typeck.c       |   4 +-
 gcc/cp/ChangeLog     |  11 ++
 gcc/cp/class.c       |   4 +-
 gcc/cp/error.c       |   2 +-
 gcc/cp/pt.c          |   4 +-
 gcc/cp/search.c      |  11 +-
 gcc/cp/semantics.c   |   2 +-
 gcc/cp/typeck.c      |  12 +-
 gcc/dwarf2out.c      |   2 +-
 gcc/java/ChangeLog   |   8 +
 gcc/java/java-tree.h | 347 ++++++++++++++++++++++---------------------
 gcc/java/jcf-write.c |  17 ++-
 gcc/tree.c           | 154 +++++++++++++++----
 gcc/tree.h           |  94 +++++++++---
 19 files changed, 490 insertions(+), 240 deletions(-)

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 765eca8d883f..b6c327c9674f 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,8 +1,25 @@
+2004-03-18  Richard Kenner  <kenner@vlsi1.ultra.nyu.edu>
+	
+	* tree.h (TREE_CHECK2, TREE_CHECK3, TREE_CHECK5): New macros.
+	(tree_check2_failed, tree_check3_failed, tree_check5_failed): New decl.
+	(FUNC_OR_METHOD_CHECK, SET_ARRAY_OR_VECTOR_CHECK): New macros.
+	(REC_OR_UNION_CHECK, NUMERICAL_TYPE_CHECK): Likewise.
+	(TYPE_VALUES, TYPE_DOMAIN, TYPE_FIELDS, TYPE_METHODS, TYPE_VFIELD):
+	Protect with proper check.
+	(TYPE_ARG_TYPES, TYPE_METHOD_BASETYPE, TYPE_OFFSET_BASETYPE): Likewise.
+	(TYPE_MIN_VALUE, TYPE_MAX_VALUE): Likewise.
+	* tree.c (type_hash_eq): Rewrite to access proper fields for each type.
+	(tree_check2_failed, tree_check3_failed, tree_check5_failed): New.
+	* c-typeck.c (build_array_ref): Use TYPE_DOMAIN, not TYPE_VALUES.
+	* dwarf2out.c (gen_enumeration_type_die): Use TYPE_VALUES,
+	not TYPE_FIELDS.
+
 2004-03-18  Mostafa Hagog  <mustafa@il.ibm.com>
 
 	* gcse.c (eliminate_partially_redundant_loads): Reject change if
 	dest is set between beginning and current insn.
 
+>>>>>>> 2.3204
 2004-03-18  Mark Mitchell  <mark@codesourcery.com>
 
 	* c-decl.c (grokdeclarator): Do not complain about redeclaring
@@ -47,6 +64,7 @@
         * config/rs6000/rs6000.h: Definition of DWARF_CIE_DATA_ALIGNMENT
         macro for mixed mode.
 
+>>>>>>> 2.3203
 2004-03-18  Jan Hubicka  <jh@suse.cz>
 
 	* predict.c (propagate_freq): Compute correctly frequency of
diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index 5e2af3e25334..c614f8f06de4 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,14 @@
+2004-03-18  Richard Kenner  <kenner@vlsi1.ultra.nyu.edu>
+
+	* ada-tree.h (TYPE_LEFT_JUSTIFIED_MODULAR_P): Add checking.
+	(TYPE_CONTAINS_TEMPLATE_P, TYPE_OBJECT_RECORD_TYPE): Likewise.
+	(TYPE_RM_SIZE_INT): Directly use type.values.
+	(TREE_LOOP_ID): Clean up check.
+	* decl.c (gnat_to_gnu_entity, case E_Enumeration_Type): Use
+	TYPE_VALUES, not TYPE_FIELDS.
+	* trans.c (convert_with_check): Delay access of bounds of basetype
+	until sure is numeric.
+
 2004-03-18  Arnaud Charlet  <charlet@act-europe.fr>
 
 	* 5atpopsp.adb: Remove RTEMS from list of platforms using this file.
diff --git a/gcc/ada/ada-tree.h b/gcc/ada/ada-tree.h
index d7767e274e4a..78d9a56de6a5 100644
--- a/gcc/ada/ada-tree.h
+++ b/gcc/ada/ada-tree.h
@@ -95,7 +95,8 @@ struct lang_type GTY(())
 
 /* For RECORD_TYPE, UNION_TYPE, and QUAL_UNION_TYPE, nonzero if this denotes
    a left-justified modular type (will only be true for RECORD_TYPE).  */
-#define TYPE_LEFT_JUSTIFIED_MODULAR_P(NODE) TYPE_LANG_FLAG_1 (NODE)
+#define TYPE_LEFT_JUSTIFIED_MODULAR_P(NODE) \
+  TYPE_LANG_FLAG_1 (REC_OR_UNION_CHECK (NODE))
 
 /* Nonzero in an arithmetic subtype if this is a subtype not known to the
    front-end.  */
@@ -107,7 +108,8 @@ struct lang_type GTY(())
 /* For RECORD_TYPE, UNION_TYPE, and QUAL_UNION_TYPE, nonzero if this is the
    type for an object whose type includes its template in addition to
    its value (only true for RECORD_TYPE).  */
-#define TYPE_CONTAINS_TEMPLATE_P(NODE) TYPE_LANG_FLAG_3 (NODE)
+#define TYPE_CONTAINS_TEMPLATE_P(NODE) \
+  TYPE_LANG_FLAG_3 (REC_OR_UNION_CHECK (NODE))
 
 /* For INTEGER_TYPE, nonzero if this really represents a VAX
    floating-point type.  */
@@ -188,7 +190,7 @@ struct lang_type GTY(())
   (TYPE_LANG_SPECIFIC (INTEGER_TYPE_CHECK (NODE)) = (struct lang_type *) (X))
 
 /* For INTEGER_TYPE, stores the RM_Size of the type.  */
-#define TYPE_RM_SIZE_INT(NODE)	TYPE_VALUES (INTEGER_TYPE_CHECK (NODE))
+#define TYPE_RM_SIZE_INT(NODE)	(INTEGER_TYPE_CHECK (NODE)->type.values)
 
 /* Likewise for ENUMERAL_TYPE.  */
 #define TYPE_RM_SIZE_ENUM(NODE)	\
@@ -224,8 +226,13 @@ struct lang_type GTY(())
   (TYPE_LANG_SPECIFIC (NODE) = (struct lang_type *)(X))
 
 /* In an UNCONSTRAINED_ARRAY_TYPE, points to the record containing both
-   the template and object.  */
-#define TYPE_OBJECT_RECORD_TYPE(NODE) TYPE_MIN_VALUE (NODE)
+   the template and object.
+
+   ??? We also put this on an ENUMERAL_TYPE that's dummy.  Technically,
+   this is a conflict on the minval field, but there doesn't seem to be
+   simple fix, so we'll live with this kludge for now.  */
+#define TYPE_OBJECT_RECORD_TYPE(NODE) \
+  (TREE_CHECK2 ((NODE), UNCONSTRAINED_ARRAY_TYPE, ENUMERAL_TYPE)->type.minval)
 
 /* Nonzero in a FUNCTION_DECL that represents a stubbed function
    discriminant.  */
@@ -277,7 +284,7 @@ struct lang_type GTY(())
 
 /* This is the loop id for a GNAT_LOOP_ID node.  */
 #define TREE_LOOP_ID(NODE) \
-  ((union lang_tree_node *) TREE_CHECK (NODE, GNAT_LOOP_ID))->loop_id.loop_id
+  ((union lang_tree_node *) GNAT_LOOP_ID_CHECK (NODE))->loop_id.loop_id
 
 /* Define fields and macros for statements.
 
diff --git a/gcc/ada/decl.c b/gcc/ada/decl.c
index 8891f607b06b..1ca2304e5972 100644
--- a/gcc/ada/decl.c
+++ b/gcc/ada/decl.c
@@ -1172,7 +1172,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 					  gnu_value, gnu_literal_list);
 	  }
 
-	TYPE_FIELDS (gnu_type) = nreverse (gnu_literal_list);
+	TYPE_VALUES (gnu_type) = nreverse (gnu_literal_list);
 
 	/* Note that the bounds are updated at the end of this function
 	   because to avoid an infinite recursion when we get the bounds of
diff --git a/gcc/ada/trans.c b/gcc/ada/trans.c
index fb1b766da778..69e80d48c280 100644
--- a/gcc/ada/trans.c
+++ b/gcc/ada/trans.c
@@ -4714,10 +4714,6 @@ convert_with_check (Entity_Id gnat_type,
   tree gnu_in_basetype = get_base_type (gnu_in_type);
   tree gnu_base_type = get_base_type (gnu_type);
   tree gnu_ada_base_type = get_ada_base_type (gnu_type);
-  tree gnu_in_lb = TYPE_MIN_VALUE (gnu_in_basetype);
-  tree gnu_in_ub = TYPE_MAX_VALUE (gnu_in_basetype);
-  tree gnu_out_lb = TYPE_MIN_VALUE (gnu_base_type);
-  tree gnu_out_ub = TYPE_MAX_VALUE (gnu_base_type);
   tree gnu_result = gnu_expr;
 
   /* If we are not doing any checks, the output is an integral type, and
@@ -4745,6 +4741,10 @@ convert_with_check (Entity_Id gnat_type,
       /* Ensure GNU_EXPR only gets evaluated once.  */
       tree gnu_input = protect_multiple_eval (gnu_result);
       tree gnu_cond = integer_zero_node;
+      tree gnu_in_lb = TYPE_MIN_VALUE (gnu_in_basetype);
+      tree gnu_in_ub = TYPE_MAX_VALUE (gnu_in_basetype);
+      tree gnu_out_lb = TYPE_MIN_VALUE (gnu_base_type);
+      tree gnu_out_ub = TYPE_MAX_VALUE (gnu_base_type);
 
       /* Convert the lower bounds to signed types, so we're sure we're
 	 comparing them properly.  Likewise, convert the upper bounds
diff --git a/gcc/c-typeck.c b/gcc/c-typeck.c
index c532cc6eb69d..1d069a9289cd 100644
--- a/gcc/c-typeck.c
+++ b/gcc/c-typeck.c
@@ -1510,8 +1510,8 @@ build_array_ref (tree array, tree index)
 	 would get a crash in store_bit_field/extract_bit_field when trying
 	 to access a non-existent part of the register.  */
       if (TREE_CODE (index) == INTEGER_CST
-	  && TYPE_VALUES (TREE_TYPE (array))
-	  && ! int_fits_type_p (index, TYPE_VALUES (TREE_TYPE (array))))
+	  && TYPE_DOMAIN (TREE_TYPE (array))
+	  && ! int_fits_type_p (index, TYPE_DOMAIN (TREE_TYPE (array))))
 	{
 	  if (!c_mark_addressable (array))
 	    return error_mark_node;
diff --git a/gcc/cp/ChangeLog b/gcc/cp/ChangeLog
index 408fa1ce7dc0..9ce136ba4431 100644
--- a/gcc/cp/ChangeLog
+++ b/gcc/cp/ChangeLog
@@ -1,3 +1,14 @@
+2004-03-18  Richard Kenner  <kenner@vlsi1.ultra.nyu.edu>
+
+	* class.c (finish_struct_bits): Use TYPE_VFIELD and TYPE_METHODS.
+	* error.c (dump_type): Use TYPEOF_TYPE_EXPR.
+	* pt.c (tsubst): Likewise.
+	* semantics.c (finish_typeof): Likewise.
+	* search.c (dfs_unuse_fields): Handle TYPENAME_TYPE, TYPEOF_TYPE,
+	and TEMPLATE_TYPE_PARM.
+	* typeck.c (comptypes): Use TYPE_ORIG_SIZE_TYPE, not TYPE_DOMAIN.
+	(build_array_ref): Use TYPE_DOMAIN, not TYPE_VALUES.
+
 2004-03-16  Mark Mitchell  <mark@codesourcery.com>
 
 	PR c++/14586
diff --git a/gcc/cp/class.c b/gcc/cp/class.c
index eddfda80429c..de0517f5b094 100644
--- a/gcc/cp/class.c
+++ b/gcc/cp/class.c
@@ -1422,8 +1422,8 @@ finish_struct_bits (tree t)
       TYPE_POLYMORPHIC_P (variants) = TYPE_POLYMORPHIC_P (t);
       TYPE_USES_VIRTUAL_BASECLASSES (variants) = TYPE_USES_VIRTUAL_BASECLASSES (t);
       /* Copy whatever these are holding today.  */
-      TYPE_MIN_VALUE (variants) = TYPE_MIN_VALUE (t);
-      TYPE_MAX_VALUE (variants) = TYPE_MAX_VALUE (t);
+      TYPE_VFIELD (variants) = TYPE_VFIELD (t);
+      TYPE_METHODS (variants) = TYPE_METHODS (t);
       TYPE_FIELDS (variants) = TYPE_FIELDS (t);
       TYPE_SIZE (variants) = TYPE_SIZE (t);
       TYPE_SIZE_UNIT (variants) = TYPE_SIZE_UNIT (t);
diff --git a/gcc/cp/error.c b/gcc/cp/error.c
index bbd90c9d1881..5b2490e76f29 100644
--- a/gcc/cp/error.c
+++ b/gcc/cp/error.c
@@ -404,7 +404,7 @@ dump_type (tree t, int flags)
 
     case TYPEOF_TYPE:
       pp_string (cxx_pp, "__typeof (");
-      dump_expr (TYPE_FIELDS (t), flags & ~TFF_EXPR_IN_PARENS);
+      dump_expr (TYPEOF_TYPE_EXPR (t), flags & ~TFF_EXPR_IN_PARENS);
       pp_right_paren (cxx_pp);
       break;
 
diff --git a/gcc/cp/pt.c b/gcc/cp/pt.c
index 6001b1c027dd..365cb18bf668 100644
--- a/gcc/cp/pt.c
+++ b/gcc/cp/pt.c
@@ -7223,8 +7223,8 @@ tsubst (tree t, tree args, tsubst_flags_t complain, tree in_decl)
       {
 	tree type;
 
-	type = finish_typeof (tsubst_expr (TYPE_FIELDS (t), args, complain, 
-					   in_decl));
+	type = finish_typeof (tsubst_expr (TYPEOF_TYPE_EXPR (t), args,
+					   complain, in_decl));
 	return cp_build_qualified_type_real (type,
 					     cp_type_quals (t)
 					     | cp_type_quals (type),
diff --git a/gcc/cp/search.c b/gcc/cp/search.c
index 5b66000c34e5..30dc0d29e45a 100644
--- a/gcc/cp/search.c
+++ b/gcc/cp/search.c
@@ -2249,7 +2249,16 @@ dfs_unuse_fields (tree binfo, void *data ATTRIBUTE_UNUSED)
   tree type = TREE_TYPE (binfo);
   tree fields;
 
-  for (fields = TYPE_FIELDS (type); fields; fields = TREE_CHAIN (fields))
+  if (TREE_CODE (type) == TYPENAME_TYPE)
+    fields = TYPENAME_TYPE_FULLNAME (type);
+  else if (TREE_CODE (type) == TYPEOF_TYPE)
+    fields = TYPEOF_TYPE_EXPR (type);
+  else if (TREE_CODE (type) == TEMPLATE_TYPE_PARM)
+    fields = TEMPLATE_TYPE_PARM_INDEX (type);
+  else
+    fields = TYPE_FIELDS (type);
+
+  for (; fields; fields = TREE_CHAIN (fields))
     {
       if (TREE_CODE (fields) != FIELD_DECL || DECL_ARTIFICIAL (fields))
 	continue;
diff --git a/gcc/cp/semantics.c b/gcc/cp/semantics.c
index 9142a2c12186..e7d377173bb6 100644
--- a/gcc/cp/semantics.c
+++ b/gcc/cp/semantics.c
@@ -2685,7 +2685,7 @@ finish_typeof (tree expr)
   if (type_dependent_expression_p (expr))
     {
       type = make_aggr_type (TYPEOF_TYPE);
-      TYPE_FIELDS (type) = expr;
+      TYPEOF_TYPE_EXPR (type) = expr;
 
       return type;
     }
diff --git a/gcc/cp/typeck.c b/gcc/cp/typeck.c
index 31ca3e0ce001..10103c8aecbb 100644
--- a/gcc/cp/typeck.c
+++ b/gcc/cp/typeck.c
@@ -953,12 +953,12 @@ comptypes (tree t1, tree t2, int strict)
   /* If either type is the internal version of sizetype, use the
      language version.  */
   if (TREE_CODE (t1) == INTEGER_TYPE && TYPE_IS_SIZETYPE (t1)
-      && TYPE_DOMAIN (t1))
-    t1 = TYPE_DOMAIN (t1);
+      && TYPE_ORIG_SIZE_TYPE (t1))
+    t1 = TYPE_ORIG_SIZE_TYPE (t1);
 
   if (TREE_CODE (t2) == INTEGER_TYPE && TYPE_IS_SIZETYPE (t2)
-      && TYPE_DOMAIN (t2))
-    t2 = TYPE_DOMAIN (t2);
+      && TYPE_ORIG_SIZE_TYPE (t2))
+    t2 = TYPE_ORIG_SIZE_TYPE (t2);
 
   if (TYPE_PTRMEMFUNC_P (t1))
     t1 = TYPE_PTRMEMFUNC_FN_TYPE (t1);
@@ -2197,8 +2197,8 @@ build_array_ref (tree array, tree idx)
 	 would get a crash in store_bit_field/extract_bit_field when trying
 	 to access a non-existent part of the register.  */
       if (TREE_CODE (idx) == INTEGER_CST
-	  && TYPE_VALUES (TREE_TYPE (array))
-	  && ! int_fits_type_p (idx, TYPE_VALUES (TREE_TYPE (array))))
+	  && TYPE_DOMAIN (TREE_TYPE (array))
+	  && ! int_fits_type_p (idx, TYPE_DOMAIN (TREE_TYPE (array))))
 	{
 	  if (!cxx_mark_addressable (array))
 	    return error_mark_node;
diff --git a/gcc/dwarf2out.c b/gcc/dwarf2out.c
index 88a06e2b566a..485dc2678d6e 100644
--- a/gcc/dwarf2out.c
+++ b/gcc/dwarf2out.c
@@ -10860,7 +10860,7 @@ gen_enumeration_type_die (tree type, dw_die_ref context_die)
       if (type_die->die_parent == NULL)
 	add_child_die (scope_die_for (type, context_die), type_die);
 
-      for (link = TYPE_FIELDS (type);
+      for (link = TYPE_VALUES (type);
 	   link != NULL; link = TREE_CHAIN (link))
 	{
 	  dw_die_ref enum_die = new_die (DW_TAG_enumerator, type_die, link);
diff --git a/gcc/java/ChangeLog b/gcc/java/ChangeLog
index 2f48c3527be2..39e3aef3b00d 100644
--- a/gcc/java/ChangeLog
+++ b/gcc/java/ChangeLog
@@ -1,3 +1,11 @@
+2004-03-18  Richard Kenner <kenner@vlsi1.ultra.nyu.edu>
+
+	* java-tree.h: Changes throughout to add checking to macros
+	and numerous whitespace changes.
+	(VAR_OR_FIELD_CHECK): New macro.
+	* jcf-write.c (get_access_flags): Use FIELD_PUBLIC, METHOD_PUBLIC,
+	FIELD_FINAL, and METHOD_FINAL instead of CLASS_PUBLIC and CLASS_FINAL.
+
 2004-03-16  Per Bothner  <per@bothner.com>
 
 	* jcf-jump.c (options):  New --print-constants option.
diff --git a/gcc/java/java-tree.h b/gcc/java/java-tree.h
index ded58a60422b..57931b8d16e3 100644
--- a/gcc/java/java-tree.h
+++ b/gcc/java/java-tree.h
@@ -117,9 +117,12 @@ struct JCF;
       FIELD_THISN (in FIELD_DECL)
 */
 
+#define VAR_OR_FIELD_CHECK(DECL) \
+  TREE_CHECK3 (DECL, FIELD_DECL, VAR_DECL, PARM_DECL)
+
 /* True if the class whose TYPE_BINFO this is has a superclass.
    (True of all classes except Object.) */
-#define CLASS_HAS_SUPER_FLAG(BINFO) TREE_LANG_FLAG_1(BINFO)
+#define CLASS_HAS_SUPER_FLAG(BINFO) TREE_LANG_FLAG_1 (TREE_VEC_CHECK (BINFO))
 #define CLASS_HAS_SUPER(TYPE) CLASS_HAS_SUPER_FLAG (TYPE_BINFO (TYPE))
 
 /* Return the supertype of class TYPE, or NULL_TREE is it has none. */
@@ -822,61 +825,63 @@ union lang_tree_node
   (DECL_LANG_SPECIFIC(DECL)->u.f.init_calls_this)
 
 /* True when DECL (a field) is Synthetic.  */
-#define FIELD_SYNTHETIC(DECL) DECL_LANG_FLAG_2 (DECL)
+#define FIELD_SYNTHETIC(DECL) DECL_LANG_FLAG_2 (VAR_OR_FIELD_CHECK (DECL))
 
 /* True when DECL aliases an outer context local variable.  */
-#define FIELD_LOCAL_ALIAS(DECL) DECL_LANG_FLAG_6 (DECL)
+#define FIELD_LOCAL_ALIAS(DECL) DECL_LANG_FLAG_6 (VAR_OR_FIELD_CHECK (DECL))
 
 /* True when DECL, which aliases an outer context local variable is
    used by the inner classe */
-#define FIELD_LOCAL_ALIAS_USED(DECL) DECL_LANG_FLAG_7 (DECL)
+#define FIELD_LOCAL_ALIAS_USED(DECL) DECL_LANG_FLAG_7 (VAR_OR_FIELD_CHECK (DECL))
 
 /* True when DECL is a this$<n> field. Note that
    FIELD_LOCAL_ALIAS_USED can be differentiated when tested against
    FIELD_LOCAL_ALIAS.  */
-#define FIELD_THISN(DECL) DECL_LANG_FLAG_7 (DECL)
+#define FIELD_THISN(DECL) DECL_LANG_FLAG_7 (VAR_OR_FIELD_CHECK (DECL))
 
 /* In a LABEL_DECL, a TREE_VEC that saves the type_map at that point. */
-#define LABEL_TYPE_STATE(NODE) (DECL_INITIAL (NODE))
+#define LABEL_TYPE_STATE(NODE) (DECL_INITIAL (LABEL_DECL_CHECK (NODE)))
 
 /* In the label of a subroutine, a dummy label that records the
    state following a merge of all the ret instructions in this subroutine. */
 #define LABEL_RETURN_LABEL(DECL) DECL_ARGUMENTS(DECL)
 
 /* In the label of a sub-routine, records the type state at return.
- * A local may be TYPE_UNUSED, which means that the local is not
- * used (stored to or loaded from) in this subroutine - at least for
- * code that we have verified so far. */
-#define LABEL_RETURN_TYPE_STATE(NODE) LABEL_TYPE_STATE (LABEL_RETURN_LABEL (NODE))
+   A local may be TYPE_UNUSED, which means that the local is not
+   used (stored to or loaded from) in this subroutine - at least for
+   code that we have verified so far. */
+#define LABEL_RETURN_TYPE_STATE(NODE) \
+  LABEL_TYPE_STATE (LABEL_RETURN_LABEL (NODE))
 
 /* In a TREE_VEC for a LABEL_RETURN_TYPE_STATE, notes that
    TREE_VEC_LENGTH has been adjusted to the correct stack size. */
-#define RETURN_MAP_ADJUSTED(NODE) TREE_LANG_FLAG_2(NODE)
+#define RETURN_MAP_ADJUSTED(NODE) TREE_LANG_FLAG_2 (TREE_VEC_CHECK (NODE))
 
 /* In the label of a sub-routine, a chain of the return location labels. */
 #define LABEL_RETURN_LABELS(node) \
-  (LABEL_DECL_CHECK (LABEL_RETURN_LABEL(node))->decl.result)
+  (LABEL_DECL_CHECK (LABEL_RETURN_LABEL (node))->decl.result)
 
 /* In a LABEL_DECL, the next pending label.
    See pending_blocks in expr.c. */
 #define LABEL_PENDING_CHAIN(NODE) (LABEL_DECL_CHECK (NODE)->decl.result)
 
 /* In a LABEL_DECL, the corresponding bytecode program counter. */
-#define LABEL_PC(NODE) ((NODE)->decl.u2.i)
+#define LABEL_PC(NODE) (LABEL_DECL_CHECK (NODE)->decl.u2.i)
 
 /* Used during verification to mark the label has "changed". (See JVM Spec). */
-#define LABEL_CHANGED(NODE) DECL_LANG_FLAG_6(NODE)
+#define LABEL_CHANGED(NODE) DECL_LANG_FLAG_6 (LABEL_DECL_CHECK (NODE))
 
 /* In a LABEL_DECL, true if we have verified instructions starting here. */
-#define LABEL_VERIFIED(NODE) (instruction_bits[LABEL_PC(NODE)]&BCODE_VERIFIED)
+#define LABEL_VERIFIED(NODE) \
+  (instruction_bits[LABEL_PC (NODE)] & BCODE_VERIFIED)
 
 /* True if this code is within a subroutine (target of a jsr). */
-#define LABEL_IN_SUBR(NODE) DECL_LANG_FLAG_4(NODE)
+#define LABEL_IN_SUBR(NODE) DECL_LANG_FLAG_4 (LABEL_DECL_CHECK (NODE))
 /* True if this code is the start of a subroutine (target of a jsr). */
-#define LABEL_IS_SUBR_START(NODE) DECL_LANG_FLAG_5(NODE)
+#define LABEL_IS_SUBR_START(NODE) DECL_LANG_FLAG_5 (LABEL_DECL_CHECK (NODE))
 
 /* In a LABEL_DECL, if LABEL_IN_SUBR(NODE), points to start of subroutine. */
-#define LABEL_SUBR_START(NODE) DECL_ABSTRACT_ORIGIN(NODE)
+#define LABEL_SUBR_START(NODE) DECL_ABSTRACT_ORIGIN (LABEL_DECL_CHECK (NODE))
 
 /* In a LABEL_DECL that has LABEL_IS_SUBR_START, this points to the start
    of surrounding subroutine in the case of a nested subroutine,
@@ -885,34 +890,28 @@ union lang_tree_node
 
 /* The slot number for this local variable. */
 #define DECL_LOCAL_SLOT_NUMBER(NODE) \
-  (DECL_LANG_SPECIFIC(NODE)->u.v.slot_number)
+  (DECL_LANG_SPECIFIC (NODE)->u.v.slot_number)
 /* The start (bytecode) pc for the valid range of this local variable. */
-#define DECL_LOCAL_START_PC(NODE) \
-  (DECL_LANG_SPECIFIC(NODE)->u.v.start_pc)
+#define DECL_LOCAL_START_PC(NODE)  (DECL_LANG_SPECIFIC (NODE)->u.v.start_pc)
 /* The end (bytecode) pc for the valid range of this local variable. */
-#define DECL_LOCAL_END_PC(NODE) \
-  (DECL_LANG_SPECIFIC(NODE)->u.v.end_pc)
+#define DECL_LOCAL_END_PC(NODE)    (DECL_LANG_SPECIFIC (NODE)->u.v.end_pc)
 /* For a VAR_DECLor PARM_DECL, used to chain decls with the same
    slot_number in decl_map. */
-#define DECL_LOCAL_SLOT_CHAIN(NODE) \
-  (DECL_LANG_SPECIFIC(NODE)->u.v.slot_chain)
+#define DECL_LOCAL_SLOT_CHAIN(NODE) (DECL_LANG_SPECIFIC(NODE)->u.v.slot_chain)
 /* For a FIELD_DECL, holds the name of the access method. Used to
    read/write the content of the field from an inner class.  */
 #define FIELD_INNER_ACCESS(DECL) \
-  (DECL_LANG_SPECIFIC(DECL)->u.v.am)
+  (DECL_LANG_SPECIFIC (VAR_OR_FIELD_CHECK (DECL))->u.v.am)
 /* Safely tests whether FIELD_INNER_ACCESS exists or not. */
 #define FIELD_INNER_ACCESS_P(DECL) \
   DECL_LANG_SPECIFIC (DECL) && FIELD_INNER_ACCESS (DECL)
 /* True if a final variable was initialized upon its declaration,
    or (if a field) in an initializer.  Set after definite assignment. */
-#define DECL_FIELD_FINAL_IUD(NODE) \
-  (DECL_LANG_SPECIFIC(NODE)->u.v.final_iud)
+#define DECL_FIELD_FINAL_IUD(NODE)  (DECL_LANG_SPECIFIC (NODE)->u.v.final_iud)
 /* The original WFL of a final variable. */
-#define DECL_FIELD_FINAL_WFL(NODE) \
-  (DECL_LANG_SPECIFIC(NODE)->u.v.wfl)
+#define DECL_FIELD_FINAL_WFL(NODE)  (DECL_LANG_SPECIFIC(NODE)->u.v.wfl)
 /* The class that's the owner of a dynamic binding table.  */
-#define DECL_OWNER(NODE) \
-  (DECL_LANG_SPECIFIC(NODE)->u.v.owner)
+#define DECL_OWNER(NODE)            (DECL_LANG_SPECIFIC(NODE)->u.v.owner)
 /* True if NODE is a local variable final. */
 #define LOCAL_FINAL_P(NODE) (DECL_LANG_SPECIFIC (NODE) && DECL_FINAL (NODE))
 /* True if NODE is a final field. */
@@ -923,13 +922,13 @@ union lang_tree_node
 /* True if NODE is a class initialization flag. This macro accesses
    the flag to read or set it.  */
 #define LOCAL_CLASS_INITIALIZATION_FLAG(NODE) \
-    (DECL_LANG_SPECIFIC(NODE)->u.v.cif)
+    (DECL_LANG_SPECIFIC (NODE)->u.v.cif)
 /* True if NODE is a class initialization flag. */
 #define LOCAL_CLASS_INITIALIZATION_FLAG_P(NODE) \
     (DECL_LANG_SPECIFIC (NODE) && LOCAL_CLASS_INITIALIZATION_FLAG(NODE))
 /* True if NODE is a variable that is out of scope.  */
 #define LOCAL_VAR_OUT_OF_SCOPE_P(NODE) \
-    (DECL_LANG_SPECIFIC(NODE)->u.v.freed)
+    (DECL_LANG_SPECIFIC (NODE)->u.v.freed)
 /* Create a DECL_LANG_SPECIFIC if necessary. */
 #define MAYBE_CREATE_VAR_LANG_DECL_SPECIFIC(T)			\
   if (DECL_LANG_SPECIFIC (T) == NULL)				\
@@ -946,11 +945,11 @@ union lang_tree_node
        && TREE_CODE (TREE_TYPE (NODE)) != POINTER_TYPE) \
    || TREE_CODE (NODE) == REAL_CST)
 
-/* For a local VAR_DECL, holds the index into a words bitstring that
-   specifies if this decl is definitively assigned.
+/* For a local VAR_DECL or PARM_DECL, holds the index into a words bitstring
+   that specifies if this decl is definitively assigned.
    The value -1 means the variable has been definitely assigned (and not
    definitely unassigned).  The value -2 means we already reported an error. */
-#define DECL_BIT_INDEX(DECL) (DECL_CHECK (DECL)->decl.pointer_alias_set)
+#define DECL_BIT_INDEX(DECL) VAR_OR_FIELD_CHECK (DECL)->decl.pointer_alias_set
 
 /* DECL_LANG_SPECIFIC for FUNCTION_DECLs. */
 struct lang_decl_func GTY(())
@@ -1020,65 +1019,61 @@ struct lang_decl_var GTY(())
 
 /* This is what 'lang_decl' really points to.  */
 
-enum lang_decl_desc {
-  LANG_DECL_FUNC,
-  LANG_DECL_VAR
-};
+enum lang_decl_desc {LANG_DECL_FUNC, LANG_DECL_VAR};
 
 struct lang_decl GTY(())
 {
   enum lang_decl_desc desc;
-  union lang_decl_u {
-    struct lang_decl_func GTY ((tag ("LANG_DECL_FUNC"))) f;
-    struct lang_decl_var GTY ((tag ("LANG_DECL_VAR"))) v;
-  } GTY ((desc ("%0.desc"))) u;
+  union lang_decl_u
+    {
+      struct lang_decl_func GTY ((tag ("LANG_DECL_FUNC"))) f;
+      struct lang_decl_var GTY ((tag ("LANG_DECL_VAR"))) v;
+    } GTY ((desc ("%0.desc"))) u;
 };
 
 /* Macro to access fields in `struct lang_type'.  */
 
-#define TYPE_SIGNATURE(T) (TYPE_LANG_SPECIFIC(T)->signature)
-#define TYPE_JCF(T) (TYPE_LANG_SPECIFIC(T)->jcf)
-#define TYPE_CPOOL(T) (TYPE_LANG_SPECIFIC(T)->cpool)
-#define TYPE_CPOOL_DATA_REF(T) (TYPE_LANG_SPECIFIC(T)->cpool_data_ref)
-#define MAYBE_CREATE_TYPE_TYPE_LANG_SPECIFIC(T)				 \
-  if (TYPE_LANG_SPECIFIC ((T)) == NULL)					 \
-    {									 \
-      TYPE_LANG_SPECIFIC ((T)) 					 	 \
-        = ggc_alloc_cleared (sizeof (struct lang_type));		 \
-    }
-
-#define TYPE_FINIT_STMT_LIST(T)  (TYPE_LANG_SPECIFIC(T)->finit_stmt_list)
-#define TYPE_CLINIT_STMT_LIST(T) (TYPE_LANG_SPECIFIC(T)->clinit_stmt_list)
-#define TYPE_II_STMT_LIST(T)     (TYPE_LANG_SPECIFIC(T)->ii_block)
+#define TYPE_SIGNATURE(T)	(TYPE_LANG_SPECIFIC (T)->signature)
+#define TYPE_JCF(T)		(TYPE_LANG_SPECIFIC (T)->jcf)
+#define TYPE_CPOOL(T)		(TYPE_LANG_SPECIFIC (T)->cpool)
+#define TYPE_CPOOL_DATA_REF(T)	(TYPE_LANG_SPECIFIC (T)->cpool_data_ref)
+#define MAYBE_CREATE_TYPE_TYPE_LANG_SPECIFIC(T) \
+  if (TYPE_LANG_SPECIFIC ((T)) == NULL)		\
+     TYPE_LANG_SPECIFIC ((T))			\
+     = ggc_alloc_cleared (sizeof (struct lang_type));
+
+#define TYPE_FINIT_STMT_LIST(T)  (TYPE_LANG_SPECIFIC (T)->finit_stmt_list)
+#define TYPE_CLINIT_STMT_LIST(T) (TYPE_LANG_SPECIFIC (T)->clinit_stmt_list)
+#define TYPE_II_STMT_LIST(T)     (TYPE_LANG_SPECIFIC (T)->ii_block)
 /* The decl of the synthetic method `class$' used to handle `.class'
    for non primitive types when compiling to bytecode. */
-#define TYPE_DOT_CLASS(T)        (TYPE_LANG_SPECIFIC(T)->dot_class)
-#define TYPE_PACKAGE_LIST(T)     (TYPE_LANG_SPECIFIC(T)->package_list)
-#define TYPE_IMPORT_LIST(T)      (TYPE_LANG_SPECIFIC(T)->import_list)
-#define TYPE_IMPORT_DEMAND_LIST(T) (TYPE_LANG_SPECIFIC(T)->import_demand_list)
-#define TYPE_PRIVATE_INNER_CLASS(T) (TYPE_LANG_SPECIFIC(T)->pic)
-#define TYPE_PROTECTED_INNER_CLASS(T) (TYPE_LANG_SPECIFIC(T)->poic)
-#define TYPE_STRICTFP(T) (TYPE_LANG_SPECIFIC(T)->strictfp)
-#define TYPE_USES_ASSERTIONS(T) (TYPE_LANG_SPECIFIC(T)->assertions)
+#define TYPE_DOT_CLASS(T)        (TYPE_LANG_SPECIFIC (T)->dot_class)
+#define TYPE_PACKAGE_LIST(T)     (TYPE_LANG_SPECIFIC (T)->package_list)
+#define TYPE_IMPORT_LIST(T)      (TYPE_LANG_SPECIFIC (T)->import_list)
+#define TYPE_IMPORT_DEMAND_LIST(T) (TYPE_LANG_SPECIFIC (T)->import_demand_list)
+#define TYPE_PRIVATE_INNER_CLASS(T) (TYPE_LANG_SPECIFIC (T)->pic)
+#define TYPE_PROTECTED_INNER_CLASS(T) (TYPE_LANG_SPECIFIC (T)->poic)
+#define TYPE_STRICTFP(T) (TYPE_LANG_SPECIFIC (T)->strictfp)
+#define TYPE_USES_ASSERTIONS(T) (TYPE_LANG_SPECIFIC (T)->assertions)
 
-#define TYPE_ATABLE_METHODS(T)   (TYPE_LANG_SPECIFIC(T)->atable_methods)
-#define TYPE_ATABLE_SYMS_DECL(T) (TYPE_LANG_SPECIFIC(T)->atable_syms_decl)
-#define TYPE_ATABLE_DECL(T)      (TYPE_LANG_SPECIFIC(T)->atable_decl)
+#define TYPE_ATABLE_METHODS(T)   (TYPE_LANG_SPECIFIC (T)->atable_methods)
+#define TYPE_ATABLE_SYMS_DECL(T) (TYPE_LANG_SPECIFIC (T)->atable_syms_decl)
+#define TYPE_ATABLE_DECL(T)      (TYPE_LANG_SPECIFIC (T)->atable_decl)
 
-#define TYPE_OTABLE_METHODS(T)   (TYPE_LANG_SPECIFIC(T)->otable_methods)
-#define TYPE_OTABLE_SYMS_DECL(T) (TYPE_LANG_SPECIFIC(T)->otable_syms_decl)
-#define TYPE_OTABLE_DECL(T)      (TYPE_LANG_SPECIFIC(T)->otable_decl)
+#define TYPE_OTABLE_METHODS(T)   (TYPE_LANG_SPECIFIC (T)->otable_methods)
+#define TYPE_OTABLE_SYMS_DECL(T) (TYPE_LANG_SPECIFIC (T)->otable_syms_decl)
+#define TYPE_OTABLE_DECL(T)      (TYPE_LANG_SPECIFIC (T)->otable_decl)
 
-#define TYPE_CTABLE_DECL(T)      (TYPE_LANG_SPECIFIC(T)->ctable_decl)
-#define TYPE_CATCH_CLASSES(T)    (TYPE_LANG_SPECIFIC(T)->catch_classes)
+#define TYPE_CTABLE_DECL(T)      (TYPE_LANG_SPECIFIC (T)->ctable_decl)
+#define TYPE_CATCH_CLASSES(T)    (TYPE_LANG_SPECIFIC (T)->catch_classes)
 
-#define TYPE_TO_RUNTIME_MAP(T)   (TYPE_LANG_SPECIFIC(T)->type_to_runtime_map)
+#define TYPE_TO_RUNTIME_MAP(T)   (TYPE_LANG_SPECIFIC (T)->type_to_runtime_map)
 
 struct lang_type GTY(())
 {
   tree signature;
-  struct JCF * jcf;
-  struct CPool * cpool;
+  struct JCF *jcf;
+  struct CPool *cpool;
   tree cpool_data_ref;		/* Cached */
   tree finit_stmt_list;		/* List of statements finit$ will use */
   tree clinit_stmt_list;	/* List of statements <clinit> will use  */
@@ -1091,19 +1086,23 @@ struct lang_type GTY(())
   tree import_list;		/* Imported types, in the CU of this class */
   tree import_demand_list;	/* Imported types, in the CU of this class */
 
-  tree otable_methods;          /* List of static decls referred to by this class.  */
+  tree otable_methods;          /* List of static decls referred to by this
+				   class.  */
   tree otable_decl;		/* The static address table.  */
   tree otable_syms_decl;
 
-  tree atable_methods;          /* List of static decls referred to by this class.  */
+  tree atable_methods;          /* List of static decls referred to by this
+				   class.  */
   tree atable_decl;		/* The static address table.  */
   tree atable_syms_decl;
 
-  tree ctable_decl;             /* The table of classes for the runtime type matcher.  */
+  tree ctable_decl;             /* The table of classes for the runtime
+				   type matcher.  */
   tree catch_classes;
 
   htab_t GTY ((param_is (struct treetreehash_entry))) type_to_runtime_map;   
-                                /* The mapping of classes to exception region markers.  */
+                                /* The mapping of classes to exception region
+				   markers.  */
 
   unsigned pic:1;		/* Private Inner Class. */
   unsigned poic:1;		/* Protected Inner Class. */
@@ -1156,8 +1155,10 @@ extern tree build_internal_class_name (tree);
 extern tree build_constants_constructor (void);
 extern tree build_ref_from_constant_pool (int);
 extern tree build_utf8_ref (tree);
-extern tree ident_subst (const char*, int, const char*, int, int, const char*);
-extern tree identifier_subst (const tree, const char *, int, int, const char *);
+extern tree ident_subst (const char *, int, const char *, int, int,
+			 const char *);
+extern tree identifier_subst (const tree, const char *, int, int,
+			      const char *);
 extern int global_bindings_p (void);
 extern int kept_level_p (void);
 extern tree getdecls (void);
@@ -1178,12 +1179,12 @@ extern tree find_stack_slot (int index, tree type);
 extern tree build_prim_array_type (tree, HOST_WIDE_INT);
 extern tree build_java_array_type (tree, HOST_WIDE_INT);
 extern int is_compiled_class (tree);
-extern tree mangled_classname (const char*, tree);
+extern tree mangled_classname (const char *, tree);
 extern tree lookup_label (int);
-extern tree pop_type_0 (tree, char**);
+extern tree pop_type_0 (tree, char **);
 extern tree pop_type (tree);
 extern tree decode_newarray_type (int);
-extern tree lookup_field (tree*, tree);
+extern tree lookup_field (tree *, tree);
 extern int is_array_type_p (tree);
 extern HOST_WIDE_INT java_array_type_length (tree);
 extern int read_class (tree);
@@ -1297,7 +1298,8 @@ extern void jcf_trim_old_input (struct JCF *);
 #ifdef BUFSIZ
 extern void jcf_print_utf8 (FILE *, const unsigned char *, int);
 extern void jcf_print_char (FILE *, int);
-extern void jcf_print_utf8_replace (FILE *, const unsigned char *, int, int, int);
+extern void jcf_print_utf8_replace (FILE *, const unsigned char *, int,
+				    int, int);
 extern const char* open_class (const char *, struct JCF *, int, const char *);
 #endif
 extern void java_debug_context (void);
@@ -1349,16 +1351,19 @@ extern void gen_indirect_dispatch_tables (tree type);
 
 /* Access flags etc for a method (a FUNCTION_DECL): */
 
-#define METHOD_PUBLIC(DECL) DECL_LANG_FLAG_1 (DECL)
-#define METHOD_PRIVATE(DECL) TREE_PRIVATE (DECL)
-#define METHOD_PROTECTED(DECL) TREE_PROTECTED (DECL)
-#define METHOD_STATIC(DECL) DECL_LANG_FLAG_2 (DECL)
-#define METHOD_FINAL(DECL) DECL_FINAL (DECL)
-#define METHOD_SYNCHRONIZED(DECL) DECL_LANG_FLAG_4 (DECL)
-#define METHOD_NATIVE(DECL) (DECL_LANG_SPECIFIC(DECL)->u.f.native)
-#define METHOD_ABSTRACT(DECL) DECL_LANG_FLAG_5 (DECL)
-#define METHOD_STRICTFP(DECL) (DECL_LANG_SPECIFIC (DECL)->u.f.strictfp)
-#define METHOD_INVISIBLE(DECL) (DECL_LANG_SPECIFIC (DECL)->u.f.invisible)
+#define METHOD_PUBLIC(DECL) DECL_LANG_FLAG_1 (FUNCTION_DECL_CHECK (DECL))
+#define METHOD_PRIVATE(DECL) TREE_PRIVATE (FUNCTION_DECL_CHECK (DECL))
+#define METHOD_PROTECTED(DECL) TREE_PROTECTED (FUNCTION_DECL_CHECK (DECL))
+#define METHOD_STATIC(DECL) DECL_LANG_FLAG_2 (FUNCTION_DECL_CHECK (DECL))
+#define METHOD_FINAL(DECL) DECL_FINAL (FUNCTION_DECL_CHECK (DECL))
+#define METHOD_SYNCHRONIZED(DECL) DECL_LANG_FLAG_4 (FUNCTION_DECL_CHECK (DECL))
+#define METHOD_NATIVE(DECL) \
+  (DECL_LANG_SPECIFIC (FUNCTION_DECL_CHECK (DECL))->u.f.native)
+#define METHOD_ABSTRACT(DECL) DECL_LANG_FLAG_5 (FUNCTION_DECL_CHECK (DECL))
+#define METHOD_STRICTFP(DECL) \
+  (DECL_LANG_SPECIFIC (FUNCTION_DECL_CHECK (DECL))->u.f.strictfp)
+#define METHOD_INVISIBLE(DECL) \
+  (DECL_LANG_SPECIFIC (FUNCTION_DECL_CHECK (DECL))->u.f.invisible)
 
 #define JAVA_FILE_P(NODE) TREE_LANG_FLAG_2 (NODE)
 #define CLASS_FILE_P(NODE) TREE_LANG_FLAG_3 (NODE)
@@ -1366,7 +1371,7 @@ extern void gen_indirect_dispatch_tables (tree type);
 
 /* Other predicates on method decls  */
 
-#define DECL_CONSTRUCTOR_P(DECL) DECL_LANG_FLAG_7(DECL)
+#define DECL_CONSTRUCTOR_P(DECL) DECL_LANG_FLAG_7 (FUNCTION_DECL_CHECK (DECL))
 
 #define DECL_INIT_P(DECL)   (ID_INIT_P (DECL_NAME (DECL)))
 #define DECL_FINIT_P(DECL)  (ID_FINIT_P (DECL_NAME (DECL)))
@@ -1381,27 +1386,27 @@ extern void gen_indirect_dispatch_tables (tree type);
 #define ID_CLASSDOLLAR_P(ID) ((ID) == classdollar_identifier_node)
 #define ID_INSTINIT_P(ID) ((ID) == instinit_identifier_node)
 
-/* Access flags etc for a variable/field (a FIELD_DECL): */
+/* Access flags etc for variable/field (FIELD_DECL, VAR_DECL, or PARM_DECL): */
 
-#define FIELD_PRIVATE(DECL) TREE_PRIVATE (DECL)
-#define FIELD_PROTECTED(DECL) TREE_PROTECTED (DECL)
-#define FIELD_PUBLIC(DECL) DECL_LANG_FLAG_1 (DECL)
-#define FIELD_STATIC(DECL) TREE_STATIC (DECL)
-#define FIELD_FINAL(DECL) DECL_FINAL (DECL)
-#define FIELD_VOLATILE(DECL) DECL_LANG_FLAG_4 (DECL)
-#define FIELD_TRANSIENT(DECL) DECL_LANG_FLAG_5 (DECL)
+#define FIELD_PRIVATE(DECL)	TREE_PRIVATE (VAR_OR_FIELD_CHECK (DECL))
+#define FIELD_PROTECTED(DECL)	TREE_PROTECTED (VAR_OR_FIELD_CHECK (DECL))
+#define FIELD_PUBLIC(DECL)	DECL_LANG_FLAG_1 (VAR_OR_FIELD_CHECK (DECL))
+#define FIELD_STATIC(DECL)	TREE_STATIC (VAR_OR_FIELD_CHECK (DECL))
+#define FIELD_FINAL(DECL)	DECL_FINAL (VAR_OR_FIELD_CHECK (DECL))
+#define FIELD_VOLATILE(DECL)	DECL_LANG_FLAG_4 (VAR_OR_FIELD_CHECK (DECL))
+#define FIELD_TRANSIENT(DECL)	DECL_LANG_FLAG_5 (VAR_OR_FIELD_CHECK (DECL))
 
 /* Access flags etc for a class (a TYPE_DECL): */
 
-#define CLASS_PUBLIC(DECL) DECL_LANG_FLAG_1 (DECL)
-#define CLASS_FINAL(DECL) DECL_FINAL (DECL)
-#define CLASS_INTERFACE(DECL) DECL_LANG_FLAG_4 (DECL)
-#define CLASS_ABSTRACT(DECL) DECL_LANG_FLAG_5 (DECL)
-#define CLASS_SUPER(DECL) DECL_LANG_FLAG_6 (DECL)
-#define CLASS_STATIC(DECL) DECL_LANG_FLAG_7 (DECL)
-#define CLASS_PRIVATE(DECL) (TYPE_PRIVATE_INNER_CLASS (TREE_TYPE (DECL)))
-#define CLASS_PROTECTED(DECL) (TYPE_PROTECTED_INNER_CLASS (TREE_TYPE (DECL)))
-#define CLASS_STRICTFP(DECL) (TYPE_STRICTFP (TREE_TYPE (DECL)))
+#define CLASS_PUBLIC(DECL)	DECL_LANG_FLAG_1 (TYPE_DECL_CHECK (DECL))
+#define CLASS_FINAL(DECL)	DECL_FINAL (TYPE_DECL_CHECK (DECL))
+#define CLASS_INTERFACE(DECL)	DECL_LANG_FLAG_4 (TYPE_DECL_CHECK (DECL))
+#define CLASS_ABSTRACT(DECL)	DECL_LANG_FLAG_5 (TYPE_DECL_CHECK (DECL))
+#define CLASS_SUPER(DECL)	DECL_LANG_FLAG_6 (TYPE_DECL_CHECK (DECL))
+#define CLASS_STATIC(DECL)	DECL_LANG_FLAG_7 (TYPE_DECL_CHECK (DECL))
+#define CLASS_PRIVATE(DECL)	(TYPE_PRIVATE_INNER_CLASS (TREE_TYPE (DECL)))
+#define CLASS_PROTECTED(DECL)	(TYPE_PROTECTED_INNER_CLASS (TREE_TYPE (DECL)))
+#define CLASS_STRICTFP(DECL)	(TYPE_STRICTFP (TREE_TYPE (DECL)))
 #define CLASS_USES_ASSERTIONS(DECL) (TYPE_USES_ASSERTIONS (TREE_TYPE (DECL)))
 
 /* @deprecated marker flag on methods, fields and classes */
@@ -1412,8 +1417,8 @@ extern void gen_indirect_dispatch_tables (tree type);
 #define DECL_DEPRECATED(DECL) DECL_LANG_FLAG_0 (DECL)
 
 /* The number of virtual methods in this class's dispatch table.
- Does not include initial two dummy entries (one points to the
- Class object, and the other is for G++ -fvtable-thunks compatibility). */
+   Does not include initial two dummy entries (one points to the
+   Class object, and the other is for G++ -fvtable-thunks compatibility). */
 #define TYPE_NVIRTUALS(TYPE) TYPE_BINFO_VIRTUALS (TYPE)
 
 /* A TREE_VEC (indexed by DECL_VINDEX) containing this class's
@@ -1482,7 +1487,7 @@ extern int linenumber_count;
 extern tree *type_map;
 
 /* Map a stack index to the type currently in that slot. */
-#define stack_type_map (type_map+DECL_MAX_LOCALS(current_function_decl))
+#define stack_type_map (type_map + DECL_MAX_LOCALS (current_function_decl))
 
 /* True iff TYPE takes two variable/stack slots. */
 #define TYPE_IS_WIDE(TYPE) \
@@ -1498,11 +1503,12 @@ extern tree *type_map;
 #define IS_ARRAY_LENGTH_ACCESS(NODE) TREE_LANG_FLAG_4 (NODE)
 
 /* If FUNCTION_TYPE or METHOD_TYPE: cache for build_java_argument_signature. */
-#define TYPE_ARGUMENT_SIGNATURE(TYPE) TYPE_VFIELD(TYPE)
+#define TYPE_ARGUMENT_SIGNATURE(TYPE) \
+  (TREE_CHECK2 (TYPE, FUNCTION_TYPE, METHOD_TYPE)->type.minval)
 
 /* Given an array type, give the type of the elements. */
 /* FIXME this use of TREE_TYPE conflicts with something or other. */
-#define TYPE_ARRAY_ELEMENT(ATYPE) TREE_TYPE(ATYPE)
+#define TYPE_ARRAY_ELEMENT(ATYPE) TREE_TYPE (ATYPE)
 
 /* True if class TYPE has been loaded (i.e. parsed plus laid out).
    (The check for CLASS_PARSED_P is needed because of Object and Class.) */
@@ -1519,8 +1525,7 @@ extern tree *type_map;
 #define CLASS_P(TYPE) TYPE_LANG_FLAG_4 (TYPE)
 
 /* True if class TYPE was requested (on command line) to be compiled.*/
-#define CLASS_FROM_CURRENTLY_COMPILED_P(TYPE) \
-  TYPE_LANG_FLAG_5 (TYPE)
+#define CLASS_FROM_CURRENTLY_COMPILED_P(TYPE) TYPE_LANG_FLAG_5 (TYPE)
 
 /* True if class TYPE is currently being laid out. Helps in detection
    of inheritance cycle occurring as a side effect of performing the
@@ -1552,15 +1557,16 @@ extern tree *type_map;
 #define COMPOUND_ASSIGN_P(EXPR) TREE_LANG_FLAG_1 (EXPR)
 
 /* True if a SWITCH_EXPR has a DEFAULT_EXPR. */
-#define SWITCH_HAS_DEFAULT(NODE) TREE_LANG_FLAG_3 (NODE)
+#define SWITCH_HAS_DEFAULT(NODE) TREE_LANG_FLAG_3 (SWITCH_EXPR_CHECK (NODE))
 
 /* True if EXPR (a WFL in that case) was created after the
    reduction of PRIMARY . XXX */
-#define PRIMARY_P(EXPR) TREE_LANG_FLAG_2 (EXPR)
+#define PRIMARY_P(EXPR) TREE_LANG_FLAG_2 (EXPR_CHECK (EXPR))
 
 /* True if EXPR (a MODIFY_EXPR in that case) is the result of variable
    initialization during its declaration */
-#define MODIFY_EXPR_FROM_INITIALIZATION_P(EXPR) TREE_LANG_FLAG_2 (EXPR)
+#define MODIFY_EXPR_FROM_INITIALIZATION_P(EXPR) \
+  TREE_LANG_FLAG_2 (MODIFY_EXPR_CHECK (EXPR))
 
 /* True if EXPR (a TREE_TYPE denoting a class type) has its methods
    already checked (for redefinitions, etc, see java_check_regular_methods.) */
@@ -1571,29 +1577,29 @@ extern tree *type_map;
 #define HAS_FINALIZER_P(EXPR) TREE_LANG_FLAG_3 (EXPR)
 
 /* True if EXPR (a LOOP_EXPR in that case) is part of a for statement */
-#define FOR_LOOP_P(EXPR) TREE_LANG_FLAG_0 (EXPR)
+#define FOR_LOOP_P(EXPR) TREE_LANG_FLAG_0 (EXPR_CHECK (EXPR))
 
 /* True if NODE (a RECORD_TYPE in that case) is an anonymous class.  */
-#define ANONYMOUS_CLASS_P(NODE) TREE_LANG_FLAG_0 (NODE)
+#define ANONYMOUS_CLASS_P(NODE) TREE_LANG_FLAG_0 (RECORD_TYPE_CHECK (NODE))
 
 /* True if NODE (a RECORD_TYPE in that case) is a block local class.  */
-#define LOCAL_CLASS_P(NODE) TREE_LANG_FLAG_1 (NODE)
+#define LOCAL_CLASS_P(NODE) TREE_LANG_FLAG_1 (RECORD_TYPE_CHECK (NODE))
 
 /* True if NODE (a TREE_LIST) hold a pair of argument name/type
    declared with the final modifier */
-#define ARG_FINAL_P(NODE) TREE_LANG_FLAG_0 (NODE)
+#define ARG_FINAL_P(NODE) TREE_LANG_FLAG_0 (TREE_LIST_CHECK (NODE))
 
 /* True if NODE (some kind of EXPR, but not a WFL) should not give an
    error if it is found to be unreachable.  This can only be applied
    to those EXPRs which can be used as the update expression of a
    `for' loop.  In particular it can't be set on a LOOP_EXPR.  */
-#define SUPPRESS_UNREACHABLE_ERROR(NODE) TREE_LANG_FLAG_0 (NODE)
+#define SUPPRESS_UNREACHABLE_ERROR(NODE) TREE_LANG_FLAG_0 (EXPR_CHECK (NODE))
 
 /* True if EXPR (a WFL in that case) resolves into a package name */
-#define RESOLVE_PACKAGE_NAME_P(WFL) TREE_LANG_FLAG_3 (WFL)
+#define RESOLVE_PACKAGE_NAME_P(WFL) TREE_LANG_FLAG_3 (EXPR_CHECK (WFL))
 
 /* True if EXPR (a WFL in that case) resolves into a type name */
-#define RESOLVE_TYPE_NAME_P(WFL) TREE_LANG_FLAG_4 (WFL)
+#define RESOLVE_TYPE_NAME_P(WFL) TREE_LANG_FLAG_4 (EXPR_CHECK (WFL))
 
 /* True if STMT (a WFL in that case) holds a BREAK statement */
 #define IS_BREAK_STMT_P(WFL) TREE_LANG_FLAG_5 (WFL)
@@ -1603,17 +1609,18 @@ extern tree *type_map;
 
 /* True if EXPR (a SAVE_EXPR in that case) had its content already
    checked for (un)initialized local variables.  */
-#define IS_INIT_CHECKED(EXPR) TREE_LANG_FLAG_5 (EXPR)
+#define IS_INIT_CHECKED(EXPR) TREE_LANG_FLAG_5 (SAVE_EXPR_CHECK (EXPR))
 
 /* If set in CALL_EXPR, the receiver is 'super'. */
-#define CALL_USING_SUPER(EXPR) TREE_LANG_FLAG_4 (EXPR)
+#define CALL_USING_SUPER(EXPR) TREE_LANG_FLAG_4 (EXPR_CHECK (EXPR))
 
 /* True if NODE (a statement) can complete normally. */
-#define CAN_COMPLETE_NORMALLY(NODE) TREE_LANG_FLAG_6(NODE)
+#define CAN_COMPLETE_NORMALLY(NODE) TREE_LANG_FLAG_6 (NODE)
 
 /* True if NODE (an IDENTIFIER) bears the name of a outer field from
    inner class access function.  */
-#define OUTER_FIELD_ACCESS_IDENTIFIER_P(NODE) TREE_LANG_FLAG_6(NODE)
+#define OUTER_FIELD_ACCESS_IDENTIFIER_P(NODE) \
+  TREE_LANG_FLAG_6 (IDENTIFIER_NODE_CHECK (NODE))
 
 /* True if NODE belongs to an inner class TYPE_DECL node.
    Verifies that NODE as the attributes of a decl.  */
@@ -1652,7 +1659,7 @@ extern tree *type_map;
 
 /* On a TYPE_DECL, hold the list of inner classes defined within the
    scope of TYPE_DECL.  */
-#define DECL_INNER_CLASS_LIST(NODE) DECL_INITIAL (NODE)
+#define DECL_INNER_CLASS_LIST(NODE) DECL_INITIAL (TYPE_DECL_CHECK (NODE))
 
 /* Build a IDENTIFIER_NODE for a file name we're considering. Since
    all_class_filename is a registered root, putting this identifier
@@ -1673,47 +1680,53 @@ extern tree *type_map;
    if compiling java.lang.Object or java.lang.Class. */
 
 #define PUSH_FIELD(RTYPE, FIELD, NAME, FTYPE) \
-{ tree tmp_field = build_decl (FIELD_DECL, get_identifier(NAME), FTYPE); \
-  if (TYPE_FIELDS (RTYPE) == NULL_TREE) TYPE_FIELDS (RTYPE) = tmp_field; \
-  else TREE_CHAIN(FIELD) = tmp_field; \
-  DECL_CONTEXT (tmp_field) = RTYPE; \
-  DECL_ARTIFICIAL (tmp_field) = 1; \
-  FIELD = tmp_field; }
+{ tree _field = build_decl (FIELD_DECL, get_identifier ((NAME)), (FTYPE)); \
+  if (TYPE_FIELDS (RTYPE) == NULL_TREE)	\
+    TYPE_FIELDS (RTYPE) = _field; 	\
+  else					\
+    TREE_CHAIN(FIELD) = _field;		\
+  DECL_CONTEXT (_field) = (RTYPE);	\
+  DECL_ARTIFICIAL (_field) = 1;		\
+  FIELD = _field; }
 
 #define FINISH_RECORD(RTYPE) layout_type (RTYPE)
 
 /* Start building a RECORD_TYPE constructor with a given TYPE in CONS. */
-#define START_RECORD_CONSTRUCTOR(CONS, CTYPE) { \
-  CONS = build_constructor (CTYPE, NULL_TREE);\
-  TREE_CHAIN(CONS) = TYPE_FIELDS (CTYPE); }
+#define START_RECORD_CONSTRUCTOR(CONS, CTYPE)	\
+{ CONS = build_constructor ((CTYPE), NULL_TREE);	\
+  TREE_CHAIN (CONS) = TYPE_FIELDS (CTYPE); }
 
 /* Append a field initializer to CONS for the dummy field for the inherited
    fields.  The dummy field has the given VALUE, and the same type as the
    super-class.   Must be specified before calls to PUSH_FIELD_VALUE. */
-
-#define PUSH_SUPER_VALUE(CONS, VALUE) {\
-  tree field = TREE_CHAIN(CONS);\
-  if (DECL_NAME (field) != NULL_TREE) abort();\
-  CONSTRUCTOR_ELTS(CONS) = tree_cons (field, VALUE, CONSTRUCTOR_ELTS(CONS));\
-  TREE_CHAIN(CONS) = TREE_CHAIN (field); }
+#define PUSH_SUPER_VALUE(CONS, VALUE)			\
+{							\
+  tree _field = TREE_CHAIN (CONS);			\
+  if (DECL_NAME (_field) != NULL_TREE)			\
+    abort ();						\
+  CONSTRUCTOR_ELTS (CONS)				\
+    = tree_cons (_field, (VALUE), CONSTRUCTOR_ELTS (CONS)); \
+  TREE_CHAIN (CONS) = TREE_CHAIN (_field);		\
+}
 
 /* Append a field initializer to CONS for a field with the given VALUE.
    NAME is a char* string used for error checking;
    the initializer must be specified in order. */
-#define PUSH_FIELD_VALUE(CONS, NAME, VALUE) 					\
-do										\
-{										\
-  tree field = TREE_CHAIN(CONS);						\
-  if (strcmp (IDENTIFIER_POINTER (DECL_NAME (field)), NAME) != 0) 		\
-    abort();									\
-  CONSTRUCTOR_ELTS(CONS) = tree_cons (field, VALUE, CONSTRUCTOR_ELTS(CONS));	\
-  TREE_CHAIN(CONS) = TREE_CHAIN (field); 					\
-}										\
+#define PUSH_FIELD_VALUE(CONS, NAME, VALUE) 				\
+do									\
+{									\
+  tree _field = TREE_CHAIN (CONS);					\
+  if (strcmp (IDENTIFIER_POINTER (DECL_NAME (_field)), NAME) != 0) 	\
+    abort ();								\
+  CONSTRUCTOR_ELTS (CONS)						\
+    = tree_cons (_field, (VALUE), CONSTRUCTOR_ELTS (CONS));		\
+  TREE_CHAIN (CONS) = TREE_CHAIN (_field); 				\
+}									\
 while (0)
 
 /* Finish creating a record CONSTRUCTOR CONS. */
 #define FINISH_RECORD_CONSTRUCTOR(CONS) \
-  CONSTRUCTOR_ELTS(CONS) = nreverse (CONSTRUCTOR_ELTS(CONS))
+  CONSTRUCTOR_ELTS(CONS) = nreverse (CONSTRUCTOR_ELTS (CONS))
 
 /* Macros on constructors invocations.  */
 #define CALL_CONSTRUCTOR_P(NODE)		\
@@ -1731,13 +1744,14 @@ while (0)
    && EXPR_WFL_NODE (TREE_OPERAND (NODE, 0)) == super_identifier_node)
 
 /* Using a FINALLY_EXPR node */
-#define FINALLY_EXPR_LABEL(NODE) TREE_OPERAND ((NODE), 0)
-#define FINALLY_EXPR_BLOCK(NODE) TREE_OPERAND ((NODE), 1)
+#define FINALLY_EXPR_LABEL(NODE) TREE_OPERAND (FINALLY_EXPR_CHECK (NODE), 0)
+#define FINALLY_EXPR_BLOCK(NODE) TREE_OPERAND (FINALLY_EXPR_CHECK (NODE), 1)
 
 #define BLOCK_EXPR_DECLS(NODE)  BLOCK_VARS(NODE)
 #define BLOCK_EXPR_BODY(NODE)   BLOCK_SUBBLOCKS(NODE)
+
 /* True for an implicit block surrounding declaration not at start of {...}. */
-#define BLOCK_IS_IMPLICIT(NODE) TREE_LANG_FLAG_1 (NODE)
+#define BLOCK_IS_IMPLICIT(NODE) TREE_LANG_FLAG_1 (BLOCK_CHECK (NODE))
 #define BLOCK_EMPTY_P(NODE) \
   (TREE_CODE (NODE) == BLOCK && BLOCK_EXPR_BODY (NODE) == empty_stmt_node)
 
@@ -1797,7 +1811,6 @@ enum
   JV_STATE_ERROR = 12,
 
   JV_STATE_DONE = 14		/* Must be last.  */
-
 };
 
 #undef DEBUG_JAVA_BINDING_LEVELS
diff --git a/gcc/java/jcf-write.c b/gcc/java/jcf-write.c
index 74ebc1aa886a..dbc34c6d8fca 100644
--- a/gcc/java/jcf-write.c
+++ b/gcc/java/jcf-write.c
@@ -633,10 +633,7 @@ get_access_flags (tree decl)
 {
   int flags = 0;
   int isfield = TREE_CODE (decl) == FIELD_DECL || TREE_CODE (decl) == VAR_DECL;
-  if (CLASS_PUBLIC (decl))  /* same as FIELD_PUBLIC and METHOD_PUBLIC */
-    flags |= ACC_PUBLIC;
-  if (CLASS_FINAL (decl))  /* same as FIELD_FINAL and METHOD_FINAL */
-    flags |= ACC_FINAL;
+
   if (isfield || TREE_CODE (decl) == FUNCTION_DECL)
     {
       if (TREE_PROTECTED (decl))
@@ -646,6 +643,10 @@ get_access_flags (tree decl)
     }
   else if (TREE_CODE (decl) == TYPE_DECL)
     {
+      if (CLASS_PUBLIC (decl))
+	flags |= ACC_PUBLIC;
+      if (CLASS_FINAL (decl))
+	flags |= ACC_FINAL;
       if (CLASS_SUPER (decl))
 	flags |= ACC_SUPER;
       if (CLASS_ABSTRACT (decl))
@@ -669,6 +670,10 @@ get_access_flags (tree decl)
 
   if (TREE_CODE (decl) == FUNCTION_DECL)
     {
+      if (METHOD_PUBLIC (decl))
+	flags |= ACC_PUBLIC;
+      if (METHOD_FINAL (decl))
+	flags |= ACC_FINAL;
       if (METHOD_NATIVE (decl))
 	flags |= ACC_NATIVE;
       if (METHOD_STATIC (decl))
@@ -682,6 +687,10 @@ get_access_flags (tree decl)
     }
   if (isfield)
     {
+      if (FIELD_PUBLIC (decl))
+	flags |= ACC_PUBLIC;
+      if (FIELD_FINAL (decl))
+	flags |= ACC_FINAL;
       if (FIELD_STATIC (decl))
 	flags |= ACC_STATIC;
       if (FIELD_VOLATILE (decl))
diff --git a/gcc/tree.c b/gcc/tree.c
index 6a62e7183d69..a2994e5b36ab 100644
--- a/gcc/tree.c
+++ b/gcc/tree.c
@@ -1798,7 +1798,6 @@ type_contains_placeholder_p (tree type)
     {
     case VOID_TYPE:
     case COMPLEX_TYPE:
-    case VECTOR_TYPE:
     case ENUMERAL_TYPE:
     case BOOLEAN_TYPE:
     case CHAR_TYPE:
@@ -1818,6 +1817,7 @@ type_contains_placeholder_p (tree type)
 
     case ARRAY_TYPE:
     case SET_TYPE:
+    case VECTOR_TYPE:
       /* We're already checked the component type (TREE_TYPE), so just check
 	 the index type.  */
       return type_contains_placeholder_p (TYPE_DOMAIN (type));
@@ -3080,34 +3080,95 @@ type_hash_list (tree list, hashval_t hashcode)
 
 /* These are the Hashtable callback functions.  */
 
-/* Returns true if the types are equal.  */
+/* Returns true iff the types are equivalent.  */
 
 static int
 type_hash_eq (const void *va, const void *vb)
 {
   const struct type_hash *a = va, *b = vb;
-  if (a->hash == b->hash
-      && TREE_CODE (a->type) == TREE_CODE (b->type)
-      && TREE_TYPE (a->type) == TREE_TYPE (b->type)
-      && attribute_list_equal (TYPE_ATTRIBUTES (a->type),
-			       TYPE_ATTRIBUTES (b->type))
-      && TYPE_ALIGN (a->type) == TYPE_ALIGN (b->type)
-      && (TYPE_MAX_VALUE (a->type) == TYPE_MAX_VALUE (b->type)
-	  || tree_int_cst_equal (TYPE_MAX_VALUE (a->type),
-				 TYPE_MAX_VALUE (b->type)))
-      && (TYPE_MIN_VALUE (a->type) == TYPE_MIN_VALUE (b->type)
-	  || tree_int_cst_equal (TYPE_MIN_VALUE (a->type),
-				 TYPE_MIN_VALUE (b->type)))
-      /* Note that TYPE_DOMAIN is TYPE_ARG_TYPES for FUNCTION_TYPE.  */
-      && (TYPE_DOMAIN (a->type) == TYPE_DOMAIN (b->type)
-	  || (TYPE_DOMAIN (a->type)
-	      && TREE_CODE (TYPE_DOMAIN (a->type)) == TREE_LIST
-	      && TYPE_DOMAIN (b->type)
-	      && TREE_CODE (TYPE_DOMAIN (b->type)) == TREE_LIST
-	      && type_list_equal (TYPE_DOMAIN (a->type),
-				  TYPE_DOMAIN (b->type)))))
-    return 1;
-  return 0;
+
+  /* First test the things that are the same for all types.  */
+  if (a->hash != b->hash
+      || TREE_CODE (a->type) != TREE_CODE (b->type)
+      || TREE_TYPE (a->type) != TREE_TYPE (b->type)
+      || !attribute_list_equal (TYPE_ATTRIBUTES (a->type),
+				 TYPE_ATTRIBUTES (b->type))
+      || TYPE_ALIGN (a->type) != TYPE_ALIGN (b->type)
+      || TYPE_MODE (a->type) != TYPE_MODE (b->type))
+    return 0;
+
+  switch (TREE_CODE (a->type))
+    {
+    case VOID_TYPE:
+    case COMPLEX_TYPE:
+    case VECTOR_TYPE:
+    case POINTER_TYPE:
+    case REFERENCE_TYPE:
+      return 1;
+
+    case ENUMERAL_TYPE:
+      if (TYPE_VALUES (a->type) != TYPE_VALUES (b->type)
+	  && !(TYPE_VALUES (a->type)
+	       && TREE_CODE (TYPE_VALUES (a->type)) == TREE_LIST
+	       && TYPE_VALUES (b->type)
+	       && TREE_CODE (TYPE_VALUES (b->type)) == TREE_LIST
+	       && type_list_equal (TYPE_VALUES (a->type),
+				   TYPE_VALUES (b->type))))
+	return 0;
+
+      /* ... fall through ... */
+
+    case INTEGER_TYPE:
+    case REAL_TYPE:
+    case BOOLEAN_TYPE:
+    case CHAR_TYPE:
+      return ((TYPE_MAX_VALUE (a->type) == TYPE_MAX_VALUE (b->type)
+	       || tree_int_cst_equal (TYPE_MAX_VALUE (a->type),
+				      TYPE_MAX_VALUE (b->type)))
+	      && (TYPE_MIN_VALUE (a->type) == TYPE_MIN_VALUE (b->type)
+		  && tree_int_cst_equal (TYPE_MIN_VALUE (a->type),
+					 TYPE_MIN_VALUE (b->type))));
+
+    case OFFSET_TYPE:
+      return TYPE_OFFSET_BASETYPE (a->type) == TYPE_OFFSET_BASETYPE (b->type);
+
+    case METHOD_TYPE:
+      return (TYPE_METHOD_BASETYPE (a->type) == TYPE_METHOD_BASETYPE (b->type)
+	      && (TYPE_ARG_TYPES (a->type) == TYPE_ARG_TYPES (b->type)
+		  || (TYPE_ARG_TYPES (a->type)
+		      && TREE_CODE (TYPE_ARG_TYPES (a->type)) == TREE_LIST
+		      && TYPE_ARG_TYPES (b->type)
+		      && TREE_CODE (TYPE_ARG_TYPES (b->type)) == TREE_LIST
+		      && type_list_equal (TYPE_ARG_TYPES (a->type),
+					  TYPE_ARG_TYPES (b->type)))));
+								      
+    case ARRAY_TYPE:
+    case SET_TYPE:
+      return TYPE_DOMAIN (a->type) == TYPE_DOMAIN (b->type);
+
+    case RECORD_TYPE:
+    case UNION_TYPE:
+    case QUAL_UNION_TYPE:
+      return (TYPE_FIELDS (a->type) == TYPE_FIELDS (b->type)
+	      || (TYPE_FIELDS (a->type)
+		  && TREE_CODE (TYPE_FIELDS (a->type)) == TREE_LIST
+		  && TYPE_FIELDS (b->type)
+		  && TREE_CODE (TYPE_FIELDS (b->type)) == TREE_LIST
+		  && type_list_equal (TYPE_FIELDS (a->type),
+				      TYPE_FIELDS (b->type))));
+
+    case FUNCTION_TYPE:
+      return (TYPE_ARG_TYPES (a->type) == TYPE_ARG_TYPES (b->type)
+	      || (TYPE_ARG_TYPES (a->type)
+		  && TREE_CODE (TYPE_ARG_TYPES (a->type)) == TREE_LIST
+		  && TYPE_ARG_TYPES (b->type)
+		  && TREE_CODE (TYPE_ARG_TYPES (b->type)) == TREE_LIST
+		  && type_list_equal (TYPE_ARG_TYPES (a->type),
+				      TYPE_ARG_TYPES (b->type))));
+
+    default:
+      return 0;
+    }
 }
 
 /* Return the cached hash value.  */
@@ -4894,6 +4955,7 @@ get_set_constructor_bytes (tree init, unsigned char *buffer, int wd_size)
 }
 
 #if defined ENABLE_TREE_CHECKING && (GCC_VERSION >= 2007)
+
 /* Complain that the tree code of NODE does not match the expected CODE.
    FILE, LINE, and FUNCTION are of the caller.  */
 
@@ -4906,7 +4968,49 @@ tree_check_failed (const tree node, enum tree_code code, const char *file,
 		  function, trim_filename (file), line);
 }
 
-/* Similar to above, except that we check for a class of tree
+/* Similar to above except that we allowed the code to be one of two
+   different codes.  */
+
+void
+tree_check2_failed (const tree node, enum tree_code code1,
+		    enum tree_code code2, const char *file,
+		    int line, const char *function)
+{
+  internal_error ("tree check: expected %s or %s, have %s in %s, at %s:%d",
+		  tree_code_name[code1], tree_code_name[code2],
+		  tree_code_name[TREE_CODE (node)],
+		  function, trim_filename (file), line);
+}
+
+/* Likewise for three different codes.  */
+
+void
+tree_check3_failed (const tree node, enum tree_code code1,
+		    enum tree_code code2, enum tree_code code3,
+		    const char *file, int line, const char *function)
+{
+  internal_error ("tree check: expected %s, %s or %s; have %s in %s, at %s:%d",
+		  tree_code_name[code1], tree_code_name[code2],
+		  tree_code_name[code3], tree_code_name[TREE_CODE (node)],
+		  function, trim_filename (file), line);
+}
+
+/* ... and for four different codes.  */
+
+void
+tree_check5_failed (const tree node, enum tree_code code1,
+		    enum tree_code code2, enum tree_code code3,
+		    enum tree_code code4, enum tree_code code5,
+		    const char *file, int line, const char *function)
+{
+  internal_error
+    ("tree check: expected %s, %s, %s, %s or %s; have %s in %s, at %s:%d",
+     tree_code_name[code1], tree_code_name[code2], tree_code_name[code3],
+     tree_code_name[code4], tree_code_name[code5],
+     tree_code_name[TREE_CODE (node)], function, trim_filename (file), line);
+}
+
+/* Similar to tree_check_failed, except that we check for a class of tree
    code, given in CL.  */
 
 void
diff --git a/gcc/tree.h b/gcc/tree.h
index a923048fcf53..e5e710d63a46 100644
--- a/gcc/tree.h
+++ b/gcc/tree.h
@@ -307,6 +307,34 @@ struct tree_common GTY(())
       tree_check_failed (__t, (CODE), __FILE__, __LINE__, __FUNCTION__); \
     __t; })
 
+#define TREE_CHECK2(T, CODE1, CODE2) __extension__			\
+({  const tree __t = (T);						\
+    if (TREE_CODE (__t) != (CODE1)					\
+	&& TREE_CODE (__t) != (CODE2))					\
+      tree_check2_failed (__t, (CODE1), (CODE2), __FILE__, __LINE__,	\
+			  __FUNCTION__);				\
+    __t; })
+
+#define TREE_CHECK3(T, CODE1, CODE2, CODE3) __extension__		\
+({  const tree __t = (T);						\
+    if (TREE_CODE (__t) != (CODE1)					\
+	&& TREE_CODE (__t) != (CODE2)					\
+	&& TREE_CODE (__t) != (CODE3))					\
+      tree_check3_failed (__t, (CODE1), (CODE2), (CODE3), __FILE__,	\
+			  __LINE__, __FUNCTION__);			\
+    __t; })
+
+#define TREE_CHECK5(T, CODE1, CODE2, CODE3, CODE4, CODE5) __extension__	\
+({  const tree __t = (T);						\
+    if (TREE_CODE (__t) != (CODE1)					\
+	&& TREE_CODE (__t) != (CODE2)					\
+	&& TREE_CODE (__t) != (CODE3)					\
+	&& TREE_CODE (__t) != (CODE4)					\
+	&& TREE_CODE (__t) != (CODE5))					\
+      tree_check5_failed (__t, (CODE1), (CODE2), (CODE3), (CODE4),	\
+			  (CODE5), __FILE__, __LINE__, __FUNCTION__);	\
+    __t; })
+
 #define TREE_CLASS_CHECK(T, CLASS) __extension__			\
 ({  const tree __t = (T);						\
     if (TREE_CODE_CLASS (TREE_CODE(__t)) != (CLASS))			\
@@ -367,6 +395,17 @@ struct tree_common GTY(())
 extern void tree_check_failed (const tree, enum tree_code,
 			       const char *, int, const char *)
     ATTRIBUTE_NORETURN;
+extern void tree_check2_failed (const tree, enum tree_code, enum tree_code,
+			       const char *, int, const char *)
+    ATTRIBUTE_NORETURN;
+extern void tree_check3_failed (const tree, enum tree_code, enum tree_code,
+				enum tree_code, const char *, int,
+				const char *)
+    ATTRIBUTE_NORETURN;
+extern void tree_check5_failed (const tree, enum tree_code, enum tree_code,
+				enum tree_code, enum tree_code, enum tree_code,
+				const char *, int, const char *)
+    ATTRIBUTE_NORETURN;
 extern void tree_class_check_failed (const tree, int,
 				     const char *, int, const char *)
     ATTRIBUTE_NORETURN;
@@ -380,12 +419,15 @@ extern void tree_operand_check_failed (int, enum tree_code,
 
 #else /* not ENABLE_TREE_CHECKING, or not gcc */
 
-#define TREE_CHECK(T, CODE)		(T)
-#define TREE_CLASS_CHECK(T, CODE)	(T)
-#define EXPR_CHECK(T)			(T)
-#define TREE_VEC_ELT_CHECK(T, I)	((T)->vec.a[I])
-#define TREE_OPERAND_CHECK(T, I)	((T)->exp.operands[I])
-#define TREE_OPERAND_CHECK_CODE(T, CODE, I) ((T)->exp.operands[I])
+#define TREE_CHECK(T, CODE)			(T)
+#define TREE_CHECK2(T, CODE1, CODE2)		(T)
+#define TREE_CHECK3(T, CODE1, CODE2, CODE3)	(T)
+#define TREE_CHECK5(T, CODE1, CODE2, CODE3, CODE4, CODE5) (T)
+#define TREE_CLASS_CHECK(T, CODE)		(T)
+#define EXPR_CHECK(T)				(T)
+#define TREE_VEC_ELT_CHECK(T, I)		((T)->vec.a[I])
+#define TREE_OPERAND_CHECK(T, I)		((T)->exp.operands[I])
+#define TREE_OPERAND_CHECK_CODE(T, CODE, I)	((T)->exp.operands[I])
 #define TREE_RTL_OPERAND_CHECK(T, CODE, I)  (*(rtx *) &((T)->exp.operands[I]))
 
 #endif
@@ -396,6 +438,17 @@ extern void tree_operand_check_failed (int, enum tree_code,
 #define DECL_CHECK(T)		TREE_CLASS_CHECK (T, 'd')
 #define CST_CHECK(T)		TREE_CLASS_CHECK (T, 'c')
 #define STMT_CHECK(T)		TREE_CLASS_CHECK (T, 's')
+#define FUNC_OR_METHOD_CHECK(T)	TREE_CHECK2 (T, FUNCTION_TYPE, METHOD_TYPE)
+
+#define SET_ARRAY_OR_VECTOR_CHECK(T) \
+  TREE_CHECK3 (T, ARRAY_TYPE, SET_TYPE, VECTOR_TYPE)
+
+#define REC_OR_UNION_CHECK(T)	\
+  TREE_CHECK3 (T, RECORD_TYPE, UNION_TYPE, QUAL_UNION_TYPE)
+
+#define NUMERICAL_TYPE_CHECK(T)					\
+  TREE_CHECK5 (T, INTEGER_TYPE, ENUMERAL_TYPE, BOOLEAN_TYPE,	\
+	       CHAR_TYPE, REAL_TYPE)
 
 /* In all nodes that are expressions, this is the data type of the expression.
    In POINTER_TYPE nodes, this is the type that the pointer points to.
@@ -945,24 +998,31 @@ struct tree_block GTY(())
 /* Define fields and accessors for nodes representing data types.  */
 
 /* See tree.def for documentation of the use of these fields.
-   Look at the documentation of the various ..._TYPE tree codes.  */
+   Look at the documentation of the various ..._TYPE tree codes.
+
+   Note that the type.values, type.minval, and type.maxval fiels are
+   overloaded and used for different macros in different kinds of types.
+   Each macro must check to ensure the tree node is of the proper kind of
+   type.  Note also that some of the front-ends also overload these fields,
+   so they must be checked as well.  */
 
 #define TYPE_UID(NODE) (TYPE_CHECK (NODE)->type.uid)
 #define TYPE_SIZE(NODE) (TYPE_CHECK (NODE)->type.size)
 #define TYPE_SIZE_UNIT(NODE) (TYPE_CHECK (NODE)->type.size_unit)
 #define TYPE_MODE(NODE) (TYPE_CHECK (NODE)->type.mode)
-#define TYPE_VALUES(NODE) (TYPE_CHECK (NODE)->type.values)
-#define TYPE_DOMAIN(NODE) (TYPE_CHECK (NODE)->type.values)
-#define TYPE_FIELDS(NODE) (TYPE_CHECK (NODE)->type.values)
-#define TYPE_METHODS(NODE) (TYPE_CHECK (NODE)->type.maxval)
-#define TYPE_VFIELD(NODE) (TYPE_CHECK (NODE)->type.minval)
-#define TYPE_ARG_TYPES(NODE) (TYPE_CHECK (NODE)->type.values)
-#define TYPE_METHOD_BASETYPE(NODE) (TYPE_CHECK (NODE)->type.maxval)
-#define TYPE_OFFSET_BASETYPE(NODE) (TYPE_CHECK (NODE)->type.maxval)
+#define TYPE_ORIG_SIZE_TYPE(NODE) (INTEGER_TYPE_CHECK (NODE)->type.values)
+#define TYPE_VALUES(NODE) (ENUMERAL_TYPE_CHECK (NODE)->type.values)
+#define TYPE_DOMAIN(NODE) (SET_ARRAY_OR_VECTOR_CHECK (NODE)->type.values)
+#define TYPE_FIELDS(NODE) (REC_OR_UNION_CHECK (NODE)->type.values)
+#define TYPE_METHODS(NODE) (REC_OR_UNION_CHECK (NODE)->type.maxval)
+#define TYPE_VFIELD(NODE) (REC_OR_UNION_CHECK (NODE)->type.minval)
+#define TYPE_ARG_TYPES(NODE) (FUNC_OR_METHOD_CHECK (NODE)->type.values)
+#define TYPE_METHOD_BASETYPE(NODE) (FUNC_OR_METHOD_CHECK (NODE)->type.maxval)
+#define TYPE_OFFSET_BASETYPE(NODE) (OFFSET_TYPE_CHECK (NODE)->type.maxval)
 #define TYPE_POINTER_TO(NODE) (TYPE_CHECK (NODE)->type.pointer_to)
 #define TYPE_REFERENCE_TO(NODE) (TYPE_CHECK (NODE)->type.reference_to)
-#define TYPE_MIN_VALUE(NODE) (TYPE_CHECK (NODE)->type.minval)
-#define TYPE_MAX_VALUE(NODE) (TYPE_CHECK (NODE)->type.maxval)
+#define TYPE_MIN_VALUE(NODE) (NUMERICAL_TYPE_CHECK (NODE)->type.minval)
+#define TYPE_MAX_VALUE(NODE) (NUMERICAL_TYPE_CHECK (NODE)->type.maxval)
 #define TYPE_PRECISION(NODE) (TYPE_CHECK (NODE)->type.precision)
 #define TYPE_SYMTAB_ADDRESS(NODE) (TYPE_CHECK (NODE)->type.symtab.address)
 #define TYPE_SYMTAB_POINTER(NODE) (TYPE_CHECK (NODE)->type.symtab.pointer)
-- 
GitLab