diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 46f3306a18db8ae40fffd298d99f46413b7273c5..8abc3fc39cbe7673801e42c0da02828f001f6324 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,74 @@
+2010-07-15  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* tree.h (DECL_CHAIN): Define.
+	* alias.c: Carefully replace TREE_CHAIN with DECL_CHAIN.
+	* c-decl.c: Likewise.
+	* c-parser.c: Likewise.
+	* c-typeck.c: Likewise.
+	* cfgexpand.c: Likewise.
+	* cgraph.c: Likewise.
+	* cgraphunit.c: Likewise.
+	* combine.c: Likewise.
+	* config/alpha/alpha.c: Likewise.
+	* config/arm/arm.c: Likewise.
+	* config/frv/frv.c: Likewise.
+	* config/i386/i386.c: Likewise.
+	* config/i386/winnt-cxx.c: Likewise.
+	* config/ia64/ia64.c: Likewise.
+	* config/iq2000/iq2000.c: Likewise.
+	* config/mep/mep.c: Likewise.
+	* config/mips/mips.c: Likewise.
+	* config/pa/som.h: Likewise.
+	* config/rs6000/rs6000.c: Likewise.
+	* config/s390/s390.c: Likewise.
+	* config/sh/sh.c: Likewise.
+	* config/sh/symbian-cxx.c: Likewise.
+	* config/sparc/sparc.c: Likewise.
+	* config/spu/spu.c: Likewise.
+	* config/stormy16/stormy16.c: Likewise.
+	* config/vxworks.c: Likewise.
+	* config/xtensa/xtensa.c: Likewise.
+	* coverage.c: Likewise.
+	* dbxout.c: Likewise.
+	* dwarf2out.c: Likewise.
+	* emit-rtl.c: Likewise.
+	* expr.c: Likewise.
+	* function.c: Likewise.
+	* gimple-low.c: Likewise.
+	* gimple-pretty-print.c: Likewise.
+	* gimplify.c: Likewise.
+	* integrate.c: Likewise.
+	* ipa-inline.c: Likewise.
+	* ipa-prop.c: Likewise.
+	* ipa-split.c: Likewise.
+	* ipa-struct-reorg.c: Likewise.
+	* ipa-type-escape.c: Likewise.
+	* langhooks.c: Likewise.
+	* lto-cgraph.c: Likewise.
+	* omp-low.c: Likewise.
+	* stor-layout.c: Likewise.
+	* tree-cfg.c: Likewise.
+	* tree-complex.c: Likewise.
+	* tree-dfa.c: Likewise.
+	* tree-dump.c: Likewise.
+	* tree-inline.c: Likewise.
+	* tree-mudflap.c: Likewise.
+	* tree-nested.c: Likewise.
+	* tree-object-size.c: Likewise.
+	* tree-pretty-print.c: Likewise.
+	* tree-sra.c: Likewise.
+	* tree-ssa-live.c: Likewise.
+	* tree-ssa-loop-niter.c: Likewise.
+	* tree-ssa-math-opts.c: Likewise.
+	* tree-ssa-reassoc.c: Likewise.
+	* tree-ssa-sccvn.c: Likewise.
+	* tree-ssa-structalias.c: Likewise.
+	* tree-tailcall.c: Likewise.
+	* tree-vrp.c: Likewise.
+	* tree.c: Likewise.
+	* var-tracking.c: Likewise.
+	* varasm.c: Likewise.
+
 2010-07-15  Ulrich Weigand  <Ulrich.Weigand@de.ibm.com>
 
 	PR target/44877
diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index 1ad721d905100aac360361769ab7af9745e2ba0b..d145b668a59666f44acef3e387577eed0c0e8227 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,10 @@
+2010-07-15  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* gcc-interface/decl.c: Carefully replace TREE_CHAIN with DECL_CHAIN.
+	* gcc-interface/trans.c: Likewise.
+	* gcc-interface/utils.c: Likewise.
+	* gcc-interface/utils2.c: Likewise.
+
 2010-07-13  Laurent GUERBY  <laurent@guerby.net>
 
         PR bootstrap/44458
diff --git a/gcc/ada/gcc-interface/decl.c b/gcc/ada/gcc-interface/decl.c
index b5168e79951cd73bedccb32ff0e6f31d7cd6c7d6..54d02225e01681e1e4c7fbeb9b4c6d97b6a8e54f 100644
--- a/gcc/ada/gcc-interface/decl.c
+++ b/gcc/ada/gcc-interface/decl.c
@@ -1049,7 +1049,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 		: TYPE_FIELDS (gnu_type);
 	    VEC(constructor_elt,gc) *v = VEC_alloc (constructor_elt, gc, 1);
 	    tree t = build_template (TREE_TYPE (template_field),
-				     TREE_TYPE (TREE_CHAIN (template_field)),
+				     TREE_TYPE (DECL_CHAIN (template_field)),
 				     NULL_TREE);
 	    CONSTRUCTOR_APPEND_ELT (v, template_field, t);
 	    gnu_expr = gnat_build_constructor (gnu_type, v);
@@ -1207,7 +1207,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 		    && TYPE_CONTAINS_TEMPLATE_P (gnu_alloc_type))
 		  {
 		    gnu_alloc_type
-		      = TREE_TYPE (TREE_CHAIN (TYPE_FIELDS (gnu_alloc_type)));
+		      = TREE_TYPE (DECL_CHAIN (TYPE_FIELDS (gnu_alloc_type)));
 
 		    if (TREE_CODE (gnu_expr) == CONSTRUCTOR
 			&& 1 == VEC_length (constructor_elt,
@@ -1217,7 +1217,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 		      gnu_expr
 			= build_component_ref
 			    (gnu_expr, NULL_TREE,
-			     TREE_CHAIN (TYPE_FIELDS (TREE_TYPE (gnu_expr))),
+			     DECL_CHAIN (TYPE_FIELDS (TREE_TYPE (gnu_expr))),
 			     false);
 		  }
 
@@ -1896,7 +1896,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 	   fields once we build them.  */
 	tem = build3 (COMPONENT_REF, gnu_ptr_template,
 		      build0 (PLACEHOLDER_EXPR, gnu_fat_type),
-		      TREE_CHAIN (TYPE_FIELDS (gnu_fat_type)), NULL_TREE);
+		      DECL_CHAIN (TYPE_FIELDS (gnu_fat_type)), NULL_TREE);
 	gnu_template_reference
 	  = build_unary_op (INDIRECT_REF, gnu_template_type, tem);
 	TREE_READONLY (gnu_template_reference) = 1;
@@ -2435,7 +2435,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 		  gnu_field = create_field_decl (gnu_index_name, gnu_index,
 						 gnu_bound_rec, NULL_TREE,
 						 NULL_TREE, 0, 0);
-		  TREE_CHAIN (gnu_field) = gnu_field_list;
+		  DECL_CHAIN (gnu_field) = gnu_field_list;
 		  gnu_field_list = gnu_field;
 		}
 
@@ -2905,7 +2905,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 
 	      if (!is_unchecked_union)
 		{
-		  TREE_CHAIN (gnu_field) = gnu_field_list;
+		  DECL_CHAIN (gnu_field) = gnu_field_list;
 		  gnu_field_list = gnu_field;
 		}
 	    }
@@ -2950,8 +2950,8 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 	    for (gnu_field = TYPE_FIELDS (gnu_type),
 		 gnu_std_field = TYPE_FIELDS (except_type_node);
 		 gnu_field;
-		 gnu_field = TREE_CHAIN (gnu_field),
-		 gnu_std_field = TREE_CHAIN (gnu_std_field))
+		 gnu_field = DECL_CHAIN (gnu_field),
+		 gnu_std_field = DECL_CHAIN (gnu_std_field))
 	      SET_DECL_ORIGINAL_FIELD_TO_FIELD (gnu_field, gnu_std_field);
 	    gcc_assert (!gnu_std_field);
 	  }
@@ -3207,7 +3207,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 		    /* Put it in one of the new variants directly.  */
 		    if (gnu_cont_type != gnu_type)
 		      {
-			TREE_CHAIN (gnu_field) = TYPE_FIELDS (gnu_cont_type);
+			DECL_CHAIN (gnu_field) = TYPE_FIELDS (gnu_cont_type);
 			TYPE_FIELDS (gnu_cont_type) = gnu_field;
 		      }
 
@@ -3231,7 +3231,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 		       the other fields.  */
 		    else
 		      {
-			TREE_CHAIN (gnu_field) = gnu_field_list;
+			DECL_CHAIN (gnu_field) = gnu_field_list;
 			gnu_field_list = gnu_field;
 			if (!gnu_last)
 			  gnu_last = gnu_field;
@@ -3248,7 +3248,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 		    = create_variant_part_from (gnu_variant_part,
 						gnu_variant_list, gnu_type,
 						gnu_pos_list, gnu_subst_list);
-		  TREE_CHAIN (new_variant_part) = gnu_field_list;
+		  DECL_CHAIN (new_variant_part) = gnu_field_list;
 		  gnu_field_list = new_variant_part;
 		}
 
@@ -3520,7 +3520,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 		  = create_field_decl (get_identifier ("P_ARRAY"),
 				       gnu_ptr_array, gnu_type,
 				       NULL_TREE, NULL_TREE, 0, 0);
-		TREE_CHAIN (fields)
+		DECL_CHAIN (fields)
 		  = create_field_decl (get_identifier ("P_BOUNDS"),
 				       gnu_ptr_template, gnu_type,
 				       NULL_TREE, NULL_TREE, 0, 0);
@@ -4141,7 +4141,7 @@ gnat_to_gnu_entity (Entity_Id gnat_entity, tree gnu_expr, int definition)
 				       0, 0);
 		Sloc_to_locus (Sloc (gnat_param),
 			       &DECL_SOURCE_LOCATION (gnu_field));
-		TREE_CHAIN (gnu_field) = gnu_field_list;
+		DECL_CHAIN (gnu_field) = gnu_field_list;
 		gnu_field_list = gnu_field;
 		gnu_cico_list
 		  = tree_cons (gnu_field, gnu_param, gnu_cico_list);
@@ -6140,7 +6140,7 @@ make_packable_type (tree type, bool in_record)
   /* Now copy the fields, keeping the position and size as we don't want
      to change the layout by propagating the packedness downwards.  */
   for (old_field = TYPE_FIELDS (type); old_field;
-       old_field = TREE_CHAIN (old_field))
+       old_field = DECL_CHAIN (old_field))
     {
       tree new_field_type = TREE_TYPE (old_field);
       tree new_field, new_size;
@@ -6155,7 +6155,7 @@ make_packable_type (tree type, bool in_record)
       /* However, for the last field in a not already packed record type
 	 that is of an aggregate type, we need to use the RM size in the
 	 packable version of the record type, see finish_record_type.  */
-      if (!TREE_CHAIN (old_field)
+      if (!DECL_CHAIN (old_field)
 	  && !TYPE_PACKED (type)
 	  && (TREE_CODE (new_field_type) == RECORD_TYPE
 	      || TREE_CODE (new_field_type) == UNION_TYPE
@@ -6178,7 +6178,7 @@ make_packable_type (tree type, bool in_record)
       if (TREE_CODE (new_type) == QUAL_UNION_TYPE)
 	DECL_QUALIFIER (new_field) = DECL_QUALIFIER (old_field);
 
-      TREE_CHAIN (new_field) = field_list;
+      DECL_CHAIN (new_field) = field_list;
       field_list = new_field;
     }
 
@@ -6831,7 +6831,7 @@ is_variable_size (tree type)
       && TREE_CODE (type) != QUAL_UNION_TYPE)
     return false;
 
-  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
     if (is_variable_size (TREE_TYPE (field)))
       return true;
 
@@ -6929,14 +6929,14 @@ components_to_record (tree gnu_record_type, Node_Id gnat_component_list,
 	       fields except for the _Tag or _Parent field.  */
 	    else if (gnat_name == Name_uController && gnu_last)
 	      {
-		TREE_CHAIN (gnu_field) = TREE_CHAIN (gnu_last);
-		TREE_CHAIN (gnu_last) = gnu_field;
+		DECL_CHAIN (gnu_field) = DECL_CHAIN (gnu_last);
+		DECL_CHAIN (gnu_last) = gnu_field;
 	      }
 
 	    /* If this is a regular field, put it after the other fields.  */
 	    else
 	      {
-		TREE_CHAIN (gnu_field) = gnu_field_list;
+		DECL_CHAIN (gnu_field) = gnu_field_list;
 		gnu_field_list = gnu_field;
 		if (!gnu_last)
 		  gnu_last = gnu_field;
@@ -7035,7 +7035,7 @@ components_to_record (tree gnu_record_type, Node_Id gnat_component_list,
 	     use this field directly to match the layout of C unions.  */
 	  if (unchecked_union
 	      && TYPE_FIELDS (gnu_variant_type)
-	      && !TREE_CHAIN (TYPE_FIELDS (gnu_variant_type)))
+	      && !DECL_CHAIN (TYPE_FIELDS (gnu_variant_type)))
 	    gnu_field = TYPE_FIELDS (gnu_variant_type);
 	  else
 	    {
@@ -7067,7 +7067,7 @@ components_to_record (tree gnu_record_type, Node_Id gnat_component_list,
 		DECL_QUALIFIER (gnu_field) = gnu_qual;
 	    }
 
-	  TREE_CHAIN (gnu_field) = gnu_variant_list;
+	  DECL_CHAIN (gnu_field) = gnu_variant_list;
 	  gnu_variant_list = gnu_field;
 	}
 
@@ -7111,7 +7111,7 @@ components_to_record (tree gnu_record_type, Node_Id gnat_component_list,
 				 union_field_packed, 0);
 
 	  DECL_INTERNAL_P (gnu_union_field) = 1;
-	  TREE_CHAIN (gnu_union_field) = gnu_field_list;
+	  DECL_CHAIN (gnu_union_field) = gnu_field_list;
 	  gnu_field_list = gnu_union_field;
 	}
     }
@@ -7126,16 +7126,16 @@ components_to_record (tree gnu_record_type, Node_Id gnat_component_list,
   gnu_last = NULL_TREE;
   for (gnu_field = gnu_field_list; gnu_field; gnu_field = gnu_next)
     {
-      gnu_next = TREE_CHAIN (gnu_field);
+      gnu_next = DECL_CHAIN (gnu_field);
 
       if (DECL_FIELD_OFFSET (gnu_field))
 	{
 	  if (!gnu_last)
 	    gnu_field_list = gnu_next;
 	  else
-	    TREE_CHAIN (gnu_last) = gnu_next;
+	    DECL_CHAIN (gnu_last) = gnu_next;
 
-	  TREE_CHAIN (gnu_field) = gnu_our_rep_list;
+	  DECL_CHAIN (gnu_field) = gnu_our_rep_list;
 	  gnu_our_rep_list = gnu_field;
 	}
       else
@@ -7159,7 +7159,7 @@ components_to_record (tree gnu_record_type, Node_Id gnat_component_list,
 
       for (gnu_field = gnu_our_rep_list, i = 0;
 	   gnu_field;
-	   gnu_field = TREE_CHAIN (gnu_field), i++)
+	   gnu_field = DECL_CHAIN (gnu_field), i++)
 	gnu_arr[i] = gnu_field;
 
       qsort (gnu_arr, len, sizeof (tree), compare_field_bitpos);
@@ -7169,7 +7169,7 @@ components_to_record (tree gnu_record_type, Node_Id gnat_component_list,
       gnu_our_rep_list = NULL_TREE;
       for (i = len - 1; i >= 0; i--)
 	{
-	  TREE_CHAIN (gnu_arr[i]) = gnu_our_rep_list;
+	  DECL_CHAIN (gnu_arr[i]) = gnu_our_rep_list;
 	  gnu_our_rep_list = gnu_arr[i];
 	  DECL_CONTEXT (gnu_arr[i]) = gnu_rep_type;
 	}
@@ -7353,7 +7353,7 @@ annotate_object (Entity_Id gnat_entity, tree gnu_type, tree size, bool by_ref)
     {
       if (TREE_CODE (gnu_type) == RECORD_TYPE
 	  && TYPE_CONTAINS_TEMPLATE_P (gnu_type))
-	size = TYPE_SIZE (TREE_TYPE (TREE_CHAIN (TYPE_FIELDS (gnu_type))));
+	size = TYPE_SIZE (TREE_TYPE (DECL_CHAIN (TYPE_FIELDS (gnu_type))));
       else if (!size)
 	size = TYPE_SIZE (gnu_type);
 
@@ -7469,7 +7469,7 @@ build_position_list (tree gnu_type, bool do_not_flatten_variant, tree gnu_pos,
 
   for (gnu_field = TYPE_FIELDS (gnu_type);
        gnu_field;
-       gnu_field = TREE_CHAIN (gnu_field))
+       gnu_field = DECL_CHAIN (gnu_field))
     {
       tree gnu_our_bitpos = size_binop (PLUS_EXPR, gnu_bitpos,
 					DECL_FIELD_BIT_OFFSET (gnu_field));
@@ -7555,7 +7555,7 @@ build_variant_list (tree qual_union_type, tree subst_list, tree gnu_list)
 
   for (gnu_field = TYPE_FIELDS (qual_union_type);
        gnu_field;
-       gnu_field = TREE_CHAIN (gnu_field))
+       gnu_field = DECL_CHAIN (gnu_field))
     {
       tree t, qual = DECL_QUALIFIER (gnu_field);
 
@@ -8292,7 +8292,7 @@ get_variant_part (tree record_type)
   tree field;
 
   /* The variant part is the only internal field that is a qualified union.  */
-  for (field = TYPE_FIELDS (record_type); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (record_type); field; field = DECL_CHAIN (field))
     if (DECL_INTERNAL_P (field)
 	&& TREE_CODE (TREE_TYPE (field)) == QUAL_UNION_TYPE)
       return field;
@@ -8363,7 +8363,7 @@ create_variant_part_from (tree old_variant_part, tree variant_list,
 	  tree new_variant_subpart
 	    = create_variant_part_from (old_variant_subpart, variant_list,
 					new_variant, pos_list, subst_list);
-	  TREE_CHAIN (new_variant_subpart) = field_list;
+	  DECL_CHAIN (new_variant_subpart) = field_list;
 	  field_list = new_variant_subpart;
 	}
 
@@ -8380,7 +8380,7 @@ create_variant_part_from (tree old_variant_part, tree variant_list,
 				  pos_list, subst_list);
       DECL_QUALIFIER (new_field) = TREE_VEC_ELT (TREE_VALUE (t), 1);
       DECL_INTERNAL_P (new_field) = 1;
-      TREE_CHAIN (new_field) = union_field_list;
+      DECL_CHAIN (new_field) = union_field_list;
       union_field_list = new_field;
     }
 
@@ -8401,7 +8401,7 @@ create_variant_part_from (tree old_variant_part, tree variant_list,
      statically selected while outer ones are not; in this case, the list
      of fields of the inner variant is not flattened and we end up with a
      qualified union with a single member.  Drop the useless container.  */
-  if (!TREE_CHAIN (union_field_list))
+  if (!DECL_CHAIN (union_field_list))
     {
       DECL_CONTEXT (union_field_list) = record_type;
       DECL_FIELD_OFFSET (union_field_list)
@@ -8566,7 +8566,7 @@ substitute_in_type (tree t, tree f, tree r)
 	nt = copy_type (t);
 	TYPE_FIELDS (nt) = NULL_TREE;
 
-	for (field = TYPE_FIELDS (t); field; field = TREE_CHAIN (field))
+	for (field = TYPE_FIELDS (t); field; field = DECL_CHAIN (field))
 	  {
 	    tree new_field = copy_node (field), new_n;
 
@@ -8598,7 +8598,7 @@ substitute_in_type (tree t, tree f, tree r)
 	    DECL_CONTEXT (new_field) = nt;
 	    SET_DECL_ORIGINAL_FIELD_TO_FIELD (new_field, field);
 
-	    TREE_CHAIN (new_field) = TYPE_FIELDS (nt);
+	    DECL_CHAIN (new_field) = TYPE_FIELDS (nt);
 	    TYPE_FIELDS (nt) = new_field;
 	  }
 
@@ -8632,7 +8632,7 @@ rm_size (tree gnu_type)
       && TYPE_CONTAINS_TEMPLATE_P (gnu_type))
     return
       size_binop (PLUS_EXPR,
-		  rm_size (TREE_TYPE (TREE_CHAIN (TYPE_FIELDS (gnu_type)))),
+		  rm_size (TREE_TYPE (DECL_CHAIN (TYPE_FIELDS (gnu_type)))),
 		  DECL_SIZE (TYPE_FIELDS (gnu_type)));
 
   /* For record types, we store the size explicitly.  */
diff --git a/gcc/ada/gcc-interface/trans.c b/gcc/ada/gcc-interface/trans.c
index 988bfa9ffbfd5393afa8a6d9561969d57a95f295..4bf89477d0dc5989814c886e815944202336e4d1 100644
--- a/gcc/ada/gcc-interface/trans.c
+++ b/gcc/ada/gcc-interface/trans.c
@@ -7362,7 +7362,7 @@ extract_values (tree values, tree record_type)
   tree field, tem;
   VEC(constructor_elt,gc) *v = NULL;
 
-  for (field = TYPE_FIELDS (record_type); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (record_type); field; field = DECL_CHAIN (field))
     {
       tree value = 0;
 
diff --git a/gcc/ada/gcc-interface/utils.c b/gcc/ada/gcc-interface/utils.c
index 3572af585932389e4b10361ca067baa7964307c7..de0d25c4841e96ee9b4e22e04b453069fe19947a 100644
--- a/gcc/ada/gcc-interface/utils.c
+++ b/gcc/ada/gcc-interface/utils.c
@@ -461,7 +461,7 @@ gnat_pushdecl (tree decl, Node_Id gnat_node)
 	}
       else
 	{
-	  TREE_CHAIN (decl) = BLOCK_VARS (current_binding_level->block);
+	  DECL_CHAIN (decl) = BLOCK_VARS (current_binding_level->block);
 	  BLOCK_VARS (current_binding_level->block) = decl;
 	}
     }
@@ -589,7 +589,7 @@ finish_record_type (tree record_type, tree field_list, int rep_level,
   if (code == QUAL_UNION_TYPE)
     field_list = nreverse (field_list);
 
-  for (field = field_list; field; field = TREE_CHAIN (field))
+  for (field = field_list; field; field = DECL_CHAIN (field))
     {
       tree type = TREE_TYPE (field);
       tree pos = bit_position (field);
@@ -741,7 +741,7 @@ rest_of_record_type_compilation (tree record_type)
   enum tree_code code = TREE_CODE (record_type);
   bool var_size = false;
 
-  for (field = field_list; field; field = TREE_CHAIN (field))
+  for (field = field_list; field; field = DECL_CHAIN (field))
     {
       /* We need to make an XVE/XVU record if any field has variable size,
 	 whether or not the record does.  For example, if we have a union,
@@ -795,7 +795,7 @@ rest_of_record_type_compilation (tree record_type)
       /* Now scan all the fields, replacing each field with a new
 	 field corresponding to the new encoding.  */
       for (old_field = TYPE_FIELDS (record_type); old_field;
-	   old_field = TREE_CHAIN (old_field))
+	   old_field = DECL_CHAIN (old_field))
 	{
 	  tree field_type = TREE_TYPE (old_field);
 	  tree field_name = DECL_NAME (old_field);
@@ -911,7 +911,7 @@ rest_of_record_type_compilation (tree record_type)
 	  new_field
 	    = create_field_decl (field_name, field_type, new_record_type,
 				 DECL_SIZE (old_field), pos, 0, 0);
-	  TREE_CHAIN (new_field) = TYPE_FIELDS (new_record_type);
+	  DECL_CHAIN (new_field) = TYPE_FIELDS (new_record_type);
 	  TYPE_FIELDS (new_record_type) = new_field;
 
 	  /* If old_field is a QUAL_UNION_TYPE, take its size as being
@@ -1079,7 +1079,7 @@ create_subprog_type (tree return_type, tree param_decl_list, tree cico_list,
   tree param_type_list = NULL_TREE;
   tree t, type;
 
-  for (t = param_decl_list; t; t = TREE_CHAIN (t))
+  for (t = param_decl_list; t; t = DECL_CHAIN (t))
     param_type_list = tree_cons (NULL_TREE, TREE_TYPE (t), param_type_list);
 
   /* The list of the function parameter types has to be terminated by the void
@@ -1416,7 +1416,7 @@ aggregate_type_contains_array_p (tree type)
     case QUAL_UNION_TYPE:
       {
 	tree field;
-	for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+	for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	  if (AGGREGATE_TYPE_P (TREE_TYPE (field))
 	      && aggregate_type_contains_array_p (TREE_TYPE (field)))
 	    return true;
@@ -1860,7 +1860,7 @@ begin_subprog_body (tree subprog_decl)
   gnat_pushlevel ();
 
   for (param_decl = DECL_ARGUMENTS (subprog_decl); param_decl;
-       param_decl = TREE_CHAIN (param_decl))
+       param_decl = DECL_CHAIN (param_decl))
     DECL_CONTEXT (param_decl) = subprog_decl;
 
   make_decl_rtl (subprog_decl);
@@ -2246,7 +2246,7 @@ build_template (tree template_type, tree array_type, tree expr)
        (bound_list
 	? (bound_list = TREE_CHAIN (bound_list))
 	: (array_type = TREE_TYPE (array_type))),
-       field = TREE_CHAIN (TREE_CHAIN (field)))
+       field = DECL_CHAIN (DECL_CHAIN (field)))
     {
       tree bounds, min, max;
 
@@ -2265,7 +2265,7 @@ build_template (tree template_type, tree array_type, tree expr)
 	gcc_unreachable ();
 
       min = convert (TREE_TYPE (field), TYPE_MIN_VALUE (bounds));
-      max = convert (TREE_TYPE (TREE_CHAIN (field)), TYPE_MAX_VALUE (bounds));
+      max = convert (TREE_TYPE (DECL_CHAIN (field)), TYPE_MAX_VALUE (bounds));
 
       /* If either MIN or MAX involve a PLACEHOLDER_EXPR, we must
 	 substitute it from OBJECT.  */
@@ -2273,7 +2273,7 @@ build_template (tree template_type, tree array_type, tree expr)
       max = SUBSTITUTE_PLACEHOLDER_IN_EXPR (max, expr);
 
       CONSTRUCTOR_APPEND_ELT (template_elts, field, min);
-      CONSTRUCTOR_APPEND_ELT (template_elts, TREE_CHAIN (field), max);
+      CONSTRUCTOR_APPEND_ELT (template_elts, DECL_CHAIN (field), max);
     }
 
   return gnat_build_constructor (template_type, template_elts);
@@ -2929,9 +2929,9 @@ convert_vms_descriptor64 (tree gnu_type, tree gnu_expr, Entity_Id gnat_subprog)
   tree desc_type = TREE_TYPE (TREE_TYPE (gnu_expr));
   tree desc = build1 (INDIRECT_REF, desc_type, gnu_expr);
   /* The CLASS field is the 3rd field in the descriptor.  */
-  tree klass = TREE_CHAIN (TREE_CHAIN (TYPE_FIELDS (desc_type)));
+  tree klass = DECL_CHAIN (DECL_CHAIN (TYPE_FIELDS (desc_type)));
   /* The POINTER field is the 6th field in the descriptor.  */
-  tree pointer = TREE_CHAIN (TREE_CHAIN (TREE_CHAIN (klass)));
+  tree pointer = DECL_CHAIN (DECL_CHAIN (DECL_CHAIN (klass)));
 
   /* Retrieve the value of the POINTER field.  */
   tree gnu_expr64
@@ -2962,7 +2962,7 @@ convert_vms_descriptor64 (tree gnu_type, tree gnu_expr, Entity_Id gnat_subprog)
 	case 15: /* Class SB */
 	  /* Build {1, LENGTH} template; LENGTH64 is the 5th field.  */
 	  v = VEC_alloc (constructor_elt, gc, 2);
-	  t = TREE_CHAIN (TREE_CHAIN (klass));
+	  t = DECL_CHAIN (DECL_CHAIN (klass));
 	  t = build3 (COMPONENT_REF, TREE_TYPE (t), desc, t, NULL_TREE);
 	  CONSTRUCTOR_APPEND_ELT (v, min_field,
 				  convert (TREE_TYPE (min_field),
@@ -2990,7 +2990,7 @@ convert_vms_descriptor64 (tree gnu_type, tree gnu_expr, Entity_Id gnat_subprog)
 	  t = TREE_CHAIN (t);
           ufield = build3 (COMPONENT_REF, TREE_TYPE (t), desc, t, NULL_TREE);
           ufield = convert
-           (TREE_TYPE (TREE_CHAIN (TYPE_FIELDS (template_type))), ufield);
+           (TREE_TYPE (DECL_CHAIN (TYPE_FIELDS (template_type))), ufield);
 
 	  /* Build the template in the form of a constructor. */
 	  v = VEC_alloc (constructor_elt, gc, 2);
@@ -3009,7 +3009,7 @@ convert_vms_descriptor64 (tree gnu_type, tree gnu_expr, Entity_Id gnat_subprog)
 	case 4:  /* Class A */
 	  /* The AFLAGS field is the 3rd field after the pointer in the
              descriptor.  */
-	  t = TREE_CHAIN (TREE_CHAIN (TREE_CHAIN (pointer)));
+	  t = DECL_CHAIN (DECL_CHAIN (DECL_CHAIN (pointer)));
 	  aflags = build3 (COMPONENT_REF, TREE_TYPE (t), desc, t, NULL_TREE);
 	  /* The DIMCT field is the next field in the descriptor after
              aflags.  */
@@ -3030,7 +3030,7 @@ convert_vms_descriptor64 (tree gnu_type, tree gnu_expr, Entity_Id gnat_subprog)
 						u));
 	  /* There is already a template in the descriptor and it is located
              in block 3.  The fields are 64bits so they must be repacked. */
-	  t = TREE_CHAIN (TREE_CHAIN (TREE_CHAIN (TREE_CHAIN (TREE_CHAIN
+	  t = DECL_CHAIN (DECL_CHAIN (DECL_CHAIN (DECL_CHAIN (DECL_CHAIN
               (t)))));
           lfield = build3 (COMPONENT_REF, TREE_TYPE (t), desc, t, NULL_TREE);
           lfield = convert (TREE_TYPE (TYPE_FIELDS (template_type)), lfield);
@@ -3038,12 +3038,12 @@ convert_vms_descriptor64 (tree gnu_type, tree gnu_expr, Entity_Id gnat_subprog)
 	  t = TREE_CHAIN (t);
           ufield = build3 (COMPONENT_REF, TREE_TYPE (t), desc, t, NULL_TREE);
           ufield = convert
-           (TREE_TYPE (TREE_CHAIN (TYPE_FIELDS (template_type))), ufield);
+           (TREE_TYPE (DECL_CHAIN (TYPE_FIELDS (template_type))), ufield);
 
 	  /* Build the template in the form of a constructor. */
 	  v = VEC_alloc (constructor_elt, gc, 2);
 	  CONSTRUCTOR_APPEND_ELT (v, TYPE_FIELDS (template_type), lfield);
-	  CONSTRUCTOR_APPEND_ELT (v, TREE_CHAIN (TYPE_FIELDS (template_type)),
+	  CONSTRUCTOR_APPEND_ELT (v, DECL_CHAIN (TYPE_FIELDS (template_type)),
 				  ufield);
 	  template_tree = gnat_build_constructor (template_type, v);
 	  template_tree = build3 (COND_EXPR, template_type, u,
@@ -3064,7 +3064,7 @@ convert_vms_descriptor64 (tree gnu_type, tree gnu_expr, Entity_Id gnat_subprog)
       /* Build the fat pointer in the form of a constructor.  */
       v = VEC_alloc (constructor_elt, gc, 2);
       CONSTRUCTOR_APPEND_ELT (v, TYPE_FIELDS (gnu_type), gnu_expr64);
-      CONSTRUCTOR_APPEND_ELT (v, TREE_CHAIN (TYPE_FIELDS (gnu_type)),
+      CONSTRUCTOR_APPEND_ELT (v, DECL_CHAIN (TYPE_FIELDS (gnu_type)),
 			      template_addr);
       return gnat_build_constructor (gnu_type, v);
     }
@@ -3083,9 +3083,9 @@ convert_vms_descriptor32 (tree gnu_type, tree gnu_expr, Entity_Id gnat_subprog)
   tree desc_type = TREE_TYPE (TREE_TYPE (gnu_expr));
   tree desc = build1 (INDIRECT_REF, desc_type, gnu_expr);
   /* The CLASS field is the 3rd field in the descriptor.  */
-  tree klass = TREE_CHAIN (TREE_CHAIN (TYPE_FIELDS (desc_type)));
+  tree klass = DECL_CHAIN (DECL_CHAIN (TYPE_FIELDS (desc_type)));
   /* The POINTER field is the 4th field in the descriptor.  */
-  tree pointer = TREE_CHAIN (klass);
+  tree pointer = DECL_CHAIN (klass);
 
   /* Retrieve the value of the POINTER field.  */
   tree gnu_expr32
@@ -3147,7 +3147,7 @@ convert_vms_descriptor32 (tree gnu_type, tree gnu_expr, Entity_Id gnat_subprog)
 
 	case 4:  /* Class A */
 	  /* The AFLAGS field is the 7th field in the descriptor.  */
-	  t = TREE_CHAIN (TREE_CHAIN (TREE_CHAIN (pointer)));
+	  t = DECL_CHAIN (DECL_CHAIN (DECL_CHAIN (pointer)));
 	  aflags = build3 (COMPONENT_REF, TREE_TYPE (t), desc, t, NULL_TREE);
 	  /* The DIMCT field is the 8th field in the descriptor.  */
 	  t = TREE_CHAIN (t);
@@ -3167,7 +3167,7 @@ convert_vms_descriptor32 (tree gnu_type, tree gnu_expr, Entity_Id gnat_subprog)
 						u));
 	  /* There is already a template in the descriptor and it is
 	     located at the start of block 3 (12th field).  */
-	  t = TREE_CHAIN (TREE_CHAIN (TREE_CHAIN (TREE_CHAIN (t))));
+	  t = DECL_CHAIN (DECL_CHAIN (DECL_CHAIN (DECL_CHAIN (t))));
 	  template_tree
 	    = build3 (COMPONENT_REF, TREE_TYPE (t), desc, t, NULL_TREE);
 	  template_tree = build3 (COND_EXPR, TREE_TYPE (t), u,
@@ -3188,7 +3188,7 @@ convert_vms_descriptor32 (tree gnu_type, tree gnu_expr, Entity_Id gnat_subprog)
       /* Build the fat pointer in the form of a constructor.  */
       v = VEC_alloc (constructor_elt, gc, 2);
       CONSTRUCTOR_APPEND_ELT (v, TYPE_FIELDS (gnu_type), gnu_expr32);
-      CONSTRUCTOR_APPEND_ELT (v, TREE_CHAIN (TYPE_FIELDS (gnu_type)),
+      CONSTRUCTOR_APPEND_ELT (v, DECL_CHAIN (TYPE_FIELDS (gnu_type)),
 			      template_addr);
 
       return gnat_build_constructor (gnu_type, v);
@@ -3211,7 +3211,7 @@ convert_vms_descriptor (tree gnu_type, tree gnu_expr, tree gnu_expr_alt_type,
   tree desc = build1 (INDIRECT_REF, desc_type, gnu_expr);
   tree mbo = TYPE_FIELDS (desc_type);
   const char *mbostr = IDENTIFIER_POINTER (DECL_NAME (mbo));
-  tree mbmo = TREE_CHAIN (TREE_CHAIN (TREE_CHAIN (mbo)));
+  tree mbmo = DECL_CHAIN (DECL_CHAIN (DECL_CHAIN (mbo)));
   tree is64bit, gnu_expr32, gnu_expr64;
 
   /* If the field name is not MBO, it must be 32-bit and no alternate.
@@ -3321,7 +3321,7 @@ build_unc_object_type (tree template_type, tree object_type, tree name,
 
   TYPE_NAME (type) = name;
   TYPE_CONTAINS_TEMPLATE_P (type) = 1;
-  TREE_CHAIN (template_field) = array_field;
+  DECL_CHAIN (template_field) = array_field;
   finish_record_type (type, template_field, 0, true);
 
   /* Declare it now since it will never be declared otherwise.  This is
@@ -3343,7 +3343,7 @@ build_unc_object_type_from_ptr (tree thin_fat_ptr_type, tree object_type,
 
   template_type
     = (TYPE_IS_FAT_POINTER_P (thin_fat_ptr_type)
-       ? TREE_TYPE (TREE_TYPE (TREE_CHAIN (TYPE_FIELDS (thin_fat_ptr_type))))
+       ? TREE_TYPE (TREE_TYPE (DECL_CHAIN (TYPE_FIELDS (thin_fat_ptr_type))))
        : TREE_TYPE (TYPE_FIELDS (TREE_TYPE (thin_fat_ptr_type))));
 
   return
@@ -3362,7 +3362,7 @@ shift_unc_components_for_thin_pointers (tree type)
      that COMPONENT_REFs on (*thin_ptr) designate the proper location.  */
 
   tree bounds_field = TYPE_FIELDS (type);
-  tree array_field  = TREE_CHAIN (TYPE_FIELDS (type));
+  tree array_field  = DECL_CHAIN (TYPE_FIELDS (type));
 
   DECL_FIELD_OFFSET (bounds_field)
     = size_binop (MINUS_EXPR, size_zero_node, byte_position (array_field));
@@ -3481,12 +3481,12 @@ update_pointer_to (tree old_type, tree new_type)
 	return;
 
       array_field = TYPE_FIELDS (ptr);
-      bounds_field = TREE_CHAIN (array_field);
+      bounds_field = DECL_CHAIN (array_field);
 
       /* Make pointers to the dummy template point to the real template.  */
       update_pointer_to
 	(TREE_TYPE (TREE_TYPE (bounds_field)),
-	 TREE_TYPE (TREE_TYPE (TREE_CHAIN (TYPE_FIELDS (new_ptr)))));
+	 TREE_TYPE (TREE_TYPE (DECL_CHAIN (TYPE_FIELDS (new_ptr)))));
 
       /* The references to the template bounds present in the array type use
 	 the bounds field of NEW_PTR through a PLACEHOLDER_EXPR.  Since we
@@ -3501,7 +3501,7 @@ update_pointer_to (tree old_type, tree new_type)
       update_pointer_to
 	(TREE_TYPE (TREE_TYPE (array_field)),
 	 substitute_in_type (TREE_TYPE (TREE_TYPE (TYPE_FIELDS (new_ptr))),
-			     TREE_CHAIN (TYPE_FIELDS (new_ptr)), new_ref));
+			     DECL_CHAIN (TYPE_FIELDS (new_ptr)), new_ref));
 
       /* Merge PTR in NEW_PTR.  */
       DECL_FIELD_CONTEXT (array_field) = new_ptr;
@@ -3532,7 +3532,7 @@ update_pointer_to (tree old_type, tree new_type)
 	 points to.  Update all pointers from the old record into the new
 	 one, update the type of the array field, and recompute the size.  */
       update_pointer_to (TYPE_OBJECT_RECORD_TYPE (old_type), new_obj_rec);
-      TREE_TYPE (TREE_CHAIN (TYPE_FIELDS (new_obj_rec)))
+      TREE_TYPE (DECL_CHAIN (TYPE_FIELDS (new_obj_rec)))
 	= TREE_TYPE (TREE_TYPE (array_field));
 
       /* The size recomputation needs to account for alignment constraints, so
@@ -3540,7 +3540,7 @@ update_pointer_to (tree old_type, tree new_type)
 	 what they would be in a regular record, so we shift them back to what
 	 we want them to be for a thin pointer designated type afterwards.  */
       DECL_SIZE (TYPE_FIELDS (new_obj_rec)) = NULL_TREE;
-      DECL_SIZE (TREE_CHAIN (TYPE_FIELDS (new_obj_rec))) = NULL_TREE;
+      DECL_SIZE (DECL_CHAIN (TYPE_FIELDS (new_obj_rec))) = NULL_TREE;
       TYPE_SIZE (new_obj_rec) = NULL_TREE;
       layout_type (new_obj_rec);
       shift_unc_components_for_thin_pointers (new_obj_rec);
@@ -3556,7 +3556,7 @@ update_pointer_to (tree old_type, tree new_type)
 static tree
 convert_to_fat_pointer (tree type, tree expr)
 {
-  tree template_type = TREE_TYPE (TREE_TYPE (TREE_CHAIN (TYPE_FIELDS (type))));
+  tree template_type = TREE_TYPE (TREE_TYPE (DECL_CHAIN (TYPE_FIELDS (type))));
   tree p_array_type = TREE_TYPE (TYPE_FIELDS (type));
   tree etype = TREE_TYPE (expr);
   tree template_tree;
@@ -3568,7 +3568,7 @@ convert_to_fat_pointer (tree type, tree expr)
     {
       CONSTRUCTOR_APPEND_ELT (v, TYPE_FIELDS (type),
 			      convert (p_array_type, expr));
-      CONSTRUCTOR_APPEND_ELT (v, TREE_CHAIN (TYPE_FIELDS (type)),
+      CONSTRUCTOR_APPEND_ELT (v, DECL_CHAIN (TYPE_FIELDS (type)),
 			      convert (build_pointer_type (template_type),
 				       expr));
       return gnat_build_constructor (type, v);
@@ -3588,7 +3588,7 @@ convert_to_fat_pointer (tree type, tree expr)
       template_tree = build_component_ref (expr, NULL_TREE, fields, false);
       expr = build_unary_op (ADDR_EXPR, NULL_TREE,
 			     build_component_ref (expr, NULL_TREE,
-						  TREE_CHAIN (fields), false));
+						  DECL_CHAIN (fields), false));
     }
 
   /* Otherwise, build the constructor for the template.  */
@@ -3609,7 +3609,7 @@ convert_to_fat_pointer (tree type, tree expr)
      will only refer to the provided TEMPLATE_TYPE in this case.  */
   CONSTRUCTOR_APPEND_ELT (v, TYPE_FIELDS (type),
 			  convert (p_array_type, expr));
-  CONSTRUCTOR_APPEND_ELT (v, TREE_CHAIN (TYPE_FIELDS (type)),
+  CONSTRUCTOR_APPEND_ELT (v, DECL_CHAIN (TYPE_FIELDS (type)),
 			  build_unary_op (ADDR_EXPR, NULL_TREE,
 					  template_tree));
   return gnat_build_constructor (type, v);
@@ -3775,7 +3775,7 @@ convert (tree type, tree expr)
      type and then build the template. */
   if (code == RECORD_TYPE && TYPE_CONTAINS_TEMPLATE_P (type))
     {
-      tree obj_type = TREE_TYPE (TREE_CHAIN (TYPE_FIELDS (type)));
+      tree obj_type = TREE_TYPE (DECL_CHAIN (TYPE_FIELDS (type)));
       VEC(constructor_elt,gc) *v = VEC_alloc (constructor_elt, gc, 2);
 
       /* If the source already has a template, get a reference to the
@@ -3786,7 +3786,7 @@ convert (tree type, tree expr)
       CONSTRUCTOR_APPEND_ELT (v, TYPE_FIELDS (type),
 			      build_template (TREE_TYPE (TYPE_FIELDS (type)),
 					      obj_type, NULL_TREE));
-      CONSTRUCTOR_APPEND_ELT (v, TREE_CHAIN (TYPE_FIELDS (type)),
+      CONSTRUCTOR_APPEND_ELT (v, DECL_CHAIN (TYPE_FIELDS (type)),
 			      convert (obj_type, expr));
       return gnat_build_constructor (type, v);
     }
@@ -3882,8 +3882,8 @@ convert (tree type, tree expr)
 		  && !initializer_constant_valid_for_bitfield_p (value))
 		clear_constant = true;
 
-	      efield = TREE_CHAIN (efield);
-	      field = TREE_CHAIN (field);
+	      efield = DECL_CHAIN (efield);
+	      field = DECL_CHAIN (field);
 	    }
 
 	  /* If we have been able to match and convert all the input fields
@@ -4264,14 +4264,14 @@ maybe_unconstrained_array (tree exp)
 	      && TYPE_CONTAINS_TEMPLATE_P (TREE_TYPE (new_exp)))
 	    return
 	      build_component_ref (new_exp, NULL_TREE,
-				   TREE_CHAIN
+				   DECL_CHAIN
 				   (TYPE_FIELDS (TREE_TYPE (new_exp))),
 				   false);
 	}
       else if (TYPE_CONTAINS_TEMPLATE_P (TREE_TYPE (exp)))
 	return
 	  build_component_ref (exp, NULL_TREE,
-			       TREE_CHAIN (TYPE_FIELDS (TREE_TYPE (exp))),
+			       DECL_CHAIN (TYPE_FIELDS (TREE_TYPE (exp))),
 			       false);
       break;
 
diff --git a/gcc/ada/gcc-interface/utils2.c b/gcc/ada/gcc-interface/utils2.c
index ab3814ec4e0b0a050bcf07288ac7b7727254171d..bd78686e2407134305f829e6717d6d65d607888a 100644
--- a/gcc/ada/gcc-interface/utils2.c
+++ b/gcc/ada/gcc-interface/utils2.c
@@ -1612,7 +1612,7 @@ build_simple_component_ref (tree record_variable, tree component,
 
       /* First loop thru normal components.  */
       for (new_field = TYPE_FIELDS (record_type); new_field;
-	   new_field = TREE_CHAIN (new_field))
+	   new_field = DECL_CHAIN (new_field))
 	if (SAME_FIELD_P (field, new_field))
 	  break;
 
@@ -1622,7 +1622,7 @@ build_simple_component_ref (tree record_variable, tree component,
          _Parent field.  */
       if (!new_field)
 	for (new_field = TYPE_FIELDS (record_type); new_field;
-	     new_field = TREE_CHAIN (new_field))
+	     new_field = DECL_CHAIN (new_field))
 	  if (DECL_INTERNAL_P (new_field))
 	    {
 	      tree field_ref
@@ -1996,7 +1996,7 @@ build_allocator (tree type, tree init, tree result_type, Entity_Id gnat_proc,
 
 	  CONSTRUCTOR_APPEND_ELT (v, TYPE_FIELDS (storage_type),
 				  build_template (template_type, type, init));
-	  CONSTRUCTOR_APPEND_ELT (v, TREE_CHAIN (TYPE_FIELDS (storage_type)),
+	  CONSTRUCTOR_APPEND_ELT (v, DECL_CHAIN (TYPE_FIELDS (storage_type)),
 				  init);
 
 	  return convert
@@ -2088,7 +2088,7 @@ fill_vms_descriptor (tree expr, Entity_Id gnat_formal, Node_Id gnat_actual)
   expr = maybe_unconstrained_array (expr);
   gnat_mark_addressable (expr);
 
-  for (field = TYPE_FIELDS (record_type); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (record_type); field; field = DECL_CHAIN (field))
     {
       tree conexpr = convert (TREE_TYPE (field),
 			      SUBSTITUTE_PLACEHOLDER_IN_EXPR
diff --git a/gcc/alias.c b/gcc/alias.c
index e46c8e9741a746f473a0daa952d6bedec6702fe0..2e28212f5b323066296d4c5604c28258c29a7fce 100644
--- a/gcc/alias.c
+++ b/gcc/alias.c
@@ -903,7 +903,7 @@ record_component_aliases (tree type)
 	    record_alias_subset (superset,
 				 get_alias_set (BINFO_TYPE (base_binfo)));
 	}
-      for (field = TYPE_FIELDS (type); field != 0; field = TREE_CHAIN (field))
+      for (field = TYPE_FIELDS (type); field != 0; field = DECL_CHAIN (field))
 	if (TREE_CODE (field) == FIELD_DECL && !DECL_NONADDRESSABLE_P (field))
 	  record_alias_subset (superset, get_alias_set (TREE_TYPE (field)));
       break;
diff --git a/gcc/c-decl.c b/gcc/c-decl.c
index 73a8dc01aecee00ff30c17113a5462cbf8359e7c..cd56513a66ba672652eaefdcd16b58796fdfc2f4 100644
--- a/gcc/c-decl.c
+++ b/gcc/c-decl.c
@@ -1076,7 +1076,7 @@ pop_scope (void)
     {
       tree file_decl = build_decl (UNKNOWN_LOCATION,
 	  			   TRANSLATION_UNIT_DECL, 0, 0);
-      TREE_CHAIN (file_decl) = all_translation_units;
+      DECL_CHAIN (file_decl) = all_translation_units;
       all_translation_units = file_decl;
       context = file_decl;
     }
@@ -1100,7 +1100,7 @@ pop_scope (void)
 	    warn_for_unused_label (p);
 
 	  /* Labels go in BLOCK_VARS.  */
-	  TREE_CHAIN (p) = BLOCK_VARS (block);
+	  DECL_CHAIN (p) = BLOCK_VARS (block);
 	  BLOCK_VARS (block) = p;
 	  gcc_assert (I_LABEL_BINDING (b->id) == b);
 	  I_LABEL_BINDING (b->id) = b->shadowed;
@@ -1188,7 +1188,7 @@ pop_scope (void)
 	     binding in the home scope.  */
 	  if (!b->nested)
 	    {
-	      TREE_CHAIN (p) = BLOCK_VARS (block);
+	      DECL_CHAIN (p) = BLOCK_VARS (block);
 	      BLOCK_VARS (block) = p;
 	    }
 	  else if (VAR_OR_FUNCTION_DECL_P (p))
@@ -1211,7 +1211,7 @@ pop_scope (void)
 		}
 	      if (b->locus != UNKNOWN_LOCATION)
 		DECL_SOURCE_LOCATION (extp) = b->locus;
-	      TREE_CHAIN (extp) = BLOCK_VARS (block);
+	      DECL_CHAIN (extp) = BLOCK_VARS (block);
 	      BLOCK_VARS (block) = extp;
 	    }
 	  /* If this is the file scope, and we are processing more
@@ -1293,7 +1293,7 @@ push_file_scope (void)
 
   start_fname_decls ();
 
-  for (decl = visible_builtins; decl; decl = TREE_CHAIN (decl))
+  for (decl = visible_builtins; decl; decl = DECL_CHAIN (decl))
     bind (DECL_NAME (decl), decl, file_scope,
 	  /*invisible=*/false, /*nested=*/true, DECL_SOURCE_LOCATION (decl));
 }
@@ -2400,7 +2400,7 @@ merge_decls (tree newdecl, tree olddecl, tree newtype, tree oldtype)
 	  DECL_STRUCT_FUNCTION (newdecl) = DECL_STRUCT_FUNCTION (olddecl);
 	  DECL_SAVED_TREE (newdecl) = DECL_SAVED_TREE (olddecl);
 	  DECL_ARGUMENTS (newdecl) = copy_list (DECL_ARGUMENTS (olddecl));
-	  for (t = DECL_ARGUMENTS (newdecl); t ; t = TREE_CHAIN (t))
+	  for (t = DECL_ARGUMENTS (newdecl); t ; t = DECL_CHAIN (t))
 	    DECL_CONTEXT (t) = newdecl;
 
 	  /* See if we've got a function to instantiate from.  */
@@ -3567,7 +3567,7 @@ c_builtin_function (tree decl)
      needing to be explicitly declared.  See push_file_scope.  */
   if (name[0] == '_' && (name[1] == '_' || ISUPPER (name[1])))
     {
-      TREE_CHAIN (decl) = visible_builtins;
+      DECL_CHAIN (decl) = visible_builtins;
       visible_builtins = decl;
     }
 
@@ -3593,7 +3593,7 @@ c_builtin_function_ext_scope (tree decl)
      needing to be explicitly declared.  See push_file_scope.  */
   if (name[0] == '_' && (name[1] == '_' || ISUPPER (name[1])))
     {
-      TREE_CHAIN (decl) = visible_builtins;
+      DECL_CHAIN (decl) = visible_builtins;
       visible_builtins = decl;
     }
 
@@ -4061,7 +4061,7 @@ start_decl (struct c_declarator *declarator, struct c_declspecs *declspecs,
       if (ce->kind == cdk_function)
 	{
 	  tree args = ce->u.arg_info->parms;
-	  for (; args; args = TREE_CHAIN (args))
+	  for (; args; args = DECL_CHAIN (args))
 	    {
 	      tree type = TREE_TYPE (args);
 	      if (type && INTEGRAL_TYPE_P (type)
@@ -4574,8 +4574,8 @@ flexible_array_type_p (tree type)
       x = TYPE_FIELDS (type);
       if (x == NULL_TREE)
 	return false;
-      while (TREE_CHAIN (x) != NULL_TREE)
-	x = TREE_CHAIN (x);
+      while (DECL_CHAIN (x) != NULL_TREE)
+	x = DECL_CHAIN (x);
       if (TREE_CODE (TREE_TYPE (x)) == ARRAY_TYPE
 	  && TYPE_SIZE (TREE_TYPE (x)) == NULL_TREE
 	  && TYPE_DOMAIN (TREE_TYPE (x)) != NULL_TREE
@@ -4583,7 +4583,7 @@ flexible_array_type_p (tree type)
 	return true;
       return false;
     case UNION_TYPE:
-      for (x = TYPE_FIELDS (type); x != NULL_TREE; x = TREE_CHAIN (x))
+      for (x = TYPE_FIELDS (type); x != NULL_TREE; x = DECL_CHAIN (x))
 	{
 	  if (flexible_array_type_p (TREE_TYPE (x)))
 	    return true;
@@ -6125,7 +6125,7 @@ grokparms (struct c_arg_info *arg_info, bool funcdef_flag)
 
       for (parm = arg_info->parms, typelt = arg_types, parmno = 1;
 	   parm;
-	   parm = TREE_CHAIN (parm), typelt = TREE_CHAIN (typelt), parmno++)
+	   parm = DECL_CHAIN (parm), typelt = TREE_CHAIN (typelt), parmno++)
 	{
 	  type = TREE_VALUE (typelt);
 	  if (type == error_mark_node)
@@ -6272,7 +6272,7 @@ get_parm_info (bool ellipsis)
 	  else
 	    {
 	      /* Valid parameter, add it to the list.  */
-	      TREE_CHAIN (decl) = parms;
+	      DECL_CHAIN (decl) = parms;
 	      parms = decl;
 
 	      /* Since there is a prototype, args are passed in their
@@ -6336,7 +6336,7 @@ get_parm_info (bool ellipsis)
 	  gcc_assert (TREE_CODE (decl) == FUNCTION_DECL
 		      ? b->nested
 		      : !b->nested);
-	  TREE_CHAIN (decl) = others;
+	  DECL_CHAIN (decl) = others;
 	  others = decl;
 	  /* fall through */
 
@@ -6659,7 +6659,7 @@ detect_field_duplicates_hash (tree fieldlist, htab_t htab)
   tree x, y;
   void **slot;
 
-  for (x = fieldlist; x ; x = TREE_CHAIN (x))
+  for (x = fieldlist; x ; x = DECL_CHAIN (x))
     if ((y = DECL_NAME (x)) != 0)
       {
 	slot = htab_find_slot (htab, y, INSERT);
@@ -6688,7 +6688,7 @@ detect_field_duplicates (tree fieldlist)
      This is trivially true if there are zero or one fields.  */
   if (!fieldlist)
     return;
-  x = TREE_CHAIN (fieldlist);
+  x = DECL_CHAIN (fieldlist);
   if (!x)
     return;
   do {
@@ -6697,7 +6697,7 @@ detect_field_duplicates (tree fieldlist)
 	&& (TREE_CODE (TREE_TYPE (x)) == RECORD_TYPE
 	    || TREE_CODE (TREE_TYPE (x)) == UNION_TYPE))
       timeout = 0;
-    x = TREE_CHAIN (x);
+    x = DECL_CHAIN (x);
   } while (timeout > 0 && x);
 
   /* If there were "few" fields and no anonymous structures or unions,
@@ -6705,7 +6705,8 @@ detect_field_duplicates (tree fieldlist)
      the nested traversal thing.  */
   if (timeout > 0)
     {
-      for (x = TREE_CHAIN (fieldlist); x ; x = TREE_CHAIN (x))
+      for (x = TREE_CHAIN (fieldlist); x ;
+	   x = TREE_CHAIN (x))
 	if (DECL_NAME (x))
 	  {
 	    for (y = fieldlist; y != x; y = TREE_CHAIN (y))
@@ -6760,7 +6761,7 @@ warn_cxx_compat_finish_struct (tree fieldlist)
 	   ++ix)
 	pointer_set_insert (tset, DECL_NAME (x));
 
-      for (x = fieldlist; x != NULL_TREE; x = TREE_CHAIN (x))
+      for (x = fieldlist; x != NULL_TREE; x = DECL_CHAIN (x))
 	{
 	  if (pointer_set_contains (tset, DECL_NAME (x)))
 	    {
@@ -6809,7 +6810,7 @@ finish_struct (location_t loc, tree t, tree fieldlist, tree attributes,
 
   if (pedantic)
     {
-      for (x = fieldlist; x; x = TREE_CHAIN (x))
+      for (x = fieldlist; x; x = DECL_CHAIN (x))
 	{
 	  if (DECL_NAME (x) != 0)
 	    break;
@@ -6846,7 +6847,7 @@ finish_struct (location_t loc, tree t, tree fieldlist, tree attributes,
      until now.)  */
 
   saw_named_field = 0;
-  for (x = fieldlist; x; x = TREE_CHAIN (x))
+  for (x = fieldlist; x; x = DECL_CHAIN (x))
     {
       if (TREE_TYPE (x) == error_mark_node)
 	continue;
@@ -6901,7 +6902,7 @@ finish_struct (location_t loc, tree t, tree fieldlist, tree attributes,
 			"flexible array member in union");
 	      TREE_TYPE (x) = error_mark_node;
 	    }
-	  else if (TREE_CHAIN (x) != NULL_TREE)
+	  else if (DECL_CHAIN (x) != NULL_TREE)
 	    {
 	      error_at (DECL_SOURCE_LOCATION (x),
 			"flexible array member not at end of struct");
@@ -6954,7 +6955,7 @@ finish_struct (location_t loc, tree t, tree fieldlist, tree attributes,
 	  DECL_INITIAL (*fieldlistp) = 0;
 	}
       else
-	fieldlistp = &TREE_CHAIN (*fieldlistp);
+	fieldlistp = &DECL_CHAIN (*fieldlistp);
   }
 
   /* Now we have the truly final field list.
@@ -6968,7 +6969,7 @@ finish_struct (location_t loc, tree t, tree fieldlist, tree attributes,
   {
     int len = 0;
 
-    for (x = fieldlist; x; x = TREE_CHAIN (x))
+    for (x = fieldlist; x; x = DECL_CHAIN (x))
       {
 	if (len > 15 || DECL_NAME (x) == NULL)
 	  break;
@@ -6994,7 +6995,7 @@ finish_struct (location_t loc, tree t, tree fieldlist, tree attributes,
 	len = 0;
 	space->s = space2;
 	field_array = &space2->elts[0];
-	for (x = fieldlist; x; x = TREE_CHAIN (x))
+	for (x = fieldlist; x; x = DECL_CHAIN (x))
 	  {
 	    field_array[len++] = x;
 
@@ -7666,7 +7667,7 @@ store_parm_decls_newstyle (tree fndecl, const struct c_arg_info *arg_info)
 
   /* Now make all the parameter declarations visible in the function body.
      We can bypass most of the grunt work of pushdecl.  */
-  for (decl = arg_info->parms; decl; decl = TREE_CHAIN (decl))
+  for (decl = arg_info->parms; decl; decl = DECL_CHAIN (decl))
     {
       DECL_CONTEXT (decl) = current_function_decl;
       if (DECL_NAME (decl))
@@ -7685,7 +7686,7 @@ store_parm_decls_newstyle (tree fndecl, const struct c_arg_info *arg_info)
   DECL_ARGUMENTS (fndecl) = arg_info->parms;
 
   /* Now make all the ancillary declarations visible, likewise.  */
-  for (decl = arg_info->others; decl; decl = TREE_CHAIN (decl))
+  for (decl = arg_info->others; decl; decl = DECL_CHAIN (decl))
     {
       DECL_CONTEXT (decl) = current_function_decl;
       if (DECL_NAME (decl))
@@ -7837,10 +7838,10 @@ store_parm_decls_oldstyle (tree fndecl, const struct c_arg_info *arg_info)
       for (parm = TREE_CHAIN (parm); parm; parm = TREE_CHAIN (parm))
 	if (TREE_PURPOSE (parm))
 	  {
-	    TREE_CHAIN (last) = TREE_PURPOSE (parm);
+	    DECL_CHAIN (last) = TREE_PURPOSE (parm);
 	    last = TREE_PURPOSE (parm);
 	  }
-      TREE_CHAIN (last) = 0;
+      DECL_CHAIN (last) = 0;
     }
 
   pointer_set_destroy (seen_args);
@@ -7856,7 +7857,7 @@ store_parm_decls_oldstyle (tree fndecl, const struct c_arg_info *arg_info)
 	     type = current_function_prototype_arg_types;
 	   parm || (type && TREE_VALUE (type) != error_mark_node
                    && (TYPE_MAIN_VARIANT (TREE_VALUE (type)) != void_type_node));
-	   parm = TREE_CHAIN (parm), type = TREE_CHAIN (type))
+	   parm = DECL_CHAIN (parm), type = TREE_CHAIN (type))
 	{
 	  if (parm == 0 || type == 0
 	      || TYPE_MAIN_VARIANT (TREE_VALUE (type)) == void_type_node)
@@ -7947,7 +7948,7 @@ store_parm_decls_oldstyle (tree fndecl, const struct c_arg_info *arg_info)
     {
       tree actual = 0, last = 0, type;
 
-      for (parm = DECL_ARGUMENTS (fndecl); parm; parm = TREE_CHAIN (parm))
+      for (parm = DECL_ARGUMENTS (fndecl); parm; parm = DECL_CHAIN (parm))
 	{
 	  type = tree_cons (NULL_TREE, DECL_ARG_TYPE (parm), NULL_TREE);
 	  if (last)
@@ -8068,7 +8069,7 @@ finish_function (void)
       && targetm.calls.promote_prototypes (TREE_TYPE (fndecl)))
     {
       tree args = DECL_ARGUMENTS (fndecl);
-      for (; args; args = TREE_CHAIN (args))
+      for (; args; args = DECL_CHAIN (args))
 	{
 	  tree type = TREE_TYPE (args);
 	  if (INTEGRAL_TYPE_P (type)
@@ -8131,7 +8132,7 @@ finish_function (void)
 
       for (decl = DECL_ARGUMENTS (fndecl);
 	   decl;
-	   decl = TREE_CHAIN (decl))
+	   decl = DECL_CHAIN (decl))
 	if (TREE_USED (decl)
 	    && TREE_CODE (decl) == PARM_DECL
 	    && !DECL_READ_P (decl)
@@ -9567,7 +9568,7 @@ c_write_global_declarations_1 (tree globals)
   bool reconsider;
 
   /* Process the decls in the order they were written.  */
-  for (decl = globals; decl; decl = TREE_CHAIN (decl))
+  for (decl = globals; decl; decl = DECL_CHAIN (decl))
     {
       /* Check for used but undefined static functions using the C
 	 standard's definition of "used", and set TREE_NO_WARNING so
@@ -9588,12 +9589,12 @@ c_write_global_declarations_1 (tree globals)
   do
     {
       reconsider = false;
-      for (decl = globals; decl; decl = TREE_CHAIN (decl))
+      for (decl = globals; decl; decl = DECL_CHAIN (decl))
 	reconsider |= wrapup_global_declaration_2 (decl);
     }
   while (reconsider);
 
-  for (decl = globals; decl; decl = TREE_CHAIN (decl))
+  for (decl = globals; decl; decl = DECL_CHAIN (decl))
     check_global_declaration_1 (decl);
 }
 
@@ -9605,7 +9606,7 @@ c_write_global_declarations_2 (tree globals)
 {
   tree decl;
 
-  for (decl = globals; decl ; decl = TREE_CHAIN (decl))
+  for (decl = globals; decl ; decl = DECL_CHAIN (decl))
     debug_hooks->global_decl (decl);
 }
 
@@ -9689,7 +9690,7 @@ c_write_global_declarations (void)
 
   /* Process all file scopes in this compilation, and the external_scope,
      through wrapup_global_declarations and check_global_declarations.  */
-  for (t = all_translation_units; t; t = TREE_CHAIN (t))
+  for (t = all_translation_units; t; t = DECL_CHAIN (t))
     c_write_global_declarations_1 (BLOCK_VARS (DECL_INITIAL (t)));
   c_write_global_declarations_1 (BLOCK_VARS (ext_block));
 
@@ -9702,7 +9703,7 @@ c_write_global_declarations (void)
   if (!seen_error ())
     {
       timevar_push (TV_SYMOUT);
-      for (t = all_translation_units; t; t = TREE_CHAIN (t))
+      for (t = all_translation_units; t; t = DECL_CHAIN (t))
 	c_write_global_declarations_2 (BLOCK_VARS (DECL_INITIAL (t)));
       c_write_global_declarations_2 (BLOCK_VARS (ext_block));
       timevar_pop (TV_SYMOUT);
diff --git a/gcc/c-family/ChangeLog b/gcc/c-family/ChangeLog
index 61e781d8b18204ffdb325013d04e34f07896db4d..b1d118fe6a1818062a588108a50b3b77079315e7 100644
--- a/gcc/c-family/ChangeLog
+++ b/gcc/c-family/ChangeLog
@@ -1,3 +1,8 @@
+2010-07-15  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* c-common.c: Carefully replace TREE_CHAIN with DECL_CHAIN.
+	* c-format.c: Likewise.
+
 2010-07-08  Manuel López-Ibáñez  <manu@gcc.gnu.org>
 
 	* c-common.h: Include diagnostic-core.h. Error if already
diff --git a/gcc/c-family/c-common.c b/gcc/c-family/c-common.c
index 491dd9e9500f595296c8e46be4483da6282458c8..e2a0561c7c6185e78ea8751b092b3fdaa24b73b5 100644
--- a/gcc/c-family/c-common.c
+++ b/gcc/c-family/c-common.c
@@ -4022,7 +4022,7 @@ c_type_hash (const void *p)
     default:
       gcc_unreachable ();
     }
-  for (; t2; t2 = TREE_CHAIN (t2))
+  for (; t2; t2 = DECL_CHAIN (t2))
     i++;
   /* We might have a VLA here.  */
   if (TREE_CODE (TYPE_SIZE (t)) != INTEGER_CST)
@@ -8390,8 +8390,8 @@ fold_offsetof_1 (tree expr, tree stop_ref)
 		    if (TREE_CODE (TREE_TYPE (TREE_OPERAND (v, 0)))
 			== RECORD_TYPE)
 		      {
-			tree fld_chain = TREE_CHAIN (TREE_OPERAND (v, 1));
-			for (; fld_chain; fld_chain = TREE_CHAIN (fld_chain))
+			tree fld_chain = DECL_CHAIN (TREE_OPERAND (v, 1));
+			for (; fld_chain; fld_chain = DECL_CHAIN (fld_chain))
 			  if (TREE_CODE (fld_chain) == FIELD_DECL)
 			    break;
 
diff --git a/gcc/c-family/c-format.c b/gcc/c-family/c-format.c
index 2c73ead370ce486231d98cb7c89fe53a051ba3d7..e7fd2295d52903b1cdb40b92acd433f6e505294d 100644
--- a/gcc/c-family/c-format.c
+++ b/gcc/c-family/c-format.c
@@ -911,7 +911,7 @@ check_function_format (tree attrs, int nargs, tree *argarray)
 		  tree args;
 		  for (args = DECL_ARGUMENTS (current_function_decl);
 		       args != 0;
-		       args = TREE_CHAIN (args))
+		       args = DECL_CHAIN (args))
 		    {
 		      if (TREE_CODE (TREE_TYPE (args)) == POINTER_TYPE
 			  && (TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE (args)))
diff --git a/gcc/c-parser.c b/gcc/c-parser.c
index 0493524a1b20dd4452d9bfdfd55e64126879119b..e773fe0d0fc421f0f0032a53e89e628210d74ab5 100644
--- a/gcc/c-parser.c
+++ b/gcc/c-parser.c
@@ -2229,7 +2229,7 @@ c_parser_struct_declaration (c_parser *parser)
 			 declarator, specs, width, &all_prefix_attrs);
 	  decl_attributes (&d, chainon (postfix_attrs,
 					all_prefix_attrs), 0);
-	  TREE_CHAIN (d) = decls;
+	  DECL_CHAIN (d) = decls;
 	  decls = d;
 	  if (c_parser_next_token_is_keyword (parser, RID_ATTRIBUTE))
 	    all_prefix_attrs = chainon (c_parser_attributes (parser),
@@ -6431,7 +6431,7 @@ c_parser_objc_class_instance_variables (c_parser *parser)
 	/* Comma-separated instance variables are chained together in
 	   reverse order; add them one by one.  */
 	tree ivar = nreverse (decls);
-	for (; ivar; ivar = TREE_CHAIN (ivar))
+	for (; ivar; ivar = DECL_CHAIN (ivar))
 	  objc_add_instance_variable (copy_node (ivar));
       }
       c_parser_skip_until_found (parser, CPP_SEMICOLON, "expected %<;%>");
diff --git a/gcc/c-typeck.c b/gcc/c-typeck.c
index 18e4bdcebfeb9717aa5854d1df189901733c7b2b..edf0d8b2c9dc00ee18f3fda49b365d325bbc4bc3 100644
--- a/gcc/c-typeck.c
+++ b/gcc/c-typeck.c
@@ -555,7 +555,7 @@ composite_type (tree t1, tree t2)
 		    && TREE_CODE (mv2) != ARRAY_TYPE)
 		  mv2 = TYPE_MAIN_VARIANT (mv2);
 		for (memb = TYPE_FIELDS (TREE_VALUE (p1));
-		     memb; memb = TREE_CHAIN (memb))
+		     memb; memb = DECL_CHAIN (memb))
 		  {
 		    tree mv3 = TREE_TYPE (memb);
 		    if (mv3 && mv3 != error_mark_node
@@ -580,7 +580,7 @@ composite_type (tree t1, tree t2)
 		    && TREE_CODE (mv1) != ARRAY_TYPE)
 		  mv1 = TYPE_MAIN_VARIANT (mv1);
 		for (memb = TYPE_FIELDS (TREE_VALUE (p2));
-		     memb; memb = TREE_CHAIN (memb))
+		     memb; memb = DECL_CHAIN (memb))
 		  {
 		    tree mv3 = TREE_TYPE (memb);
 		    if (mv3 && mv3 != error_mark_node
@@ -1434,7 +1434,7 @@ tagged_types_tu_compatible_p (const_tree t1, const_tree t2,
 
 	/*  Speed up the common case where the fields are in the same order. */
 	for (s1 = TYPE_FIELDS (t1), s2 = TYPE_FIELDS (t2); s1 && s2;
-	     s1 = TREE_CHAIN (s1), s2 = TREE_CHAIN (s2))
+	     s1 = DECL_CHAIN (s1), s2 = DECL_CHAIN (s2))
 	  {
 	    int result;
 
@@ -1467,11 +1467,11 @@ tagged_types_tu_compatible_p (const_tree t1, const_tree t2,
 	    return tu->val;
 	  }
 
-	for (s1 = TYPE_FIELDS (t1); s1; s1 = TREE_CHAIN (s1))
+	for (s1 = TYPE_FIELDS (t1); s1; s1 = DECL_CHAIN (s1))
 	  {
 	    bool ok = false;
 
-	    for (s2 = TYPE_FIELDS (t2); s2; s2 = TREE_CHAIN (s2))
+	    for (s2 = TYPE_FIELDS (t2); s2; s2 = DECL_CHAIN (s2))
 	      if (DECL_NAME (s1) == DECL_NAME (s2))
 		{
 		  int result;
@@ -1514,7 +1514,7 @@ tagged_types_tu_compatible_p (const_tree t1, const_tree t2,
 
 	for (s1 = TYPE_FIELDS (t1), s2 = TYPE_FIELDS (t2);
 	     s1 && s2;
-	     s1 = TREE_CHAIN (s1), s2 = TREE_CHAIN (s2))
+	     s1 = DECL_CHAIN (s1), s2 = DECL_CHAIN (s2))
 	  {
 	    int result;
 	    if (TREE_CODE (s1) != TREE_CODE (s2)
@@ -1684,7 +1684,7 @@ type_lists_compatible_p (const_tree args1, const_tree args2,
 	    {
 	      tree memb;
 	      for (memb = TYPE_FIELDS (a1);
-		   memb; memb = TREE_CHAIN (memb))
+		   memb; memb = DECL_CHAIN (memb))
 		{
 		  tree mv3 = TREE_TYPE (memb);
 		  if (mv3 && mv3 != error_mark_node
@@ -1706,7 +1706,7 @@ type_lists_compatible_p (const_tree args1, const_tree args2,
 	    {
 	      tree memb;
 	      for (memb = TYPE_FIELDS (a2);
-		   memb; memb = TREE_CHAIN (memb))
+		   memb; memb = DECL_CHAIN (memb))
 		{
 		  tree mv3 = TREE_TYPE (memb);
 		  if (mv3 && mv3 != error_mark_node
@@ -2081,7 +2081,7 @@ lookup_field (tree type, tree component)
     }
   else
     {
-      for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+      for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	{
 	  if (DECL_NAME (field) == NULL_TREE
 	      && (TREE_CODE (TREE_TYPE (field)) == RECORD_TYPE
@@ -4560,7 +4560,7 @@ build_c_cast (location_t loc, tree type, tree expr)
     {
       tree field;
 
-      for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+      for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	if (TREE_TYPE (field) != error_mark_node
 	    && comptypes (TYPE_MAIN_VARIANT (TREE_TYPE (field)),
 			  TYPE_MAIN_VARIANT (TREE_TYPE (value))))
@@ -5192,7 +5192,7 @@ convert_for_assignment (location_t location, tree type, tree rhs,
     {
       tree memb, marginal_memb = NULL_TREE;
 
-      for (memb = TYPE_FIELDS (type); memb ; memb = TREE_CHAIN (memb))
+      for (memb = TYPE_FIELDS (type); memb ; memb = DECL_CHAIN (memb))
 	{
 	  tree memb_type = TREE_TYPE (memb);
 
@@ -6483,7 +6483,7 @@ really_start_incremental_init (tree type)
       /* Skip any nameless bit fields at the beginning.  */
       while (constructor_fields != 0 && DECL_C_BIT_FIELD (constructor_fields)
 	     && DECL_NAME (constructor_fields) == 0)
-	constructor_fields = TREE_CHAIN (constructor_fields);
+	constructor_fields = DECL_CHAIN (constructor_fields);
 
       constructor_unfilled_fields = constructor_fields;
       constructor_bit_index = bitsize_zero_node;
@@ -6802,7 +6802,7 @@ pop_init_level (int implicit, struct obstack * braced_init_obstack)
 	  /* We have already issued an error message for the existence
 	     of a flexible array member not at the end of the structure.
 	     Discard the initializer so that we do not die later.  */
-	  if (TREE_CHAIN (constructor_fields) != NULL_TREE)
+	  if (DECL_CHAIN (constructor_fields) != NULL_TREE)
 	    constructor_type = NULL_TREE;
 	}
     }
@@ -6817,7 +6817,7 @@ pop_init_level (int implicit, struct obstack * braced_init_obstack)
 	while (constructor_unfilled_fields
 	       && (!DECL_SIZE (constructor_unfilled_fields)
 		   || integer_zerop (DECL_SIZE (constructor_unfilled_fields))))
-	  constructor_unfilled_fields = TREE_CHAIN (constructor_unfilled_fields);
+	  constructor_unfilled_fields = DECL_CHAIN (constructor_unfilled_fields);
 
 	/* Do not warn if this level of the initializer uses member
 	   designators; it is likely to be deliberate.  */
@@ -7650,7 +7650,7 @@ output_init_element (tree value, tree origtype, bool strict_string, tree type,
 	  || (COMPLETE_TYPE_P (TREE_TYPE (field))
 	      && integer_zerop (TYPE_SIZE (TREE_TYPE (field)))
 	      && (TREE_CODE (constructor_type) == ARRAY_TYPE
-		  || TREE_CHAIN (field)))))
+		  || DECL_CHAIN (field)))))
     return;
 
   if (semantic_type)
@@ -7738,14 +7738,14 @@ output_init_element (tree value, tree origtype, bool strict_string, tree type,
   else if (TREE_CODE (constructor_type) == RECORD_TYPE)
     {
       constructor_unfilled_fields
-	= TREE_CHAIN (constructor_unfilled_fields);
+	= DECL_CHAIN (constructor_unfilled_fields);
 
       /* Skip any nameless bit fields.  */
       while (constructor_unfilled_fields != 0
 	     && DECL_C_BIT_FIELD (constructor_unfilled_fields)
 	     && DECL_NAME (constructor_unfilled_fields) == 0)
 	constructor_unfilled_fields =
-	  TREE_CHAIN (constructor_unfilled_fields);
+	  DECL_CHAIN (constructor_unfilled_fields);
     }
   else if (TREE_CODE (constructor_type) == UNION_TYPE)
     constructor_unfilled_fields = 0;
@@ -8062,22 +8062,22 @@ process_init_element (struct c_expr value, bool implicit,
 		 it isn't now, so update.  */
 	      if (constructor_unfilled_fields == constructor_fields)
 		{
-		  constructor_unfilled_fields = TREE_CHAIN (constructor_fields);
+		  constructor_unfilled_fields = DECL_CHAIN (constructor_fields);
 		  /* Skip any nameless bit fields.  */
 		  while (constructor_unfilled_fields != 0
 			 && DECL_C_BIT_FIELD (constructor_unfilled_fields)
 			 && DECL_NAME (constructor_unfilled_fields) == 0)
 		    constructor_unfilled_fields =
-		      TREE_CHAIN (constructor_unfilled_fields);
+		      DECL_CHAIN (constructor_unfilled_fields);
 		}
 	    }
 
-	  constructor_fields = TREE_CHAIN (constructor_fields);
+	  constructor_fields = DECL_CHAIN (constructor_fields);
 	  /* Skip any nameless bit fields at the beginning.  */
 	  while (constructor_fields != 0
 		 && DECL_C_BIT_FIELD (constructor_fields)
 		 && DECL_NAME (constructor_fields) == 0)
-	    constructor_fields = TREE_CHAIN (constructor_fields);
+	    constructor_fields = DECL_CHAIN (constructor_fields);
 	}
       else if (TREE_CODE (constructor_type) == UNION_TYPE)
 	{
diff --git a/gcc/cfgexpand.c b/gcc/cfgexpand.c
index b39d4db2cc5f453f63a8908ddc4cb1e3ffd582ef..d8378ee14b6891a1e3539b607a98f8a712f85edf 100644
--- a/gcc/cfgexpand.c
+++ b/gcc/cfgexpand.c
@@ -344,7 +344,7 @@ aggregate_contains_union_type (tree type)
   if (TREE_CODE (type) != RECORD_TYPE)
     return false;
 
-  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
     if (TREE_CODE (field) == FIELD_DECL)
       if (aggregate_contains_union_type (TREE_TYPE (field)))
 	return true;
@@ -1019,7 +1019,7 @@ expand_used_vars_for_block (tree block, bool toplevel)
   old_sv_num = toplevel ? 0 : stack_vars_num;
 
   /* Expand all variables at this level.  */
-  for (t = BLOCK_VARS (block); t ; t = TREE_CHAIN (t))
+  for (t = BLOCK_VARS (block); t ; t = DECL_CHAIN (t))
     if (TREE_USED (t))
       expand_one_var (t, toplevel, true);
 
@@ -1051,7 +1051,7 @@ clear_tree_used (tree block)
 {
   tree t;
 
-  for (t = BLOCK_VARS (block); t ; t = TREE_CHAIN (t))
+  for (t = BLOCK_VARS (block); t ; t = DECL_CHAIN (t))
     /* if (!TREE_STATIC (t) && !DECL_EXTERNAL (t)) */
       TREE_USED (t) = 0;
 
@@ -1210,7 +1210,7 @@ account_used_vars_for_block (tree block, bool toplevel)
   HOST_WIDE_INT size = 0;
 
   /* Expand all variables at this level.  */
-  for (t = BLOCK_VARS (block); t ; t = TREE_CHAIN (t))
+  for (t = BLOCK_VARS (block); t ; t = DECL_CHAIN (t))
     if (TREE_USED (t))
       size += expand_one_var (t, toplevel, false);
 
diff --git a/gcc/cgraph.c b/gcc/cgraph.c
index 66a88db4610bac79fa9dd89c42ab70eb3c581ce3..63fed497b471be8eaa2fc1bed034f5fdbe32bf53 100644
--- a/gcc/cgraph.c
+++ b/gcc/cgraph.c
@@ -2302,7 +2302,7 @@ cgraph_create_virtual_clone (struct cgraph_node *old_node,
       struct cgraph_node *orig_node;
       for (orig_node = old_node; orig_node->clone_of; orig_node = orig_node->clone_of)
         ;
-      for (arg = DECL_ARGUMENTS (orig_node->decl); arg; arg = TREE_CHAIN (arg), oldi++)
+      for (arg = DECL_ARGUMENTS (orig_node->decl); arg; arg = DECL_CHAIN (arg), oldi++)
 	{
 	  if (bitmap_bit_p (old_node->clone.combined_args_to_skip, oldi))
 	    {
diff --git a/gcc/cgraphunit.c b/gcc/cgraphunit.c
index f0d0a97141bfe1c0434841d46bd7cad7a07f0c1b..2367067af69ddd94faae92750a26265dc9375ab1 100644
--- a/gcc/cgraphunit.c
+++ b/gcc/cgraphunit.c
@@ -1527,7 +1527,7 @@ assemble_thunk (struct cgraph_node *node)
             restmp = create_tmp_var_raw (restype, "retval");
 	}
 
-      for (arg = a; arg; arg = TREE_CHAIN (arg))
+      for (arg = a; arg; arg = DECL_CHAIN (arg))
         nargs++;
       vargs = VEC_alloc (tree, heap, nargs);
       if (this_adjusting)
@@ -1537,7 +1537,7 @@ assemble_thunk (struct cgraph_node *node)
 				      virtual_offset));
       else
         VEC_quick_push (tree, vargs, a);
-      for (i = 1, arg = TREE_CHAIN (a); i < nargs; i++, arg = TREE_CHAIN (arg))
+      for (i = 1, arg = DECL_CHAIN (a); i < nargs; i++, arg = DECL_CHAIN (arg))
         VEC_quick_push (tree, vargs, arg);
       call = gimple_build_call_vec (build_fold_addr_expr_loc (0, alias), vargs);
       VEC_free (tree, heap, vargs);
diff --git a/gcc/combine.c b/gcc/combine.c
index 4dcb6cef5ca92ad7ceb28a8e9ce146510d8ef7ac..0a1e787cbb712d8f81dbedc2a1074653a9122c1a 100644
--- a/gcc/combine.c
+++ b/gcc/combine.c
@@ -1341,7 +1341,7 @@ setup_incoming_promotions (rtx first)
   bool strictly_local = false;
 
   for (arg = DECL_ARGUMENTS (current_function_decl); arg;
-       arg = TREE_CHAIN (arg))
+       arg = DECL_CHAIN (arg))
     {
       rtx x, reg = DECL_INCOMING_RTL (arg);
       int uns1, uns3;
diff --git a/gcc/config/alpha/alpha.c b/gcc/config/alpha/alpha.c
index f36e1fd173fb61914b2940a36ec8273f12a74141..336c107be513f95196c33444980ef800c1519cd2 100644
--- a/gcc/config/alpha/alpha.c
+++ b/gcc/config/alpha/alpha.c
@@ -5944,13 +5944,13 @@ alpha_build_builtin_va_list (void)
 		    FIELD_DECL, get_identifier ("__offset"),
 		    integer_type_node);
   DECL_FIELD_CONTEXT (ofs) = record;
-  TREE_CHAIN (ofs) = space;
+  DECL_CHAIN (ofs) = space;
 
   base = build_decl (BUILTINS_LOCATION,
 		     FIELD_DECL, get_identifier ("__base"),
 		     ptr_type_node);
   DECL_FIELD_CONTEXT (base) = record;
-  TREE_CHAIN (base) = ofs;
+  DECL_CHAIN (base) = ofs;
 
   TYPE_FIELDS (record) = base;
   layout_type (record);
@@ -6304,7 +6304,7 @@ alpha_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
   else
     {
       base_field = TYPE_FIELDS (TREE_TYPE (valist));
-      offset_field = TREE_CHAIN (base_field);
+      offset_field = DECL_CHAIN (base_field);
 
       base_field = build3 (COMPONENT_REF, TREE_TYPE (base_field),
 			   valist, base_field, NULL_TREE);
@@ -6408,7 +6408,7 @@ alpha_gimplify_va_arg (tree valist, tree type, gimple_seq *pre_p,
     return std_gimplify_va_arg_expr (valist, type, pre_p, post_p);
 
   base_field = TYPE_FIELDS (va_list_type_node);
-  offset_field = TREE_CHAIN (base_field);
+  offset_field = DECL_CHAIN (base_field);
   base_field = build3 (COMPONENT_REF, TREE_TYPE (base_field),
 		       valist, base_field, NULL_TREE);
   offset_field = build3 (COMPONENT_REF, TREE_TYPE (offset_field),
diff --git a/gcc/config/arm/arm.c b/gcc/config/arm/arm.c
index aa0f9cc7590c9fe8041f6fe54257eb7a4aaaa269..7b01afb3136baf9273af2cd06f942bb3d0b6b8ba 100644
--- a/gcc/config/arm/arm.c
+++ b/gcc/config/arm/arm.c
@@ -3536,7 +3536,7 @@ arm_return_in_memory (const_tree type, const_tree fntype)
 	 have been created by C++.  */
       for (field = TYPE_FIELDS (type);
 	   field && TREE_CODE (field) != FIELD_DECL;
-	   field = TREE_CHAIN (field))
+	   field = DECL_CHAIN (field))
 	continue;
 
       if (field == NULL)
@@ -3555,9 +3555,9 @@ arm_return_in_memory (const_tree type, const_tree fntype)
 
       /* Now check the remaining fields, if any.  Only bitfields are allowed,
 	 since they are not addressable.  */
-      for (field = TREE_CHAIN (field);
+      for (field = DECL_CHAIN (field);
 	   field;
-	   field = TREE_CHAIN (field))
+	   field = DECL_CHAIN (field))
 	{
 	  if (TREE_CODE (field) != FIELD_DECL)
 	    continue;
@@ -3577,7 +3577,7 @@ arm_return_in_memory (const_tree type, const_tree fntype)
 	 integral, or can be returned in an integer register.  */
       for (field = TYPE_FIELDS (type);
 	   field;
-	   field = TREE_CHAIN (field))
+	   field = DECL_CHAIN (field))
 	{
 	  if (TREE_CODE (field) != FIELD_DECL)
 	    continue;
@@ -3837,7 +3837,7 @@ aapcs_vfp_sub_candidate (const_tree type, enum machine_mode *modep)
 	if (!COMPLETE_TYPE_P(type))
 	  return -1;
 
-	for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+	for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	  {
 	    if (TREE_CODE (field) != FIELD_DECL)
 	      continue;
@@ -3869,7 +3869,7 @@ aapcs_vfp_sub_candidate (const_tree type, enum machine_mode *modep)
 	if (!COMPLETE_TYPE_P(type))
 	  return -1;
 
-	for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+	for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	  {
 	    if (TREE_CODE (field) != FIELD_DECL)
 	      continue;
diff --git a/gcc/config/frv/frv.c b/gcc/config/frv/frv.c
index 3a85fc5fa7645d51c65f39760e6ca9b98f6688e1..10768fb81c5b5871eaa161df2d473e627919e51e 100644
--- a/gcc/config/frv/frv.c
+++ b/gcc/config/frv/frv.c
@@ -1182,7 +1182,7 @@ frv_stack_info (void)
       /* Find the last argument, and see if it is __builtin_va_alist.  */
       for (cur_arg = DECL_ARGUMENTS (fndecl); cur_arg != (tree)0; cur_arg = next_arg)
 	{
-	  next_arg = TREE_CHAIN (cur_arg);
+	  next_arg = DECL_CHAIN (cur_arg);
 	  if (next_arg == (tree)0)
 	    {
 	      if (DECL_NAME (cur_arg)
@@ -6634,7 +6634,7 @@ frv_adjust_field_align (tree field, int computed)
       tree prev = NULL_TREE;
       tree cur;
 
-      for (cur = TYPE_FIELDS (parent); cur && cur != field; cur = TREE_CHAIN (cur))
+      for (cur = TYPE_FIELDS (parent); cur && cur != field; cur = DECL_CHAIN (cur))
 	{
 	  if (TREE_CODE (cur) != FIELD_DECL)
 	    continue;
diff --git a/gcc/config/i386/i386.c b/gcc/config/i386/i386.c
index 4fd2aab96f48b4aae63a0066ee9a7b14759a9f81..beb263465a47d63ed0aa9a17157333a8fe3a0506 100644
--- a/gcc/config/i386/i386.c
+++ b/gcc/config/i386/i386.c
@@ -5475,7 +5475,7 @@ classify_argument (enum machine_mode mode, const_tree type,
 	{
 	case RECORD_TYPE:
 	  /* And now merge the fields of structure.  */
-	  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+	  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	    {
 	      if (TREE_CODE (field) == FIELD_DECL)
 		{
@@ -5563,7 +5563,7 @@ classify_argument (enum machine_mode mode, const_tree type,
 	case QUAL_UNION_TYPE:
 	  /* Unions are similar to RECORD_TYPE but offset is always 0.
 	     */
-	  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+	  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	    {
 	      if (TREE_CODE (field) == FIELD_DECL)
 		{
@@ -6532,7 +6532,7 @@ contains_aligned_value_p (tree type)
 	    tree field;
 
 	    /* Walk all the structure fields.  */
-	    for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+	    for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	      {
 		if (TREE_CODE (field) == FIELD_DECL
 		    && contains_aligned_value_p (TREE_TYPE (field)))
@@ -6998,9 +6998,9 @@ ix86_build_builtin_va_list_abi (enum calling_abi abi)
   TREE_CHAIN (record) = type_decl;
   TYPE_NAME (record) = type_decl;
   TYPE_FIELDS (record) = f_gpr;
-  TREE_CHAIN (f_gpr) = f_fpr;
-  TREE_CHAIN (f_fpr) = f_ovf;
-  TREE_CHAIN (f_ovf) = f_sav;
+  DECL_CHAIN (f_gpr) = f_fpr;
+  DECL_CHAIN (f_fpr) = f_ovf;
+  DECL_CHAIN (f_ovf) = f_sav;
 
   layout_type (record);
 
@@ -7212,9 +7212,9 @@ ix86_va_start (tree valist, rtx nextarg)
     }
 
   f_gpr = TYPE_FIELDS (TREE_TYPE (sysv_va_list_type_node));
-  f_fpr = TREE_CHAIN (f_gpr);
-  f_ovf = TREE_CHAIN (f_fpr);
-  f_sav = TREE_CHAIN (f_ovf);
+  f_fpr = DECL_CHAIN (f_gpr);
+  f_ovf = DECL_CHAIN (f_fpr);
+  f_sav = DECL_CHAIN (f_ovf);
 
   valist = build_simple_mem_ref (valist);
   TREE_TYPE (valist) = TREE_TYPE (sysv_va_list_type_node);
@@ -7299,9 +7299,9 @@ ix86_gimplify_va_arg (tree valist, tree type, gimple_seq *pre_p,
     return std_gimplify_va_arg_expr (valist, type, pre_p, post_p);
 
   f_gpr = TYPE_FIELDS (TREE_TYPE (sysv_va_list_type_node));
-  f_fpr = TREE_CHAIN (f_gpr);
-  f_ovf = TREE_CHAIN (f_fpr);
-  f_sav = TREE_CHAIN (f_ovf);
+  f_fpr = DECL_CHAIN (f_gpr);
+  f_ovf = DECL_CHAIN (f_fpr);
+  f_sav = DECL_CHAIN (f_ovf);
 
   gpr = build3 (COMPONENT_REF, TREE_TYPE (f_gpr),
 		build_va_arg_indirect_ref (valist), f_gpr, NULL_TREE);
diff --git a/gcc/config/i386/winnt-cxx.c b/gcc/config/i386/winnt-cxx.c
index f22f818254a50a0adae10d549440274a5ce688f9..9191c08a676a159fc85bcf76067e75faa8a501af 100644
--- a/gcc/config/i386/winnt-cxx.c
+++ b/gcc/config/i386/winnt-cxx.c
@@ -99,12 +99,12 @@ i386_pe_adjust_class_at_definition (tree t)
   if (lookup_attribute ("dllexport", TYPE_ATTRIBUTES (t)) != NULL_TREE)
     {
       /* Check static VAR_DECL's.  */
-      for (member = TYPE_FIELDS (t); member; member = TREE_CHAIN (member))
+      for (member = TYPE_FIELDS (t); member; member = DECL_CHAIN (member))
 	if (TREE_CODE (member) == VAR_DECL)     
 	  maybe_add_dllexport (member);
     
       /* Check FUNCTION_DECL's.  */
-      for (member = TYPE_METHODS (t); member;  member = TREE_CHAIN (member))
+      for (member = TYPE_METHODS (t); member;  member = DECL_CHAIN (member))
 	if (TREE_CODE (member) == FUNCTION_DECL)
 	  {
 	    tree thunk;
@@ -116,7 +116,7 @@ i386_pe_adjust_class_at_definition (tree t)
 	      maybe_add_dllexport (thunk);
 	}
       /* Check vtables  */
-      for (member = CLASSTYPE_VTABLES (t); member;  member = TREE_CHAIN (member))
+      for (member = CLASSTYPE_VTABLES (t); member;  member = DECL_CHAIN (member))
 	if (TREE_CODE (member) == VAR_DECL) 
 	  maybe_add_dllexport (member);
     }
@@ -132,12 +132,12 @@ i386_pe_adjust_class_at_definition (tree t)
 	 definition.   */
 
       /* Check static VAR_DECL's.  */
-      for (member = TYPE_FIELDS (t); member; member = TREE_CHAIN (member))
+      for (member = TYPE_FIELDS (t); member; member = DECL_CHAIN (member))
 	if (TREE_CODE (member) == VAR_DECL)     
 	  maybe_add_dllimport (member);
     
       /* Check FUNCTION_DECL's.  */
-      for (member = TYPE_METHODS (t); member;  member = TREE_CHAIN (member))
+      for (member = TYPE_METHODS (t); member;  member = DECL_CHAIN (member))
 	if (TREE_CODE (member) == FUNCTION_DECL)
 	  {
 	    tree thunk;
@@ -145,12 +145,12 @@ i386_pe_adjust_class_at_definition (tree t)
 	  
 	    /* Also add the attribute to its thunks.  */
 	    for (thunk = DECL_THUNKS (member); thunk;
-		 thunk = TREE_CHAIN (thunk))
+		 thunk = DECL_CHAIN (thunk))
 	      maybe_add_dllimport (thunk);
 	 }
  
       /* Check vtables  */
-      for (member = CLASSTYPE_VTABLES (t); member;  member = TREE_CHAIN (member))
+      for (member = CLASSTYPE_VTABLES (t); member;  member = DECL_CHAIN (member))
 	if (TREE_CODE (member) == VAR_DECL) 
 	  maybe_add_dllimport (member);
 
diff --git a/gcc/config/ia64/ia64.c b/gcc/config/ia64/ia64.c
index 865d2abb50273a6a92fa18dc5ddbbc50c504fc91..475f3d9b5873af06efa4655a51a111f5e215f9d4 100644
--- a/gcc/config/ia64/ia64.c
+++ b/gcc/config/ia64/ia64.c
@@ -4160,7 +4160,7 @@ hfa_element_mode (const_tree type, bool nested)
     case RECORD_TYPE:
     case UNION_TYPE:
     case QUAL_UNION_TYPE:
-      for (t = TYPE_FIELDS (type); t; t = TREE_CHAIN (t))
+      for (t = TYPE_FIELDS (type); t; t = DECL_CHAIN (t))
 	{
 	  if (TREE_CODE (t) != FIELD_DECL)
 	    continue;
diff --git a/gcc/config/iq2000/iq2000.c b/gcc/config/iq2000/iq2000.c
index a7d65354323fb794b8cbb65959231219f393fad3..71642099120402fae60ef449cfac4aa79227808f 100644
--- a/gcc/config/iq2000/iq2000.c
+++ b/gcc/config/iq2000/iq2000.c
@@ -1274,7 +1274,7 @@ function_arg (CUMULATIVE_ARGS *cum, enum machine_mode mode, const_tree type,
 	{
 	  tree field;
 
-	  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+	  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	    if (TREE_CODE (field) == FIELD_DECL
 		&& TREE_CODE (TREE_TYPE (field)) == REAL_TYPE
 		&& TYPE_PRECISION (TREE_TYPE (field)) == BITS_PER_WORD
@@ -1311,7 +1311,7 @@ function_arg (CUMULATIVE_ARGS *cum, enum machine_mode mode, const_tree type,
 		{
 		  rtx reg;
 
-		  for (; field; field = TREE_CHAIN (field))
+		  for (; field; field = DECL_CHAIN (field))
 		    if (TREE_CODE (field) == FIELD_DECL
 			&& int_bit_position (field) >= bitpos)
 		      break;
@@ -1901,7 +1901,7 @@ iq2000_expand_prologue (void)
 					      PARM_DECL, NULL_TREE, type);
 
       DECL_ARG_TYPE (function_result_decl) = type;
-      TREE_CHAIN (function_result_decl) = fnargs;
+      DECL_CHAIN (function_result_decl) = fnargs;
       fnargs = function_result_decl;
     }
 
@@ -1930,7 +1930,7 @@ iq2000_expand_prologue (void)
       entry_parm = FUNCTION_ARG (args_so_far, passed_mode, passed_type, 1);
 
       FUNCTION_ARG_ADVANCE (args_so_far, passed_mode, passed_type, 1);
-      next_arg = TREE_CHAIN (cur_arg);
+      next_arg = DECL_CHAIN (cur_arg);
 
       if (entry_parm && store_args_on_stack)
 	{
diff --git a/gcc/config/mep/mep.c b/gcc/config/mep/mep.c
index af556df4c5e2b5691dbdd3b253635b5c2b973812..1d83d8d76e2ede3298ec39be0f914626900414cd 100644
--- a/gcc/config/mep/mep.c
+++ b/gcc/config/mep/mep.c
@@ -3611,9 +3611,9 @@ mep_build_builtin_va_list (void)
   DECL_FIELD_CONTEXT (f_next_stack) = record;
 
   TYPE_FIELDS (record) = f_next_gp;
-  TREE_CHAIN (f_next_gp) = f_next_gp_limit;
-  TREE_CHAIN (f_next_gp_limit) = f_next_cop;
-  TREE_CHAIN (f_next_cop) = f_next_stack;
+  DECL_CHAIN (f_next_gp) = f_next_gp_limit;
+  DECL_CHAIN (f_next_gp_limit) = f_next_cop;
+  DECL_CHAIN (f_next_cop) = f_next_stack;
 
   layout_type (record);
 
@@ -3631,9 +3631,9 @@ mep_expand_va_start (tree valist, rtx nextarg)
   ns = cfun->machine->arg_regs_to_save;
 
   f_next_gp = TYPE_FIELDS (va_list_type_node);
-  f_next_gp_limit = TREE_CHAIN (f_next_gp);
-  f_next_cop = TREE_CHAIN (f_next_gp_limit);
-  f_next_stack = TREE_CHAIN (f_next_cop);
+  f_next_gp_limit = DECL_CHAIN (f_next_gp);
+  f_next_cop = DECL_CHAIN (f_next_gp_limit);
+  f_next_stack = DECL_CHAIN (f_next_cop);
 
   next_gp = build3 (COMPONENT_REF, TREE_TYPE (f_next_gp), valist, f_next_gp,
 		    NULL_TREE);
@@ -3697,9 +3697,9 @@ mep_gimplify_va_arg_expr (tree valist, tree type,
   rsize = (size + UNITS_PER_WORD - 1) & -UNITS_PER_WORD;
 
   f_next_gp = TYPE_FIELDS (va_list_type_node);
-  f_next_gp_limit = TREE_CHAIN (f_next_gp);
-  f_next_cop = TREE_CHAIN (f_next_gp_limit);
-  f_next_stack = TREE_CHAIN (f_next_cop);
+  f_next_gp_limit = DECL_CHAIN (f_next_gp);
+  f_next_cop = DECL_CHAIN (f_next_gp_limit);
+  f_next_stack = DECL_CHAIN (f_next_cop);
 
   next_gp = build3 (COMPONENT_REF, TREE_TYPE (f_next_gp), valist, f_next_gp,
 		    NULL_TREE);
diff --git a/gcc/config/mips/mips.c b/gcc/config/mips/mips.c
index c4938f6f0eff439a5f2ef06f642d0b5cfb8e3ce7..3d4ffaeabeb3c85de80193a8356ea5ddba1cbaa3 100644
--- a/gcc/config/mips/mips.c
+++ b/gcc/config/mips/mips.c
@@ -4857,7 +4857,7 @@ mips_function_arg (const CUMULATIVE_ARGS *cum, enum machine_mode mode,
       tree field;
 
       /* First check to see if there is any such field.  */
-      for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+      for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	if (TREE_CODE (field) == FIELD_DECL
 	    && SCALAR_FLOAT_TYPE_P (TREE_TYPE (field))
 	    && TYPE_PRECISION (TREE_TYPE (field)) == BITS_PER_WORD
@@ -4884,7 +4884,7 @@ mips_function_arg (const CUMULATIVE_ARGS *cum, enum machine_mode mode,
 	    {
 	      rtx reg;
 
-	      for (; field; field = TREE_CHAIN (field))
+	      for (; field; field = DECL_CHAIN (field))
 		if (TREE_CODE (field) == FIELD_DECL
 		    && int_bit_position (field) >= bitpos)
 		  break;
@@ -5122,7 +5122,7 @@ mips_fpr_return_fields (const_tree valtype, tree *fields)
     return 0;
 
   i = 0;
-  for (field = TYPE_FIELDS (valtype); field != 0; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (valtype); field != 0; field = DECL_CHAIN (field))
     {
       if (TREE_CODE (field) != FIELD_DECL)
 	continue;
@@ -5444,11 +5444,11 @@ mips_build_builtin_va_list (void)
       DECL_FIELD_CONTEXT (f_res) = record;
 
       TYPE_FIELDS (record) = f_ovfl;
-      TREE_CHAIN (f_ovfl) = f_gtop;
-      TREE_CHAIN (f_gtop) = f_ftop;
-      TREE_CHAIN (f_ftop) = f_goff;
-      TREE_CHAIN (f_goff) = f_foff;
-      TREE_CHAIN (f_foff) = f_res;
+      DECL_CHAIN (f_ovfl) = f_gtop;
+      DECL_CHAIN (f_gtop) = f_ftop;
+      DECL_CHAIN (f_ftop) = f_goff;
+      DECL_CHAIN (f_goff) = f_foff;
+      DECL_CHAIN (f_foff) = f_res;
 
       layout_type (record);
       return record;
@@ -5483,10 +5483,10 @@ mips_va_start (tree valist, rtx nextarg)
 	= (MAX_ARGS_IN_REGISTERS - cum->num_fprs) * UNITS_PER_FPREG;
 
       f_ovfl = TYPE_FIELDS (va_list_type_node);
-      f_gtop = TREE_CHAIN (f_ovfl);
-      f_ftop = TREE_CHAIN (f_gtop);
-      f_goff = TREE_CHAIN (f_ftop);
-      f_foff = TREE_CHAIN (f_goff);
+      f_gtop = DECL_CHAIN (f_ovfl);
+      f_ftop = DECL_CHAIN (f_gtop);
+      f_goff = DECL_CHAIN (f_ftop);
+      f_foff = DECL_CHAIN (f_goff);
 
       ovfl = build3 (COMPONENT_REF, TREE_TYPE (f_ovfl), valist, f_ovfl,
 		     NULL_TREE);
@@ -5568,10 +5568,10 @@ mips_gimplify_va_arg_expr (tree valist, tree type, gimple_seq *pre_p,
       tree t, u;
 
       f_ovfl = TYPE_FIELDS (va_list_type_node);
-      f_gtop = TREE_CHAIN (f_ovfl);
-      f_ftop = TREE_CHAIN (f_gtop);
-      f_goff = TREE_CHAIN (f_ftop);
-      f_foff = TREE_CHAIN (f_goff);
+      f_gtop = DECL_CHAIN (f_ovfl);
+      f_ftop = DECL_CHAIN (f_gtop);
+      f_goff = DECL_CHAIN (f_ftop);
+      f_foff = DECL_CHAIN (f_goff);
 
       /* Let:
 
diff --git a/gcc/config/pa/som.h b/gcc/config/pa/som.h
index 5d1c054a3eb7c51dd373b46c2445bbb86f4c5b42..8be8deffe32aa449508b42728231de66f0146a4b 100644
--- a/gcc/config/pa/som.h
+++ b/gcc/config/pa/som.h
@@ -118,7 +118,7 @@ do {								\
 		 fputs (",PRIV_LEV=3", FILE);				\
 	       }							\
 	     for (parm = DECL_ARGUMENTS (DECL), i = 0; parm && i < 4;	\
-		  parm = TREE_CHAIN (parm))				\
+		  parm = DECL_CHAIN (parm))				\
 	       {							\
 		 if (TYPE_MODE (DECL_ARG_TYPE (parm)) == SFmode		\
 		     && ! TARGET_SOFT_FLOAT)				\
diff --git a/gcc/config/rs6000/rs6000.c b/gcc/config/rs6000/rs6000.c
index 23f6a563ad7cbe89aa03effc61d123d4e196eb7c..c6f67d433eab987f55f9fd984a020d0a2d71390a 100644
--- a/gcc/config/rs6000/rs6000.c
+++ b/gcc/config/rs6000/rs6000.c
@@ -5093,7 +5093,7 @@ rs6000_special_round_type_align (tree type, unsigned int computed,
 
   /* Skip all non field decls */
   while (field != NULL && TREE_CODE (field) != FIELD_DECL)
-    field = TREE_CHAIN (field);
+    field = DECL_CHAIN (field);
 
   if (field != NULL && field != type)
     {
@@ -5125,7 +5125,7 @@ darwin_rs6000_special_round_type_align (tree type, unsigned int computed,
     tree field = TYPE_FIELDS (type);
     /* Skip all non field decls */
     while (field != NULL && TREE_CODE (field) != FIELD_DECL)
-      field = TREE_CHAIN (field);
+      field = DECL_CHAIN (field);
     if (! field)
       break;
     /* A packed field does not contribute any extra alignment.  */
@@ -7574,7 +7574,7 @@ rs6000_darwin64_record_arg_advance_recurse (CUMULATIVE_ARGS *cum,
 {
   tree f;
 
-  for (f = TYPE_FIELDS (type); f ; f = TREE_CHAIN (f))
+  for (f = TYPE_FIELDS (type); f ; f = DECL_CHAIN (f))
     if (TREE_CODE (f) == FIELD_DECL)
       {
 	HOST_WIDE_INT bitpos = startbitpos;
@@ -7974,7 +7974,7 @@ rs6000_darwin64_record_arg_recurse (CUMULATIVE_ARGS *cum, const_tree type,
 {
   tree f;
 
-  for (f = TYPE_FIELDS (type); f ; f = TREE_CHAIN (f))
+  for (f = TYPE_FIELDS (type); f ; f = DECL_CHAIN (f))
     if (TREE_CODE (f) == FIELD_DECL)
       {
 	HOST_WIDE_INT bitpos = startbitpos;
@@ -8801,10 +8801,10 @@ rs6000_build_builtin_va_list (void)
   TREE_CHAIN (record) = type_decl;
   TYPE_NAME (record) = type_decl;
   TYPE_FIELDS (record) = f_gpr;
-  TREE_CHAIN (f_gpr) = f_fpr;
-  TREE_CHAIN (f_fpr) = f_res;
-  TREE_CHAIN (f_res) = f_ovf;
-  TREE_CHAIN (f_ovf) = f_sav;
+  DECL_CHAIN (f_gpr) = f_fpr;
+  DECL_CHAIN (f_fpr) = f_res;
+  DECL_CHAIN (f_res) = f_ovf;
+  DECL_CHAIN (f_ovf) = f_sav;
 
   layout_type (record);
 
@@ -8829,10 +8829,10 @@ rs6000_va_start (tree valist, rtx nextarg)
     }
 
   f_gpr = TYPE_FIELDS (TREE_TYPE (va_list_type_node));
-  f_fpr = TREE_CHAIN (f_gpr);
-  f_res = TREE_CHAIN (f_fpr);
-  f_ovf = TREE_CHAIN (f_res);
-  f_sav = TREE_CHAIN (f_ovf);
+  f_fpr = DECL_CHAIN (f_gpr);
+  f_res = DECL_CHAIN (f_fpr);
+  f_ovf = DECL_CHAIN (f_res);
+  f_sav = DECL_CHAIN (f_ovf);
 
   valist = build_va_arg_indirect_ref (valist);
   gpr = build3 (COMPONENT_REF, TREE_TYPE (f_gpr), valist, f_gpr, NULL_TREE);
@@ -8950,10 +8950,10 @@ rs6000_gimplify_va_arg (tree valist, tree type, gimple_seq *pre_p,
     }
 
   f_gpr = TYPE_FIELDS (TREE_TYPE (va_list_type_node));
-  f_fpr = TREE_CHAIN (f_gpr);
-  f_res = TREE_CHAIN (f_fpr);
-  f_ovf = TREE_CHAIN (f_res);
-  f_sav = TREE_CHAIN (f_ovf);
+  f_fpr = DECL_CHAIN (f_gpr);
+  f_res = DECL_CHAIN (f_fpr);
+  f_ovf = DECL_CHAIN (f_res);
+  f_sav = DECL_CHAIN (f_ovf);
 
   valist = build_va_arg_indirect_ref (valist);
   gpr = build3 (COMPONENT_REF, TREE_TYPE (f_gpr), valist, f_gpr, NULL_TREE);
@@ -14292,7 +14292,7 @@ rs6000_alloc_sdmode_stack_slot (void)
       }
 
   /* Check for any SDmode parameters of the function.  */
-  for (t = DECL_ARGUMENTS (cfun->decl); t; t = TREE_CHAIN (t))
+  for (t = DECL_ARGUMENTS (cfun->decl); t; t = DECL_CHAIN (t))
     {
       if (TREE_TYPE (t) == error_mark_node)
 	continue;
@@ -21002,7 +21002,7 @@ rs6000_output_function_epilogue (FILE *file,
 	  int next_parm_info_bit = 31;
 
 	  for (decl = DECL_ARGUMENTS (current_function_decl);
-	       decl; decl = TREE_CHAIN (decl))
+	       decl; decl = DECL_CHAIN (decl))
 	    {
 	      rtx parameter = DECL_INCOMING_RTL (decl);
 	      enum machine_mode mode = GET_MODE (parameter);
diff --git a/gcc/config/s390/s390.c b/gcc/config/s390/s390.c
index 4d6ba981abb7c50a37c58d9648dfacb0755cf890..56cbac2022c8f990941d4a3031e4d02b8e3ed7c1 100644
--- a/gcc/config/s390/s390.c
+++ b/gcc/config/s390/s390.c
@@ -8283,7 +8283,7 @@ s390_function_arg_float (enum machine_mode mode, tree type)
     {
       tree field, single = NULL_TREE;
 
-      for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+      for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	{
 	  if (TREE_CODE (field) != FIELD_DECL)
 	    continue;
@@ -8591,9 +8591,9 @@ s390_build_builtin_va_list (void)
   TREE_CHAIN (record) = type_decl;
   TYPE_NAME (record) = type_decl;
   TYPE_FIELDS (record) = f_gpr;
-  TREE_CHAIN (f_gpr) = f_fpr;
-  TREE_CHAIN (f_fpr) = f_ovf;
-  TREE_CHAIN (f_ovf) = f_sav;
+  DECL_CHAIN (f_gpr) = f_fpr;
+  DECL_CHAIN (f_fpr) = f_ovf;
+  DECL_CHAIN (f_ovf) = f_sav;
 
   layout_type (record);
 
@@ -8623,9 +8623,9 @@ s390_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
   tree gpr, fpr, ovf, sav, t;
 
   f_gpr = TYPE_FIELDS (TREE_TYPE (va_list_type_node));
-  f_fpr = TREE_CHAIN (f_gpr);
-  f_ovf = TREE_CHAIN (f_fpr);
-  f_sav = TREE_CHAIN (f_ovf);
+  f_fpr = DECL_CHAIN (f_gpr);
+  f_ovf = DECL_CHAIN (f_fpr);
+  f_sav = DECL_CHAIN (f_ovf);
 
   valist = build_va_arg_indirect_ref (valist);
   gpr = build3 (COMPONENT_REF, TREE_TYPE (f_gpr), valist, f_gpr, NULL_TREE);
@@ -8721,9 +8721,9 @@ s390_gimplify_va_arg (tree valist, tree type, gimple_seq *pre_p,
   tree lab_false, lab_over, addr;
 
   f_gpr = TYPE_FIELDS (TREE_TYPE (va_list_type_node));
-  f_fpr = TREE_CHAIN (f_gpr);
-  f_ovf = TREE_CHAIN (f_fpr);
-  f_sav = TREE_CHAIN (f_ovf);
+  f_fpr = DECL_CHAIN (f_gpr);
+  f_ovf = DECL_CHAIN (f_fpr);
+  f_sav = DECL_CHAIN (f_ovf);
 
   valist = build_va_arg_indirect_ref (valist);
   gpr = build3 (COMPONENT_REF, TREE_TYPE (f_gpr), valist, f_gpr, NULL_TREE);
diff --git a/gcc/config/sh/sh.c b/gcc/config/sh/sh.c
index 2055a5b161a750bed726a5916727d42a18d981f9..8ace99c732cdd849931be19605f0e5bdb2ef2b03 100644
--- a/gcc/config/sh/sh.c
+++ b/gcc/config/sh/sh.c
@@ -7694,10 +7694,10 @@ sh_build_builtin_va_list (void)
   TREE_CHAIN (record) = type_decl;
   TYPE_NAME (record) = type_decl;
   TYPE_FIELDS (record) = f_next_o;
-  TREE_CHAIN (f_next_o) = f_next_o_limit;
-  TREE_CHAIN (f_next_o_limit) = f_next_fp;
-  TREE_CHAIN (f_next_fp) = f_next_fp_limit;
-  TREE_CHAIN (f_next_fp_limit) = f_next_stack;
+  DECL_CHAIN (f_next_o) = f_next_o_limit;
+  DECL_CHAIN (f_next_o_limit) = f_next_fp;
+  DECL_CHAIN (f_next_fp) = f_next_fp_limit;
+  DECL_CHAIN (f_next_fp_limit) = f_next_stack;
 
   layout_type (record);
 
@@ -7729,10 +7729,10 @@ sh_va_start (tree valist, rtx nextarg)
     }
 
   f_next_o = TYPE_FIELDS (va_list_type_node);
-  f_next_o_limit = TREE_CHAIN (f_next_o);
-  f_next_fp = TREE_CHAIN (f_next_o_limit);
-  f_next_fp_limit = TREE_CHAIN (f_next_fp);
-  f_next_stack = TREE_CHAIN (f_next_fp_limit);
+  f_next_o_limit = DECL_CHAIN (f_next_o);
+  f_next_fp = DECL_CHAIN (f_next_o_limit);
+  f_next_fp_limit = DECL_CHAIN (f_next_fp);
+  f_next_stack = DECL_CHAIN (f_next_fp_limit);
 
   next_o = build3 (COMPONENT_REF, TREE_TYPE (f_next_o), valist, f_next_o,
 		   NULL_TREE);
@@ -7791,7 +7791,7 @@ find_sole_member (tree type)
 {
   tree field, member = NULL_TREE;
 
-  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
     {
       if (TREE_CODE (field) != FIELD_DECL)
 	continue;
@@ -7834,10 +7834,10 @@ sh_gimplify_va_arg_expr (tree valist, tree type, gimple_seq *pre_p,
       tree member;
 
       f_next_o = TYPE_FIELDS (va_list_type_node);
-      f_next_o_limit = TREE_CHAIN (f_next_o);
-      f_next_fp = TREE_CHAIN (f_next_o_limit);
-      f_next_fp_limit = TREE_CHAIN (f_next_fp);
-      f_next_stack = TREE_CHAIN (f_next_fp_limit);
+      f_next_o_limit = DECL_CHAIN (f_next_o);
+      f_next_fp = DECL_CHAIN (f_next_o_limit);
+      f_next_fp_limit = DECL_CHAIN (f_next_fp);
+      f_next_stack = DECL_CHAIN (f_next_fp_limit);
 
       next_o = build3 (COMPONENT_REF, TREE_TYPE (f_next_o), valist, f_next_o,
 		       NULL_TREE);
diff --git a/gcc/config/sh/symbian-cxx.c b/gcc/config/sh/symbian-cxx.c
index 1496f02e55e4a2e5c6544be1328b9af88165d077..5f1ef93ca6e6605dc3b10f2fd4d35c6160374c13 100644
--- a/gcc/config/sh/symbian-cxx.c
+++ b/gcc/config/sh/symbian-cxx.c
@@ -630,7 +630,7 @@ sh_symbian_handle_dll_attribute (tree *pnode, tree name, tree args,
 	  sh_symbian_add_attribute (function, attr);
 
 	  /* Propagate the attribute to any function thunks as well.  */
-	  for (thunk = DECL_THUNKS (function); thunk; thunk = TREE_CHAIN (thunk))
+	  for (thunk = DECL_THUNKS (function); thunk; thunk = DECL_CHAIN (thunk))
 	    if (TREE_CODE (thunk) == FUNCTION_DECL)
 	      sh_symbian_add_attribute (thunk, attr);
 	}
@@ -639,7 +639,7 @@ sh_symbian_handle_dll_attribute (tree *pnode, tree name, tree args,
   if (TREE_CODE (node) == FUNCTION_DECL && DECL_VIRTUAL_P (node))
     {
       /* Propagate the attribute to any thunks of this function.  */
-      for (thunk = DECL_THUNKS (node); thunk; thunk = TREE_CHAIN (thunk))
+      for (thunk = DECL_THUNKS (node); thunk; thunk = DECL_CHAIN (thunk))
 	if (TREE_CODE (thunk) == FUNCTION_DECL)
 	  sh_symbian_add_attribute (thunk, attr);
     }
diff --git a/gcc/config/sparc/sparc.c b/gcc/config/sparc/sparc.c
index 8335daf3b64eca49723c95481c8c624e6511e1d2..d476955403345bff150ac500a365d4d0e388b62b 100644
--- a/gcc/config/sparc/sparc.c
+++ b/gcc/config/sparc/sparc.c
@@ -4873,7 +4873,7 @@ scan_record_type (tree type, int *intregs_p, int *fpregs_p, int *packed_p)
 {
   tree field;
 
-  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
     {
       if (TREE_CODE (field) == FIELD_DECL)
 	{
@@ -5093,7 +5093,7 @@ function_arg_record_value_1 (const_tree type, HOST_WIDE_INT startbitpos,
       }
 
   /* Compute how many registers we need.  */
-  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
     {
       if (TREE_CODE (field) == FIELD_DECL)
 	{
@@ -5232,7 +5232,7 @@ function_arg_record_value_2 (const_tree type, HOST_WIDE_INT startbitpos,
   tree field;
 
   if (! packed_p)
-    for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+    for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
       {
 	if (TREE_CODE (field) == FIELD_DECL && DECL_PACKED (field))
 	  {
@@ -5241,7 +5241,7 @@ function_arg_record_value_2 (const_tree type, HOST_WIDE_INT startbitpos,
 	  }
       }
 
-  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
     {
       if (TREE_CODE (field) == FIELD_DECL)
 	{
diff --git a/gcc/config/spu/spu.c b/gcc/config/spu/spu.c
index 9a600ebed47eb93cf34305d2bf00f08f7bbe03e5..689b50048ffa1f79efe2dd9e792a7bc18b1d0da7 100644
--- a/gcc/config/spu/spu.c
+++ b/gcc/config/spu/spu.c
@@ -4076,7 +4076,7 @@ spu_build_builtin_va_list (void)
   TREE_CHAIN (record) = type_decl;
   TYPE_NAME (record) = type_decl;
   TYPE_FIELDS (record) = f_args;
-  TREE_CHAIN (f_args) = f_skip;
+  DECL_CHAIN (f_args) = f_skip;
 
   /* We know this is being padded and we want it too.  It is an internal
      type so hide the warnings from the user. */
@@ -4111,7 +4111,7 @@ spu_va_start (tree valist, rtx nextarg)
   tree args, skip, t;
 
   f_args = TYPE_FIELDS (TREE_TYPE (va_list_type_node));
-  f_skip = TREE_CHAIN (f_args);
+  f_skip = DECL_CHAIN (f_args);
 
   valist = build_va_arg_indirect_ref (valist);
   args =
@@ -4166,7 +4166,7 @@ spu_gimplify_va_arg_expr (tree valist, tree type, gimple_seq * pre_p,
   bool pass_by_reference_p;
 
   f_args = TYPE_FIELDS (TREE_TYPE (va_list_type_node));
-  f_skip = TREE_CHAIN (f_args);
+  f_skip = DECL_CHAIN (f_args);
 
   valist = build_simple_mem_ref (valist);
   args =
diff --git a/gcc/config/stormy16/stormy16.c b/gcc/config/stormy16/stormy16.c
index 91dc53a2c3351f78f3438f8a3d1b2da9217255eb..bdfd07d0c4cce56aeab916588ee1702665a6ddfa 100644
--- a/gcc/config/stormy16/stormy16.c
+++ b/gcc/config/stormy16/stormy16.c
@@ -1317,7 +1317,7 @@ xstormy16_build_builtin_va_list (void)
   TREE_CHAIN (record) = type_decl;
   TYPE_NAME (record) = type_decl;
   TYPE_FIELDS (record) = f_1;
-  TREE_CHAIN (f_1) = f_2;
+  DECL_CHAIN (f_1) = f_2;
 
   layout_type (record);
 
@@ -1340,7 +1340,7 @@ xstormy16_expand_builtin_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
     error ("cannot use va_start in interrupt function");
 
   f_base = TYPE_FIELDS (va_list_type_node);
-  f_count = TREE_CHAIN (f_base);
+  f_count = DECL_CHAIN (f_base);
 
   base = build3 (COMPONENT_REF, TREE_TYPE (f_base), valist, f_base, NULL_TREE);
   count = build3 (COMPONENT_REF, TREE_TYPE (f_count), valist, f_count,
@@ -1377,7 +1377,7 @@ xstormy16_gimplify_va_arg_expr (tree valist, tree type, gimple_seq *pre_p,
   tree size_tree;
 
   f_base = TYPE_FIELDS (va_list_type_node);
-  f_count = TREE_CHAIN (f_base);
+  f_count = DECL_CHAIN (f_base);
 
   base = build3 (COMPONENT_REF, TREE_TYPE (f_base), valist, f_base, NULL_TREE);
   count = build3 (COMPONENT_REF, TREE_TYPE (f_count), valist, f_count,
diff --git a/gcc/config/vxworks.c b/gcc/config/vxworks.c
index 410fcef15e614e3745defc8bbdfa0ee21e350705..94e412d25b011f9f0dcd0cad2f1f9908f8712c62 100644
--- a/gcc/config/vxworks.c
+++ b/gcc/config/vxworks.c
@@ -78,13 +78,13 @@ vxworks_emutls_var_fields (tree type, tree *name)
   field = build_decl (FIELD_DECL, get_identifier ("module_id"),
 		      unsigned_type_node);
   DECL_CONTEXT (field) = type;
-  TREE_CHAIN (field) = next_field;
+  DECL_CHAIN (field) = next_field;
   next_field = field;
 
   field = build_decl (FIELD_DECL, get_identifier ("offset"),
 		      unsigned_type_node);
   DECL_CONTEXT (field) = type;
-  TREE_CHAIN (field) = next_field;
+  DECL_CHAIN (field) = next_field;
 
   return field;
 }
@@ -108,12 +108,12 @@ vxworks_emutls_var_init (tree var, tree decl, tree tmpl_addr)
   elt->value = fold_convert (TREE_TYPE (field), tmpl_addr);
   
   elt = VEC_quick_push (constructor_elt, v, NULL);
-  field = TREE_CHAIN (field);
+  field = DECL_CHAIN (field);
   elt->index = field;
   elt->value = build_int_cst (TREE_TYPE (field), 0);
   
   elt = VEC_quick_push (constructor_elt, v, NULL);
-  field = TREE_CHAIN (field);
+  field = DECL_CHAIN (field);
   elt->index = field;
   elt->value = fold_convert (TREE_TYPE (field), DECL_SIZE_UNIT (decl));
   
diff --git a/gcc/config/xtensa/xtensa.c b/gcc/config/xtensa/xtensa.c
index 915feeb41919fcc5c065618f5c913bda3ad569d8..610a2723cd21f0c7cb07c15629f37eeafb2702b6 100644
--- a/gcc/config/xtensa/xtensa.c
+++ b/gcc/config/xtensa/xtensa.c
@@ -2685,8 +2685,8 @@ xtensa_build_builtin_va_list (void)
   TREE_CHAIN (record) = type_decl;
   TYPE_NAME (record) = type_decl;
   TYPE_FIELDS (record) = f_stk;
-  TREE_CHAIN (f_stk) = f_reg;
-  TREE_CHAIN (f_reg) = f_ndx;
+  DECL_CHAIN (f_stk) = f_reg;
+  DECL_CHAIN (f_reg) = f_ndx;
 
   layout_type (record);
   return record;
@@ -2740,8 +2740,8 @@ xtensa_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
   arg_words = crtl->args.info.arg_words;
 
   f_stk = TYPE_FIELDS (va_list_type_node);
-  f_reg = TREE_CHAIN (f_stk);
-  f_ndx = TREE_CHAIN (f_reg);
+  f_reg = DECL_CHAIN (f_stk);
+  f_ndx = DECL_CHAIN (f_reg);
 
   stk = build3 (COMPONENT_REF, TREE_TYPE (f_stk), valist, f_stk, NULL_TREE);
   reg = build3 (COMPONENT_REF, TREE_TYPE (f_reg), unshare_expr (valist),
@@ -2810,8 +2810,8 @@ xtensa_gimplify_va_arg_expr (tree valist, tree type, gimple_seq *pre_p,
     }
 
   f_stk = TYPE_FIELDS (va_list_type_node);
-  f_reg = TREE_CHAIN (f_stk);
-  f_ndx = TREE_CHAIN (f_reg);
+  f_reg = DECL_CHAIN (f_stk);
+  f_ndx = DECL_CHAIN (f_reg);
 
   stk = build3 (COMPONENT_REF, TREE_TYPE (f_stk), valist,
 		f_stk, NULL_TREE);
diff --git a/gcc/coverage.c b/gcc/coverage.c
index 9b8a6900e6bb762f7acd6f23442fc34e0a623545..20aaa1074ce138c6aa48c05888dbf1ab9c68b86b 100644
--- a/gcc/coverage.c
+++ b/gcc/coverage.c
@@ -648,7 +648,7 @@ build_fn_info_type (unsigned int counters)
   /* checksum */
   field = build_decl (BUILTINS_LOCATION,
 		      FIELD_DECL, NULL_TREE, get_gcov_unsigned_t ());
-  TREE_CHAIN (field) = fields;
+  DECL_CHAIN (field) = fields;
   fields = field;
 
   array_type = build_int_cst (NULL_TREE, counters - 1);
@@ -658,7 +658,7 @@ build_fn_info_type (unsigned int counters)
   /* counters */
   field = build_decl (BUILTINS_LOCATION,
 		      FIELD_DECL, NULL_TREE, array_type);
-  TREE_CHAIN (field) = fields;
+  DECL_CHAIN (field) = fields;
   fields = field;
 
   finish_builtin_struct (type, "__gcov_fn_info", fields, NULL_TREE);
@@ -682,13 +682,13 @@ build_fn_info_value (const struct function_list *function, tree type)
   CONSTRUCTOR_APPEND_ELT (v1, fields,
 			  build_int_cstu (get_gcov_unsigned_t (),
 					  function->ident));
-  fields = TREE_CHAIN (fields);
+  fields = DECL_CHAIN (fields);
 
   /* checksum */
   CONSTRUCTOR_APPEND_ELT (v1, fields,
 			  build_int_cstu (get_gcov_unsigned_t (),
 					  function->checksum));
-  fields = TREE_CHAIN (fields);
+  fields = DECL_CHAIN (fields);
 
   /* counters */
   for (ix = 0; ix != GCOV_COUNTERS; ix++)
@@ -716,13 +716,13 @@ build_ctr_info_type (void)
   /* counters */
   field = build_decl (BUILTINS_LOCATION,
 		      FIELD_DECL, NULL_TREE, get_gcov_unsigned_t ());
-  TREE_CHAIN (field) = fields;
+  DECL_CHAIN (field) = fields;
   fields = field;
 
   /* values */
   field = build_decl (BUILTINS_LOCATION,
 		      FIELD_DECL, NULL_TREE, gcov_ptr_type);
-  TREE_CHAIN (field) = fields;
+  DECL_CHAIN (field) = fields;
   fields = field;
 
   /* merge */
@@ -733,7 +733,7 @@ build_ctr_info_type (void)
   field = build_decl (BUILTINS_LOCATION,
 		      FIELD_DECL, NULL_TREE,
 		      build_pointer_type (gcov_merge_fn_type));
-  TREE_CHAIN (field) = fields;
+  DECL_CHAIN (field) = fields;
   fields = field;
 
   finish_builtin_struct (type, "__gcov_ctr_info", fields, NULL_TREE);
@@ -756,7 +756,7 @@ build_ctr_info_value (unsigned int counter, tree type)
   CONSTRUCTOR_APPEND_ELT (v, fields,
 			  build_int_cstu (get_gcov_unsigned_t (),
 					  prg_n_ctrs[counter]));
-  fields = TREE_CHAIN (fields);
+  fields = DECL_CHAIN (fields);
 
   if (prg_n_ctrs[counter])
     {
@@ -779,7 +779,7 @@ build_ctr_info_value (unsigned int counter, tree type)
     }
   else
     CONSTRUCTOR_APPEND_ELT (v, fields, null_pointer_node);
-  fields = TREE_CHAIN (fields);
+  fields = DECL_CHAIN (fields);
 
   fn = build_decl (BUILTINS_LOCATION,
 		   FUNCTION_DECL,
@@ -826,7 +826,7 @@ build_gcov_info (void)
   /* Version ident */
   field = build_decl (BUILTINS_LOCATION,
 		      FIELD_DECL, NULL_TREE, get_gcov_unsigned_t ());
-  TREE_CHAIN (field) = fields;
+  DECL_CHAIN (field) = fields;
   fields = field;
   CONSTRUCTOR_APPEND_ELT (v1, field,
 			  build_int_cstu (TREE_TYPE (field), GCOV_VERSION));
@@ -834,14 +834,14 @@ build_gcov_info (void)
   /* next -- NULL */
   field = build_decl (BUILTINS_LOCATION,
 		      FIELD_DECL, NULL_TREE, build_pointer_type (const_type));
-  TREE_CHAIN (field) = fields;
+  DECL_CHAIN (field) = fields;
   fields = field;
   CONSTRUCTOR_APPEND_ELT (v1, field, null_pointer_node);
 
   /* stamp */
   field = build_decl (BUILTINS_LOCATION,
 		      FIELD_DECL, NULL_TREE, get_gcov_unsigned_t ());
-  TREE_CHAIN (field) = fields;
+  DECL_CHAIN (field) = fields;
   fields = field;
   CONSTRUCTOR_APPEND_ELT (v1, field,
 			  build_int_cstu (TREE_TYPE (field), local_tick));
@@ -851,7 +851,7 @@ build_gcov_info (void)
 						    TYPE_QUAL_CONST));
   field = build_decl (BUILTINS_LOCATION,
 		      FIELD_DECL, NULL_TREE, string_type);
-  TREE_CHAIN (field) = fields;
+  DECL_CHAIN (field) = fields;
   fields = field;
   da_file_name_len = strlen (da_file_name);
   filename_string = build_string (da_file_name_len + 1, da_file_name);
@@ -885,7 +885,7 @@ build_gcov_info (void)
   /* number of functions */
   field = build_decl (BUILTINS_LOCATION,
 		      FIELD_DECL, NULL_TREE, get_gcov_unsigned_t ());
-  TREE_CHAIN (field) = fields;
+  DECL_CHAIN (field) = fields;
   fields = field;
   CONSTRUCTOR_APPEND_ELT (v1, field,
 			  build_int_cstu (get_gcov_unsigned_t (), n_fns));
@@ -893,14 +893,14 @@ build_gcov_info (void)
   /* fn_info table */
   field = build_decl (BUILTINS_LOCATION,
 		      FIELD_DECL, NULL_TREE, fn_info_ptr_type);
-  TREE_CHAIN (field) = fields;
+  DECL_CHAIN (field) = fields;
   fields = field;
   CONSTRUCTOR_APPEND_ELT (v1, field, fn_info_value);
 
   /* counter_mask */
   field = build_decl (BUILTINS_LOCATION,
 		      FIELD_DECL, NULL_TREE, get_gcov_unsigned_t ());
-  TREE_CHAIN (field) = fields;
+  DECL_CHAIN (field) = fields;
   fields = field;
   CONSTRUCTOR_APPEND_ELT (v1, field, 
 			  build_int_cstu (get_gcov_unsigned_t (),
@@ -920,7 +920,7 @@ build_gcov_info (void)
 
   field = build_decl (BUILTINS_LOCATION,
 		      FIELD_DECL, NULL_TREE, ctr_info_ary_type);
-  TREE_CHAIN (field) = fields;
+  DECL_CHAIN (field) = fields;
   fields = field;
   CONSTRUCTOR_APPEND_ELT (v1, field, ctr_info_value);
 
diff --git a/gcc/cp/ChangeLog b/gcc/cp/ChangeLog
index ea3e9b51d1fd7ac98cd5835257282b145b6555c1..8b1399c81e6e43324aaa3ffb0d78fd8a7ba19de8 100644
--- a/gcc/cp/ChangeLog
+++ b/gcc/cp/ChangeLog
@@ -1,3 +1,23 @@
+2010-07-15  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* cp-tree.h: Carefully replace TREE_CHAIN with DECL_CHAIN.
+	* call.c: Likewise.
+	* class.c: Likewise.
+	* cp-gimplify.c: Likewise.
+	* decl.c: Likewise.
+	* decl2.c: Likewise.
+	* init.c: Likewise.
+	* mangle.c: Likewise.
+	* name-lookup.c: Likewise.
+	* optimize.c: Likewise.
+	* parser.c: Likewise.
+	* pt.c: Likewise.
+	* rtti.c: Likewise.
+	* search.c: Likewise.
+	* semantics.c: Likewise.
+	* typeck.c: Likewise.
+	* typeck2.c: Likewise.
+
 2010-07-14  Jason Merrill  <jason@redhat.com>
 
 	* init.c (sort_mem_initializers): Rename "field_type" to "ctx".
diff --git a/gcc/cp/call.c b/gcc/cp/call.c
index 1c6414950bb5b71772d3b0c6d2caba1f56cfcc2a..8e259ee6e0ded62ea0c359a0c7908cbc06403e2e 100644
--- a/gcc/cp/call.c
+++ b/gcc/cp/call.c
@@ -641,7 +641,7 @@ build_aggr_conv (tree type, tree ctor, int flags)
   tree field = next_initializable_field (TYPE_FIELDS (type));
   tree empty_ctor = NULL_TREE;
 
-  for (; field; field = next_initializable_field (TREE_CHAIN (field)))
+  for (; field; field = next_initializable_field (DECL_CHAIN (field)))
     {
       if (i < CONSTRUCTOR_NELTS (ctor))
 	{
@@ -6095,7 +6095,7 @@ build_java_interface_fn_ref (tree fn, tree instance)
 
   /* Determine the itable index of FN.  */
   i = 1;
-  for (method = TYPE_METHODS (iface); method; method = TREE_CHAIN (method))
+  for (method = TYPE_METHODS (iface); method; method = DECL_CHAIN (method))
     {
       if (!DECL_VIRTUAL_P (method))
 	continue;
@@ -6227,7 +6227,7 @@ build_special_member_call (tree instance, tree name, VEC(tree,gc) **args,
       /* If the current function is a complete object constructor
 	 or destructor, then we fetch the VTT directly.
 	 Otherwise, we look it up using the VTT we were given.  */
-      vtt = TREE_CHAIN (CLASSTYPE_VTABLES (current_class_type));
+      vtt = DECL_CHAIN (CLASSTYPE_VTABLES (current_class_type));
       vtt = decay_conversion (vtt);
       vtt = build3 (COND_EXPR, TREE_TYPE (vtt),
 		    build2 (EQ_EXPR, boolean_type_node,
diff --git a/gcc/cp/class.c b/gcc/cp/class.c
index a572af83f637c3d4dfec909b03e7187f1b07af18..79b5a26d77522c3f420e4de54dbbddb6b5e2bc45 100644
--- a/gcc/cp/class.c
+++ b/gcc/cp/class.c
@@ -469,7 +469,7 @@ build_simple_base_path (tree expr, tree binfo)
   expr = build_simple_base_path (expr, d_binfo);
 
   for (field = TYPE_FIELDS (BINFO_TYPE (d_binfo));
-       field; field = TREE_CHAIN (field))
+       field; field = DECL_CHAIN (field))
     /* Is this the base field created by build_base_field?  */
     if (TREE_CODE (field) == FIELD_DECL
 	&& DECL_FIELD_IS_BASE (field)
@@ -1262,7 +1262,7 @@ check_bases (tree t,
   seen_non_virtual_nearly_empty_base_p = 0;
 
   if (!CLASSTYPE_NON_STD_LAYOUT (t))
-    for (field = TYPE_FIELDS (t); field; field = TREE_CHAIN (field))
+    for (field = TYPE_FIELDS (t); field; field = DECL_CHAIN (field))
       if (TREE_CODE (field) == FIELD_DECL)
 	break;
 
@@ -1351,7 +1351,7 @@ check_bases (tree t,
 	       members, or has no base classes with non-static data
 	       members */
 	    for (basefield = TYPE_FIELDS (basetype); basefield;
-		 basefield = TREE_CHAIN (basefield))
+		 basefield = DECL_CHAIN (basefield))
 	      if (TREE_CODE (basefield) == FIELD_DECL)
 		{
 		  if (field)
@@ -1609,7 +1609,7 @@ maybe_warn_about_overly_private_class (tree t)
      functions are private.  (Since there are no friends or
      non-private statics, we can't ever call any of the private member
      functions.)  */
-  for (fn = TYPE_METHODS (t); fn; fn = TREE_CHAIN (fn))
+  for (fn = TYPE_METHODS (t); fn; fn = DECL_CHAIN (fn))
     /* We're not interested in compiler-generated methods; they don't
        provide any way to call private members.  */
     if (!DECL_ARTIFICIAL (fn))
@@ -1814,7 +1814,7 @@ finish_struct_methods (tree t)
 
   /* Clear DECL_IN_AGGR_P for all functions.  */
   for (fn_fields = TYPE_METHODS (t); fn_fields;
-       fn_fields = TREE_CHAIN (fn_fields))
+       fn_fields = DECL_CHAIN (fn_fields))
     DECL_IN_AGGR_P (fn_fields) = 0;
 
   /* Issue warnings about private constructors and such.  If there are
@@ -2545,7 +2545,7 @@ finish_struct_anon (tree t)
 {
   tree field;
 
-  for (field = TYPE_FIELDS (t); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (t); field; field = DECL_CHAIN (field))
     {
       if (TREE_STATIC (field))
 	continue;
@@ -2557,7 +2557,7 @@ finish_struct_anon (tree t)
 	{
 	  bool is_union = TREE_CODE (TREE_TYPE (field)) == UNION_TYPE;
 	  tree elt = TYPE_FIELDS (TREE_TYPE (field));
-	  for (; elt; elt = TREE_CHAIN (elt))
+	  for (; elt; elt = DECL_CHAIN (elt))
 	    {
 	      /* We're generally only interested in entities the user
 		 declared, but we also find nested classes by noticing
@@ -2750,7 +2750,7 @@ count_fields (tree fields)
 {
   tree x;
   int n_fields = 0;
-  for (x = fields; x; x = TREE_CHAIN (x))
+  for (x = fields; x; x = DECL_CHAIN (x))
     {
       if (TREE_CODE (x) == FIELD_DECL && ANON_AGGR_TYPE_P (TREE_TYPE (x)))
 	n_fields += count_fields (TYPE_FIELDS (TREE_TYPE (x)));
@@ -2767,7 +2767,7 @@ static int
 add_fields_to_record_type (tree fields, struct sorted_fields_type *field_vec, int idx)
 {
   tree x;
-  for (x = fields; x; x = TREE_CHAIN (x))
+  for (x = fields; x; x = DECL_CHAIN (x))
     {
       if (TREE_CODE (x) == FIELD_DECL && ANON_AGGR_TYPE_P (TREE_TYPE (x)))
 	idx = add_fields_to_record_type (TYPE_FIELDS (TREE_TYPE (x)), field_vec, idx);
@@ -2874,7 +2874,7 @@ check_field_decl (tree field,
     {
       tree fields;
 
-      for (fields = TYPE_FIELDS (type); fields; fields = TREE_CHAIN (fields))
+      for (fields = TYPE_FIELDS (type); fields; fields = DECL_CHAIN (fields))
 	if (TREE_CODE (fields) == FIELD_DECL && !DECL_C_BIT_FIELD (field))
 	  check_field_decl (fields, t, cant_have_const_ctor,
 			    no_const_asn_ref, any_default_members,
@@ -2999,12 +2999,12 @@ check_field_decls (tree t, tree *access_decls,
       tree type = TREE_TYPE (x);
       int this_field_access;
 
-      next = &TREE_CHAIN (x);
+      next = &DECL_CHAIN (x);
 
       if (TREE_CODE (x) == USING_DECL)
 	{
 	  /* Prune the access declaration from the list of fields.  */
-	  *field = TREE_CHAIN (x);
+	  *field = DECL_CHAIN (x);
 
 	  /* Save the access declarations for our caller.  */
 	  *access_decls = tree_cons (NULL_TREE, x, *access_decls);
@@ -3439,7 +3439,7 @@ walk_subobject_offsets (tree type,
 	}
 
       /* Iterate through the fields of TYPE.  */
-      for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+      for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	if (TREE_CODE (field) == FIELD_DECL && !DECL_ARTIFICIAL (field))
 	  {
 	    tree field_offset;
@@ -3788,9 +3788,9 @@ build_base_field (record_layout_info rli, tree binfo,
 	     objects of the same type at the same address.  */
 	  layout_nonempty_base_or_field (rli, decl, binfo, offsets);
 	  /* Add the new FIELD_DECL to the list of fields for T.  */
-	  TREE_CHAIN (decl) = *next_field;
+	  DECL_CHAIN (decl) = *next_field;
 	  *next_field = decl;
-	  next_field = &TREE_CHAIN (decl);
+	  next_field = &DECL_CHAIN (decl);
 	}
     }
   else
@@ -3902,7 +3902,7 @@ check_methods (tree t)
 {
   tree x;
 
-  for (x = TYPE_METHODS (t); x; x = TREE_CHAIN (x))
+  for (x = TYPE_METHODS (t); x; x = DECL_CHAIN (x))
     {
       check_for_override (x, t);
       if (DECL_PURE_VIRTUAL_P (x) && ! DECL_VINDEX (x))
@@ -3941,8 +3941,8 @@ build_clone (tree fn, tree name)
   /* Remember where this function came from.  */
   DECL_ABSTRACT_ORIGIN (clone) = fn;
   /* Make it easy to find the CLONE given the FN.  */
-  TREE_CHAIN (clone) = TREE_CHAIN (fn);
-  TREE_CHAIN (fn) = clone;
+  DECL_CHAIN (clone) = DECL_CHAIN (fn);
+  DECL_CHAIN (fn) = clone;
 
   /* If this is a template, do the rest on the DECL_TEMPLATE_RESULT.  */
   if (TREE_CODE (clone) == TEMPLATE_DECL)
@@ -4006,8 +4006,8 @@ build_clone (tree fn, tree name)
   /* Remove the in-charge parameter.  */
   if (DECL_HAS_IN_CHARGE_PARM_P (clone))
     {
-      TREE_CHAIN (DECL_ARGUMENTS (clone))
-	= TREE_CHAIN (TREE_CHAIN (DECL_ARGUMENTS (clone)));
+      DECL_CHAIN (DECL_ARGUMENTS (clone))
+	= DECL_CHAIN (DECL_CHAIN (DECL_ARGUMENTS (clone)));
       DECL_HAS_IN_CHARGE_PARM_P (clone) = 0;
     }
   /* And the VTT parm, in a complete [cd]tor.  */
@@ -4017,13 +4017,13 @@ build_clone (tree fn, tree name)
 	DECL_HAS_VTT_PARM_P (clone) = 1;
       else
 	{
-	  TREE_CHAIN (DECL_ARGUMENTS (clone))
-	    = TREE_CHAIN (TREE_CHAIN (DECL_ARGUMENTS (clone)));
+	  DECL_CHAIN (DECL_ARGUMENTS (clone))
+	    = DECL_CHAIN (DECL_CHAIN (DECL_ARGUMENTS (clone)));
 	  DECL_HAS_VTT_PARM_P (clone) = 0;
 	}
     }
 
-  for (parms = DECL_ARGUMENTS (clone); parms; parms = TREE_CHAIN (parms))
+  for (parms = DECL_ARGUMENTS (clone); parms; parms = DECL_CHAIN (parms))
     {
       DECL_CONTEXT (parms) = clone;
       cxx_dup_lang_specific_decl (parms);
@@ -4086,8 +4086,8 @@ clone_function_decl (tree fn, int update_method_vec_p)
   tree clone;
 
   /* Avoid inappropriate cloning.  */
-  if (TREE_CHAIN (fn)
-      && DECL_CLONED_FUNCTION_P (TREE_CHAIN (fn)))
+  if (DECL_CHAIN (fn)
+      && DECL_CLONED_FUNCTION_P (DECL_CHAIN (fn)))
     return;
 
   if (DECL_MAYBE_IN_CHARGE_CONSTRUCTOR_P (fn))
@@ -4144,8 +4144,8 @@ adjust_clone_args (tree decl)
 {
   tree clone;
 
-  for (clone = TREE_CHAIN (decl); clone && DECL_CLONED_FUNCTION_P (clone);
-       clone = TREE_CHAIN (clone))
+  for (clone = DECL_CHAIN (decl); clone && DECL_CLONED_FUNCTION_P (clone);
+       clone = DECL_CHAIN (clone))
     {
       tree orig_clone_parms = TYPE_ARG_TYPES (TREE_TYPE (clone));
       tree orig_decl_parms = TYPE_ARG_TYPES (TREE_TYPE (decl));
@@ -4416,9 +4416,9 @@ remove_zero_width_bit_fields (tree t)
 	     check_bitfield_decl eventually sets DECL_SIZE (*fieldsp)
 	     to that width.  */
 	  && integer_zerop (DECL_SIZE (*fieldsp)))
-	*fieldsp = TREE_CHAIN (*fieldsp);
+	*fieldsp = DECL_CHAIN (*fieldsp);
       else
-	fieldsp = &TREE_CHAIN (*fieldsp);
+	fieldsp = &DECL_CHAIN (*fieldsp);
     }
 }
 
@@ -4577,7 +4577,7 @@ check_bases_and_members (tree t)
     {
       tree field;
 
-      for (field = TYPE_FIELDS (t); field; field = TREE_CHAIN (field))
+      for (field = TYPE_FIELDS (t); field; field = DECL_CHAIN (field))
 	{
 	  tree type;
 
@@ -4605,7 +4605,7 @@ check_bases_and_members (tree t)
 
   /* Check defaulted declarations here so we have cant_have_const_ctor
      and don't need to worry about clones.  */
-  for (fn = TYPE_METHODS (t); fn; fn = TREE_CHAIN (fn))
+  for (fn = TYPE_METHODS (t); fn; fn = DECL_CHAIN (fn))
     if (DECL_DEFAULTED_IN_CLASS_P (fn))
       {
 	int copy = copy_fn_p (fn);
@@ -4671,7 +4671,7 @@ create_vtable_ptr (tree t, tree* virtuals_p)
   tree fn;
 
   /* Collect the virtual functions declared in T.  */
-  for (fn = TYPE_METHODS (t); fn; fn = TREE_CHAIN (fn))
+  for (fn = TYPE_METHODS (t); fn; fn = DECL_CHAIN (fn))
     if (DECL_VINDEX (fn) && !DECL_MAYBE_IN_CHARGE_DESTRUCTOR_P (fn)
 	&& TREE_CODE (DECL_VINDEX (fn)) != INTEGER_CST)
       {
@@ -4806,7 +4806,7 @@ layout_virtual_bases (record_layout_info rli, splay_tree offsets)
      bases will go after the last extant field to date.  */
   next_field = &TYPE_FIELDS (t);
   while (*next_field)
-    next_field = &TREE_CHAIN (*next_field);
+    next_field = &DECL_CHAIN (*next_field);
 
   /* Go through the virtual bases, allocating space for each virtual
      base that is not already a primary base class.  These are
@@ -5047,9 +5047,9 @@ layout_class_type (tree t, tree *virtuals_p)
   /* The vptr is always the first thing in the class.  */
   if (vptr)
     {
-      TREE_CHAIN (vptr) = TYPE_FIELDS (t);
+      DECL_CHAIN (vptr) = TYPE_FIELDS (t);
       TYPE_FIELDS (t) = vptr;
-      next_field = &TREE_CHAIN (vptr);
+      next_field = &DECL_CHAIN (vptr);
       place_field (rli, vptr);
     }
   else
@@ -5061,7 +5061,7 @@ layout_class_type (tree t, tree *virtuals_p)
   build_base_fields (rli, empty_base_offsets, next_field);
 
   /* Layout the non-static data members.  */
-  for (field = non_static_data_members; field; field = TREE_CHAIN (field))
+  for (field = non_static_data_members; field; field = DECL_CHAIN (field))
     {
       tree type;
       tree padding;
@@ -5342,7 +5342,7 @@ layout_class_type (tree t, tree *virtuals_p)
 
       /* Copy the fields from T.  */
       next_field = &TYPE_FIELDS (base_t);
-      for (field = TYPE_FIELDS (t); field; field = TREE_CHAIN (field))
+      for (field = TYPE_FIELDS (t); field; field = DECL_CHAIN (field))
 	if (TREE_CODE (field) == FIELD_DECL)
 	  {
 	    *next_field = build_decl (input_location,
@@ -5355,7 +5355,7 @@ layout_class_type (tree t, tree *virtuals_p)
 	      = DECL_FIELD_BIT_OFFSET (field);
 	    DECL_SIZE (*next_field) = DECL_SIZE (field);
 	    DECL_MODE (*next_field) = DECL_MODE (field);
-	    next_field = &TREE_CHAIN (*next_field);
+	    next_field = &DECL_CHAIN (*next_field);
 	  }
 
       /* Record the base version of the type.  */
@@ -5402,7 +5402,7 @@ layout_class_type (tree t, tree *virtuals_p)
   warn_about_ambiguous_bases (t);
 
   /* Now that we're done with layout, give the base fields the real types.  */
-  for (field = TYPE_FIELDS (t); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (t); field; field = DECL_CHAIN (field))
     if (DECL_ARTIFICIAL (field) && IS_FAKE_BASE_TYPE (TREE_TYPE (field)))
       TREE_TYPE (field) = TYPE_CONTEXT (TREE_TYPE (field));
 
@@ -5434,7 +5434,7 @@ determine_key_method (tree type)
      key function may not be inline; those targets should not call
      this function until the end of the translation unit.  */
   for (method = TYPE_METHODS (type); method != NULL_TREE;
-       method = TREE_CHAIN (method))
+       method = DECL_CHAIN (method))
     if (DECL_VINDEX (method) != NULL_TREE
 	&& ! DECL_DECLARED_INLINE_P (method)
 	&& ! DECL_PURE_VIRTUAL_P (method))
@@ -5558,7 +5558,7 @@ finish_struct_1 (tree t)
 
   /* Complete the rtl for any static member objects of the type we're
      working on.  */
-  for (x = TYPE_FIELDS (t); x; x = TREE_CHAIN (x))
+  for (x = TYPE_FIELDS (t); x; x = DECL_CHAIN (x))
     if (TREE_CODE (x) == VAR_DECL && TREE_STATIC (x)
         && TREE_TYPE (x) != error_mark_node
 	&& same_type_p (TYPE_MAIN_VARIANT (TREE_TYPE (x)), t))
@@ -5655,13 +5655,13 @@ unreverse_member_declarations (tree t)
        x && TREE_CODE (x) != TYPE_DECL;
        x = next)
     {
-      next = TREE_CHAIN (x);
-      TREE_CHAIN (x) = prev;
+      next = DECL_CHAIN (x);
+      DECL_CHAIN (x) = prev;
       prev = x;
     }
   if (prev)
     {
-      TREE_CHAIN (TYPE_FIELDS (t)) = x;
+      DECL_CHAIN (TYPE_FIELDS (t)) = x;
       if (prev)
 	TYPE_FIELDS (t) = prev;
     }
@@ -5698,7 +5698,7 @@ finish_struct (tree t, tree attributes)
 	 CLASSTYPE_PURE_VIRTUALS contains the list of the inline friends
 	 (see CLASSTYPE_INLINE_FRIENDS) so we need to clear it.  */
       CLASSTYPE_PURE_VIRTUALS (t) = NULL;
-      for (x = TYPE_METHODS (t); x; x = TREE_CHAIN (x))
+      for (x = TYPE_METHODS (t); x; x = DECL_CHAIN (x))
 	if (DECL_PURE_VIRTUAL_P (x))
 	  VEC_safe_push (tree, gc, CLASSTYPE_PURE_VIRTUALS (t), x);
       complete_vars (t);
@@ -6798,7 +6798,7 @@ is_really_empty_class (tree type)
 	   BINFO_BASE_ITERATE (binfo, i, base_binfo); ++i)
 	if (!is_really_empty_class (BINFO_TYPE (base_binfo)))
 	  return false;
-      for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+      for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	if (TREE_CODE (field) == FIELD_DECL
 	    && !DECL_ARTIFICIAL (field)
 	    && !is_really_empty_class (TREE_TYPE (field)))
@@ -7251,8 +7251,8 @@ build_vtt (tree t)
   vtt = build_vtable (t, mangle_vtt_for_type (t), type);
   initialize_artificial_var (vtt, inits);
   /* Add the VTT to the vtables list.  */
-  TREE_CHAIN (vtt) = TREE_CHAIN (CLASSTYPE_VTABLES (t));
-  TREE_CHAIN (CLASSTYPE_VTABLES (t)) = vtt;
+  DECL_CHAIN (vtt) = DECL_CHAIN (CLASSTYPE_VTABLES (t));
+  DECL_CHAIN (CLASSTYPE_VTABLES (t)) = vtt;
 
   dump_vtt (t, vtt);
 }
@@ -8082,7 +8082,7 @@ add_vcall_offset_vtbl_entries_1 (tree binfo, vtbl_init_data* vid)
 	 order.  G++ 3.2 used the order in the vtable.  */
       for (orig_fn = TYPE_METHODS (BINFO_TYPE (binfo));
 	   orig_fn;
-	   orig_fn = TREE_CHAIN (orig_fn))
+	   orig_fn = DECL_CHAIN (orig_fn))
 	if (DECL_VINDEX (orig_fn))
 	  add_vcall_offset (orig_fn, binfo, vid);
     }
diff --git a/gcc/cp/cp-gimplify.c b/gcc/cp/cp-gimplify.c
index fa897bfa2b89f7c89c66ad84f967797dbd3cf60d..abd5bf37b6e733e644f635585624ad794302a24d 100644
--- a/gcc/cp/cp-gimplify.c
+++ b/gcc/cp/cp-gimplify.c
@@ -51,7 +51,7 @@ static tree
 begin_bc_block (enum bc_t bc)
 {
   tree label = create_artificial_label (input_location);
-  TREE_CHAIN (label) = bc_label[bc];
+  DECL_CHAIN (label) = bc_label[bc];
   bc_label[bc] = label;
   return label;
 }
@@ -73,8 +73,8 @@ finish_bc_block (enum bc_t bc, tree label, gimple_seq body)
       gimple_seq_add_stmt (&body, gimple_build_label (label));
     }
 
-  bc_label[bc] = TREE_CHAIN (label);
-  TREE_CHAIN (label) = NULL_TREE;
+  bc_label[bc] = DECL_CHAIN (label);
+  DECL_CHAIN (label) = NULL_TREE;
   return body;
 }
 
@@ -893,7 +893,7 @@ cp_genericize_r (tree *stmt_p, int *walk_subtrees, void *data)
 
 	  IMPORTED_DECL_ASSOCIATED_DECL (using_directive)
 	    = TREE_OPERAND (stmt, 0);
-	  TREE_CHAIN (using_directive) = BLOCK_VARS (block);
+	  DECL_CHAIN (using_directive) = BLOCK_VARS (block);
 	  BLOCK_VARS (block) = using_directive;
 	}
       /* The USING_STMT won't appear in GENERIC.  */
@@ -921,7 +921,7 @@ cp_genericize (tree fndecl)
   struct cp_genericize_data wtd;
 
   /* Fix up the types of parms passed by invisible reference.  */
-  for (t = DECL_ARGUMENTS (fndecl); t; t = TREE_CHAIN (t))
+  for (t = DECL_ARGUMENTS (fndecl); t; t = DECL_CHAIN (t))
     if (TREE_ADDRESSABLE (TREE_TYPE (t)))
       {
 	/* If a function's arguments are copied to create a thunk,
@@ -1178,7 +1178,7 @@ cxx_omp_predetermined_sharing (tree decl)
 	  tree var;
 
 	  if (outer)
-	    for (var = BLOCK_VARS (outer); var; var = TREE_CHAIN (var))
+	    for (var = BLOCK_VARS (outer); var; var = DECL_CHAIN (var))
 	      if (DECL_NAME (decl) == DECL_NAME (var)
 		  && (TYPE_MAIN_VARIANT (type)
 		      == TYPE_MAIN_VARIANT (TREE_TYPE (var))))
diff --git a/gcc/cp/cp-tree.h b/gcc/cp/cp-tree.h
index 8b076d358c0757d0446049da68d18f222c1699e5..70915cbc4ddd87b4f899c09256841de8b172f6ce 100644
--- a/gcc/cp/cp-tree.h
+++ b/gcc/cp/cp-tree.h
@@ -2092,9 +2092,9 @@ struct GTY((variable_size)) lang_decl {
   if (TREE_CODE (FN) == FUNCTION_DECL			\
       && (DECL_MAYBE_IN_CHARGE_CONSTRUCTOR_P (FN)	\
 	  || DECL_MAYBE_IN_CHARGE_DESTRUCTOR_P (FN)))	\
-     for (CLONE = TREE_CHAIN (FN);			\
+     for (CLONE = DECL_CHAIN (FN);			\
 	  CLONE && DECL_CLONED_FUNCTION_P (CLONE);	\
-	  CLONE = TREE_CHAIN (CLONE))
+	  CLONE = DECL_CHAIN (CLONE))
 
 /* Nonzero if NODE has DECL_DISCRIMINATOR and not DECL_ACCESS.  */
 #define DECL_DISCRIMINATOR_P(NODE)	\
diff --git a/gcc/cp/decl.c b/gcc/cp/decl.c
index 1491720a972ed2bfcfbea3317ea3e51d1ee14e29..0a9f255177e2074619a78e4f0131e8e4a6369060 100644
--- a/gcc/cp/decl.c
+++ b/gcc/cp/decl.c
@@ -393,7 +393,7 @@ pop_labels_1 (void **slot, void *data)
 
   /* Put the labels into the "variables" of the top-level block,
      so debugger can see them.  */
-  TREE_CHAIN (ent->label_decl) = BLOCK_VARS (block);
+  DECL_CHAIN (ent->label_decl) = BLOCK_VARS (block);
   BLOCK_VARS (block) = ent->label_decl;
 
   htab_clear_slot (named_labels, slot);
@@ -474,7 +474,7 @@ poplevel_named_label_1 (void **slot, void *data)
     {
       tree decl;
 
-      for (decl = ent->names_in_scope; decl; decl = TREE_CHAIN (decl))
+      for (decl = ent->names_in_scope; decl; decl = DECL_CHAIN (decl))
 	if (decl_jump_unsafe (decl))
 	  VEC_safe_push (tree, gc, ent->bad_decls, decl);
 
@@ -749,7 +749,7 @@ poplevel (int keep, int reverse, int functionbody)
 	  if (TREE_CODE (*d) == TREE_LIST)
 	    *d = TREE_CHAIN (*d);
 	  else
-	    d = &TREE_CHAIN (*d);
+	    d = &DECL_CHAIN (*d);
 	}
     }
 
@@ -822,7 +822,7 @@ walk_namespaces_r (tree name_space, walk_namespaces_fn f, void* data)
 
   result |= (*f) (name_space, data);
 
-  for (; current; current = TREE_CHAIN (current))
+  for (; current; current = DECL_CHAIN (current))
     result |= walk_namespaces_r (current, f, data);
 
   return result;
@@ -1726,7 +1726,7 @@ duplicate_decls (tree newdecl, tree olddecl, bool newdecl_is_friend)
 	      DECL_ARGUMENTS (old_result)
 		= DECL_ARGUMENTS (new_result);
 	      for (parm = DECL_ARGUMENTS (old_result); parm;
-		   parm = TREE_CHAIN (parm))
+		   parm = DECL_CHAIN (parm))
 		DECL_CONTEXT (parm) = old_result;
 	    }
 	}
@@ -1976,7 +1976,7 @@ duplicate_decls (tree newdecl, tree olddecl, bool newdecl_is_friend)
       for (oldarg = DECL_ARGUMENTS(olddecl), 
                newarg = DECL_ARGUMENTS(newdecl);
            oldarg && newarg;
-           oldarg = TREE_CHAIN(oldarg), newarg = TREE_CHAIN(newarg)) {
+           oldarg = DECL_CHAIN(oldarg), newarg = DECL_CHAIN(newarg)) {
           DECL_ATTRIBUTES (newarg)
               = (*targetm.merge_decl_attributes) (oldarg, newarg);
           DECL_ATTRIBUTES (oldarg) = DECL_ATTRIBUTES (newarg);
@@ -2040,7 +2040,7 @@ duplicate_decls (tree newdecl, tree olddecl, bool newdecl_is_friend)
 
       /* Update newdecl's parms to point at olddecl.  */
       for (parm = DECL_ARGUMENTS (newdecl); parm;
-	   parm = TREE_CHAIN (parm))
+	   parm = DECL_CHAIN (parm))
 	DECL_CONTEXT (parm) = olddecl;
 
       if (! types_match)
@@ -2586,7 +2586,7 @@ check_previous_goto_1 (tree decl, struct cp_binding_level* level, tree names,
       tree new_decls, old_decls = (b == level ? names : NULL_TREE);
 
       for (new_decls = b->names; new_decls != old_decls;
-	   new_decls = TREE_CHAIN (new_decls))
+	   new_decls = DECL_CHAIN (new_decls))
 	{
 	  int problem = decl_jump_unsafe (new_decls);
 	  if (! problem)
@@ -3885,7 +3885,7 @@ fixup_anonymous_aggr (tree t)
       if (DECL_ARTIFICIAL (*q))
 	*q = TREE_CHAIN (*q);
       else
-	q = &TREE_CHAIN (*q);
+	q = &DECL_CHAIN (*q);
     }
 
   /* ISO C++ 9.5.3.  Anonymous unions may not have function members.  */
@@ -3909,7 +3909,7 @@ fixup_anonymous_aggr (tree t)
     {
       tree field, type;
 
-      for (field = TYPE_FIELDS (t); field; field = TREE_CHAIN (field))
+      for (field = TYPE_FIELDS (t); field; field = DECL_CHAIN (field))
 	if (TREE_CODE (field) == FIELD_DECL)
 	  {
 	    type = TREE_TYPE (field);
@@ -4811,7 +4811,7 @@ next_initializable_field (tree field)
 	 && (TREE_CODE (field) != FIELD_DECL
 	     || (DECL_C_BIT_FIELD (field) && !DECL_NAME (field))
 	     || DECL_ARTIFICIAL (field)))
-    field = TREE_CHAIN (field);
+    field = DECL_CHAIN (field);
 
   return field;
 }
@@ -4981,7 +4981,7 @@ reshape_init_class (tree type, reshape_iter *d, bool first_initializer_p)
       if (TREE_CODE (type) == UNION_TYPE)
 	break;
 
-      field = next_initializable_field (TREE_CHAIN (field));
+      field = next_initializable_field (DECL_CHAIN (field));
     }
 
   return new_init;
@@ -6776,11 +6776,11 @@ grokfndecl (tree ctype,
     {
       tree parm;
       parm = build_this_parm (type, quals);
-      TREE_CHAIN (parm) = parms;
+      DECL_CHAIN (parm) = parms;
       parms = parm;
     }
   DECL_ARGUMENTS (decl) = parms;
-  for (t = parms; t; t = TREE_CHAIN (t))
+  for (t = parms; t; t = DECL_CHAIN (t))
     DECL_CONTEXT (t) = decl;
   /* Propagate volatile out from type to decl.  */
   if (TYPE_VOLATILE (type))
@@ -7280,7 +7280,7 @@ build_ptrmemfunc_type (tree type)
 
   field = build_decl (input_location, FIELD_DECL, delta_identifier, 
 		      delta_type_node);
-  TREE_CHAIN (field) = fields;
+  DECL_CHAIN (field) = fields;
   fields = field;
 
   finish_builtin_struct (t, "__ptrmemfunc_type", fields, ptr_type_node);
@@ -9204,7 +9204,7 @@ grokdeclarator (const cp_declarator *declarator,
 	{
 	  tree decl = cp_build_parm_decl (NULL_TREE, TREE_VALUE (args));
 
-	  TREE_CHAIN (decl) = decls;
+	  DECL_CHAIN (decl) = decls;
 	  decls = decl;
 	}
 
@@ -9836,7 +9836,7 @@ grokdeclarator (const cp_declarator *declarator,
 static void
 require_complete_types_for_parms (tree parms)
 {
-  for (; parms; parms = TREE_CHAIN (parms))
+  for (; parms; parms = DECL_CHAIN (parms))
     {
       if (dependent_type_p (TREE_TYPE (parms)))
 	continue;
@@ -10106,7 +10106,7 @@ grokparms (tree parmlist, tree *parms)
           && TREE_CHAIN (parm) != void_list_node)
         error ("parameter packs must be at the end of the parameter list");
 
-      TREE_CHAIN (decl) = decls;
+      DECL_CHAIN (decl) = decls;
       decls = decl;
       result = tree_cons (init, type, result);
     }
@@ -12111,11 +12111,11 @@ start_preparsed_function (tree decl1, tree attrs, int flags)
 
       /* Constructors and destructors need to know whether they're "in
 	 charge" of initializing virtual base classes.  */
-      t = TREE_CHAIN (t);
+      t = DECL_CHAIN (t);
       if (DECL_HAS_IN_CHARGE_PARM_P (decl1))
 	{
 	  current_in_charge_parm = t;
-	  t = TREE_CHAIN (t);
+	  t = DECL_CHAIN (t);
 	}
       if (DECL_HAS_VTT_PARM_P (decl1))
 	{
@@ -12326,7 +12326,7 @@ store_parm_decls (tree current_function_parms)
 
       for (parm = specparms; parm; parm = next)
 	{
-	  next = TREE_CHAIN (parm);
+	  next = DECL_CHAIN (parm);
 	  if (TREE_CODE (parm) == PARM_DECL)
 	    {
 	      if (DECL_NAME (parm) == NULL_TREE
@@ -12762,7 +12762,7 @@ finish_function (int flags)
 
       for (decl = DECL_ARGUMENTS (fndecl);
 	   decl;
-	   decl = TREE_CHAIN (decl))
+	   decl = DECL_CHAIN (decl))
 	if (TREE_USED (decl)
 	    && TREE_CODE (decl) == PARM_DECL
 	    && !DECL_READ_P (decl)
@@ -12905,7 +12905,7 @@ grokmethod (cp_decl_specifier_seq *declspecs,
 
   if (! DECL_FRIEND_P (fndecl))
     {
-      if (TREE_CHAIN (fndecl))
+      if (DECL_CHAIN (fndecl))
 	{
 	  fndecl = copy_node (fndecl);
 	  TREE_CHAIN (fndecl) = NULL_TREE;
@@ -13101,7 +13101,7 @@ revert_static_member_fn (tree decl)
     error ("static member function %q#D declared with type qualifiers", decl);
 
   if (DECL_ARGUMENTS (decl))
-    DECL_ARGUMENTS (decl) = TREE_CHAIN (DECL_ARGUMENTS (decl));
+    DECL_ARGUMENTS (decl) = DECL_CHAIN (DECL_ARGUMENTS (decl));
   DECL_STATIC_FUNCTION_P (decl) = 1;
 }
 
diff --git a/gcc/cp/decl2.c b/gcc/cp/decl2.c
index ce54c79f20e5c09c974d96f02171164a607ae1aa..a768877b1a8c214d8b1269e3f848396e35c35742 100644
--- a/gcc/cp/decl2.c
+++ b/gcc/cp/decl2.c
@@ -242,7 +242,7 @@ maybe_retrofit_in_chrg (tree fn)
   basetype = TREE_TYPE (TREE_VALUE (arg_types));
   arg_types = TREE_CHAIN (arg_types);
 
-  parms = TREE_CHAIN (DECL_ARGUMENTS (fn));
+  parms = DECL_CHAIN (DECL_ARGUMENTS (fn));
 
   /* If this is a subobject constructor or destructor, our caller will
      pass us a pointer to our VTT.  */
@@ -251,7 +251,7 @@ maybe_retrofit_in_chrg (tree fn)
       parm = build_artificial_parm (vtt_parm_identifier, vtt_parm_type);
 
       /* First add it to DECL_ARGUMENTS between 'this' and the real args...  */
-      TREE_CHAIN (parm) = parms;
+      DECL_CHAIN (parm) = parms;
       parms = parm;
 
       /* ...and then to TYPE_ARG_TYPES.  */
@@ -262,12 +262,12 @@ maybe_retrofit_in_chrg (tree fn)
 
   /* Then add the in-charge parm (before the VTT parm).  */
   parm = build_artificial_parm (in_charge_identifier, integer_type_node);
-  TREE_CHAIN (parm) = parms;
+  DECL_CHAIN (parm) = parms;
   parms = parm;
   arg_types = hash_tree_chain (integer_type_node, arg_types);
 
   /* Insert our new parameter(s) into the list.  */
-  TREE_CHAIN (DECL_ARGUMENTS (fn)) = parms;
+  DECL_CHAIN (DECL_ARGUMENTS (fn)) = parms;
 
   /* And rebuild the function type.  */
   fntype = build_method_type_directly (basetype, TREE_TYPE (TREE_TYPE (fn)),
@@ -1321,7 +1321,7 @@ build_anon_union_vars (tree type, tree object)
 
   for (field = TYPE_FIELDS (type);
        field != NULL_TREE;
-       field = TREE_CHAIN (field))
+       field = DECL_CHAIN (field))
     {
       tree decl;
       tree ref;
@@ -1826,7 +1826,7 @@ maybe_emit_vtables (tree ctype)
     determine_key_method (ctype);
 
   /* See if any of the vtables are needed.  */
-  for (vtbl = CLASSTYPE_VTABLES (ctype); vtbl; vtbl = TREE_CHAIN (vtbl))
+  for (vtbl = CLASSTYPE_VTABLES (ctype); vtbl; vtbl = DECL_CHAIN (vtbl))
     {
       import_export_decl (vtbl);
       if (DECL_NOT_REALLY_EXTERN (vtbl) && decl_needed_p (vtbl))
@@ -1845,7 +1845,7 @@ maybe_emit_vtables (tree ctype)
 
   /* The ABI requires that we emit all of the vtables if we emit any
      of them.  */
-  for (vtbl = CLASSTYPE_VTABLES (ctype); vtbl; vtbl = TREE_CHAIN (vtbl))
+  for (vtbl = CLASSTYPE_VTABLES (ctype); vtbl; vtbl = DECL_CHAIN (vtbl))
     {
       /* Mark entities references from the virtual table as used.  */
       mark_vtable_entries (vtbl);
@@ -2242,7 +2242,7 @@ constrain_class_visibility (tree type)
   if (CLASSTYPE_VISIBILITY_SPECIFIED (type))
     vis = VISIBILITY_INTERNAL;
 
-  for (t = TYPE_FIELDS (type); t; t = TREE_CHAIN (t))
+  for (t = TYPE_FIELDS (type); t; t = DECL_CHAIN (t))
     if (TREE_CODE (t) == FIELD_DECL && TREE_TYPE (t) != error_mark_node)
       {
 	tree ftype = strip_pointer_or_array_types (TREE_TYPE (t));
@@ -2868,7 +2868,7 @@ start_static_storage_duration_function (unsigned count)
   DECL_CONTEXT (priority_decl) = ssdf_decl;
   TREE_USED (priority_decl) = 1;
 
-  TREE_CHAIN (initialize_p_decl) = priority_decl;
+  DECL_CHAIN (initialize_p_decl) = priority_decl;
   DECL_ARGUMENTS (ssdf_decl) = initialize_p_decl;
 
   /* Put the function in the global scope.  */
@@ -2966,7 +2966,7 @@ fix_temporary_vars_context_r (tree *node,
     {
       tree var;
 
-      for (var = BIND_EXPR_VARS (*node); var; var = TREE_CHAIN (var))
+      for (var = BIND_EXPR_VARS (*node); var; var = DECL_CHAIN (var))
 	if (TREE_CODE (var) == VAR_DECL
 	  && !DECL_NAME (var)
 	  && DECL_ARTIFICIAL (var)
diff --git a/gcc/cp/init.c b/gcc/cp/init.c
index 98a45cd41b2e87e63e4fb533a4353073c4a2ff09..507da922b4c71f630adcf608d88f1fd2d9a7498d 100644
--- a/gcc/cp/init.c
+++ b/gcc/cp/init.c
@@ -184,7 +184,7 @@ build_zero_init (tree type, tree nelts, bool static_storage_p)
       VEC(constructor_elt,gc) *v = NULL;
 
       /* Iterate over the fields, building initializations.  */
-      for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+      for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	{
 	  if (TREE_CODE (field) != FIELD_DECL)
 	    continue;
@@ -337,7 +337,7 @@ build_value_init_noctor (tree type)
 	  VEC(constructor_elt,gc) *v = NULL;
 
 	  /* Iterate over the fields, building initializations.  */
-	  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+	  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	    {
 	      tree ftype, value;
 
@@ -562,7 +562,7 @@ build_field_list (tree t, tree list, int *uses_unions_p)
   if (TREE_CODE (t) == UNION_TYPE)
     *uses_unions_p = 1;
 
-  for (fields = TYPE_FIELDS (t); fields; fields = TREE_CHAIN (fields))
+  for (fields = TYPE_FIELDS (t); fields; fields = DECL_CHAIN (fields))
     {
       tree fieldtype;
 
@@ -1030,7 +1030,7 @@ construct_virtual_base (tree vbase, tree arguments)
      in the outer block.)  We trust the back end to figure out
      that the FLAG will not change across initializations, and
      avoid doing multiple tests.  */
-  flag = TREE_CHAIN (DECL_ARGUMENTS (current_function_decl));
+  flag = DECL_CHAIN (DECL_ARGUMENTS (current_function_decl));
   inner_if_stmt = begin_if_stmt ();
   finish_if_stmt_cond (flag, inner_if_stmt);
 
@@ -1815,7 +1815,7 @@ diagnose_uninitialized_cst_or_ref_member_1 (tree type, tree origin,
   if (type_has_user_provided_constructor (type))
     return 0;
 
-  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
     {
       tree field_type;
 
@@ -2578,7 +2578,7 @@ build_java_class_ref (tree type)
   /* Mangle the class$ field.  */
   {
     tree field;
-    for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+    for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
       if (DECL_NAME (field) == CL_suffix)
 	{
 	  mangle_decl (field);
@@ -3383,7 +3383,7 @@ push_base_cleanups (void)
     return;
 
   for (member = TYPE_FIELDS (current_class_type); member;
-       member = TREE_CHAIN (member))
+       member = DECL_CHAIN (member))
     {
       tree this_type = TREE_TYPE (member);
       if (this_type == error_mark_node
diff --git a/gcc/cp/mangle.c b/gcc/cp/mangle.c
index 9390a929adf347ccf677e2bb6658de1853168dcb..a47dfa8babf1b5a0d61bd52dda05a47a5c1d5a71 100644
--- a/gcc/cp/mangle.c
+++ b/gcc/cp/mangle.c
@@ -1289,7 +1289,7 @@ nested_anon_class_index (tree type)
 {
   int index = 0;
   tree member = TYPE_FIELDS (TYPE_CONTEXT (type));
-  for (; member; member = TREE_CHAIN (member))
+  for (; member; member = DECL_CHAIN (member))
     if (DECL_IMPLICIT_TYPEDEF_P (member))
       {
 	tree memtype = TREE_TYPE (member);
@@ -1719,7 +1719,7 @@ write_local_name (tree function, const tree local_entity,
     {
       tree t;
       int i = 0;
-      for (t = DECL_ARGUMENTS (function); t; t = TREE_CHAIN (t))
+      for (t = DECL_ARGUMENTS (function); t; t = DECL_CHAIN (t))
 	{
 	  if (t == parm)
 	    i = 1;
@@ -2303,12 +2303,12 @@ write_method_parms (tree parm_types, const int method_p, const tree decl)
   if (method_p)
     {
       parm_types = TREE_CHAIN (parm_types);
-      parm_decl = parm_decl ? TREE_CHAIN (parm_decl) : NULL_TREE;
+      parm_decl = parm_decl ? DECL_CHAIN (parm_decl) : NULL_TREE;
 
       while (parm_decl && DECL_ARTIFICIAL (parm_decl))
 	{
 	  parm_types = TREE_CHAIN (parm_types);
-	  parm_decl = TREE_CHAIN (parm_decl);
+	  parm_decl = DECL_CHAIN (parm_decl);
 	}
     }
 
diff --git a/gcc/cp/method.c b/gcc/cp/method.c
index 9876af2c6cb99241131dc5c2f7de00230d1a3217..b9511f5a6289bfd3f4a69124fdb61a6162c212be 100644
--- a/gcc/cp/method.c
+++ b/gcc/cp/method.c
@@ -103,7 +103,7 @@ make_thunk (tree function, bool this_adjusting,
   /* See if we already have the thunk in question.  For this_adjusting
      thunks VIRTUAL_OFFSET will be an INTEGER_CST, for covariant thunks it
      will be a BINFO.  */
-  for (thunk = DECL_THUNKS (function); thunk; thunk = TREE_CHAIN (thunk))
+  for (thunk = DECL_THUNKS (function); thunk; thunk = DECL_CHAIN (thunk))
     if (DECL_THIS_THUNK_P (thunk) == this_adjusting
 	&& THUNK_FIXED_OFFSET (thunk) == d
 	&& !virtual_offset == !THUNK_VIRTUAL_OFFSET (thunk)
@@ -156,7 +156,7 @@ make_thunk (tree function, bool this_adjusting,
   DECL_TEMPLATE_INFO (thunk) = NULL;
 
   /* Add it to the list of thunks associated with FUNCTION.  */
-  TREE_CHAIN (thunk) = DECL_THUNKS (function);
+  DECL_CHAIN (thunk) = DECL_THUNKS (function);
   DECL_THUNKS (function) = thunk;
 
   return thunk;
@@ -188,7 +188,7 @@ finish_thunk (tree thunk)
       tree cov_probe;
 
       for (cov_probe = DECL_THUNKS (function);
-	   cov_probe; cov_probe = TREE_CHAIN (cov_probe))
+	   cov_probe; cov_probe = DECL_CHAIN (cov_probe))
 	if (DECL_NAME (cov_probe) == name)
 	  {
 	    gcc_assert (!DECL_THUNKS (thunk));
@@ -364,10 +364,10 @@ use_thunk (tree thunk_fndecl, bool emit_p)
 
   /* Set up cloned argument trees for the thunk.  */
   t = NULL_TREE;
-  for (a = DECL_ARGUMENTS (function); a; a = TREE_CHAIN (a))
+  for (a = DECL_ARGUMENTS (function); a; a = DECL_CHAIN (a))
     {
       tree x = copy_node (a);
-      TREE_CHAIN (x) = t;
+      DECL_CHAIN (x) = t;
       DECL_CONTEXT (x) = thunk_fndecl;
       SET_DECL_RTL (x, NULL);
       DECL_HAS_VALUE_EXPR_P (x) = 0;
@@ -529,7 +529,7 @@ do_build_copy_constructor (tree fndecl)
 			 member_init_list);
 	}
 
-      for (; fields; fields = TREE_CHAIN (fields))
+      for (; fields; fields = DECL_CHAIN (fields))
 	{
 	  tree field = fields;
 	  tree expr_type;
@@ -579,7 +579,7 @@ do_build_copy_constructor (tree fndecl)
 static void
 do_build_copy_assign (tree fndecl)
 {
-  tree parm = TREE_CHAIN (DECL_ARGUMENTS (fndecl));
+  tree parm = DECL_CHAIN (DECL_ARGUMENTS (fndecl));
   tree compound_stmt;
   bool move_p = move_fn_p (fndecl);
   bool trivial = trivial_fn_p (fndecl);
@@ -630,7 +630,7 @@ do_build_copy_assign (tree fndecl)
       /* Assign to each of the non-static data members.  */
       for (fields = TYPE_FIELDS (current_class_type);
 	   fields;
-	   fields = TREE_CHAIN (fields))
+	   fields = DECL_CHAIN (fields))
 	{
 	  tree comp = current_class_ref;
 	  tree init = parm;
@@ -953,7 +953,7 @@ walk_field_subobs (tree fields, tree fnname, special_function_kind sfk,
 		   int flags, tsubst_flags_t complain)
 {
   tree field;
-  for (field = fields; field; field = TREE_CHAIN (field))
+  for (field = fields; field; field = DECL_CHAIN (field))
     {
       tree mem_type, argtype, rval;
 
@@ -1432,7 +1432,7 @@ implicitly_declare_fn (special_function_kind kind, tree type, bool const_p)
     }
   /* Add the "this" parameter.  */
   this_parm = build_this_parm (fn_type, TYPE_UNQUALIFIED);
-  TREE_CHAIN (this_parm) = DECL_ARGUMENTS (fn);
+  DECL_CHAIN (this_parm) = DECL_ARGUMENTS (fn);
   DECL_ARGUMENTS (fn) = this_parm;
 
   grokclassfn (type, fn, kind == sfk_destructor ? DTOR_FLAG : NO_SPECIAL);
@@ -1625,7 +1625,7 @@ lazily_declare_fn (special_function_kind sfk, tree type)
 		 "and may change in a future version of GCC due to "
 		 "implicit virtual destructor",
 		 type);
-      TREE_CHAIN (fn) = TYPE_METHODS (type);
+      DECL_CHAIN (fn) = TYPE_METHODS (type);
       TYPE_METHODS (type) = fn;
     }
   maybe_add_class_template_decl_list (type, fn, /*friend_p=*/0);
diff --git a/gcc/cp/name-lookup.c b/gcc/cp/name-lookup.c
index 153bdfd0ed56ca38aa52fe798fba12f1a4ee596a..c6e31c2944520bada98e1aad09458c49ccf29478 100644
--- a/gcc/cp/name-lookup.c
+++ b/gcc/cp/name-lookup.c
@@ -542,7 +542,7 @@ add_decl_to_level (tree decl, cxx_scope *b)
   if (TREE_CODE (decl) == NAMESPACE_DECL
       && !DECL_NAMESPACE_ALIAS (decl))
     {
-      TREE_CHAIN (decl) = b->namespaces;
+      DECL_CHAIN (decl) = b->namespaces;
       b->namespaces = decl;
     }
   else
@@ -1993,7 +1993,7 @@ push_using_decl (tree scope, tree name)
   timevar_push (TV_NAME_LOOKUP);
   gcc_assert (TREE_CODE (scope) == NAMESPACE_DECL);
   gcc_assert (TREE_CODE (name) == IDENTIFIER_NODE);
-  for (decl = current_binding_level->usings; decl; decl = TREE_CHAIN (decl))
+  for (decl = current_binding_level->usings; decl; decl = DECL_CHAIN (decl))
     if (USING_DECL_SCOPE (decl) == scope && DECL_NAME (decl) == name)
       break;
   if (decl)
@@ -2001,7 +2001,7 @@ push_using_decl (tree scope, tree name)
 			    namespace_bindings_p () ? decl : NULL_TREE);
   decl = build_lang_decl (USING_DECL, name, NULL_TREE);
   USING_DECL_SCOPE (decl) = scope;
-  TREE_CHAIN (decl) = current_binding_level->usings;
+  DECL_CHAIN (decl) = current_binding_level->usings;
   current_binding_level->usings = decl;
   POP_TIMEVAR_AND_RETURN (TV_NAME_LOOKUP, decl);
 }
@@ -2157,7 +2157,7 @@ push_overloaded_decl (tree decl, int flags, bool is_friend)
 
 	  for (d = &IDENTIFIER_BINDING (name)->scope->names;
 	       *d;
-	       d = &TREE_CHAIN (*d))
+	       d = &DECL_CHAIN (*d))
 	    if (*d == old
 		|| (TREE_CODE (*d) == TREE_LIST
 		    && TREE_VALUE (*d) == old))
@@ -2168,7 +2168,7 @@ push_overloaded_decl (tree decl, int flags, bool is_friend)
 		else
 		  /* Build a TREE_LIST to wrap the OVERLOAD.  */
 		  *d = tree_cons (NULL_TREE, new_binding,
-				  TREE_CHAIN (*d));
+				  DECL_CHAIN (*d));
 
 		/* And update the cxx_binding node.  */
 		IDENTIFIER_BINDING (name)->value = new_binding;
@@ -2726,7 +2726,7 @@ pushdecl_class_level (tree x)
 	 aggregate, for naming purposes.  */
       tree f;
 
-      for (f = TYPE_FIELDS (TREE_TYPE (x)); f; f = TREE_CHAIN (f))
+      for (f = TYPE_FIELDS (TREE_TYPE (x)); f; f = DECL_CHAIN (f))
 	{
 	  location_t save_location = input_location;
 	  input_location = DECL_SOURCE_LOCATION (f);
diff --git a/gcc/cp/optimize.c b/gcc/cp/optimize.c
index 7ec2034f052709b4320978f421826049ff2f9d93..302a1332d6676ea0b59223da202df6f7737a6122 100644
--- a/gcc/cp/optimize.c
+++ b/gcc/cp/optimize.c
@@ -282,16 +282,16 @@ maybe_clone_body (tree fn)
       clone_parm = DECL_ARGUMENTS (clone);
       /* Update the `this' parameter, which is always first.  */
       update_cloned_parm (parm, clone_parm, first);
-      parm = TREE_CHAIN (parm);
-      clone_parm = TREE_CHAIN (clone_parm);
+      parm = DECL_CHAIN (parm);
+      clone_parm = DECL_CHAIN (clone_parm);
       if (DECL_HAS_IN_CHARGE_PARM_P (fn))
-	parm = TREE_CHAIN (parm);
+	parm = DECL_CHAIN (parm);
       if (DECL_HAS_VTT_PARM_P (fn))
-	parm = TREE_CHAIN (parm);
+	parm = DECL_CHAIN (parm);
       if (DECL_HAS_VTT_PARM_P (clone))
-	clone_parm = TREE_CHAIN (clone_parm);
+	clone_parm = DECL_CHAIN (clone_parm);
       for (; parm;
-	   parm = TREE_CHAIN (parm), clone_parm = TREE_CHAIN (clone_parm))
+	   parm = DECL_CHAIN (parm), clone_parm = DECL_CHAIN (clone_parm))
 	/* Update this parameter.  */
 	update_cloned_parm (parm, clone_parm, first);
 
@@ -348,7 +348,7 @@ maybe_clone_body (tree fn)
                 clone_parm = DECL_ARGUMENTS (clone);
               parm;
               ++parmno,
-                parm = TREE_CHAIN (parm))
+                parm = DECL_CHAIN (parm))
             {
               /* Map the in-charge parameter to an appropriate constant.  */
               if (DECL_HAS_IN_CHARGE_PARM_P (fn) && parmno == 1)
@@ -367,7 +367,7 @@ maybe_clone_body (tree fn)
                     {
                       DECL_ABSTRACT_ORIGIN (clone_parm) = parm;
                       *pointer_map_insert (decl_map, parm) = clone_parm;
-                      clone_parm = TREE_CHAIN (clone_parm);
+                      clone_parm = DECL_CHAIN (clone_parm);
                     }
                   /* Otherwise, map the VTT parameter to `NULL'.  */
                   else
@@ -379,7 +379,7 @@ maybe_clone_body (tree fn)
               else
                 {
                   *pointer_map_insert (decl_map, parm) = clone_parm;
-                  clone_parm = TREE_CHAIN (clone_parm);
+                  clone_parm = DECL_CHAIN (clone_parm);
                 }
             }
 
diff --git a/gcc/cp/parser.c b/gcc/cp/parser.c
index b35d9a5a6c3cd3a1c2f41b2193f9b6ce37617cdc..19a158f6350fd95289302b1bef858f9b36139793 100644
--- a/gcc/cp/parser.c
+++ b/gcc/cp/parser.c
@@ -2650,7 +2650,7 @@ cp_parser_diagnose_invalid_type_name (cp_parser *parser,
 		  base_type = CLASSTYPE_PRIMARY_TEMPLATE_TYPE (base_type);
 		  for (field = TYPE_FIELDS (base_type);
 		       field;
-		       field = TREE_CHAIN (field))
+		       field = DECL_CHAIN (field))
 		    if (TREE_CODE (field) == TYPE_DECL
 			&& DECL_NAME (field) == id)
 		      {
@@ -7706,7 +7706,7 @@ cp_parser_lambda_declarator_opt (cp_parser* parser, tree lambda_expr)
 
       /* The function parameters must be in scope all the way until after the
          trailing-return-type in case of decltype.  */
-      for (t = current_binding_level->names; t; t = TREE_CHAIN (t))
+      for (t = current_binding_level->names; t; t = DECL_CHAIN (t))
 	pop_binding (DECL_NAME (t), t);
 
       leave_scope ();
@@ -14378,7 +14378,7 @@ cp_parser_direct_declarator (cp_parser* parser,
 		}
 
 	      /* Remove the function parms from scope.  */
-	      for (t = current_binding_level->names; t; t = TREE_CHAIN (t))
+	      for (t = current_binding_level->names; t; t = DECL_CHAIN (t))
 		pop_binding (DECL_NAME (t), t);
 	      leave_scope();
 
@@ -19676,7 +19676,7 @@ cp_parser_late_parsing_default_args (cp_parser *parser, tree fn)
 	 parmdecl = DECL_ARGUMENTS (fn);
        parm && parm != void_list_node;
        parm = TREE_CHAIN (parm),
-	 parmdecl = TREE_CHAIN (parmdecl))
+	 parmdecl = DECL_CHAIN (parmdecl))
     {
       cp_token_cache *tokens;
       tree default_arg = TREE_PURPOSE (parm);
diff --git a/gcc/cp/pt.c b/gcc/cp/pt.c
index 80cf7d2e4a6769637b8f29c786c2138707f7f38d..ef6e8e94d6a646956b68090e635ffed531fb9549 100644
--- a/gcc/cp/pt.c
+++ b/gcc/cp/pt.c
@@ -2553,7 +2553,7 @@ check_explicit_specialization (tree declarator,
 		     definition, not in the original declaration.  */
 		  DECL_ARGUMENTS (result) = DECL_ARGUMENTS (decl);
 		  for (parm = DECL_ARGUMENTS (result); parm;
-		       parm = TREE_CHAIN (parm))
+		       parm = DECL_CHAIN (parm))
 		    DECL_CONTEXT (parm) = result;
 		}
 	      return register_specialization (tmpl, gen_tmpl, targs,
@@ -4417,7 +4417,7 @@ push_template_decl_real (tree decl, bool is_friend)
               TREE_VALUE (argtype) = error_mark_node;
             }
 
-          arg = TREE_CHAIN (arg);
+          arg = DECL_CHAIN (arg);
           argtype = TREE_CHAIN (argtype);
         }
 
@@ -8196,7 +8196,7 @@ instantiate_class_template (tree type)
      any member functions.  We don't do this earlier because the
      default arguments may reference members of the class.  */
   if (!PRIMARY_TEMPLATE_P (templ))
-    for (t = TYPE_METHODS (type); t; t = TREE_CHAIN (t))
+    for (t = TYPE_METHODS (type); t; t = DECL_CHAIN (t))
       if (TREE_CODE (t) == FUNCTION_DECL
 	  /* Implicitly generated member functions will not have template
 	     information; they are not instantiations, but instead are
@@ -8261,7 +8261,7 @@ make_fnparm_pack (tree spec_parm)
   /* Fill in PARMVEC and PARMTYPEVEC with all of the parameters.  */
   parmvec = make_tree_vec (len);
   parmtypevec = make_tree_vec (len);
-  for (i = 0; i < len; i++, spec_parm = TREE_CHAIN (spec_parm))
+  for (i = 0; i < len; i++, spec_parm = DECL_CHAIN (spec_parm))
     {
       TREE_VEC_ELT (parmvec, i) = spec_parm;
       TREE_VEC_ELT (parmtypevec, i) = TREE_TYPE (spec_parm);
@@ -8541,7 +8541,7 @@ get_pattern_parm (tree parm, tree tmpl)
   if (DECL_ARTIFICIAL (parm))
     {
       for (patparm = DECL_ARGUMENTS (pattern);
-	   patparm; patparm = TREE_CHAIN (patparm))
+	   patparm; patparm = DECL_CHAIN (patparm))
 	if (DECL_ARTIFICIAL (patparm)
 	    && DECL_NAME (parm) == DECL_NAME (patparm))
 	  break;
@@ -8936,7 +8936,7 @@ tsubst_decl (tree t, tree args, tsubst_flags_t complain)
 	      RETURN (error_mark_node);
 
 	    r = copy_decl (t);
-	    TREE_CHAIN (r) = NULL_TREE;
+	    DECL_CHAIN (r) = NULL_TREE;
 	    TREE_TYPE (r) = new_type;
 	    DECL_TEMPLATE_RESULT (r)
 	      = build_decl (DECL_SOURCE_LOCATION (decl),
@@ -8986,7 +8986,7 @@ tsubst_decl (tree t, tree args, tsubst_flags_t complain)
 	   than the old one.  */
 	r = copy_decl (t);
 	gcc_assert (DECL_LANG_SPECIFIC (r) != 0);
-	TREE_CHAIN (r) = NULL_TREE;
+	DECL_CHAIN (r) = NULL_TREE;
 
 	DECL_TEMPLATE_INFO (r) = build_template_info (t, args);
 
@@ -9196,7 +9196,7 @@ tsubst_decl (tree t, tree args, tsubst_flags_t complain)
 	   assigned to the instantiation.  */
 	DECL_INTERFACE_KNOWN (r) = !TREE_PUBLIC (r);
 	DECL_DEFER_OUTPUT (r) = 0;
-	TREE_CHAIN (r) = NULL_TREE;
+	DECL_CHAIN (r) = NULL_TREE;
 	DECL_PENDING_INLINE_INFO (r) = 0;
 	DECL_PENDING_INLINE_P (r) = 0;
 	DECL_SAVED_TREE (r) = NULL_TREE;
@@ -9395,12 +9395,12 @@ tsubst_decl (tree t, tree args, tsubst_flags_t complain)
             /* Build a proper chain of parameters when substituting
                into a function parameter pack.  */
             if (prev_r)
-              TREE_CHAIN (prev_r) = r;
+              DECL_CHAIN (prev_r) = r;
           }
 
-	if (TREE_CHAIN (t))
-	  TREE_CHAIN (r) = tsubst (TREE_CHAIN (t), args,
-				   complain, TREE_CHAIN (t));
+	if (DECL_CHAIN (t))
+	  DECL_CHAIN (r) = tsubst (DECL_CHAIN (t), args,
+				   complain, DECL_CHAIN (t));
 
         /* FIRST_R contains the start of the chain we've built.  */
         r = first_r;
@@ -9425,7 +9425,7 @@ tsubst_decl (tree t, tree args, tsubst_flags_t complain)
 			 /*integral_constant_expression_p=*/true);
 	/* We don't have to set DECL_CONTEXT here; it is set by
 	   finish_member_declaration.  */
-	TREE_CHAIN (r) = NULL_TREE;
+	DECL_CHAIN (r) = NULL_TREE;
 	if (VOID_TYPE_P (type))
 	  error ("instantiation of %q+D as type %qT", r, type);
 
@@ -9452,7 +9452,7 @@ tsubst_decl (tree t, tree args, tsubst_flags_t complain)
       else
 	{
 	  r = copy_node (t);
-	  TREE_CHAIN (r) = NULL_TREE;
+	  DECL_CHAIN (r) = NULL_TREE;
 	}
       break;
 
@@ -9652,7 +9652,7 @@ tsubst_decl (tree t, tree args, tsubst_flags_t complain)
 	else
 	  register_local_specialization (r, t);
 
-	TREE_CHAIN (r) = NULL_TREE;
+	DECL_CHAIN (r) = NULL_TREE;
 
 	apply_late_template_attributes (&r, DECL_ATTRIBUTES (r),
 					/*flags=*/0,
@@ -13123,7 +13123,7 @@ instantiate_template (tree tmpl, tree orig_args, tsubst_flags_t complain)
      instantiate all the alternate entry points as well.  We do this
      by cloning the instantiation of the main entry point, not by
      instantiating the template clones.  */
-  if (TREE_CHAIN (gen_tmpl) && DECL_CLONED_FUNCTION_P (TREE_CHAIN (gen_tmpl)))
+  if (DECL_CHAIN (gen_tmpl) && DECL_CLONED_FUNCTION_P (DECL_CHAIN (gen_tmpl)))
     clone_function_decl (fndecl, /*update_method_vec_p=*/0);
 
   return fndecl;
@@ -16392,12 +16392,12 @@ do_type_instantiation (tree t, tree storage, tsubst_flags_t complain)
        interpretation is that it should be an explicit instantiation.  */
 
     if (! static_p)
-      for (tmp = TYPE_METHODS (t); tmp; tmp = TREE_CHAIN (tmp))
+      for (tmp = TYPE_METHODS (t); tmp; tmp = DECL_CHAIN (tmp))
 	if (TREE_CODE (tmp) == FUNCTION_DECL
 	    && DECL_TEMPLATE_INSTANTIATION (tmp))
 	  instantiate_class_member (tmp, extern_p);
 
-    for (tmp = TYPE_FIELDS (t); tmp; tmp = TREE_CHAIN (tmp))
+    for (tmp = TYPE_FIELDS (t); tmp; tmp = DECL_CHAIN (tmp))
       if (TREE_CODE (tmp) == VAR_DECL && DECL_TEMPLATE_INSTANTIATION (tmp))
 	instantiate_class_member (tmp, extern_p);
 
@@ -16485,8 +16485,8 @@ regenerate_decl_from_template (tree decl, tree tmpl)
 	      DECL_ATTRIBUTES (decl_parm) = attributes;
 	      cplus_decl_attributes (&decl_parm, attributes, /*flags=*/0);
 	    }
-	  decl_parm = TREE_CHAIN (decl_parm);
-	  pattern_parm = TREE_CHAIN (pattern_parm);
+	  decl_parm = DECL_CHAIN (decl_parm);
+	  pattern_parm = DECL_CHAIN (pattern_parm);
 	}
       /* Merge any parameters that match with the function parameter
          pack.  */
@@ -16518,7 +16518,7 @@ regenerate_decl_from_template (tree decl, tree tmpl)
                   DECL_ATTRIBUTES (decl_parm) = attributes;
                   cplus_decl_attributes (&decl_parm, attributes, /*flags=*/0);
                 }
-              decl_parm = TREE_CHAIN (decl_parm);
+              decl_parm = DECL_CHAIN (decl_parm);
             }
         }
       /* Merge additional specifiers from the CODE_PATTERN.  */
@@ -16928,8 +16928,8 @@ instantiate_decl (tree d, int defer_ok,
       while (tmpl_parm && !FUNCTION_PARAMETER_PACK_P (tmpl_parm))
 	{
 	  register_local_specialization (spec_parm, tmpl_parm);
-	  tmpl_parm = TREE_CHAIN (tmpl_parm);
-	  spec_parm = TREE_CHAIN (spec_parm);
+	  tmpl_parm = DECL_CHAIN (tmpl_parm);
+	  spec_parm = DECL_CHAIN (spec_parm);
 	}
       if (tmpl_parm && FUNCTION_PARAMETER_PACK_P (tmpl_parm))
         {
@@ -16937,7 +16937,7 @@ instantiate_decl (tree d, int defer_ok,
              TMPL_PARM, then move on.  */
 	  tree argpack = make_fnparm_pack (spec_parm);
           register_local_specialization (argpack, tmpl_parm);
-          tmpl_parm = TREE_CHAIN (tmpl_parm);
+          tmpl_parm = DECL_CHAIN (tmpl_parm);
 	  spec_parm = NULL_TREE;
         }
       gcc_assert (!spec_parm);
diff --git a/gcc/cp/rtti.c b/gcc/cp/rtti.c
index dde8e825dbe473b5e1f57a960bafc2c0b72848a3..c994683aae8e0e9d46a96db43d3df8661bdeb043 100644
--- a/gcc/cp/rtti.c
+++ b/gcc/cp/rtti.c
@@ -1210,7 +1210,7 @@ create_pseudo_type_info (int tk, const char *real_name, ...)
   /* Now add the derived fields.  */
   while ((field_decl = va_arg (ap, tree)))
     {
-      TREE_CHAIN (field_decl) = fields;
+      DECL_CHAIN (field_decl) = fields;
       fields = field_decl;
     }
 
@@ -1375,7 +1375,7 @@ create_tinfo_types (void)
 
     field = build_decl (BUILTINS_LOCATION,
 			FIELD_DECL, NULL_TREE, const_string_type_node);
-    TREE_CHAIN (field) = fields;
+    DECL_CHAIN (field) = fields;
     fields = field;
 
     ti = VEC_index (tinfo_s, tinfo_descs, TK_TYPE_INFO_TYPE);
@@ -1415,7 +1415,7 @@ create_tinfo_types (void)
 
     field = build_decl (BUILTINS_LOCATION,
 			FIELD_DECL, NULL_TREE, integer_types[itk_long]);
-    TREE_CHAIN (field) = fields;
+    DECL_CHAIN (field) = fields;
     fields = field;
 
     ti = VEC_index (tinfo_s, tinfo_descs, TK_BASE_TYPE);
diff --git a/gcc/cp/search.c b/gcc/cp/search.c
index 9dbefd3c5bc7727888d22da4b364edd2c59677fc..0249fb06d4801310215dd61ff82021d9687626a5 100644
--- a/gcc/cp/search.c
+++ b/gcc/cp/search.c
@@ -170,7 +170,7 @@ accessible_base_p (tree t, tree base, bool consider_local_p)
      public typedef created in the scope of every class.  */
   decl = TYPE_FIELDS (base);
   while (!DECL_SELF_REFERENCE_P (decl))
-    decl = TREE_CHAIN (decl);
+    decl = DECL_CHAIN (decl);
   while (ANON_AGGR_TYPE_P (t))
     t = TYPE_CONTEXT (t);
   return accessible_p (t, decl, consider_local_p);
@@ -447,7 +447,7 @@ lookup_field_1 (tree type, tree name, bool want_type)
 #ifdef GATHER_STATISTICS
   n_calls_lookup_field_1++;
 #endif /* GATHER_STATISTICS */
-  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
     {
 #ifdef GATHER_STATISTICS
       n_fields_searched++;
diff --git a/gcc/cp/semantics.c b/gcc/cp/semantics.c
index 887bb42e75f5a5724bc1e0483d095ee17929e71d..a39e0b8dc1f005aa12e46845f57ff1f21925bbf3 100644
--- a/gcc/cp/semantics.c
+++ b/gcc/cp/semantics.c
@@ -2418,7 +2418,7 @@ finish_member_declaration (tree decl)
     return;
 
   /* We should see only one DECL at a time.  */
-  gcc_assert (TREE_CHAIN (decl) == NULL_TREE);
+  gcc_assert (DECL_CHAIN (decl) == NULL_TREE);
 
   /* Set up access control for DECL.  */
   TREE_PRIVATE (decl)
@@ -2460,7 +2460,7 @@ finish_member_declaration (tree decl)
 	 CLASSTYPE_METHOD_VEC.  */
       if (add_method (current_class_type, decl, NULL_TREE))
 	{
-	  TREE_CHAIN (decl) = TYPE_METHODS (current_class_type);
+	  DECL_CHAIN (decl) = TYPE_METHODS (current_class_type);
 	  TYPE_METHODS (current_class_type) = decl;
 
 	  maybe_add_class_template_decl_list (current_class_type, decl,
@@ -2493,7 +2493,7 @@ finish_member_declaration (tree decl)
 	  = chainon (TYPE_FIELDS (current_class_type), decl);
       else
 	{
-	  TREE_CHAIN (decl) = TYPE_FIELDS (current_class_type);
+	  DECL_CHAIN (decl) = TYPE_FIELDS (current_class_type);
 	  TYPE_FIELDS (current_class_type) = decl;
 	}
 
@@ -3319,7 +3319,7 @@ emit_associated_thunks (tree fn)
     {
       tree thunk;
 
-      for (thunk = DECL_THUNKS (fn); thunk; thunk = TREE_CHAIN (thunk))
+      for (thunk = DECL_THUNKS (fn); thunk; thunk = DECL_CHAIN (thunk))
 	{
 	  if (!THUNK_ALIAS (thunk))
 	    {
@@ -3329,7 +3329,7 @@ emit_associated_thunks (tree fn)
 		  tree probe;
 
 		  for (probe = DECL_THUNKS (thunk);
-		       probe; probe = TREE_CHAIN (probe))
+		       probe; probe = DECL_CHAIN (probe))
 		    use_thunk (probe, /*emit_p=*/1);
 		}
 	    }
@@ -5850,8 +5850,8 @@ maybe_add_lambda_conv_op (tree type)
   DECL_NOT_REALLY_EXTERN (fn) = 1;
   DECL_DECLARED_INLINE_P (fn) = 1;
   DECL_STATIC_FUNCTION_P (fn) = 1;
-  DECL_ARGUMENTS (fn) = copy_list (TREE_CHAIN (DECL_ARGUMENTS (callop)));
-  for (arg = DECL_ARGUMENTS (fn); arg; arg = TREE_CHAIN (arg))
+  DECL_ARGUMENTS (fn) = copy_list (DECL_CHAIN (DECL_ARGUMENTS (callop)));
+  for (arg = DECL_ARGUMENTS (fn); arg; arg = DECL_CHAIN (arg))
     DECL_CONTEXT (arg) = fn;
   if (nested)
     DECL_INTERFACE_KNOWN (fn) = 1;
@@ -5884,7 +5884,7 @@ maybe_add_lambda_conv_op (tree type)
 		null_pointer_node);
   argvec = make_tree_vector ();
   VEC_quick_push (tree, argvec, arg);
-  for (arg = DECL_ARGUMENTS (statfn); arg; arg = TREE_CHAIN (arg))
+  for (arg = DECL_ARGUMENTS (statfn); arg; arg = DECL_CHAIN (arg))
     VEC_safe_push (tree, gc, argvec, arg);
   call = build_call_a (callop, VEC_length (tree, argvec),
 		       VEC_address (tree, argvec));
diff --git a/gcc/cp/typeck.c b/gcc/cp/typeck.c
index d5e43dedcf8bb5ffffae20e47d2134a557600d12..f51722a63cfe9df580435e92f597fd662aa3b0cf 100644
--- a/gcc/cp/typeck.c
+++ b/gcc/cp/typeck.c
@@ -2136,7 +2136,7 @@ lookup_anon_field (tree t, tree type)
 {
   tree field;
 
-  for (field = TYPE_FIELDS (t); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (t); field; field = DECL_CHAIN (field))
     {
       if (TREE_STATIC (field))
 	continue;
@@ -6988,7 +6988,7 @@ build_ptrmemfunc1 (tree type, tree delta, tree pfn)
 
   /* Pull the FIELD_DECLs out of the type.  */
   pfn_field = TYPE_FIELDS (type);
-  delta_field = TREE_CHAIN (pfn_field);
+  delta_field = DECL_CHAIN (pfn_field);
 
   /* Make sure DELTA has the type we want.  */
   delta = convert_and_check (delta_type_node, delta);
diff --git a/gcc/cp/typeck2.c b/gcc/cp/typeck2.c
index bdc14c7fa0836349c2b9e597e0e82c1163676388..efe7030dabd2903d3fb4db49157b552f838b7f51 100644
--- a/gcc/cp/typeck2.c
+++ b/gcc/cp/typeck2.c
@@ -1115,7 +1115,7 @@ process_init_constructor_record (tree type, tree init)
   /* Generally, we will always have an index for each initializer (which is
      a FIELD_DECL, put by reshape_init), but compound literals don't go trough
      reshape_init. So we need to handle both cases.  */
-  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
     {
       tree next;
       tree type;
diff --git a/gcc/dbxout.c b/gcc/dbxout.c
index 7226ec7e8c02a9b58378ff24117ccc71d8895dff..7a66a78e8caf01c041b75ce66adf913232cb64b8 100644
--- a/gcc/dbxout.c
+++ b/gcc/dbxout.c
@@ -1099,7 +1099,7 @@ dbxout_init (const char *input_file_name)
 static void
 dbxout_typedefs (tree syms)
 {
-  for (; syms != NULL_TREE; syms = TREE_CHAIN (syms))
+  for (; syms != NULL_TREE; syms = DECL_CHAIN (syms))
     {
       if (TREE_CODE (syms) == TYPE_DECL)
 	{
@@ -1423,7 +1423,7 @@ dbxout_type_fields (tree type)
 
   /* Output the name, type, position (in bits), size (in bits) of each
      field that we can support.  */
-  for (tem = TYPE_FIELDS (type); tem; tem = TREE_CHAIN (tem))
+  for (tem = TYPE_FIELDS (type); tem; tem = DECL_CHAIN (tem))
     {
       /* If one of the nodes is an error_mark or its type is then
 	 return early.  */
@@ -1566,7 +1566,7 @@ dbxout_type_methods (tree type)
 	 These differ in the types of the arguments.  */
       for (last = NULL_TREE;
 	   fndecl && (last == NULL_TREE || DECL_NAME (fndecl) == DECL_NAME (last));
-	   fndecl = TREE_CHAIN (fndecl))
+	   fndecl = DECL_CHAIN (fndecl))
 	/* Output the name of the field (after overloading), as
 	   well as the name of the field before overloading, along
 	   with its parameter list */
@@ -3307,7 +3307,7 @@ dbxout_syms (tree syms)
       comm_prev = comm_new;
 
       result += dbxout_symbol (syms, 1);
-      syms = TREE_CHAIN (syms);
+      syms = DECL_CHAIN (syms);
     }
 
   if (comm_prev != NULL)
@@ -3334,7 +3334,7 @@ dbxout_parms (tree parms)
   ++debug_nesting;
   emit_pending_bincls_if_required ();
 
-  for (; parms; parms = TREE_CHAIN (parms))
+  for (; parms; parms = DECL_CHAIN (parms))
     if (DECL_NAME (parms)
 	&& TREE_TYPE (parms) != error_mark_node
 	&& DECL_RTL_SET_P (parms)
@@ -3536,7 +3536,7 @@ dbxout_reg_parms (tree parms)
 {
   ++debug_nesting;
 
-  for (; parms; parms = TREE_CHAIN (parms))
+  for (; parms; parms = DECL_CHAIN (parms))
     if (DECL_NAME (parms) && PARM_PASSED_IN_MEMORY (parms))
       {
 	/* Report parms that live in registers during the function
diff --git a/gcc/dwarf2out.c b/gcc/dwarf2out.c
index d17787138d14578751b77a83c093084c6b6c38a3..385d5da261cc0330f3bd4b8440d2e213a0bf70c7 100644
--- a/gcc/dwarf2out.c
+++ b/gcc/dwarf2out.c
@@ -16738,7 +16738,7 @@ native_encode_initializer (tree init, unsigned char *array, int size)
 
 	  for (cnt = 0;
 	       VEC_iterate (constructor_elt, CONSTRUCTOR_ELTS (init), cnt, ce);
-	       cnt++, field = field ? TREE_CHAIN (field) : 0)
+	       cnt++, field = field ? DECL_CHAIN (field) : 0)
 	    {
 	      tree val = ce->value;
 	      int pos, fieldsize;
@@ -18295,7 +18295,7 @@ gen_formal_parameter_pack_die  (tree parm_pack,
   parm_pack_die = new_die (DW_TAG_GNU_formal_parameter_pack, subr_die, parm_pack);
   add_src_coords_attributes (parm_pack_die, parm_pack);
 
-  for (arg = pack_arg; arg; arg = TREE_CHAIN (arg))
+  for (arg = pack_arg; arg; arg = DECL_CHAIN (arg))
     {
       if (! lang_hooks.decls.function_parm_expanded_from_pack_p (arg,
 								 parm_pack))
@@ -18362,7 +18362,7 @@ gen_formal_types_die (tree function_or_method_type, dw_die_ref context_die)
 
       link = TREE_CHAIN (link);
       if (arg)
-	arg = TREE_CHAIN (arg);
+	arg = DECL_CHAIN (arg);
     }
 
   /* If this function type has an ellipsis, add a
@@ -18871,11 +18871,11 @@ gen_subprogram_die (tree decl, dw_die_ref context_die)
 	  else if (parm)
 	    {
 	      gen_decl_die (parm, NULL, subr_die);
-	      parm = TREE_CHAIN (parm);
+	      parm = DECL_CHAIN (parm);
 	    }
 
 	  if (generic_decl_parm)
-	    generic_decl_parm = TREE_CHAIN (generic_decl_parm);
+	    generic_decl_parm = DECL_CHAIN (generic_decl_parm);
 	}
 
       /* Decide whether we need an unspecified_parameters DIE at the end.
@@ -19577,7 +19577,7 @@ gen_member_die (tree type, dw_die_ref context_die)
     }
 
   /* Now output info about the data members and type members.  */
-  for (member = TYPE_FIELDS (type); member; member = TREE_CHAIN (member))
+  for (member = TYPE_FIELDS (type); member; member = DECL_CHAIN (member))
     {
       /* If we thought we were generating minimal debug info for TYPE
 	 and then changed our minds, some of the member declarations
@@ -19592,7 +19592,7 @@ gen_member_die (tree type, dw_die_ref context_die)
     }
 
   /* Now output info about the function members (if any).  */
-  for (member = TYPE_METHODS (type); member; member = TREE_CHAIN (member))
+  for (member = TYPE_METHODS (type); member; member = DECL_CHAIN (member))
     {
       /* Don't include clones in the member list.  */
       if (DECL_ABSTRACT_ORIGIN (member))
@@ -20158,7 +20158,7 @@ decls_for_scope (tree stmt, dw_die_ref context_die, int depth)
      declared directly within this block but not within any nested
      sub-blocks.  Also, nested function and tag DIEs have been
      generated with a parent of NULL; fix that up now.  */
-  for (decl = BLOCK_VARS (stmt); decl != NULL; decl = TREE_CHAIN (decl))
+  for (decl = BLOCK_VARS (stmt); decl != NULL; decl = DECL_CHAIN (decl))
     process_scope_var (stmt, decl, NULL_TREE, context_die);
   for (i = 0; i < BLOCK_NUM_NONLOCALIZED_VARS (stmt); i++)
     process_scope_var (stmt, NULL, BLOCK_NONLOCALIZED_VAR (stmt, i),
@@ -20939,7 +20939,7 @@ dwarf2out_ignore_block (const_tree block)
   tree decl;
   unsigned int i;
 
-  for (decl = BLOCK_VARS (block); decl; decl = TREE_CHAIN (decl))
+  for (decl = BLOCK_VARS (block); decl; decl = DECL_CHAIN (decl))
     if (TREE_CODE (decl) == FUNCTION_DECL
 	|| (TREE_CODE (decl) == TYPE_DECL && TYPE_DECL_IS_STUB (decl)))
       return 0;
diff --git a/gcc/emit-rtl.c b/gcc/emit-rtl.c
index bb9f63a66d4fbf3a719fd299a10b5910de92ca41..32741dc6b809af671e1e6e457f9f911699037379 100644
--- a/gcc/emit-rtl.c
+++ b/gcc/emit-rtl.c
@@ -2375,7 +2375,7 @@ unshare_all_rtl_again (rtx insn)
   set_used_decls (DECL_INITIAL (cfun->decl));
 
   /* Make sure that virtual parameters are not shared.  */
-  for (decl = DECL_ARGUMENTS (cfun->decl); decl; decl = TREE_CHAIN (decl))
+  for (decl = DECL_ARGUMENTS (cfun->decl); decl; decl = DECL_CHAIN (decl))
     set_used_flags (DECL_RTL (decl));
 
   reset_used_flags (stack_slot_list);
@@ -2585,7 +2585,7 @@ set_used_decls (tree blk)
   tree t;
 
   /* Mark decls.  */
-  for (t = BLOCK_VARS (blk); t; t = TREE_CHAIN (t))
+  for (t = BLOCK_VARS (blk); t; t = DECL_CHAIN (t))
     if (DECL_RTL_SET_P (t))
       set_used_flags (DECL_RTL (t));
 
diff --git a/gcc/expr.c b/gcc/expr.c
index 899d5b83ebbb06aec9cf70dd6ed0452f3e06f2e4..1ffe58977eec9b85500be2e3446917cebe7609e8 100644
--- a/gcc/expr.c
+++ b/gcc/expr.c
@@ -5054,7 +5054,7 @@ count_type_elements (const_tree type, bool allow_flexarr)
 	HOST_WIDE_INT n = 0, t;
 	tree f;
 
-	for (f = TYPE_FIELDS (type); f ; f = TREE_CHAIN (f))
+	for (f = TYPE_FIELDS (type); f ; f = DECL_CHAIN (f))
 	  if (TREE_CODE (f) == FIELD_DECL)
 	    {
 	      t = count_type_elements (TREE_TYPE (f), false);
@@ -5063,7 +5063,7 @@ count_type_elements (const_tree type, bool allow_flexarr)
 		  /* Check for structures with flexible array member.  */
 		  tree tf = TREE_TYPE (f);
 		  if (allow_flexarr
-		      && TREE_CHAIN (f) == NULL
+		      && DECL_CHAIN (f) == NULL
 		      && TREE_CODE (tf) == ARRAY_TYPE
 		      && TYPE_DOMAIN (tf)
 		      && TYPE_MIN_VALUE (TYPE_DOMAIN (tf))
diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 29ae010326b67444333ad5fda97f614607af9309..d783ff511dfc91bc9df7406d7d0cdf3572426226 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,11 @@
+2010-07-15  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* f95-lang.c: Carefully replace TREE_CHAIN with DECL_CHAIN.
+	* trans-common.c: Likewise.
+	* trans-decl.c: Likewise.
+	* trans-types.c: Likewise.
+	* trans.c: Likewise.
+
 2010-07-15  Janus Weil  <janus@gcc.gnu.org>
 
 	PR fortran/44936
diff --git a/gcc/fortran/f95-lang.c b/gcc/fortran/f95-lang.c
index c6af0026ba85f72a40bd8c43d89da4c6306a44a1..5b676214e6a60ce461ccb5210265b05e41dece9c 100644
--- a/gcc/fortran/f95-lang.c
+++ b/gcc/fortran/f95-lang.c
@@ -310,7 +310,7 @@ struct GTY(())
 binding_level {
   /* A chain of ..._DECL nodes for all variables, constants, functions,
      parameters and type declarations.  These ..._DECL nodes are chained
-     through the TREE_CHAIN field. Note that these ..._DECL nodes are stored
+     through the DECL_CHAIN field. Note that these ..._DECL nodes are stored
      in the reverse of the order supplied to be compatible with the
      back-end.  */
   tree names;
@@ -409,7 +409,7 @@ poplevel (int keep, int reverse, int functionbody)
   /* Clear out the meanings of the local variables of this level.  */
 
   for (subblock_node = decl_chain; subblock_node;
-       subblock_node = TREE_CHAIN (subblock_node))
+       subblock_node = DECL_CHAIN (subblock_node))
     if (DECL_NAME (subblock_node) != 0)
       /* If the identifier was used or addressed via a local extern decl,
          don't forget that fact.  */
@@ -467,7 +467,7 @@ pushdecl (tree decl)
      order. The list will be reversed later if necessary.  This needs to be
      this way for compatibility with the back-end.  */
 
-  TREE_CHAIN (decl) = current_binding_level->names;
+  DECL_CHAIN (decl) = current_binding_level->names;
   current_binding_level->names = decl;
 
   /* For the declaration of a type, set its name if it is not already set.  */
diff --git a/gcc/fortran/trans-common.c b/gcc/fortran/trans-common.c
index 1162636fe5af58e756e9c90d244107c3e6d4a210..a19facb8317c6e70a4d91e8560725e0eaaf68203 100644
--- a/gcc/fortran/trans-common.c
+++ b/gcc/fortran/trans-common.c
@@ -432,7 +432,7 @@ build_common_decl (gfc_common_head *com, tree union_type, bool is_init)
 	     what C will do.  */
 	  tree field = NULL_TREE;
 	  field = TYPE_FIELDS (TREE_TYPE (decl));
-	  if (TREE_CHAIN (field) == NULL_TREE)
+	  if (DECL_CHAIN (field) == NULL_TREE)
 	    DECL_ALIGN (decl) = TYPE_ALIGN (TREE_TYPE (field));
 	}
       DECL_USER_ALIGN (decl) = 0;
@@ -608,7 +608,7 @@ create_common (gfc_common_head *com, segment_info *head, bool saw_equiv)
     {
       is_init = true;
       *field_link = field;
-      field_link = &TREE_CHAIN (field);
+      field_link = &DECL_CHAIN (field);
     }
 
   for (s = head; s; s = s->next)
@@ -617,7 +617,7 @@ create_common (gfc_common_head *com, segment_info *head, bool saw_equiv)
 
       /* Link the field into the type.  */
       *field_link = s->field;
-      field_link = &TREE_CHAIN (s->field);
+      field_link = &DECL_CHAIN (s->field);
 
       /* Has initial value.  */
       if (s->sym->value)
diff --git a/gcc/fortran/trans-decl.c b/gcc/fortran/trans-decl.c
index dd238fe4a4840d2fee2555f8ff77eacd0295b7d4..bd7363d933d8414d9d69ba4e54ce089d803efcb9 100644
--- a/gcc/fortran/trans-decl.c
+++ b/gcc/fortran/trans-decl.c
@@ -174,7 +174,7 @@ gfc_add_decl_to_parent_function (tree decl)
   gcc_assert (decl);
   DECL_CONTEXT (decl) = DECL_CONTEXT (current_function_decl);
   DECL_NONLOCAL (decl) = 1;
-  TREE_CHAIN (decl) = saved_parent_function_decls;
+  DECL_CHAIN (decl) = saved_parent_function_decls;
   saved_parent_function_decls = decl;
 }
 
@@ -184,7 +184,7 @@ gfc_add_decl_to_function (tree decl)
   gcc_assert (decl);
   TREE_USED (decl) = 1;
   DECL_CONTEXT (decl) = current_function_decl;
-  TREE_CHAIN (decl) = saved_function_decls;
+  DECL_CHAIN (decl) = saved_function_decls;
   saved_function_decls = decl;
 }
 
@@ -194,7 +194,7 @@ add_decl_as_local (tree decl)
   gcc_assert (decl);
   TREE_USED (decl) = 1;
   DECL_CONTEXT (decl) = current_function_decl;
-  TREE_CHAIN (decl) = saved_local_decls;
+  DECL_CHAIN (decl) = saved_local_decls;
   saved_local_decls = decl;
 }
 
@@ -960,7 +960,7 @@ gfc_nonlocal_dummy_array_decl (gfc_symbol *sym)
   SET_DECL_VALUE_EXPR (decl, sym->backend_decl);
   DECL_HAS_VALUE_EXPR_P (decl) = 1;
   DECL_CONTEXT (decl) = DECL_CONTEXT (sym->backend_decl);
-  TREE_CHAIN (decl) = nonlocal_dummy_decls;
+  DECL_CHAIN (decl) = nonlocal_dummy_decls;
   nonlocal_dummy_decls = decl;
 }
 
@@ -1091,7 +1091,7 @@ gfc_get_symbol_decl (gfc_symbol * sym)
 	  /* For entry master function skip over the __entry
 	     argument.  */
 	  if (sym->ns->proc_name->attr.entry_master)
-	    sym->backend_decl = TREE_CHAIN (sym->backend_decl);
+	    sym->backend_decl = DECL_CHAIN (sym->backend_decl);
 	}
 
       /* Dummy variables should already have been created.  */
@@ -2015,7 +2015,7 @@ build_entry_thunks (gfc_namespace * ns)
 	      tree ref = DECL_ARGUMENTS (current_function_decl);
 	      VEC_safe_push (tree, gc, args, ref);
 	      if (ns->proc_name->ts.type == BT_CHARACTER)
-		VEC_safe_push (tree, gc, args, TREE_CHAIN (ref));
+		VEC_safe_push (tree, gc, args, DECL_CHAIN (ref));
 	    }
 	}
 
@@ -2083,7 +2083,7 @@ build_entry_thunks (gfc_namespace * ns)
 	  gfc_add_expr_to_block (&body, tmp);
 
 	  for (field = TYPE_FIELDS (TREE_TYPE (union_decl));
-	       field; field = TREE_CHAIN (field))
+	       field; field = DECL_CHAIN (field))
 	    if (strcmp (IDENTIFIER_POINTER (DECL_NAME (field)),
 		thunk_sym->result->name) == 0)
 	      break;
@@ -2219,7 +2219,7 @@ gfc_get_fake_result_decl (gfc_symbol * sym, int parent_flag)
 	  tree field;
 
 	  for (field = TYPE_FIELDS (TREE_TYPE (decl));
-	       field; field = TREE_CHAIN (field))
+	       field; field = DECL_CHAIN (field))
 	    if (strcmp (IDENTIFIER_POINTER (DECL_NAME (field)),
 		sym->name) == 0)
 	      break;
@@ -2270,7 +2270,7 @@ gfc_get_fake_result_decl (gfc_symbol * sym, int parent_flag)
 
       if (sym->ns->proc_name->backend_decl == this_function_decl
 	  && sym->ns->proc_name->attr.entry_master)
-	decl = TREE_CHAIN (decl);
+	decl = DECL_CHAIN (decl);
 
       TREE_USED (decl) = 1;
       if (sym->as)
@@ -4531,8 +4531,8 @@ gfc_generate_function_code (gfc_namespace * ns)
     {
       tree next;
 
-      next = TREE_CHAIN (decl);
-      TREE_CHAIN (decl) = NULL_TREE;
+      next = DECL_CHAIN (decl);
+      DECL_CHAIN (decl) = NULL_TREE;
       pushdecl (decl);
       decl = next;
     }
@@ -4710,8 +4710,8 @@ gfc_process_block_locals (gfc_namespace* ns)
     {
       tree next;
 
-      next = TREE_CHAIN (decl);
-      TREE_CHAIN (decl) = NULL_TREE;
+      next = DECL_CHAIN (decl);
+      DECL_CHAIN (decl) = NULL_TREE;
       pushdecl (decl);
       decl = next;
     }
diff --git a/gcc/fortran/trans-types.c b/gcc/fortran/trans-types.c
index 741ea2fd9d0255ad62e4da40fb3bbe373e0800a5..db3a165a3ed07748c318180ac70756ff5082a131 100644
--- a/gcc/fortran/trans-types.c
+++ b/gcc/fortran/trans-types.c
@@ -1849,14 +1849,14 @@ gfc_add_field_to_struct_1 (tree context, tree name, tree type, tree **chain)
   tree decl = build_decl (input_location, FIELD_DECL, name, type);
 
   DECL_CONTEXT (decl) = context;
-  TREE_CHAIN (decl) = NULL_TREE;
+  DECL_CHAIN (decl) = NULL_TREE;
   if (TYPE_FIELDS (context) == NULL_TREE)
     TYPE_FIELDS (context) = decl;
   if (chain != NULL)
     {
       if (*chain != NULL)
 	**chain = decl;
-      *chain = &TREE_CHAIN (decl);
+      *chain = &DECL_CHAIN (decl);
     }
 
   return decl;
@@ -2539,16 +2539,16 @@ gfc_get_array_descr_info (const_tree type, struct array_descr_info *info)
     elem_size = fold_convert (gfc_array_index_type, TYPE_SIZE_UNIT (etype));
   field = TYPE_FIELDS (TYPE_MAIN_VARIANT (type));
   data_off = byte_position (field);
-  field = TREE_CHAIN (field);
-  field = TREE_CHAIN (field);
-  field = TREE_CHAIN (field);
+  field = DECL_CHAIN (field);
+  field = DECL_CHAIN (field);
+  field = DECL_CHAIN (field);
   dim_off = byte_position (field);
   dim_size = TYPE_SIZE_UNIT (TREE_TYPE (TREE_TYPE (field)));
   field = TYPE_FIELDS (TREE_TYPE (TREE_TYPE (field)));
   stride_suboff = byte_position (field);
-  field = TREE_CHAIN (field);
+  field = DECL_CHAIN (field);
   lower_suboff = byte_position (field);
-  field = TREE_CHAIN (field);
+  field = DECL_CHAIN (field);
   upper_suboff = byte_position (field);
 
   t = base_decl;
diff --git a/gcc/fortran/trans.c b/gcc/fortran/trans.c
index 4b20b962fba26585fd361942ff0e8f41647ddb17..003f6090c2f38334515baa80ebb077b12f429166 100644
--- a/gcc/fortran/trans.c
+++ b/gcc/fortran/trans.c
@@ -57,7 +57,7 @@ gfc_advance_chain (tree t, int n)
   for (; n > 0; n--)
     {
       gcc_assert (t != NULL_TREE);
-      t = TREE_CHAIN (t);
+      t = DECL_CHAIN (t);
     }
   return t;
 }
@@ -218,8 +218,8 @@ gfc_merge_block_scope (stmtblock_t * block)
   /* Add them to the parent scope.  */
   while (decl != NULL_TREE)
     {
-      next = TREE_CHAIN (decl);
-      TREE_CHAIN (decl) = NULL_TREE;
+      next = DECL_CHAIN (decl);
+      DECL_CHAIN (decl) = NULL_TREE;
 
       pushdecl (decl);
       decl = next;
diff --git a/gcc/function.c b/gcc/function.c
index 9075e08e633bc9aaee00ff3e33b9a0794cf41358..a2b4814a582f499f0c5566b33d099398e11c1425 100644
--- a/gcc/function.c
+++ b/gcc/function.c
@@ -1793,7 +1793,7 @@ instantiate_decls_1 (tree let)
 {
   tree t;
 
-  for (t = BLOCK_VARS (let); t; t = TREE_CHAIN (t))
+  for (t = BLOCK_VARS (let); t; t = DECL_CHAIN (t))
     {
       if (DECL_RTL_SET_P (t))
 	instantiate_decl_rtl (DECL_RTL (t));
@@ -1819,7 +1819,7 @@ instantiate_decls (tree fndecl)
   unsigned ix;
 
   /* Process all parameters of the function.  */
-  for (decl = DECL_ARGUMENTS (fndecl); decl; decl = TREE_CHAIN (decl))
+  for (decl = DECL_ARGUMENTS (fndecl); decl; decl = DECL_CHAIN (decl))
     {
       instantiate_decl_rtl (DECL_RTL (decl));
       instantiate_decl_rtl (DECL_INCOMING_RTL (decl));
@@ -2222,7 +2222,7 @@ assign_parms_augmented_arg_list (struct assign_parm_data_all *all)
   VEC(tree, heap) *fnargs = NULL;
   tree arg;
 
-  for (arg = DECL_ARGUMENTS (fndecl); arg; arg = TREE_CHAIN (arg))
+  for (arg = DECL_ARGUMENTS (fndecl); arg; arg = DECL_CHAIN (arg))
     VEC_safe_push (tree, heap, fnargs, arg);
 
   all->orig_fnargs = DECL_ARGUMENTS (fndecl);
@@ -2241,7 +2241,7 @@ assign_parms_augmented_arg_list (struct assign_parm_data_all *all)
       DECL_ARTIFICIAL (decl) = 1;
       DECL_IGNORED_P (decl) = 1;
 
-      TREE_CHAIN (decl) = all->orig_fnargs;
+      DECL_CHAIN (decl) = all->orig_fnargs;
       all->orig_fnargs = decl;
       VEC_safe_insert (tree, heap, fnargs, 0, decl);
 
@@ -2272,7 +2272,7 @@ assign_parm_find_data_types (struct assign_parm_data_all *all, tree parm,
   /* NAMED_ARG is a misnomer.  We really mean 'non-variadic'. */
   if (!cfun->stdarg)
     data->named_arg = 1;  /* No variadic parms.  */
-  else if (TREE_CHAIN (parm))
+  else if (DECL_CHAIN (parm))
     data->named_arg = 1;  /* Not the last non-variadic parm. */
   else if (targetm.calls.strict_argument_naming (&all->args_so_far))
     data->named_arg = 1;  /* Only variadic ones are unnamed.  */
@@ -3245,7 +3245,7 @@ assign_parms (tree fndecl)
 	    }
 	}
 
-      if (cfun->stdarg && !TREE_CHAIN (parm))
+      if (cfun->stdarg && !DECL_CHAIN (parm))
 	assign_parms_setup_varargs (&all, &data, false);
 
       /* Find out where the parameter arrives in this function.  */
@@ -3825,7 +3825,7 @@ setjmp_vars_warning (bitmap setjmp_crosses, tree block)
 {
   tree decl, sub;
 
-  for (decl = BLOCK_VARS (block); decl; decl = TREE_CHAIN (decl))
+  for (decl = BLOCK_VARS (block); decl; decl = DECL_CHAIN (decl))
     {
       if (TREE_CODE (decl) == VAR_DECL
 	  && DECL_RTL_SET_P (decl)
@@ -3847,7 +3847,7 @@ setjmp_args_warning (bitmap setjmp_crosses)
 {
   tree decl;
   for (decl = DECL_ARGUMENTS (current_function_decl);
-       decl; decl = TREE_CHAIN (decl))
+       decl; decl = DECL_CHAIN (decl))
     if (DECL_RTL (decl) != 0
 	&& REG_P (DECL_RTL (decl))
 	&& regno_clobbered_at_setjmp (setjmp_crosses, REGNO (DECL_RTL (decl))))
@@ -4689,7 +4689,7 @@ do_warn_unused_parameter (tree fn)
   tree decl;
 
   for (decl = DECL_ARGUMENTS (fn);
-       decl; decl = TREE_CHAIN (decl))
+       decl; decl = DECL_CHAIN (decl))
     if (!TREE_USED (decl) && TREE_CODE (decl) == PARM_DECL
 	&& DECL_NAME (decl) && !DECL_ARTIFICIAL (decl)
 	&& !TREE_NO_WARNING (decl))
diff --git a/gcc/gimple-low.c b/gcc/gimple-low.c
index 213e446d87e091f292f48c0a52affb5cfc0c4cba..1f7ae2ffdac23c9347651f02377098c60daaaaf3 100644
--- a/gcc/gimple-low.c
+++ b/gcc/gimple-low.c
@@ -241,7 +241,7 @@ gimple_check_call_args (gimple stmt)
     {
       for (i = 0, p = DECL_ARGUMENTS (fndecl);
 	   i < nargs;
-	   i++, p = TREE_CHAIN (p))
+	   i++, p = DECL_CHAIN (p))
 	{
 	  /* We cannot distinguish a varargs function from the case
 	     of excess parameters, still deferring the inlining decision
@@ -894,7 +894,7 @@ record_vars_into (tree vars, tree fn)
   if (fn != current_function_decl)
     push_cfun (DECL_STRUCT_FUNCTION (fn));
 
-  for (; vars; vars = TREE_CHAIN (vars))
+  for (; vars; vars = DECL_CHAIN (vars))
     {
       tree var = vars;
 
diff --git a/gcc/gimple-pretty-print.c b/gcc/gimple-pretty-print.c
index 491eae3b51bf01d71657bfaabb9f251be3c45eb1..0c613e4a8bbc377120b205c33d6819524e104555 100644
--- a/gcc/gimple-pretty-print.c
+++ b/gcc/gimple-pretty-print.c
@@ -765,7 +765,7 @@ dump_gimple_bind (pretty_printer *buffer, gimple gs, int spc, int flags)
     {
       tree var;
 
-      for (var = gimple_bind_vars (gs); var; var = TREE_CHAIN (var))
+      for (var = gimple_bind_vars (gs); var; var = DECL_CHAIN (var))
 	{
           newline_and_indent (buffer, 2);
 	  print_declaration (buffer, var, spc, flags);
diff --git a/gcc/gimplify.c b/gcc/gimplify.c
index 8fbe1bafd446b5f5992ea71f9e4b4c989f81e676..8b97ee3d0e8e665d9a12a56bd594654c8a3104dc 100644
--- a/gcc/gimplify.c
+++ b/gcc/gimplify.c
@@ -653,7 +653,7 @@ declare_vars (tree vars, gimple scope, bool debug_info)
       gcc_assert (!block || TREE_CODE (block) == BLOCK);
       if (!block || !debug_info)
 	{
-	  TREE_CHAIN (last) = gimple_bind_vars (scope);
+	  DECL_CHAIN (last) = gimple_bind_vars (scope);
 	  gimple_bind_set_vars (scope, temps);
 	}
       else
@@ -701,7 +701,7 @@ force_constant_size (tree var)
 void
 gimple_add_tmp_var (tree tmp)
 {
-  gcc_assert (!TREE_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
+  gcc_assert (!DECL_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
 
   /* Later processing assumes that the object size is constant, which might
      not be true at this point.  Force the use of a constant upper bound in
@@ -714,7 +714,7 @@ gimple_add_tmp_var (tree tmp)
 
   if (gimplify_ctxp)
     {
-      TREE_CHAIN (tmp) = gimplify_ctxp->temps;
+      DECL_CHAIN (tmp) = gimplify_ctxp->temps;
       gimplify_ctxp->temps = tmp;
 
       /* Mark temporaries local within the nearest enclosing parallel.  */
@@ -1133,7 +1133,7 @@ gimplify_bind_expr (tree *expr_p, gimple_seq *pre_p)
   tree temp = voidify_wrapper_expr (bind_expr, NULL);
 
   /* Mark variables seen in this bind expr.  */
-  for (t = BIND_EXPR_VARS (bind_expr); t ; t = TREE_CHAIN (t))
+  for (t = BIND_EXPR_VARS (bind_expr); t ; t = DECL_CHAIN (t))
     {
       if (TREE_CODE (t) == VAR_DECL)
 	{
@@ -1902,7 +1902,7 @@ gimplify_var_or_parm_decl (tree *expr_p)
 	      SET_DECL_RTL (copy, 0);
 	      TREE_USED (copy) = 1;
 	      block = DECL_INITIAL (current_function_decl);
-	      TREE_CHAIN (copy) = BLOCK_VARS (block);
+	      DECL_CHAIN (copy) = BLOCK_VARS (block);
 	      BLOCK_VARS (block) = copy;
 	      SET_DECL_VALUE_EXPR (copy, unshare_expr (value_expr));
 	      DECL_HAS_VALUE_EXPR_P (copy) = 1;
@@ -5392,7 +5392,7 @@ omp_firstprivatize_type_sizes (struct gimplify_omp_ctx *ctx, tree type)
     case QUAL_UNION_TYPE:
       {
 	tree field;
-	for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+	for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	  if (TREE_CODE (field) == FIELD_DECL)
 	    {
 	      omp_firstprivatize_variable (ctx, DECL_FIELD_OFFSET (field));
@@ -7532,7 +7532,7 @@ gimplify_type_sizes (tree type, gimple_seq *list_p)
     case RECORD_TYPE:
     case UNION_TYPE:
     case QUAL_UNION_TYPE:
-      for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+      for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	if (TREE_CODE (field) == FIELD_DECL)
 	  {
 	    gimplify_one_sizepos (&DECL_FIELD_OFFSET (field), list_p);
@@ -7691,7 +7691,7 @@ gimplify_body (tree *body_p, tree fndecl, bool do_parms)
       gimple_bind_set_body (outer_bind, parm_stmts);
 
       for (parm = DECL_ARGUMENTS (current_function_decl);
-	   parm; parm = TREE_CHAIN (parm))
+	   parm; parm = DECL_CHAIN (parm))
 	if (DECL_HAS_VALUE_EXPR_P (parm))
 	  {
 	    DECL_HAS_VALUE_EXPR_P (parm) = 0;
@@ -7741,7 +7741,7 @@ gimplify_function_tree (tree fndecl)
   else
     push_struct_function (fndecl);
 
-  for (parm = DECL_ARGUMENTS (fndecl); parm ; parm = TREE_CHAIN (parm))
+  for (parm = DECL_ARGUMENTS (fndecl); parm ; parm = DECL_CHAIN (parm))
     {
       /* Preliminarily mark non-addressed complex variables as eligible
          for promotion to gimple registers.  We'll transform their uses
@@ -8037,7 +8037,7 @@ force_gimple_operand (tree expr, gimple_seq *stmts, bool simple, tree var)
     }
 
   if (gimple_referenced_vars (cfun))
-    for (t = gimplify_ctxp->temps; t ; t = TREE_CHAIN (t))
+    for (t = gimplify_ctxp->temps; t ; t = DECL_CHAIN (t))
       add_referenced_var (t);
 
   pop_gimplify_context (NULL);
diff --git a/gcc/integrate.c b/gcc/integrate.c
index 10f75d1c511813762ea0cf53cb43197db8043d97..dd75758c9aa510a9788f5086c64eead0bc7d0fd4 100644
--- a/gcc/integrate.c
+++ b/gcc/integrate.c
@@ -112,7 +112,7 @@ set_block_origin_self (tree stmt)
 
 	for (local_decl = BLOCK_VARS (stmt);
 	     local_decl != NULL_TREE;
-	     local_decl = TREE_CHAIN (local_decl))
+	     local_decl = DECL_CHAIN (local_decl))
 	  set_decl_origin_self (local_decl);	/* Potential recursion.  */
       }
 
@@ -148,7 +148,7 @@ set_decl_origin_self (tree decl)
 	{
 	  tree arg;
 
-	  for (arg = DECL_ARGUMENTS (decl); arg; arg = TREE_CHAIN (arg))
+	  for (arg = DECL_ARGUMENTS (decl); arg; arg = DECL_CHAIN (arg))
 	    DECL_ABSTRACT_ORIGIN (arg) = arg;
 	  if (DECL_INITIAL (decl) != NULL_TREE
 	      && DECL_INITIAL (decl) != error_mark_node)
@@ -173,7 +173,7 @@ set_block_abstract_flags (tree stmt, int setting)
 
   for (local_decl = BLOCK_VARS (stmt);
        local_decl != NULL_TREE;
-       local_decl = TREE_CHAIN (local_decl))
+       local_decl = DECL_CHAIN (local_decl))
     set_decl_abstract_flags (local_decl, setting);
 
   for (i = 0; i < BLOCK_NUM_NONLOCALIZED_VARS (stmt); i++)
@@ -204,7 +204,7 @@ set_decl_abstract_flags (tree decl, int setting)
     {
       tree arg;
 
-      for (arg = DECL_ARGUMENTS (decl); arg; arg = TREE_CHAIN (arg))
+      for (arg = DECL_ARGUMENTS (decl); arg; arg = DECL_CHAIN (arg))
 	DECL_ABSTRACT (arg) = setting;
       if (DECL_INITIAL (decl) != NULL_TREE
 	  && DECL_INITIAL (decl) != error_mark_node)
diff --git a/gcc/ipa-inline.c b/gcc/ipa-inline.c
index e65c6968ab4de78208167653252565da9d818a9e..b9e684489539cf8e67c4f90a5c6e9a0f54a16720 100644
--- a/gcc/ipa-inline.c
+++ b/gcc/ipa-inline.c
@@ -1987,7 +1987,7 @@ estimate_function_body_sizes (struct cgraph_node *node)
       time_inlining_benefit += cost;
       size_inlining_benefit += cost;
     }
-  for (arg = DECL_ARGUMENTS (node->decl); arg; arg = TREE_CHAIN (arg))
+  for (arg = DECL_ARGUMENTS (node->decl); arg; arg = DECL_CHAIN (arg))
     if (!VOID_TYPE_P (TREE_TYPE (arg)))
       {
         int cost = estimate_move_cost (TREE_TYPE (arg));
diff --git a/gcc/ipa-prop.c b/gcc/ipa-prop.c
index 9bd07f039b98870499fe57ba4e50363cf1c72217..77e84c11f7a1927dd942a74814752b15100faa25 100644
--- a/gcc/ipa-prop.c
+++ b/gcc/ipa-prop.c
@@ -154,7 +154,7 @@ ipa_populate_param_decls (struct cgraph_node *node,
   fndecl = node->decl;
   fnargs = DECL_ARGUMENTS (fndecl);
   param_num = 0;
-  for (parm = fnargs; parm; parm = TREE_CHAIN (parm))
+  for (parm = fnargs; parm; parm = DECL_CHAIN (parm))
     {
       info->params[param_num].decl = parm;
       param_num++;
@@ -169,7 +169,7 @@ count_formal_params_1 (tree fndecl)
   tree parm;
   int count = 0;
 
-  for (parm = DECL_ARGUMENTS (fndecl); parm; parm = TREE_CHAIN (parm))
+  for (parm = DECL_ARGUMENTS (fndecl); parm; parm = DECL_CHAIN (parm))
     count++;
 
   return count;
@@ -616,13 +616,13 @@ type_like_member_ptr_p (tree type, tree *method_ptr, tree *delta)
   if (method_ptr)
     *method_ptr = fld;
 
-  fld = TREE_CHAIN (fld);
+  fld = DECL_CHAIN (fld);
   if (!fld || INTEGRAL_TYPE_P (fld))
     return false;
   if (delta)
     *delta = fld;
 
-  if (TREE_CHAIN (fld))
+  if (DECL_CHAIN (fld))
     return false;
 
   return true;
@@ -1932,7 +1932,7 @@ ipa_get_vector_of_formal_parms (tree fndecl)
 
   count = count_formal_params_1 (fndecl);
   args = VEC_alloc (tree, heap, count);
-  for (parm = DECL_ARGUMENTS (fndecl); parm; parm = TREE_CHAIN (parm))
+  for (parm = DECL_ARGUMENTS (fndecl); parm; parm = DECL_CHAIN (parm))
     VEC_quick_push (tree, args, parm);
 
   return args;
@@ -2017,7 +2017,7 @@ ipa_modify_formal_parameters (tree fndecl, ipa_parm_adjustment_vec adjustments,
 							     adj->base_index),
 				       new_arg_types);
 	  *link = parm;
-	  link = &TREE_CHAIN (parm);
+	  link = &DECL_CHAIN (parm);
 	}
       else if (!adj->remove_param)
 	{
@@ -2050,7 +2050,7 @@ ipa_modify_formal_parameters (tree fndecl, ipa_parm_adjustment_vec adjustments,
 
 	  *link = new_parm;
 
-	  link = &TREE_CHAIN (new_parm);
+	  link = &DECL_CHAIN (new_parm);
 	}
     }
 
diff --git a/gcc/ipa-split.c b/gcc/ipa-split.c
index 28f96b23854515aa6607886db2617eab76512199..4bd3f05deb86fb53af2d051fb931ca18d78e3837 100644
--- a/gcc/ipa-split.c
+++ b/gcc/ipa-split.c
@@ -319,7 +319,7 @@ consider_split (struct split_point *current, bitmap non_ssa_vars,
      call overhead.  */
   call_overhead = eni_size_weights.call_cost;
   for (parm = DECL_ARGUMENTS (current_function_decl); parm;
-       parm = TREE_CHAIN (parm))
+       parm = DECL_CHAIN (parm))
     {
       if (!is_gimple_reg (parm))
 	{
@@ -889,7 +889,7 @@ split_function (struct split_point *split_point)
 
   /* Collect the parameters of new function and args_to_skip bitmap.  */
   for (parm = DECL_ARGUMENTS (current_function_decl);
-       parm; parm = TREE_CHAIN (parm), num++)
+       parm; parm = DECL_CHAIN (parm), num++)
     if (!is_gimple_reg (parm)
 	|| !gimple_default_def (cfun, parm)
 	|| !bitmap_bit_p (split_point->ssa_names_to_pass,
diff --git a/gcc/ipa-struct-reorg.c b/gcc/ipa-struct-reorg.c
index 4ee8e024a7d62e88d2a8a673ead089e0ee1dab93..6f62b703c5e29bcd0dbcdc349e3a2aac4cb06a4b 100644
--- a/gcc/ipa-struct-reorg.c
+++ b/gcc/ipa-struct-reorg.c
@@ -2925,7 +2925,7 @@ exclude_types_passed_to_local_func (VEC (tree, heap) **unsuitable_types)
 	tree fn = c_node->decl;
 	tree arg;
 
-	for (arg = DECL_ARGUMENTS (fn); arg; arg = TREE_CHAIN (arg))
+	for (arg = DECL_ARGUMENTS (fn); arg; arg = DECL_CHAIN (arg))
 	  {
 	    tree type = TREE_TYPE (arg);
 
diff --git a/gcc/ipa-type-escape.c b/gcc/ipa-type-escape.c
index 3b395f94e2192441ca1d11d1c43f03f06d94d945..354e651c4768e6ff8b0d172dc069ff34e440f116 100644
--- a/gcc/ipa-type-escape.c
+++ b/gcc/ipa-type-escape.c
@@ -1048,7 +1048,7 @@ check_function_parameter_and_return_types (tree fn, bool escapes)
 	 from the TYPE_ARG_LIST. However, Geoff is wrong, this code
 	 does seem to be live.  */
 
-      for (arg = DECL_ARGUMENTS (fn); arg; arg = TREE_CHAIN (arg))
+      for (arg = DECL_ARGUMENTS (fn); arg; arg = DECL_CHAIN (arg))
 	{
 	  tree type = get_canon_type (TREE_TYPE (arg), false, false);
 	  if (escapes)
@@ -1767,7 +1767,7 @@ close_type_seen (tree type)
      subfields.  */
   for (field = TYPE_FIELDS (type);
        field;
-       field = TREE_CHAIN (field))
+       field = DECL_CHAIN (field))
     {
       tree field_type;
       if (TREE_CODE (field) != FIELD_DECL)
diff --git a/gcc/java/ChangeLog b/gcc/java/ChangeLog
index aeee56a55819d42444d6b53c1f3b5925dfef0809..372739ff5a71a1a6c3e7ed6e48aa55c6fb831e7a 100644
--- a/gcc/java/ChangeLog
+++ b/gcc/java/ChangeLog
@@ -1,3 +1,14 @@
+2010-07-15  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* java-tree.h: Carefully replace TREE_CHAIN with DECL_CHAIN.
+	* boehm.c: Likewise.
+	* class.c: Likewise.
+	* decl.c: Likewise.
+	* expr.c: Likewise.
+	* jcf-parse.c: Likewise.
+	* typeck.c: Likewise.
+	* verify-glue.c: Likewise.
+
 2010-07-08  Manuel López-Ibáñez  <manu@gcc.gnu.org>
 
 	* boehm.c: Include diagnostic-core.h in every file that includes
diff --git a/gcc/java/boehm.c b/gcc/java/boehm.c
index f77530802e983a7d1f935c497dd77832d1a113e3..2a0690ce51d266858e30c7a9e95b549bf0911c66 100644
--- a/gcc/java/boehm.c
+++ b/gcc/java/boehm.c
@@ -63,10 +63,10 @@ mark_reference_fields (tree field,
 			     mask, ubit,
 			     pointer_after_end, all_bits_set,
 			     last_set_index, last_view_index);
-      field = TREE_CHAIN (field);
+      field = DECL_CHAIN (field);
     }
 
-  for (; field != NULL_TREE; field = TREE_CHAIN (field))
+  for (; field != NULL_TREE; field = DECL_CHAIN (field))
     {
       HOST_WIDE_INT offset;
       HOST_WIDE_INT size_bytes;
diff --git a/gcc/java/class.c b/gcc/java/class.c
index 7734c5961f2d76bba2b9e1e6a224c77610259223..78f77ab2d264c794608ec19b64ee4f66f2254bdd 100644
--- a/gcc/java/class.c
+++ b/gcc/java/class.c
@@ -782,7 +782,7 @@ add_method_1 (tree this_class, int access_flags, tree name, tree function_type)
     DECL_FUNCTION_INITIALIZED_CLASS_TABLE (fndecl) =
       htab_create_ggc (50, htab_hash_pointer, htab_eq_pointer, NULL);
 
-  TREE_CHAIN (fndecl) = TYPE_METHODS (this_class);
+  DECL_CHAIN (fndecl) = TYPE_METHODS (this_class);
   TYPE_METHODS (this_class) = fndecl;
 
   /* If pointers to member functions use the least significant bit to
@@ -853,7 +853,7 @@ add_field (tree klass, tree name, tree field_type, int flags)
   tree field;
   field = build_decl (input_location,
 		      is_static ? VAR_DECL : FIELD_DECL, name, field_type);
-  TREE_CHAIN (field) = TYPE_FIELDS (klass);
+  DECL_CHAIN (field) = TYPE_FIELDS (klass);
   TYPE_FIELDS (klass) = field;
   DECL_CONTEXT (field) = klass;
   MAYBE_CREATE_VAR_LANG_DECL_SPECIFIC (field);
@@ -1460,7 +1460,7 @@ make_field_value (tree fdecl)
       field_address = build_address_of (fdecl);
 
     index = (FIELD_STATIC (fdecl)
-	     ? TREE_CHAIN (TYPE_FIELDS (field_info_union_node))
+	     ? DECL_CHAIN (TYPE_FIELDS (field_info_union_node))
 	     : TYPE_FIELDS (field_info_union_node));
     value = (FIELD_STATIC (fdecl)
 	     ? field_address
@@ -1599,7 +1599,7 @@ get_dispatch_vector (tree type)
 	}
 
       for (method = TYPE_METHODS (type);  method != NULL_TREE;
-	   method = TREE_CHAIN (method))
+	   method = DECL_CHAIN (method))
 	{
 	  tree method_index = get_method_index (method);
 	  if (method_index != NULL_TREE
@@ -1842,13 +1842,13 @@ make_class_data (tree type)
   /* Build Field array. */
   field = TYPE_FIELDS (type);
   while (field && DECL_ARTIFICIAL (field))
-    field = TREE_CHAIN (field);  /* Skip dummy fields.  */
+    field = DECL_CHAIN (field);  /* Skip dummy fields.  */
   if (field && DECL_NAME (field) == NULL_TREE)
-    field = TREE_CHAIN (field);  /* Skip dummy field for inherited data. */
+    field = DECL_CHAIN (field);  /* Skip dummy field for inherited data. */
   first_real_field = field;
 
   /* First count static and instance fields.  */
-  for ( ; field != NULL_TREE; field = TREE_CHAIN (field))
+  for ( ; field != NULL_TREE; field = DECL_CHAIN (field))
     {
       if (! DECL_ARTIFICIAL (field))
 	{
@@ -1877,7 +1877,7 @@ make_class_data (tree type)
 
     for (i = 0, field = first_real_field; 
 	 field != NULL_TREE; 
-	 field = TREE_CHAIN (field), i++)
+	 field = DECL_CHAIN (field), i++)
     {
       if (! DECL_ARTIFICIAL (field))
 	{
@@ -1894,7 +1894,7 @@ make_class_data (tree type)
   }
 
   for (field = first_real_field; field != NULL_TREE; 
-       field = TREE_CHAIN (field))
+       field = DECL_CHAIN (field))
     {
       if (! DECL_ARTIFICIAL (field))
 	{
@@ -1945,7 +1945,7 @@ make_class_data (tree type)
 
   /* Build Method array. */
   for (method = TYPE_METHODS (type);
-       method != NULL_TREE; method = TREE_CHAIN (method))
+       method != NULL_TREE; method = DECL_CHAIN (method))
     {
       tree init;
       if (METHOD_PRIVATE (method)
@@ -2390,7 +2390,7 @@ push_super_field (tree this_class, tree super_class)
   base_decl = build_decl (input_location,
 			  FIELD_DECL, NULL_TREE, super_class);
   DECL_IGNORED_P (base_decl) = 1;
-  TREE_CHAIN (base_decl) = TYPE_FIELDS (this_class);
+  DECL_CHAIN (base_decl) = TYPE_FIELDS (this_class);
   TYPE_FIELDS (this_class) = base_decl;
   DECL_SIZE (base_decl) = TYPE_SIZE (super_class);
   DECL_SIZE_UNIT (base_decl) = TYPE_SIZE_UNIT (super_class);
@@ -2550,7 +2550,7 @@ add_miranda_methods (tree base_class, tree search_class)
          will be correct.  This code must match similar layout code in the 
          runtime.  */
       for (method_decl = TYPE_METHODS (elt);
-	   method_decl; method_decl = TREE_CHAIN (method_decl))
+	   method_decl; method_decl = DECL_CHAIN (method_decl))
 	{
 	  tree sig, override;
 
@@ -2614,7 +2614,7 @@ layout_class_methods (tree this_class)
   TYPE_METHODS (this_class) = nreverse (TYPE_METHODS (this_class));
 
   for (method_decl = TYPE_METHODS (this_class);
-       method_decl; method_decl = TREE_CHAIN (method_decl))
+       method_decl; method_decl = DECL_CHAIN (method_decl))
     dtable_count = layout_class_method (this_class, super_class,
 					method_decl, dtable_count);
 
@@ -2629,7 +2629,7 @@ get_interface_method_index (tree method, tree interface)
   tree meth;
   int i = 1;
 
-  for (meth = TYPE_METHODS (interface); ; meth = TREE_CHAIN (meth))
+  for (meth = TYPE_METHODS (interface); ; meth = DECL_CHAIN (meth))
     {
       if (meth == method)
 	return i;
diff --git a/gcc/java/decl.c b/gcc/java/decl.c
index 5c112c3ef062f23ddf0f329284ef7281a24b57e0..36a2c2916e047fa5feb3207fcd30e52d9731b4f6 100644
--- a/gcc/java/decl.c
+++ b/gcc/java/decl.c
@@ -825,7 +825,7 @@ java_init_decl_processing (void)
   if (! flag_hash_synchronization)
     PUSH_FIELD (input_location, object_type_node, field, "sync_info",
 		build_pointer_type (object_type_node));
-  for (t = TYPE_FIELDS (object_type_node); t != NULL_TREE; t = TREE_CHAIN (t))
+  for (t = TYPE_FIELDS (object_type_node); t != NULL_TREE; t = DECL_CHAIN (t))
     FIELD_PRIVATE (t) = 1;
   FINISH_RECORD (object_type_node);
 
@@ -907,7 +907,7 @@ java_init_decl_processing (void)
   PUSH_FIELD (input_location, class_type_node, field, "engine", ptr_type_node);
   PUSH_FIELD (input_location,
 	      class_type_node, field, "reflection_data", ptr_type_node);
-  for (t = TYPE_FIELDS (class_type_node);  t != NULL_TREE;  t = TREE_CHAIN (t))
+  for (t = TYPE_FIELDS (class_type_node);  t != NULL_TREE;  t = DECL_CHAIN (t))
     FIELD_PRIVATE (t) = 1;
   push_super_field (class_type_node, object_type_node);
 
@@ -1215,7 +1215,7 @@ lookup_name_current_level (tree name)
   if (IDENTIFIER_LOCAL_VALUE (name) == 0)
     return 0;
 
-  for (t = current_binding_level->names; t; t = TREE_CHAIN (t))
+  for (t = current_binding_level->names; t; t = DECL_CHAIN (t))
     if (DECL_NAME (t) == name)
       break;
 
@@ -1284,7 +1284,7 @@ pushdecl (tree x)
 
   /* Put decls on list in reverse order.
      We will reverse them later if necessary.  */
-  TREE_CHAIN (x) = b->names;
+  DECL_CHAIN (x) = b->names;
   b->names = x;
 
   return x;
@@ -1435,7 +1435,7 @@ poplevel (int keep, int reverse, int functionbody)
   else
     decls = current_binding_level->names;
 
-  for (decl = decls; decl; decl = TREE_CHAIN (decl))
+  for (decl = decls; decl; decl = DECL_CHAIN (decl))
     if (TREE_CODE (decl) == VAR_DECL
 	&& DECL_LANG_SPECIFIC (decl) != NULL
 	&& DECL_LOCAL_SLOT_NUMBER (decl))
@@ -1468,11 +1468,11 @@ poplevel (int keep, int reverse, int functionbody)
 	  /* Copy decls from names list, ignoring labels.  */
 	  while (decl)
 	    {
-	      tree next = TREE_CHAIN (decl);
+	      tree next = DECL_CHAIN (decl);
 	      if (TREE_CODE (decl) != LABEL_DECL)
 		{
 		  *var = decl;
-		  var = &TREE_CHAIN (decl);
+		  var = &DECL_CHAIN (decl);
 		}
 	      decl = next;
 	    }
@@ -1508,7 +1508,7 @@ poplevel (int keep, int reverse, int functionbody)
 
   /* Clear out the meanings of the local variables of this level.  */
 
-  for (link = decls; link; link = TREE_CHAIN (link))
+  for (link = decls; link; link = DECL_CHAIN (link))
     {
       tree name = DECL_NAME (link);
       if (name != 0 && IDENTIFIER_LOCAL_VALUE (name) == link)
@@ -1604,7 +1604,7 @@ maybe_pushlevels (int pc)
       while (*ptr != NULL_TREE
 	     && DECL_LOCAL_START_PC (*ptr) <= pc
 	     && DECL_LOCAL_END_PC (*ptr) == end_pc)
-	ptr = &TREE_CHAIN (*ptr);
+	ptr = &DECL_CHAIN (*ptr);
       pending_local_decls = *ptr;
       *ptr = NULL_TREE;
 
@@ -1614,7 +1614,7 @@ maybe_pushlevels (int pc)
 	{
 	  tree t;
 	  end_pc = current_binding_level->end_pc;
-	  for (t = decl; t != NULL_TREE; t = TREE_CHAIN (t))
+	  for (t = decl; t != NULL_TREE; t = DECL_CHAIN (t))
 	    DECL_LOCAL_END_PC (t) = end_pc;
 	}
 
@@ -1629,7 +1629,7 @@ maybe_pushlevels (int pc)
 	{
 	  int index = DECL_LOCAL_SLOT_NUMBER (decl);
 	  tree base_decl;
-	  next = TREE_CHAIN (decl);
+	  next = DECL_CHAIN (decl);
 	  push_jvm_slot (index, decl);
 	  pushdecl (decl);
 	  base_decl
@@ -1757,8 +1757,8 @@ give_name_to_locals (JCF *jcf)
 		 && (DECL_LOCAL_START_PC (*ptr) > start_pc
 		     || (DECL_LOCAL_START_PC (*ptr) == start_pc
 			 && DECL_LOCAL_END_PC (*ptr) < end_pc)))
-	    ptr = &TREE_CHAIN (*ptr);
-	  TREE_CHAIN (decl) = *ptr;
+	    ptr = &DECL_CHAIN (*ptr);
+	  DECL_CHAIN (decl) = *ptr;
 	  *ptr = decl;
 	}
     }
@@ -1767,7 +1767,7 @@ give_name_to_locals (JCF *jcf)
 
   /* Fill in default names for the parameters. */ 
   for (parm = DECL_ARGUMENTS (current_function_decl), i = 0;
-       parm != NULL_TREE;  parm = TREE_CHAIN (parm), i++)
+       parm != NULL_TREE;  parm = DECL_CHAIN (parm), i++)
     {
       if (DECL_NAME (parm) == NULL_TREE)
 	{
@@ -1840,7 +1840,7 @@ start_java_method (tree fndecl)
       DECL_ARG_TYPE (parm_decl) = parm_type;
 
       *ptr = parm_decl;
-      ptr = &TREE_CHAIN (parm_decl);
+      ptr = &DECL_CHAIN (parm_decl);
 
       /* Add parm_decl to the decl_map. */
       push_jvm_slot (i, parm_decl);
@@ -1993,7 +1993,7 @@ java_mark_class_local (tree klass)
 {
   tree t;
 
-  for (t = TYPE_FIELDS (klass); t ; t = TREE_CHAIN (t))
+  for (t = TYPE_FIELDS (klass); t ; t = DECL_CHAIN (t))
     if (FIELD_STATIC (t))
       {
 	if (DECL_EXTERNAL (t))
@@ -2001,7 +2001,7 @@ java_mark_class_local (tree klass)
 	java_mark_decl_local (t);
       }
 
-  for (t = TYPE_METHODS (klass); t ; t = TREE_CHAIN (t))
+  for (t = TYPE_METHODS (klass); t ; t = DECL_CHAIN (t))
     if (!METHOD_ABSTRACT (t))
       {
 	if (METHOD_NATIVE (t) && !flag_jni)
@@ -2089,7 +2089,7 @@ java_add_local_var (tree decl)
 {
   tree *vars = &current_binding_level->names;
   tree next = *vars;
-  TREE_CHAIN (decl) = next;
+  DECL_CHAIN (decl) = next;
   *vars = decl;
   DECL_CONTEXT (decl) = current_function_decl;
   MAYBE_CREATE_VAR_LANG_DECL_SPECIFIC (decl);
diff --git a/gcc/java/expr.c b/gcc/java/expr.c
index 3f51719404418285e99207353766d440a9b29643..3c987c5fe822734cf9fd0ac583e6dab590f3cfb7 100644
--- a/gcc/java/expr.c
+++ b/gcc/java/expr.c
@@ -1634,7 +1634,7 @@ lookup_field (tree *typep, tree name)
       tree save_field;
       int i;
 
-      for (field = TYPE_FIELDS (*typep); field; field = TREE_CHAIN (field))
+      for (field = TYPE_FIELDS (*typep); field; field = DECL_CHAIN (field))
 	if (DECL_NAME (field) == name)
 	  return field;
 
@@ -1952,7 +1952,7 @@ attach_init_test_initialization_flags (void **entry, void *ptr)
       if (TREE_CODE (block) == BIND_EXPR)
         {
 	  tree body = BIND_EXPR_BODY (block);
-	  TREE_CHAIN (ite->value) = BIND_EXPR_VARS (block);
+	  DECL_CHAIN (ite->value) = BIND_EXPR_VARS (block);
 	  BIND_EXPR_VARS (block) = ite->value;
 	  body = build2 (COMPOUND_EXPR, void_type_node,
 			 build1 (DECL_EXPR, void_type_node, ite->value), body);
@@ -2239,7 +2239,7 @@ build_known_method_ref (tree method, tree method_type ATTRIBUTE_UNUSED,
 		    lookup_field (&class_type_node, methods_ident),
 		    NULL_TREE);
       for (meth = TYPE_METHODS (self_type);
-	   ; meth = TREE_CHAIN (meth))
+	   ; meth = DECL_CHAIN (meth))
 	{
 	  if (method == meth)
 	    break;
@@ -2643,7 +2643,7 @@ build_jni_stub (tree method)
       res_var = build_decl (input_location, VAR_DECL, get_identifier ("res"),
 			    TREE_TYPE (TREE_TYPE (method)));
       DECL_CONTEXT (res_var) = method;
-      TREE_CHAIN (env_var) = res_var;
+      DECL_CHAIN (env_var) = res_var;
     }
 
   method_args = DECL_ARGUMENTS (method);
@@ -2673,7 +2673,7 @@ build_jni_stub (tree method)
   /* All the arguments to this method become arguments to the
      underlying JNI function.  If we had to wrap object arguments in a
      special way, we would do that here.  */
-  for (tem = method_args; tem != NULL_TREE; tem = TREE_CHAIN (tem))
+  for (tem = method_args; tem != NULL_TREE; tem = DECL_CHAIN (tem))
     {
       int arg_bits = TREE_INT_CST_LOW (TYPE_SIZE (TREE_TYPE (tem)));
 #ifdef PARM_BOUNDARY
@@ -3779,7 +3779,7 @@ promote_arguments (void)
   int i;
   tree arg;
   for (arg = DECL_ARGUMENTS (current_function_decl), i = 0;
-       arg != NULL_TREE;  arg = TREE_CHAIN (arg), i++)
+       arg != NULL_TREE;  arg = DECL_CHAIN (arg), i++)
     {
       tree arg_type = TREE_TYPE (arg);
       if (INTEGRAL_TYPE_P (arg_type)
diff --git a/gcc/java/java-tree.h b/gcc/java/java-tree.h
index ccaa0e34eb78a7a6331515948c54d443498e2377..110eb83e00c9c4be428a87d567110fd678d687ff 100644
--- a/gcc/java/java-tree.h
+++ b/gcc/java/java-tree.h
@@ -1461,7 +1461,7 @@ extern tree *type_map;
   if (TYPE_FIELDS (RTYPE) == NULL_TREE)	\
     TYPE_FIELDS (RTYPE) = _field; 	\
   else					\
-    TREE_CHAIN(FIELD) = _field;		\
+    DECL_CHAIN(FIELD) = _field;		\
   DECL_CONTEXT (_field) = (RTYPE);	\
   DECL_ARTIFICIAL (_field) = 1;		\
   FIELD = _field; }
@@ -1485,7 +1485,7 @@ extern tree *type_map;
   do \
     { \
       constructor_elt *_elt___ = VEC_last (constructor_elt, V); \
-      tree _next___ = TREE_CHAIN (_elt___->index); \
+      tree _next___ = DECL_CHAIN (_elt___->index); \
       gcc_assert (!DECL_NAME (_elt___->index)); \
       _elt___->value = VALUE; \
       CONSTRUCTOR_APPEND_ELT (V, _next___, NULL); \
@@ -1499,7 +1499,7 @@ extern tree *type_map;
   do \
     { \
       constructor_elt *_elt___ = VEC_last (constructor_elt, V); \
-      tree _next___ = TREE_CHAIN (_elt___->index); \
+      tree _next___ = DECL_CHAIN (_elt___->index); \
       gcc_assert (strcmp (IDENTIFIER_POINTER (DECL_NAME (_elt___->index)), \
 			  NAME) == 0); \
       _elt___->value = VALUE; \
diff --git a/gcc/java/jcf-parse.c b/gcc/java/jcf-parse.c
index 10d1c80167636cfcdaa563b0082eeabc7699ca61..c27d4b553d8fc6c22fdd913574aeb350c51a0b43 100644
--- a/gcc/java/jcf-parse.c
+++ b/gcc/java/jcf-parse.c
@@ -1571,7 +1571,7 @@ parse_class_file (void)
   gen_indirect_dispatch_tables (current_class);
 
   for (method = TYPE_METHODS (current_class);
-       method != NULL_TREE; method = TREE_CHAIN (method))
+       method != NULL_TREE; method = DECL_CHAIN (method))
     {
       JCF *jcf = current_jcf;
 
diff --git a/gcc/java/typeck.c b/gcc/java/typeck.c
index 91d71881fe85fe3ee862e8340e243c90866a6239..dca14ab5f8146b389fe3e3c3cef363793a5d834f 100644
--- a/gcc/java/typeck.c
+++ b/gcc/java/typeck.c
@@ -211,7 +211,7 @@ java_array_type_length (tree array_type)
   tree arfld;
   if (TREE_CODE (array_type) == POINTER_TYPE)
     array_type = TREE_TYPE (array_type);
-  arfld = TREE_CHAIN (TREE_CHAIN (TYPE_FIELDS (array_type)));
+  arfld = DECL_CHAIN (DECL_CHAIN (TYPE_FIELDS (array_type)));
   if (arfld != NULL_TREE)
     {
       tree index_type = TYPE_DOMAIN (TREE_TYPE (arfld));
@@ -306,7 +306,7 @@ build_java_array_type (tree element_type, HOST_WIDE_INT length)
   arfld = build_decl (input_location,
 		      FIELD_DECL, get_identifier ("data"), atype);
   DECL_CONTEXT (arfld) = t;
-  TREE_CHAIN (fld) = arfld;
+  DECL_CHAIN (fld) = arfld;
   DECL_ALIGN (arfld) = TYPE_ALIGN (element_type);
 
   /* We could layout_class, but that loads java.lang.Object prematurely.
@@ -644,7 +644,7 @@ shallow_find_method (tree searched_class, int flags, tree method_name,
 {
   tree method;
   for (method = TYPE_METHODS (searched_class);
-       method != NULL_TREE;  method = TREE_CHAIN (method))
+       method != NULL_TREE;  method = DECL_CHAIN (method))
     {
       tree method_sig = (*signature_builder) (TREE_TYPE (method));
       if (DECL_NAME (method) == method_name && method_sig == signature)
@@ -779,7 +779,7 @@ tree
 lookup_java_constructor (tree clas, tree method_signature)
 {
   tree method = TYPE_METHODS (clas);
-  for ( ; method != NULL_TREE;  method = TREE_CHAIN (method))
+  for ( ; method != NULL_TREE;  method = DECL_CHAIN (method))
     {
       tree method_sig = build_java_signature (TREE_TYPE (method));
       if (DECL_CONSTRUCTOR_P (method) && method_sig == method_signature)
diff --git a/gcc/java/verify-glue.c b/gcc/java/verify-glue.c
index 02267b41b8f3ec0fd246c368742c30b2366faab5..78d35495478360e2226b5ad3f2ffff5782cfd777 100644
--- a/gcc/java/verify-glue.c
+++ b/gcc/java/verify-glue.c
@@ -365,7 +365,7 @@ vfy_class_has_field (vfy_jclass klass, vfy_string name,
       if (DECL_NAME (field) == name
 	  && build_java_signature (TREE_TYPE (field)) == signature)
 	return true;
-      field = TREE_CHAIN (field);
+      field = DECL_CHAIN (field);
     }
   return false;
 }
diff --git a/gcc/langhooks.c b/gcc/langhooks.c
index bdda6236c72b408595edc5b90bf498509a18c51d..f56b42b7786c74f1d2f3cbd8d152fe53a7e792f4 100644
--- a/gcc/langhooks.c
+++ b/gcc/langhooks.c
@@ -320,7 +320,7 @@ write_global_declarations (void)
   /* Process the decls in reverse order--earliest first.
      Put them into VEC from back to front, then take out from front.  */
 
-  for (i = 0, decl = globals; i < len; i++, decl = TREE_CHAIN (decl))
+  for (i = 0, decl = globals; i < len; i++, decl = DECL_CHAIN (decl))
     vec[len - i - 1] = decl;
 
   wrapup_global_declarations (vec, len);
diff --git a/gcc/lto-cgraph.c b/gcc/lto-cgraph.c
index 8dd8a29641bbb2158006e68ecab0f680a3058b96..9c7af2ba50731bbcbb7e86f0220debd42a16c301 100644
--- a/gcc/lto-cgraph.c
+++ b/gcc/lto-cgraph.c
@@ -1487,7 +1487,7 @@ output_node_opt_summary (struct output_block *ob,
       tree parm;
 
       for (parm_num = 0, parm = DECL_ARGUMENTS (node->decl); parm;
-	   parm = TREE_CHAIN (parm), parm_num++)
+	   parm = DECL_CHAIN (parm), parm_num++)
 	if (map->old_tree == parm)
 	  break;
       /* At the moment we assume all old trees to be PARM_DECLs, because we have no
@@ -1571,7 +1571,7 @@ input_node_opt_summary (struct cgraph_node *node,
 
       VEC_safe_push (ipa_replace_map_p, gc, node->clone.tree_map, map);
       for (parm_num = 0, parm = DECL_ARGUMENTS (node->decl); parm_num;
-	   parm = TREE_CHAIN (parm))
+	   parm = DECL_CHAIN (parm))
 	parm_num --;
       map->parm_num = lto_input_uleb128 (ib_main);
       map->old_tree = NULL;
diff --git a/gcc/objc/ChangeLog b/gcc/objc/ChangeLog
index 17b116f6ebefc09bfdff1e7119f5ef5a8f56e600..de6cbebd2ad05d9d95790556f3938234ed09eb7b 100644
--- a/gcc/objc/ChangeLog
+++ b/gcc/objc/ChangeLog
@@ -1,3 +1,7 @@
+2010-07-15  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* objc-act.c: Carefully replace TREE_CHAIN with DECL_CHAIN.
+
 2010-07-10  Iain Sandoe  <iains@gcc.gnu.org>
 
 	PR objc/44140
diff --git a/gcc/objc/objc-act.c b/gcc/objc/objc-act.c
index a0f36906e9b34308b592ac341d94c437980495ff..81aba84eb9742b23432f30419fe6e88f11e804a2 100644
--- a/gcc/objc/objc-act.c
+++ b/gcc/objc/objc-act.c
@@ -455,7 +455,7 @@ add_field_decl (tree type, const char *name, tree **chain)
 
   if (*chain != NULL)
     **chain = field;
-  *chain = &TREE_CHAIN (field);
+  *chain = &DECL_CHAIN (field);
 
   return field;
 }
@@ -851,9 +851,9 @@ objc_build_struct (tree klass, tree fields, tree super_name)
 			      FIELD_DECL, NULL_TREE, super);
       tree field = TYPE_FIELDS (super);
 
-      while (field && TREE_CHAIN (field)
-	     && TREE_CODE (TREE_CHAIN (field)) == FIELD_DECL)
-	field = TREE_CHAIN (field);
+      while (field && DECL_CHAIN (field)
+	     && TREE_CODE (DECL_CHAIN (field)) == FIELD_DECL)
+	field = DECL_CHAIN (field);
 
       /* For ObjC ABI purposes, the "packed" size of a base class is
 	 the sum of the offset and the size (in bits) of the last field
@@ -882,7 +882,7 @@ objc_build_struct (tree klass, tree fields, tree super_name)
       if (fields)
 	TREE_NO_WARNING (fields) = 1;	/* Suppress C++ ABI warnings -- we   */
 #endif					/* are following the ObjC ABI here.  */
-      TREE_CHAIN (base) = fields;
+      DECL_CHAIN (base) = fields;
       fields = base;
     }
 
@@ -1848,11 +1848,11 @@ check_string_class_template (void)
   if (!AT_LEAST_AS_LARGE_AS (field_decl, ptr_type_node))
     return 0;
 
-  field_decl = TREE_CHAIN (field_decl);
+  field_decl = DECL_CHAIN (field_decl);
   if (!AT_LEAST_AS_LARGE_AS (field_decl, ptr_type_node))
     return 0;
 
-  field_decl = TREE_CHAIN (field_decl);
+  field_decl = DECL_CHAIN (field_decl);
   return AT_LEAST_AS_LARGE_AS (field_decl, unsigned_type_node);
 
 #undef AT_LEAST_AS_LARGE_AS
@@ -1873,10 +1873,10 @@ objc_build_internal_const_str_type (void)
   tree field = build_decl (input_location,
 			   FIELD_DECL, NULL_TREE, ptr_type_node);
 
-  TREE_CHAIN (field) = fields; fields = field;
+  DECL_CHAIN (field) = fields; fields = field;
   field = build_decl (input_location,
 		      FIELD_DECL, NULL_TREE, unsigned_type_node);
-  TREE_CHAIN (field) = fields; fields = field;
+  DECL_CHAIN (field) = fields; fields = field;
   /* NB: The finish_builtin_struct() routine expects FIELD_DECLs in
      reverse order!  */
   finish_builtin_struct (type, "__builtin_ObjCString",
@@ -2003,11 +2003,11 @@ objc_build_string_object (tree string)
 			      ? build_unary_op (input_location,
 						ADDR_EXPR, string_class_decl, 0)
 			      : build_int_cst (NULL_TREE, 0));
-      fields = TREE_CHAIN (fields);
+      fields = DECL_CHAIN (fields);
       CONSTRUCTOR_APPEND_ELT (v, fields,
 			      build_unary_op (input_location,
 					      ADDR_EXPR, string, 1));
-      fields = TREE_CHAIN (fields);
+      fields = DECL_CHAIN (fields);
       CONSTRUCTOR_APPEND_ELT (v, fields, build_int_cst (NULL_TREE, length));
       constructor = objc_build_constructor (internal_const_str_type, v);
 
@@ -2231,7 +2231,7 @@ init_objc_symtab (tree type)
     {
 
       tree field = TYPE_FIELDS (type);
-      field = TREE_CHAIN (TREE_CHAIN (TREE_CHAIN (TREE_CHAIN (field))));
+      field = DECL_CHAIN (DECL_CHAIN (DECL_CHAIN (DECL_CHAIN (field))));
 
       CONSTRUCTOR_APPEND_ELT (v, NULL_TREE, init_def_list (TREE_TYPE (field)));
     }
@@ -4253,7 +4253,7 @@ build_descriptor_table_initializer (tree type, tree entries)
       CONSTRUCTOR_APPEND_ELT (inits, NULL_TREE,
 			      objc_build_constructor (type, elts));
 
-      entries = TREE_CHAIN (entries);
+      entries = DECL_CHAIN (entries);
     }
   while (entries);
 
@@ -4356,7 +4356,7 @@ encode_method_prototype (tree method_decl)
   i = int_size_in_bytes (ptr_type_node);
   parm_offset = 2 * i;
   for (parms = METHOD_SEL_ARGS (method_decl); parms;
-       parms = TREE_CHAIN (parms))
+       parms = DECL_CHAIN (parms))
     {
       tree type = objc_method_parm_type (parms);
       int sz = objc_encoded_type_size (type);
@@ -4379,7 +4379,7 @@ encode_method_prototype (tree method_decl)
   /* Argument types.  */
   parm_offset = 2 * i;
   for (parms = METHOD_SEL_ARGS (method_decl); parms;
-       parms = TREE_CHAIN (parms))
+       parms = DECL_CHAIN (parms))
     {
       tree type = objc_method_parm_type (parms);
 
@@ -4695,7 +4695,7 @@ generate_protocols (void)
 	      encoding = encode_method_prototype (nst_methods);
 	      METHOD_ENCODING (nst_methods) = encoding;
 	    }
-	  nst_methods = TREE_CHAIN (nst_methods);
+	  nst_methods = DECL_CHAIN (nst_methods);
 	}
 
       while (cls_methods)
@@ -4706,7 +4706,7 @@ generate_protocols (void)
 	      METHOD_ENCODING (cls_methods) = encoding;
 	    }
 
-	  cls_methods = TREE_CHAIN (cls_methods);
+	  cls_methods = DECL_CHAIN (cls_methods);
 	}
       generate_method_descriptors (p);
 
@@ -5016,8 +5016,8 @@ check_ivars (tree inter, tree imp)
 			   intdecls);
 	}
 
-      intdecls = TREE_CHAIN (intdecls);
-      impdecls = TREE_CHAIN (impdecls);
+      intdecls = DECL_CHAIN (intdecls);
+      impdecls = DECL_CHAIN (impdecls);
     }
 }
 
@@ -5165,7 +5165,7 @@ build_ivar_list_initializer (tree type, tree field_decl)
       CONSTRUCTOR_APPEND_ELT (inits, NULL_TREE,
 			      objc_build_constructor (type, ivar));
       do
-	field_decl = TREE_CHAIN (field_decl);
+	field_decl = DECL_CHAIN (field_decl);
       while (field_decl && TREE_CODE (field_decl) != FIELD_DECL);
     }
   while (field_decl);
@@ -5198,7 +5198,7 @@ ivar_list_length (tree t)
 {
   int count = 0;
 
-  for (; t; t = TREE_CHAIN (t))
+  for (; t; t = DECL_CHAIN (t))
     if (TREE_CODE (t) == FIELD_DECL)
       ++count;
 
@@ -5281,7 +5281,7 @@ build_dispatch_table_initializer (tree type, tree entries)
       CONSTRUCTOR_APPEND_ELT (inits, NULL_TREE,
 			      objc_build_constructor (type, elems));
 
-      entries = TREE_CHAIN (entries);
+      entries = DECL_CHAIN (entries);
     }
   while (entries);
 
@@ -5350,14 +5350,14 @@ mark_referenced_methods (void)
       while (chain)
 	{
 	  cgraph_mark_needed_node (cgraph_node (METHOD_DEFINITION (chain)));
-	  chain = TREE_CHAIN (chain);
+	  chain = DECL_CHAIN (chain);
 	}
 
       chain = CLASS_NST_METHODS (impent->imp_context);
       while (chain)
 	{
 	  cgraph_mark_needed_node (cgraph_node (METHOD_DEFINITION (chain)));
-	  chain = TREE_CHAIN (chain);
+	  chain = DECL_CHAIN (chain);
 	}
     }
 }
@@ -5990,7 +5990,7 @@ get_arg_type_list (tree meth, int context, int superflag)
     return arglist;
 
   /* Build a list of argument types.  */
-  for (akey = METHOD_SEL_ARGS (meth); akey; akey = TREE_CHAIN (akey))
+  for (akey = METHOD_SEL_ARGS (meth); akey; akey = DECL_CHAIN (akey))
     {
       tree arg_type = TREE_VALUE (TREE_TYPE (akey));
 
@@ -6822,7 +6822,7 @@ lookup_method (tree mchain, tree method)
       if (METHOD_SEL_NAME (mchain) == key)
 	return mchain;
 
-      mchain = TREE_CHAIN (mchain);
+      mchain = DECL_CHAIN (mchain);
     }
   return NULL_TREE;
 }
@@ -6934,12 +6934,12 @@ objc_add_method (tree klass, tree method, int is_class)
       /* put method on list in reverse order */
       if (is_class)
 	{
-	  TREE_CHAIN (method) = CLASS_CLS_METHODS (klass);
+	  DECL_CHAIN (method) = CLASS_CLS_METHODS (klass);
 	  CLASS_CLS_METHODS (klass) = method;
 	}
       else
 	{
-	  TREE_CHAIN (method) = CLASS_NST_METHODS (klass);
+	  DECL_CHAIN (method) = CLASS_NST_METHODS (klass);
 	  CLASS_NST_METHODS (klass) = method;
 	}
     }
@@ -7151,7 +7151,7 @@ add_instance_variable (tree klass, int visibility, tree field_decl)
 static tree
 is_ivar (tree decl_chain, tree ident)
 {
-  for ( ; decl_chain; decl_chain = TREE_CHAIN (decl_chain))
+  for ( ; decl_chain; decl_chain = DECL_CHAIN (decl_chain))
     if (DECL_NAME (decl_chain) == ident)
       return decl_chain;
   return NULL_TREE;
@@ -7278,7 +7278,7 @@ check_methods (tree chain, tree list, int mtype)
 		   mtype, METHOD_SEL_NAME (chain));
 	}
 
-      chain = TREE_CHAIN (chain);
+      chain = DECL_CHAIN (chain);
     }
 
     return first;
@@ -7952,7 +7952,7 @@ encode_aggregate_fields (tree type, int pointed_to, int curtype, int format)
 {
   tree field = TYPE_FIELDS (type);
 
-  for (; field; field = TREE_CHAIN (field))
+  for (; field; field = DECL_CHAIN (field))
     {
 #ifdef OBJCPLUS
       /* C++ static members, and things that are not field at all,
@@ -8301,9 +8301,9 @@ objc_get_parm_info (int have_ellipsis)
   declare_parm_level ();
   while (parm_info)
     {
-      tree next = TREE_CHAIN (parm_info);
+      tree next = DECL_CHAIN (parm_info);
 
-      TREE_CHAIN (parm_info) = NULL_TREE;
+      DECL_CHAIN (parm_info) = NULL_TREE;
       parm_info = pushdecl (parm_info);
       finish_decl (parm_info, input_location, NULL_TREE, NULL_TREE, NULL_TREE);
       parm_info = next;
@@ -8381,7 +8381,7 @@ start_method_def (tree method)
       parm = build_decl (input_location,
 			 PARM_DECL, KEYWORD_ARG_NAME (parmlist), type);
       objc_push_parm (parm);
-      parmlist = TREE_CHAIN (parmlist);
+      parmlist = DECL_CHAIN (parmlist);
     }
 
   if (METHOD_ADD_ARGS (method))
@@ -8614,8 +8614,8 @@ really_start_method (tree method,
   /* Suppress unused warnings.  */
   TREE_USED (self_decl) = 1;
   DECL_READ_P (self_decl) = 1;
-  TREE_USED (TREE_CHAIN (self_decl)) = 1;
-  DECL_READ_P (TREE_CHAIN (self_decl)) = 1;
+  TREE_USED (DECL_CHAIN (self_decl)) = 1;
+  DECL_READ_P (DECL_CHAIN (self_decl)) = 1;
 #ifdef OBJCPLUS
   pop_lang_context ();
 #endif
@@ -8973,7 +8973,7 @@ gen_method_decl (tree method)
 	  strcat (errbuf, ")");
 
 	  strcat (errbuf, IDENTIFIER_POINTER (KEYWORD_ARG_NAME (chain)));
-	  if ((chain = TREE_CHAIN (chain)))
+	  if ((chain = DECL_CHAIN (chain)))
 	    strcat (errbuf, " ");
         }
       while (chain);
diff --git a/gcc/omp-low.c b/gcc/omp-low.c
index 7193c1f8abf0f5cd150ae2f8fafa85602806710f..723c2a7df3ac15704f7f9613ee49c5b49861c93f 100644
--- a/gcc/omp-low.c
+++ b/gcc/omp-low.c
@@ -841,7 +841,7 @@ omp_copy_decl_2 (tree var, tree name, tree type, omp_context *ctx)
   tree copy = copy_var_decl (var, name, type);
 
   DECL_CONTEXT (copy) = current_function_decl;
-  TREE_CHAIN (copy) = ctx->block_vars;
+  DECL_CHAIN (copy) = ctx->block_vars;
   ctx->block_vars = copy;
 
   return copy;
@@ -1286,13 +1286,13 @@ delete_omp_context (splay_tree_value value)
   if (ctx->record_type)
     {
       tree t;
-      for (t = TYPE_FIELDS (ctx->record_type); t ; t = TREE_CHAIN (t))
+      for (t = TYPE_FIELDS (ctx->record_type); t ; t = DECL_CHAIN (t))
 	DECL_ABSTRACT_ORIGIN (t) = NULL;
     }
   if (ctx->srecord_type)
     {
       tree t;
-      for (t = TYPE_FIELDS (ctx->srecord_type); t ; t = TREE_CHAIN (t))
+      for (t = TYPE_FIELDS (ctx->srecord_type); t ; t = DECL_CHAIN (t))
 	DECL_ABSTRACT_ORIGIN (t) = NULL;
     }
 
@@ -1314,7 +1314,7 @@ fixup_child_record_type (omp_context *ctx)
      variably_modified_type_p doesn't work the way we expect for
      record types.  Testing each field for whether it needs remapping
      and creating a new record by hand works, however.  */
-  for (f = TYPE_FIELDS (type); f ; f = TREE_CHAIN (f))
+  for (f = TYPE_FIELDS (type); f ; f = DECL_CHAIN (f))
     if (variably_modified_type_p (TREE_TYPE (f), ctx->cb.src_fn))
       break;
   if (f)
@@ -1327,12 +1327,12 @@ fixup_child_record_type (omp_context *ctx)
 			 TYPE_DECL, name, type);
       TYPE_NAME (type) = name;
 
-      for (f = TYPE_FIELDS (ctx->record_type); f ; f = TREE_CHAIN (f))
+      for (f = TYPE_FIELDS (ctx->record_type); f ; f = DECL_CHAIN (f))
 	{
 	  tree new_f = copy_node (f);
 	  DECL_CONTEXT (new_f) = type;
 	  TREE_TYPE (new_f) = remap_type (TREE_TYPE (f), &ctx->cb);
-	  TREE_CHAIN (new_f) = new_fields;
+	  DECL_CHAIN (new_f) = new_fields;
 	  walk_tree (&DECL_SIZE (new_f), copy_tree_body_r, &ctx->cb, NULL);
 	  walk_tree (&DECL_SIZE_UNIT (new_f), copy_tree_body_r,
 		     &ctx->cb, NULL);
@@ -1596,7 +1596,7 @@ create_omp_child_function (omp_context *ctx, bool task_copy)
       DECL_CONTEXT (t) = current_function_decl;
       TREE_USED (t) = 1;
       TREE_ADDRESSABLE (t) = 1;
-      TREE_CHAIN (t) = DECL_ARGUMENTS (decl);
+      DECL_CHAIN (t) = DECL_ARGUMENTS (decl);
       DECL_ARGUMENTS (decl) = t;
     }
 
@@ -1721,7 +1721,7 @@ scan_omp_task (gimple_stmt_iterator *gsi, omp_context *outer_ctx)
 	    q = &TREE_CHAIN (*q);
 	  }
 	else
-	  p = &TREE_CHAIN (*p);
+	  p = &DECL_CHAIN (*p);
       *p = vla_fields;
       layout_type (ctx->record_type);
       fixup_child_record_type (ctx);
@@ -2009,7 +2009,7 @@ scan_omp_1_stmt (gimple_stmt_iterator *gsi, bool *handled_ops_p,
 
 	*handled_ops_p = false;
 	if (ctx)
-	  for (var = gimple_bind_vars (stmt); var ; var = TREE_CHAIN (var))
+	  for (var = gimple_bind_vars (stmt); var ; var = DECL_CHAIN (var))
 	    insert_decl_map (&ctx->cb, var, var);
       }
       break;
@@ -2838,7 +2838,7 @@ lower_send_shared_vars (gimple_seq *ilist, gimple_seq *olist, omp_context *ctx)
     return;
 
   record_type = ctx->srecord_type ? ctx->srecord_type : ctx->record_type;
-  for (f = TYPE_FIELDS (record_type); f ; f = TREE_CHAIN (f))
+  for (f = TYPE_FIELDS (record_type); f ; f = DECL_CHAIN (f))
     {
       ovar = DECL_ABSTRACT_ORIGIN (f);
       nvar = maybe_lookup_decl (ovar, ctx);
@@ -3146,7 +3146,7 @@ vec2chain (VEC(tree,gc) *v)
 
   FOR_EACH_VEC_ELT_REVERSE (tree, v, ix, t)
     {
-      TREE_CHAIN (t) = chain;
+      DECL_CHAIN (t) = chain;
       chain = t;
     }
 
@@ -3227,7 +3227,7 @@ remove_exit_barrier (struct omp_region *region)
 		{
 		  for (local_decls = BLOCK_VARS (block);
 		       local_decls;
-		       local_decls = TREE_CHAIN (local_decls))
+		       local_decls = DECL_CHAIN (local_decls))
 		    if (TREE_ADDRESSABLE (local_decls))
 		      {
 			any_addressable_vars = 1;
@@ -3463,7 +3463,7 @@ expand_omp_taskreg (struct omp_region *region)
       /* The gimplifier could record temporaries in parallel/task block
 	 rather than in containing function's local_decls chain,
 	 which would mean cgraph missed finalizing them.  Do it now.  */
-      for (t = BLOCK_VARS (block); t; t = TREE_CHAIN (t))
+      for (t = BLOCK_VARS (block); t; t = DECL_CHAIN (t))
 	if (TREE_CODE (t) == VAR_DECL
 	    && TREE_STATIC (t)
 	    && !DECL_EXTERNAL (t))
@@ -3473,7 +3473,7 @@ expand_omp_taskreg (struct omp_region *region)
       TREE_USED (block) = 1;
 
       /* Reset DECL_CONTEXT on function arguments.  */
-      for (t = DECL_ARGUMENTS (child_fn); t; t = TREE_CHAIN (t))
+      for (t = DECL_ARGUMENTS (child_fn); t; t = DECL_CHAIN (t))
 	DECL_CONTEXT (t) = child_fn;
 
       /* Split ENTRY_BB at GIMPLE_OMP_PARALLEL or GIMPLE_OMP_TASK,
@@ -6221,7 +6221,7 @@ create_task_copyfn (gimple task_stmt, omp_context *ctx)
   DECL_SAVED_TREE (child_fn) = alloc_stmt_list ();
 
   /* Reset DECL_CONTEXT on function arguments.  */
-  for (t = DECL_ARGUMENTS (child_fn); t; t = TREE_CHAIN (t))
+  for (t = DECL_ARGUMENTS (child_fn); t; t = DECL_CHAIN (t))
     DECL_CONTEXT (t) = child_fn;
 
   /* Populate the function.  */
@@ -6237,13 +6237,13 @@ create_task_copyfn (gimple task_stmt, omp_context *ctx)
   /* Remap src and dst argument types if needed.  */
   record_type = ctx->record_type;
   srecord_type = ctx->srecord_type;
-  for (f = TYPE_FIELDS (record_type); f ; f = TREE_CHAIN (f))
+  for (f = TYPE_FIELDS (record_type); f ; f = DECL_CHAIN (f))
     if (variably_modified_type_p (TREE_TYPE (f), ctx->cb.src_fn))
       {
 	record_needs_remap = true;
 	break;
       }
-  for (f = TYPE_FIELDS (srecord_type); f ; f = TREE_CHAIN (f))
+  for (f = TYPE_FIELDS (srecord_type); f ; f = DECL_CHAIN (f))
     if (variably_modified_type_p (TREE_TYPE (f), ctx->cb.src_fn))
       {
 	srecord_needs_remap = true;
@@ -6276,7 +6276,7 @@ create_task_copyfn (gimple task_stmt, omp_context *ctx)
 
   arg = DECL_ARGUMENTS (child_fn);
   TREE_TYPE (arg) = build_pointer_type (record_type);
-  sarg = TREE_CHAIN (arg);
+  sarg = DECL_CHAIN (arg);
   TREE_TYPE (sarg) = build_pointer_type (srecord_type);
 
   /* First pass: initialize temporaries used in record_type and srecord_type
diff --git a/gcc/stor-layout.c b/gcc/stor-layout.c
index 8d3c7526737e7aa7f23a43d5f011cd0b786e8ffb..d4b266282c7a3f3a379d3a52ab1979e3f6e2de89 100644
--- a/gcc/stor-layout.c
+++ b/gcc/stor-layout.c
@@ -313,7 +313,7 @@ self_referential_size (tree size)
   sprintf (buf, "SZ"HOST_WIDE_INT_PRINT_UNSIGNED, fnno++);
   fnname = get_file_function_name (buf);
   fndecl = build_decl (input_location, FUNCTION_DECL, fnname, fntype);
-  for (t = param_decl_list; t; t = TREE_CHAIN (t))
+  for (t = param_decl_list; t; t = DECL_CHAIN (t))
     DECL_CONTEXT (t) = fndecl;
   DECL_ARGUMENTS (fndecl) = param_decl_list;
   DECL_RESULT (fndecl)
@@ -1429,8 +1429,8 @@ place_field (record_layout_info rli, tree field)
 
       /* If we ended a bitfield before the full length of the type then
 	 pad the struct out to the full length of the last type.  */
-      if ((TREE_CHAIN (field) == NULL
-	   || TREE_CODE (TREE_CHAIN (field)) != FIELD_DECL)
+      if ((DECL_CHAIN (field) == NULL
+	   || TREE_CODE (DECL_CHAIN (field)) != FIELD_DECL)
 	  && DECL_BIT_FIELD_TYPE (field)
 	  && !integer_zerop (DECL_SIZE (field)))
 	rli->bitpos = size_binop (PLUS_EXPR, rli->bitpos,
@@ -1551,7 +1551,7 @@ compute_record_mode (tree type)
   /* A record which has any BLKmode members must itself be
      BLKmode; it can't go in a register.  Unless the member is
      BLKmode only because it isn't aligned.  */
-  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
     {
       if (TREE_CODE (field) != FIELD_DECL)
 	continue;
@@ -1746,8 +1746,8 @@ finish_builtin_struct (tree type, const char *name, tree fields,
   for (tail = NULL_TREE; fields; tail = fields, fields = next)
     {
       DECL_FIELD_CONTEXT (fields) = type;
-      next = TREE_CHAIN (fields);
-      TREE_CHAIN (fields) = tail;
+      next = DECL_CHAIN (fields);
+      DECL_CHAIN (fields) = tail;
     }
   TYPE_FIELDS (type) = tail;
 
@@ -2061,7 +2061,7 @@ layout_type (tree type)
 	  TYPE_FIELDS (type) = nreverse (TYPE_FIELDS (type));
 
 	/* Place all the fields.  */
-	for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+	for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	  place_field (rli, field);
 
 	if (TREE_CODE (type) == QUAL_UNION_TYPE)
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 896929301bcb6b62cdea757af0fb7724e732d30d..d132920533370130b0dadb522df12f952b8c2d6e 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,8 @@
+2010-07-15  Nathan Froyd  <froydnj@codesourcery.com>
+
+	* g++.dg/plugin/attribute_plugin.c: Carefully replace TREE_CHAIN
+	with DECL_CHAIN.
+
 2010-07-15  Janus Weil  <janus@gcc.gnu.org>
 
 	PR fortran/44936
diff --git a/gcc/testsuite/g++.dg/plugin/attribute_plugin.c b/gcc/testsuite/g++.dg/plugin/attribute_plugin.c
index 6327095f7cddc5a6642ab2779cf175febbd51f0a..5bbb29c0697dc1fa4b5921080de954f720cc40a4 100644
--- a/gcc/testsuite/g++.dg/plugin/attribute_plugin.c
+++ b/gcc/testsuite/g++.dg/plugin/attribute_plugin.c
@@ -43,7 +43,7 @@ handle_pre_generic (void *event_data, void *data)
 {
   tree fndecl = (tree) event_data;
   tree arg;
-  for (arg = DECL_ARGUMENTS(fndecl); arg; arg = TREE_CHAIN (arg)) {
+  for (arg = DECL_ARGUMENTS(fndecl); arg; arg = DECL_CHAIN (arg)) {
       tree attr;
       for (attr = DECL_ATTRIBUTES (arg); attr; attr = TREE_CHAIN (attr)) {
           tree attrname = TREE_PURPOSE (attr);
diff --git a/gcc/tree-cfg.c b/gcc/tree-cfg.c
index b4923c1b49478b2b187ceeaa0d1a6b9c07217cc5..413d7a9fb9780f71cd84b368e3e9a6e9e9bbbd0e 100644
--- a/gcc/tree-cfg.c
+++ b/gcc/tree-cfg.c
@@ -6072,7 +6072,7 @@ replace_block_vars_by_duplicates (tree block, struct pointer_map_t *vars_map,
 {
   tree *tp, t;
 
-  for (tp = &BLOCK_VARS (block); *tp; tp = &TREE_CHAIN (*tp))
+  for (tp = &BLOCK_VARS (block); *tp; tp = &DECL_CHAIN (*tp))
     {
       t = *tp;
       if (TREE_CODE (t) != VAR_DECL && TREE_CODE (t) != CONST_DECL)
@@ -6085,7 +6085,7 @@ replace_block_vars_by_duplicates (tree block, struct pointer_map_t *vars_map,
 	      SET_DECL_VALUE_EXPR (t, DECL_VALUE_EXPR (*tp));
 	      DECL_HAS_VALUE_EXPR_P (t) = 1;
 	    }
-	  TREE_CHAIN (t) = TREE_CHAIN (*tp);
+	  DECL_CHAIN (t) = DECL_CHAIN (*tp);
 	  *tp = t;
 	}
     }
@@ -6337,9 +6337,9 @@ dump_function_to_file (tree fn, FILE *file, int flags)
       print_generic_expr (file, arg, dump_flags);
       if (flags & TDF_VERBOSE)
 	print_node (file, "", arg, 4);
-      if (TREE_CHAIN (arg))
+      if (DECL_CHAIN (arg))
 	fprintf (file, ", ");
-      arg = TREE_CHAIN (arg);
+      arg = DECL_CHAIN (arg);
     }
   fprintf (file, ")\n");
 
diff --git a/gcc/tree-complex.c b/gcc/tree-complex.c
index 77b5c6a85fd4d43665dc324e56a986a6fb40937e..49165713725ba2d17286d7f5dec1e386b23d2878 100644
--- a/gcc/tree-complex.c
+++ b/gcc/tree-complex.c
@@ -174,7 +174,7 @@ init_parameter_lattice_values (void)
 {
   tree parm, ssa_name;
 
-  for (parm = DECL_ARGUMENTS (cfun->decl); parm ; parm = TREE_CHAIN (parm))
+  for (parm = DECL_ARGUMENTS (cfun->decl); parm ; parm = DECL_CHAIN (parm))
     if (is_complex_reg (parm)
 	&& var_ann (parm) != NULL
 	&& (ssa_name = gimple_default_def (cfun, parm)) != NULL_TREE)
@@ -680,7 +680,7 @@ update_parameter_components (void)
   edge entry_edge = single_succ_edge (ENTRY_BLOCK_PTR);
   tree parm;
 
-  for (parm = DECL_ARGUMENTS (cfun->decl); parm ; parm = TREE_CHAIN (parm))
+  for (parm = DECL_ARGUMENTS (cfun->decl); parm ; parm = DECL_CHAIN (parm))
     {
       tree type = TREE_TYPE (parm);
       tree ssa_name, r, i;
diff --git a/gcc/tree-dfa.c b/gcc/tree-dfa.c
index 467a6781d7c6d99ccd7bcc4eaae651701c76b56b..37e15bf7ee23f5452373911c9203c48e919a07f3 100644
--- a/gcc/tree-dfa.c
+++ b/gcc/tree-dfa.c
@@ -770,9 +770,9 @@ get_ref_base_and_extent (tree exp, HOST_WIDE_INT *poffset,
 		    && maxsize != -1)
 		  {
 		    tree stype = TREE_TYPE (TREE_OPERAND (exp, 0));
-		    tree next = TREE_CHAIN (field);
+		    tree next = DECL_CHAIN (field);
 		    while (next && TREE_CODE (next) != FIELD_DECL)
-		      next = TREE_CHAIN (next);
+		      next = DECL_CHAIN (next);
 		    if (!next
 			|| TREE_CODE (stype) != RECORD_TYPE)
 		      {
diff --git a/gcc/tree-dump.c b/gcc/tree-dump.c
index fcbace23683ce7ca4e99d2a39a64006752088912..75fb7f72441913f6ae7d75e687f141fd7c94259a 100644
--- a/gcc/tree-dump.c
+++ b/gcc/tree-dump.c
@@ -370,8 +370,8 @@ dequeue_and_dump (dump_info_p di)
       if (CODE_CONTAINS_STRUCT (TREE_CODE (t), TS_DECL_COMMON)
 	  && DECL_ARTIFICIAL (t))
 	dump_string_field (di, "note", "artificial");
-      if (TREE_CHAIN (t) && !dump_flag (di, TDF_SLIM, NULL))
-	dump_child ("chan", TREE_CHAIN (t));
+      if (DECL_CHAIN (t) && !dump_flag (di, TDF_SLIM, NULL))
+	dump_child ("chain", DECL_CHAIN (t));
     }
   else if (code_class == tcc_type)
     {
diff --git a/gcc/tree-inline.c b/gcc/tree-inline.c
index 4298958fb51bbbcc0de7aa284a35f58dc86233da..5b429eb5485f85428a7f2b4d8cc56e9834611d33 100644
--- a/gcc/tree-inline.c
+++ b/gcc/tree-inline.c
@@ -422,11 +422,11 @@ remap_type_1 (tree type, copy_body_data *id)
       {
 	tree f, nf = NULL;
 
-	for (f = TYPE_FIELDS (new_tree); f ; f = TREE_CHAIN (f))
+	for (f = TYPE_FIELDS (new_tree); f ; f = DECL_CHAIN (f))
 	  {
 	    t = remap_decl (f, id);
 	    DECL_CONTEXT (t) = new_tree;
-	    TREE_CHAIN (t) = nf;
+	    DECL_CHAIN (t) = nf;
 	    nf = t;
 	  }
 	TYPE_FIELDS (new_tree) = nreverse (nf);
@@ -537,7 +537,7 @@ remap_decls (tree decls, VEC(tree,gc) **nonlocalized_list, copy_body_data *id)
   tree new_decls = NULL_TREE;
 
   /* Remap its variables.  */
-  for (old_var = decls; old_var; old_var = TREE_CHAIN (old_var))
+  for (old_var = decls; old_var; old_var = DECL_CHAIN (old_var))
     {
       tree new_var;
 
@@ -573,7 +573,7 @@ remap_decls (tree decls, VEC(tree,gc) **nonlocalized_list, copy_body_data *id)
       else
 	{
 	  gcc_assert (DECL_P (new_var));
-	  TREE_CHAIN (new_var) = new_decls;
+	  DECL_CHAIN (new_var) = new_decls;
 	  new_decls = new_var;
  
 	  /* Also copy value-expressions.  */
@@ -1595,7 +1595,7 @@ copy_bb (copy_body_data *id, basic_block bb, int frequency_scale,
 	      size_t nargs = gimple_call_num_args (id->gimple_call);
 	      size_t n;
 
-	      for (p = DECL_ARGUMENTS (id->src_fn); p; p = TREE_CHAIN (p))
+	      for (p = DECL_ARGUMENTS (id->src_fn); p; p = DECL_CHAIN (p))
 		nargs--;
 
 	      /* Create the new array of arguments.  */
@@ -1642,7 +1642,7 @@ copy_bb (copy_body_data *id, basic_block bb, int frequency_scale,
 	      tree count, p;
 	      gimple new_stmt;
 
-	      for (p = DECL_ARGUMENTS (id->src_fn); p; p = TREE_CHAIN (p))
+	      for (p = DECL_ARGUMENTS (id->src_fn); p; p = DECL_CHAIN (p))
 		nargs--;
 
 	      count = build_int_cst (integer_type_node, nargs);
@@ -2553,7 +2553,7 @@ setup_one_parameter (copy_body_data *id, tree p, tree value, tree fn,
     }
 
   /* Declare this new variable.  */
-  TREE_CHAIN (var) = *vars;
+  DECL_CHAIN (var) = *vars;
   *vars = var;
 
   /* Make gimplifier happy about this variable.  */
@@ -2683,7 +2683,7 @@ initialize_inlined_parameters (copy_body_data *id, gimple stmt,
 
   /* Loop through the parameter declarations, replacing each with an
      equivalent VAR_DECL, appropriately initialized.  */
-  for (p = parms, i = 0; p; p = TREE_CHAIN (p), i++)
+  for (p = parms, i = 0; p; p = DECL_CHAIN (p), i++)
     {
       tree val;
       val = i < gimple_call_num_args (stmt) ? gimple_call_arg (stmt, i) : NULL;
@@ -2693,7 +2693,7 @@ initialize_inlined_parameters (copy_body_data *id, gimple stmt,
      in a second loop over all parameters to appropriately remap
      variable sized arrays when the size is specified in a
      parameter following the array.  */
-  for (p = parms, i = 0; p; p = TREE_CHAIN (p), i++)
+  for (p = parms, i = 0; p; p = DECL_CHAIN (p), i++)
     {
       tree *varp = (tree *) pointer_map_contains (id->decl_map, p);
       if (varp
@@ -3505,7 +3505,7 @@ estimate_num_insns (gimple stmt, eni_weights *weights)
 	if (decl && DECL_ARGUMENTS (decl) && !stdarg)
 	  {
 	    tree arg;
-	    for (arg = DECL_ARGUMENTS (decl); arg; arg = TREE_CHAIN (arg))
+	    for (arg = DECL_ARGUMENTS (decl); arg; arg = DECL_CHAIN (arg))
 	      if (!VOID_TYPE_P (TREE_TYPE (arg)))
 	        cost += estimate_move_cost (TREE_TYPE (arg));
 	  }
@@ -4663,7 +4663,7 @@ static void
 declare_inline_vars (tree block, tree vars)
 {
   tree t;
-  for (t = vars; t; t = TREE_CHAIN (t))
+  for (t = vars; t; t = DECL_CHAIN (t))
     {
       DECL_SEEN_IN_BIND_EXPR_P (t) = 1;
       gcc_assert (!TREE_STATIC (t) && !TREE_ASM_WRITTEN (t));
@@ -4812,13 +4812,13 @@ copy_arguments_for_versioning (tree orig_parm, copy_body_data * id,
 
   parg = &new_parm;
 
-  for (arg = orig_parm; arg; arg = TREE_CHAIN (arg), i++)
+  for (arg = orig_parm; arg; arg = DECL_CHAIN (arg), i++)
     if (!args_to_skip || !bitmap_bit_p (args_to_skip, i))
       {
         tree new_tree = remap_decl (arg, id);
         lang_hooks.dup_lang_specific_decl (new_tree);
         *parg = new_tree;
-	parg = &TREE_CHAIN (new_tree);
+	parg = &DECL_CHAIN (new_tree);
       }
     else if (!pointer_map_contains (id->decl_map, arg))
       {
@@ -4830,7 +4830,7 @@ copy_arguments_for_versioning (tree orig_parm, copy_body_data * id,
 	add_referenced_var (var);
 	insert_decl_map (id, arg, var);
         /* Declare this new variable.  */
-        TREE_CHAIN (var) = *vars;
+        DECL_CHAIN (var) = *vars;
         *vars = var;
       }
   return new_parm;
@@ -4843,11 +4843,11 @@ copy_static_chain (tree static_chain, copy_body_data * id)
   tree *chain_copy, *pvar;
 
   chain_copy = &static_chain;
-  for (pvar = chain_copy; *pvar; pvar = &TREE_CHAIN (*pvar))
+  for (pvar = chain_copy; *pvar; pvar = &DECL_CHAIN (*pvar))
     {
       tree new_tree = remap_decl (*pvar, id);
       lang_hooks.dup_lang_specific_decl (new_tree);
-      TREE_CHAIN (new_tree) = TREE_CHAIN (*pvar);
+      DECL_CHAIN (new_tree) = DECL_CHAIN (*pvar);
       *pvar = new_tree;
     }
   return static_chain;
@@ -5081,7 +5081,7 @@ tree_function_versioning (tree old_decl, tree new_decl,
 	      {
 		int i = replace_info->parm_num;
 		tree parm;
-		for (parm = DECL_ARGUMENTS (old_decl); i; parm = TREE_CHAIN (parm))
+		for (parm = DECL_ARGUMENTS (old_decl); i; parm = DECL_CHAIN (parm))
 		  i --;
 		replace_info->old_tree = parm;
 	      }
@@ -5220,7 +5220,7 @@ maybe_inline_call_in_expr (tree exp)
       /* Remap the parameters.  */
       for (param = DECL_ARGUMENTS (fn), arg = first_call_expr_arg (exp, &iter);
 	   param;
-	   param = TREE_CHAIN (param), arg = next_call_expr_arg (&iter))
+	   param = DECL_CHAIN (param), arg = next_call_expr_arg (&iter))
 	*pointer_map_insert (decl_map, param) = arg;
 
       memset (&id, 0, sizeof (id));
diff --git a/gcc/tree-mudflap.c b/gcc/tree-mudflap.c
index e70524543c5db1af466a5dcecf75848fd5761001..b5a3e43f470bb8ffb65cc1305a0566604026f8f8 100644
--- a/gcc/tree-mudflap.c
+++ b/gcc/tree-mudflap.c
@@ -322,7 +322,7 @@ mf_make_mf_cache_struct_type (tree field_type)
   tree struct_type = make_node (RECORD_TYPE);
   DECL_CONTEXT (fieldlo) = struct_type;
   DECL_CONTEXT (fieldhi) = struct_type;
-  TREE_CHAIN (fieldlo) = fieldhi;
+  DECL_CHAIN (fieldlo) = fieldhi;
   TYPE_FIELDS (struct_type) = fieldlo;
   TYPE_NAME (struct_type) = get_identifier ("__mf_cache");
   layout_type (struct_type);
@@ -622,7 +622,7 @@ mf_build_check_statement_for (tree base, tree limit,
 
   u = build3 (COMPONENT_REF, mf_uintptr_type,
               build1 (INDIRECT_REF, mf_cache_struct_type, mf_elem),
-              TREE_CHAIN (TYPE_FIELDS (mf_cache_struct_type)), NULL_TREE);
+              DECL_CHAIN (TYPE_FIELDS (mf_cache_struct_type)), NULL_TREE);
 
   v = mf_limit;
 
@@ -1114,7 +1114,7 @@ mx_register_decls (tree decl, gimple_seq seq, location_t location)
           mf_mark (decl);
         }
 
-      decl = TREE_CHAIN (decl);
+      decl = DECL_CHAIN (decl);
     }
 
   /* Actually, (initially_stmts!=NULL) <=> (finally_stmts!=NULL) */
diff --git a/gcc/tree-nested.c b/gcc/tree-nested.c
index db704b7905578f6b922e48c1a9c7b0abbdf33aa2..81ae38f6f3aca38ab85bb0cb3a8bdb0aa9d9808f 100644
--- a/gcc/tree-nested.c
+++ b/gcc/tree-nested.c
@@ -148,7 +148,7 @@ create_tmp_var_for (struct nesting_info *info, tree type, const char *prefix)
 
   tmp_var = create_tmp_var_raw (type, prefix);
   DECL_CONTEXT (tmp_var) = info->context;
-  TREE_CHAIN (tmp_var) = info->new_local_var_chain;
+  DECL_CHAIN (tmp_var) = info->new_local_var_chain;
   DECL_SEEN_IN_BIND_EXPR_P (tmp_var) = 1;
   if (TREE_CODE (type) == COMPLEX_TYPE
       || TREE_CODE (type) == VECTOR_TYPE)
@@ -198,11 +198,11 @@ insert_field_into_struct (tree type, tree field)
 
   DECL_CONTEXT (field) = type;
 
-  for (p = &TYPE_FIELDS (type); *p ; p = &TREE_CHAIN (*p))
+  for (p = &TYPE_FIELDS (type); *p ; p = &DECL_CHAIN (*p))
     if (DECL_ALIGN (field) >= DECL_ALIGN (*p))
       break;
 
-  TREE_CHAIN (field) = *p;
+  DECL_CHAIN (field) = *p;
   *p = field;
 
   /* Set correct alignment for frame struct type.  */
@@ -698,7 +698,7 @@ check_for_nested_with_variably_modified (tree fndecl, tree orig_fndecl)
 
   for (cgn = cgn->nested; cgn ; cgn = cgn->next_nested)
     {
-      for (arg = DECL_ARGUMENTS (cgn->decl); arg; arg = TREE_CHAIN (arg))
+      for (arg = DECL_ARGUMENTS (cgn->decl); arg; arg = DECL_CHAIN (arg))
 	if (variably_modified_type_p (TREE_TYPE (arg), orig_fndecl))
 	  return true;
 
@@ -875,7 +875,7 @@ get_nonlocal_debug_decl (struct nesting_info *info, tree decl)
   DECL_HAS_VALUE_EXPR_P (new_decl) = 1;
 
   *slot = new_decl;
-  TREE_CHAIN (new_decl) = info->debug_var_chain;
+  DECL_CHAIN (new_decl) = info->debug_var_chain;
   info->debug_var_chain = new_decl;
 
   if (!optimize
@@ -1202,7 +1202,7 @@ note_nonlocal_block_vlas (struct nesting_info *info, tree block)
 {
   tree var;
 
-  for (var = BLOCK_VARS (block); var; var = TREE_CHAIN (var))
+  for (var = BLOCK_VARS (block); var; var = DECL_CHAIN (var))
     if (TREE_CODE (var) == VAR_DECL
 	&& variably_modified_type_p (TREE_TYPE (var), NULL)
 	&& DECL_HAS_VALUE_EXPR_P (var)
@@ -1367,7 +1367,7 @@ get_local_debug_decl (struct nesting_info *info, tree decl, tree field)
   DECL_HAS_VALUE_EXPR_P (new_decl) = 1;
   *slot = new_decl;
 
-  TREE_CHAIN (new_decl) = info->debug_var_chain;
+  DECL_CHAIN (new_decl) = info->debug_var_chain;
   info->debug_var_chain = new_decl;
 
   /* Do not emit debug info twice.  */
@@ -2196,7 +2196,7 @@ remap_vla_decls (tree block, struct nesting_info *root)
        subblock = BLOCK_CHAIN (subblock))
     remap_vla_decls (subblock, root);
 
-  for (var = BLOCK_VARS (block); var; var = TREE_CHAIN (var))
+  for (var = BLOCK_VARS (block); var; var = DECL_CHAIN (var))
     {
       if (TREE_CODE (var) == VAR_DECL
 	  && variably_modified_type_p (TREE_TYPE (var), NULL)
@@ -2217,7 +2217,7 @@ remap_vla_decls (tree block, struct nesting_info *root)
   id.cb.decl_map = pointer_map_create ();
   id.root = root;
 
-  for (; var; var = TREE_CHAIN (var))
+  for (; var; var = DECL_CHAIN (var))
     if (TREE_CODE (var) == VAR_DECL
 	&& variably_modified_type_p (TREE_TYPE (var), NULL)
 	&& DECL_HAS_VALUE_EXPR_P (var))
@@ -2308,11 +2308,11 @@ finalize_nesting_tree_1 (struct nesting_info *root)
 	 expression get substituted in instantiate_virtual_regs().  */
       for (adjust = &root->new_local_var_chain;
 	   *adjust != root->frame_decl;
-	   adjust = &TREE_CHAIN (*adjust))
-	gcc_assert (TREE_CHAIN (*adjust));
-      *adjust = TREE_CHAIN (*adjust);
+	   adjust = &DECL_CHAIN (*adjust))
+	gcc_assert (DECL_CHAIN (*adjust));
+      *adjust = DECL_CHAIN (*adjust);
 
-      TREE_CHAIN (root->frame_decl) = NULL_TREE;
+      DECL_CHAIN (root->frame_decl) = NULL_TREE;
       declare_vars (root->frame_decl,
 		    gimple_seq_first_stmt (gimple_body (context)), true);
     }
@@ -2323,7 +2323,7 @@ finalize_nesting_tree_1 (struct nesting_info *root)
   if (root->any_parm_remapped)
     {
       tree p;
-      for (p = DECL_ARGUMENTS (context); p ; p = TREE_CHAIN (p))
+      for (p = DECL_ARGUMENTS (context); p ; p = DECL_CHAIN (p))
 	{
 	  tree field, x, y;
 
@@ -2428,7 +2428,7 @@ finalize_nesting_tree_1 (struct nesting_info *root)
       remap_vla_decls (DECL_INITIAL (root->context), root);
 
       for (debug_var = root->debug_var_chain; debug_var;
-	   debug_var = TREE_CHAIN (debug_var))
+	   debug_var = DECL_CHAIN (debug_var))
 	if (variably_modified_type_p (TREE_TYPE (debug_var), NULL))
 	  break;
 
@@ -2443,7 +2443,7 @@ finalize_nesting_tree_1 (struct nesting_info *root)
 	  id.cb.decl_map = pointer_map_create ();
 	  id.root = root;
 
-	  for (; debug_var; debug_var = TREE_CHAIN (debug_var))
+	  for (; debug_var; debug_var = DECL_CHAIN (debug_var))
 	    if (variably_modified_type_p (TREE_TYPE (debug_var), NULL))
 	      {
 		tree type = TREE_TYPE (debug_var);
diff --git a/gcc/tree-object-size.c b/gcc/tree-object-size.c
index 8cceb715ba6c0bd164966b3a01e8746b20d769fd..0ea5538640f657450ec8f81ad6d664bde3ea24d2 100644
--- a/gcc/tree-object-size.c
+++ b/gcc/tree-object-size.c
@@ -290,8 +290,8 @@ addr_object_size (struct object_size_info *osi, const_tree ptr,
 			&& TREE_CODE (TREE_TYPE (TREE_OPERAND (v, 0)))
 			   == RECORD_TYPE)
 		      {
-			tree fld_chain = TREE_CHAIN (TREE_OPERAND (v, 1));
-			for (; fld_chain; fld_chain = TREE_CHAIN (fld_chain))
+			tree fld_chain = DECL_CHAIN (TREE_OPERAND (v, 1));
+			for (; fld_chain; fld_chain = DECL_CHAIN (fld_chain))
 			  if (TREE_CODE (fld_chain) == FIELD_DECL)
 			    break;
 
diff --git a/gcc/tree-pretty-print.c b/gcc/tree-pretty-print.c
index 3e83cd70ed33e2b49ffeeccf43b5c7e128bdfa20..4c03fbed332eecde681dabc5f58c6db9335e43de 100644
--- a/gcc/tree-pretty-print.c
+++ b/gcc/tree-pretty-print.c
@@ -1432,7 +1432,7 @@ dump_generic_node (pretty_printer *buffer, tree node, int spc, int flags,
 	    {
 	      pp_newline (buffer);
 
-	      for (op0 = BIND_EXPR_VARS (node); op0; op0 = TREE_CHAIN (op0))
+	      for (op0 = BIND_EXPR_VARS (node); op0; op0 = DECL_CHAIN (op0))
 		{
 		  print_declaration (buffer, op0, spc+2, flags);
 		  pp_newline (buffer);
@@ -2432,7 +2432,7 @@ print_struct_decl (pretty_printer *buffer, const_tree node, int spc, int flags)
 	    print_declaration (buffer, tmp, spc+2, flags);
 	    pp_newline (buffer);
 	  }
-	tmp = TREE_CHAIN (tmp);
+	tmp = DECL_CHAIN (tmp);
       }
   }
   INDENT (spc);
diff --git a/gcc/tree-sra.c b/gcc/tree-sra.c
index 05e3cf800aadad6cdf625f37325394e430c3bcee..e4971d2385b7cfc39baee24a578ce553e62928a7 100644
--- a/gcc/tree-sra.c
+++ b/gcc/tree-sra.c
@@ -634,7 +634,7 @@ type_internals_preclude_sra_p (tree type)
     case RECORD_TYPE:
     case UNION_TYPE:
     case QUAL_UNION_TYPE:
-      for (fld = TYPE_FIELDS (type); fld; fld = TREE_CHAIN (fld))
+      for (fld = TYPE_FIELDS (type); fld; fld = DECL_CHAIN (fld))
 	if (TREE_CODE (fld) == FIELD_DECL)
 	  {
 	    tree ft = TREE_TYPE (fld);
@@ -697,7 +697,7 @@ mark_parm_dereference (tree base, HOST_WIDE_INT dist, gimple stmt)
 
   for (parm = DECL_ARGUMENTS (current_function_decl);
        parm && parm != base;
-       parm = TREE_CHAIN (parm))
+       parm = DECL_CHAIN (parm))
     parm_index++;
 
   gcc_assert (parm_index < func_param_count);
@@ -821,7 +821,7 @@ type_consists_of_records_p (tree type)
   if (TREE_CODE (type) != RECORD_TYPE)
     return false;
 
-  for (fld = TYPE_FIELDS (type); fld; fld = TREE_CHAIN (fld))
+  for (fld = TYPE_FIELDS (type); fld; fld = DECL_CHAIN (fld))
     if (TREE_CODE (fld) == FIELD_DECL)
       {
 	tree ft = TREE_TYPE (fld);
@@ -849,7 +849,7 @@ completely_scalarize_record (tree base, tree decl, HOST_WIDE_INT offset)
 {
   tree fld, decl_type = TREE_TYPE (decl);
 
-  for (fld = TYPE_FIELDS (decl_type); fld; fld = TREE_CHAIN (fld))
+  for (fld = TYPE_FIELDS (decl_type); fld; fld = DECL_CHAIN (fld))
     if (TREE_CODE (fld) == FIELD_DECL)
       {
 	HOST_WIDE_INT pos = offset + int_bit_position (fld);
@@ -1344,7 +1344,7 @@ build_ref_for_offset_1 (tree *res, tree type, HOST_WIDE_INT offset,
 	case UNION_TYPE:
 	case QUAL_UNION_TYPE:
 	case RECORD_TYPE:
-	  for (fld = TYPE_FIELDS (type); fld; fld = TREE_CHAIN (fld))
+	  for (fld = TYPE_FIELDS (type); fld; fld = DECL_CHAIN (fld))
 	    {
 	      HOST_WIDE_INT pos, size;
 	      tree expr, *expr_ptr;
@@ -2862,7 +2862,7 @@ initialize_parameter_reductions (void)
 
   for (parm = DECL_ARGUMENTS (current_function_decl);
        parm;
-       parm = TREE_CHAIN (parm))
+       parm = DECL_CHAIN (parm))
     {
       VEC (access_p, heap) *access_vec;
       struct access *access;
@@ -3101,7 +3101,7 @@ find_param_candidates (void)
 
   for (parm = DECL_ARGUMENTS (current_function_decl);
        parm;
-       parm = TREE_CHAIN (parm))
+       parm = DECL_CHAIN (parm))
     {
       tree type = TREE_TYPE (parm);
 
@@ -3593,7 +3593,7 @@ splice_all_param_accesses (VEC (access_p, heap) **representatives)
 
   for (parm = DECL_ARGUMENTS (current_function_decl);
        parm;
-       parm = TREE_CHAIN (parm))
+       parm = DECL_CHAIN (parm))
     {
       if (is_unused_scalar_param (parm))
 	{
@@ -3678,7 +3678,7 @@ turn_representatives_into_adjustments (VEC (access_p, heap) *representatives,
   parms = ipa_get_vector_of_formal_parms (current_function_decl);
   adjustments = VEC_alloc (ipa_parm_adjustment_t, heap, adjustments_count);
   parm = DECL_ARGUMENTS (current_function_decl);
-  for (i = 0; i < func_param_count; i++, parm = TREE_CHAIN (parm))
+  for (i = 0; i < func_param_count; i++, parm = DECL_CHAIN (parm))
     {
       struct access *repr = VEC_index (access_p, representatives, i);
 
diff --git a/gcc/tree-ssa-live.c b/gcc/tree-ssa-live.c
index fcd277951fb6889cc8dee79cf7e15d53e9ead987..e8194aa45ff9a766015a832b2363664c2eb63f72 100644
--- a/gcc/tree-ssa-live.c
+++ b/gcc/tree-ssa-live.c
@@ -436,7 +436,7 @@ remove_unused_scope_block_p (tree scope)
 
   for (t = &BLOCK_VARS (scope); *t; t = next)
     {
-      next = &TREE_CHAIN (*t);
+      next = &DECL_CHAIN (*t);
 
       /* Debug info of nested function refers to the block of the
 	 function.  We might stil call it even if all statements
@@ -460,7 +460,7 @@ remove_unused_scope_block_p (tree scope)
       /* Remove everything we don't generate debug info for.  */
       else if (DECL_IGNORED_P (*t))
 	{
-	  *t = TREE_CHAIN (*t);
+	  *t = DECL_CHAIN (*t);
 	  next = t;
 	}
 
@@ -503,7 +503,7 @@ remove_unused_scope_block_p (tree scope)
 	;
       else
 	{
-	  *t = TREE_CHAIN (*t);
+	  *t = DECL_CHAIN (*t);
 	  next = t;
 	}
     }
@@ -626,7 +626,7 @@ dump_scope_block (FILE *file, int indent, tree scope, int flags)
 	}
     }
   fprintf (file, " \n");
-  for (var = BLOCK_VARS (scope); var; var = TREE_CHAIN (var))
+  for (var = BLOCK_VARS (scope); var; var = DECL_CHAIN (var))
     {
       bool used = false;
       var_ann_t ann;
diff --git a/gcc/tree-ssa-loop-niter.c b/gcc/tree-ssa-loop-niter.c
index 5eea6b341dc74e1ef214585a2c616396fa74caa5..6ec0575990d31e1561bffe0d1f13b327ee836eb5 100644
--- a/gcc/tree-ssa-loop-niter.c
+++ b/gcc/tree-ssa-loop-niter.c
@@ -2641,7 +2641,7 @@ array_at_struct_end_p (tree ref)
 
 	  /* Unless the field is at the end of the struct, we are done.  */
 	  field = TREE_OPERAND (ref, 1);
-	  if (TREE_CHAIN (field))
+	  if (DECL_CHAIN (field))
 	    return false;
 	}
 
diff --git a/gcc/tree-ssa-math-opts.c b/gcc/tree-ssa-math-opts.c
index 9a8b13f2c4e380cf19966d4d64c694a850b4c69b..fe0b4f405283c91d81e6a70f63c8abb563e641d1 100644
--- a/gcc/tree-ssa-math-opts.c
+++ b/gcc/tree-ssa-math-opts.c
@@ -474,7 +474,7 @@ execute_cse_reciprocals (void)
     gcc_assert (!bb->aux);
 #endif
 
-  for (arg = DECL_ARGUMENTS (cfun->decl); arg; arg = TREE_CHAIN (arg))
+  for (arg = DECL_ARGUMENTS (cfun->decl); arg; arg = DECL_CHAIN (arg))
     if (gimple_default_def (cfun, arg)
 	&& FLOAT_TYPE_P (TREE_TYPE (arg))
 	&& is_gimple_reg (arg))
diff --git a/gcc/tree-ssa-reassoc.c b/gcc/tree-ssa-reassoc.c
index caad908129bb4f260ba4187d6f344c0f3e434c09..6cd3cebfe86559f59bc25d3adc022f326aab8b2e 100644
--- a/gcc/tree-ssa-reassoc.c
+++ b/gcc/tree-ssa-reassoc.c
@@ -2192,7 +2192,7 @@ init_reassoc (void)
   /* Give each argument a distinct rank.   */
   for (param = DECL_ARGUMENTS (current_function_decl);
        param;
-       param = TREE_CHAIN (param))
+       param = DECL_CHAIN (param))
     {
       if (gimple_default_def (cfun, param) != NULL)
 	{
diff --git a/gcc/tree-ssa-sccvn.c b/gcc/tree-ssa-sccvn.c
index 99598038a3d6801fa37b5772a098c5a626df172d..9ce37f705e5cf81bdcbd63aa11f66f0d111a705d 100644
--- a/gcc/tree-ssa-sccvn.c
+++ b/gcc/tree-ssa-sccvn.c
@@ -3474,7 +3474,7 @@ run_scc_vn (void)
 
   for (param = DECL_ARGUMENTS (current_function_decl);
        param;
-       param = TREE_CHAIN (param))
+       param = DECL_CHAIN (param))
     {
       if (gimple_default_def (cfun, param) != NULL)
 	{
diff --git a/gcc/tree-ssa-structalias.c b/gcc/tree-ssa-structalias.c
index 417671c7b394ccb3b8f11d96d894ec1638ec7b50..cf5815f67e5064e12ea8088599499768a967591b 100644
--- a/gcc/tree-ssa-structalias.c
+++ b/gcc/tree-ssa-structalias.c
@@ -4987,7 +4987,7 @@ push_fields_onto_fieldstack (tree type, VEC(fieldoff_s,heap) **fieldstack,
   if (VEC_length (fieldoff_s, *fieldstack) > MAX_FIELDS_FOR_FIELD_SENSITIVE)
     return false;
 
-  for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+  for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
     if (TREE_CODE (field) == FIELD_DECL)
       {
 	bool push = false;
@@ -5065,7 +5065,7 @@ count_num_arguments (tree decl, bool *is_varargs)
 
   /* Capture named arguments for K&R functions.  They do not
      have a prototype and thus no TYPE_ARG_TYPES.  */
-  for (t = DECL_ARGUMENTS (decl); t; t = TREE_CHAIN (t))
+  for (t = DECL_ARGUMENTS (decl); t; t = DECL_CHAIN (t))
     ++num;
 
   /* Check if the function has variadic arguments.  */
@@ -5223,7 +5223,7 @@ create_function_info_for (tree decl, const char *name)
       if (arg)
 	{
 	  insert_vi_for_tree (arg, argvi);
-	  arg = TREE_CHAIN (arg);
+	  arg = DECL_CHAIN (arg);
 	}
     }
 
@@ -5495,7 +5495,7 @@ intra_create_variable_infos (void)
   /* For each incoming pointer argument arg, create the constraint ARG
      = NONLOCAL or a dummy variable if it is a restrict qualified
      passed-by-reference argument.  */
-  for (t = DECL_ARGUMENTS (current_function_decl); t; t = TREE_CHAIN (t))
+  for (t = DECL_ARGUMENTS (current_function_decl); t; t = DECL_CHAIN (t))
     {
       varinfo_t p;
 
diff --git a/gcc/tree-tailcall.c b/gcc/tree-tailcall.c
index 5a6bd23ea427563db6a5a75c14a1aedf456244e5..65eaa40cedb95fc7c4ee85f6bbb212688176d298 100644
--- a/gcc/tree-tailcall.c
+++ b/gcc/tree-tailcall.c
@@ -164,7 +164,7 @@ suitable_for_tail_call_opt_p (void)
      but not in all cases.  See PR15387 and PR19616.  Revisit for 4.1.  */
   for (param = DECL_ARGUMENTS (current_function_decl);
        param;
-       param = TREE_CHAIN (param))
+       param = DECL_CHAIN (param))
     if (TREE_ADDRESSABLE (param))
       return false;
 
@@ -423,7 +423,7 @@ find_tail_calls (basic_block bb, struct tailcall **ret)
 
       for (param = DECL_ARGUMENTS (func), idx = 0;
 	   param && idx < gimple_call_num_args (call);
-	   param = TREE_CHAIN (param), idx ++)
+	   param = DECL_CHAIN (param), idx ++)
 	{
 	  arg = gimple_call_arg (call, idx);
 	  if (param != arg)
@@ -808,7 +808,7 @@ eliminate_tail_call (struct tailcall *t)
   for (param = DECL_ARGUMENTS (current_function_decl),
 	 idx = 0, gsi = gsi_start_phis (first);
        param;
-       param = TREE_CHAIN (param), idx++)
+       param = DECL_CHAIN (param), idx++)
     {
       if (!arg_needs_copy_p (param))
 	continue;
@@ -965,7 +965,7 @@ tree_optimize_tail_calls_1 (bool opt_tailcalls)
 	  /* Copy the args if needed.  */
 	  for (param = DECL_ARGUMENTS (current_function_decl);
 	       param;
-	       param = TREE_CHAIN (param))
+	       param = DECL_CHAIN (param))
 	    if (arg_needs_copy_p (param))
 	      {
 		tree name = gimple_default_def (cfun, param);
diff --git a/gcc/tree-vrp.c b/gcc/tree-vrp.c
index afe69a3b8a147feaa9371648c75e7955f93ac193..fbb549febd52b06ae781fb19a6974c13cfeec19f 100644
--- a/gcc/tree-vrp.c
+++ b/gcc/tree-vrp.c
@@ -337,7 +337,7 @@ nonnull_arg_p (const_tree arg)
   /* Get the position number for ARG in the function signature.  */
   for (arg_num = 1, t = DECL_ARGUMENTS (current_function_decl);
        t;
-       t = TREE_CHAIN (t), arg_num++)
+       t = DECL_CHAIN (t), arg_num++)
     {
       if (t == arg)
 	break;
@@ -5165,9 +5165,9 @@ check_array_ref (location_t location, tree ref, bool ignore_off_by_one)
 
       cref = TREE_OPERAND (ref, 0);
       if (TREE_CODE (TREE_TYPE (TREE_OPERAND (cref, 0))) == RECORD_TYPE)
-	for (next = TREE_CHAIN (TREE_OPERAND (cref, 1));
+	for (next = DECL_CHAIN (TREE_OPERAND (cref, 1));
 	     next && TREE_CODE (next) != FIELD_DECL;
-	     next = TREE_CHAIN (next))
+	     next = DECL_CHAIN (next))
 	  ;
 
       /* If this is the last field in a struct type or a field in a
diff --git a/gcc/tree.c b/gcc/tree.c
index cca171c8c3c4541a9fbf3867127f8806c5fc162d..7f37d45fba28760a76fbe4e13c99c32214dad778 100644
--- a/gcc/tree.c
+++ b/gcc/tree.c
@@ -1991,7 +1991,7 @@ chain_member (const_tree elem, const_tree chain)
     {
       if (elem == chain)
 	return 1;
-      chain = TREE_CHAIN (chain);
+      chain = DECL_CHAIN (chain);
     }
 
   return 0;
@@ -2032,7 +2032,7 @@ fields_length (const_tree type)
   tree t = TYPE_FIELDS (type);
   int count = 0;
 
-  for (; t; t = TREE_CHAIN (t))
+  for (; t; t = DECL_CHAIN (t))
     if (TREE_CODE (t) == FIELD_DECL)
       ++count;
 
@@ -2860,7 +2860,7 @@ type_contains_placeholder_1 (const_tree type)
       {
 	tree field;
 
-	for (field = TYPE_FIELDS (type); field; field = TREE_CHAIN (field))
+	for (field = TYPE_FIELDS (type); field; field = DECL_CHAIN (field))
 	  if (TREE_CODE (field) == FIELD_DECL
 	      && (CONTAINS_PLACEHOLDER_P (DECL_FIELD_OFFSET (field))
 		  || (TREE_CODE (type) == QUAL_UNION_TYPE
@@ -8169,7 +8169,7 @@ variably_modified_type_p (tree type, tree fn)
 	 definition we normally use, since that would produce infinite
 	 recursion via pointers.  */
       /* This is variably modified if some field's type is.  */
-      for (t = TYPE_FIELDS (type); t; t = TREE_CHAIN (t))
+      for (t = TYPE_FIELDS (type); t; t = DECL_CHAIN (t))
 	if (TREE_CODE (t) == FIELD_DECL)
 	  {
 	    RETURN_TRUE_IF_VAR (DECL_FIELD_OFFSET (t));
@@ -10257,7 +10257,7 @@ walk_tree_1 (tree *tp, walk_tree_fn func, void *data,
     case BIND_EXPR:
       {
 	tree decl;
-	for (decl = BIND_EXPR_VARS (*tp); decl; decl = TREE_CHAIN (decl))
+	for (decl = BIND_EXPR_VARS (*tp); decl; decl = DECL_CHAIN (decl))
 	  {
 	    /* Walk the DECL_INITIAL and DECL_SIZE.  We don't want to walk
 	       into declarations that are just mentioned, rather than
@@ -10372,7 +10372,7 @@ walk_tree_1 (tree *tp, walk_tree_fn func, void *data,
 	      tree field;
 
 	      for (field = TYPE_FIELDS (*type_p); field;
-		   field = TREE_CHAIN (field))
+		   field = DECL_CHAIN (field))
 		{
 		  /* We'd like to look at the type of the field, but we can
 		     easily get infinite recursion.  So assume it's pointed
@@ -10888,7 +10888,7 @@ get_binfo_at_offset (tree binfo, HOST_WIDE_INT offset, tree expected_type)
       if (TREE_CODE (type) != RECORD_TYPE)
 	return NULL_TREE;
 
-      for (fld = TYPE_FIELDS (type); fld; fld = TREE_CHAIN (fld))
+      for (fld = TYPE_FIELDS (type); fld; fld = DECL_CHAIN (fld))
 	{
 	  if (TREE_CODE (fld) != FIELD_DECL)
 	    continue;
diff --git a/gcc/tree.h b/gcc/tree.h
index be70d2bb85098854edfecb817cbdae91959f2ef9..daf6c2bf4c4b86a553e7e20b7e081e4391c71696 100644
--- a/gcc/tree.h
+++ b/gcc/tree.h
@@ -2494,6 +2494,7 @@ enum symbol_visibility
 
 struct function;
 
+#define DECL_CHAIN(NODE) (TREE_CHAIN (DECL_MINIMAL_CHECK (NODE)))
 
 /* This is the name of the object as written by the user.
    It is an IDENTIFIER_NODE.  */
diff --git a/gcc/var-tracking.c b/gcc/var-tracking.c
index 33061c5a55d74daccead399b1d1305a3df62be74..f62b41f6e20d06e6511d1434b7815a3a89f92a42 100644
--- a/gcc/var-tracking.c
+++ b/gcc/var-tracking.c
@@ -8002,7 +8002,7 @@ vt_add_function_parameters (void)
   tree parm;
 
   for (parm = DECL_ARGUMENTS (current_function_decl);
-       parm; parm = TREE_CHAIN (parm))
+       parm; parm = DECL_CHAIN (parm))
     {
       rtx decl_rtl = DECL_RTL_IF_SET (parm);
       rtx incoming = DECL_INCOMING_RTL (parm);
diff --git a/gcc/varasm.c b/gcc/varasm.c
index 55218c4a96e202854ea5345b47c78639dea0c66c..00b4af93a9f50f4a8a84944dc929341e691a9560 100644
--- a/gcc/varasm.c
+++ b/gcc/varasm.c
@@ -246,7 +246,7 @@ default_emutls_var_fields (tree type, tree *name ATTRIBUTE_UNUSED)
 		      FIELD_DECL, get_identifier ("__offset"),
 		      ptr_type_node);
   DECL_CONTEXT (field) = type;
-  TREE_CHAIN (field) = next_field;
+  DECL_CHAIN (field) = next_field;
   next_field = field;
 
   word_type_node = lang_hooks.types.type_for_mode (word_mode, 1);
@@ -254,13 +254,13 @@ default_emutls_var_fields (tree type, tree *name ATTRIBUTE_UNUSED)
 		      FIELD_DECL, get_identifier ("__align"),
 		      word_type_node);
   DECL_CONTEXT (field) = type;
-  TREE_CHAIN (field) = next_field;
+  DECL_CHAIN (field) = next_field;
   next_field = field;
 
   field = build_decl (UNKNOWN_LOCATION,
 		      FIELD_DECL, get_identifier ("__size"), word_type_node);
   DECL_CONTEXT (field) = type;
-  TREE_CHAIN (field) = next_field;
+  DECL_CHAIN (field) = next_field;
 
   return field;
 }
@@ -2114,18 +2114,18 @@ default_emutls_var_init (tree to, tree decl, tree proxy)
   elt->value = fold_convert (TREE_TYPE (field), DECL_SIZE_UNIT (decl));
 
   elt = VEC_quick_push (constructor_elt, v, NULL);
-  field = TREE_CHAIN (field);
+  field = DECL_CHAIN (field);
   elt->index = field;
   elt->value = build_int_cst (TREE_TYPE (field),
 			      DECL_ALIGN_UNIT (decl));
 
   elt = VEC_quick_push (constructor_elt, v, NULL);
-  field = TREE_CHAIN (field);
+  field = DECL_CHAIN (field);
   elt->index = field;
   elt->value = null_pointer_node;
 
   elt = VEC_quick_push (constructor_elt, v, NULL);
-  field = TREE_CHAIN (field);
+  field = DECL_CHAIN (field);
   elt->index = field;
   elt->value = proxy;
 
@@ -2323,7 +2323,7 @@ contains_pointers_p (tree type)
       {
 	tree fields;
 	/* For a type that has fields, see if the fields have pointers.  */
-	for (fields = TYPE_FIELDS (type); fields; fields = TREE_CHAIN (fields))
+	for (fields = TYPE_FIELDS (type); fields; fields = DECL_CHAIN (fields))
 	  if (TREE_CODE (fields) == FIELD_DECL
 	      && contains_pointers_p (TREE_TYPE (fields)))
 	    return 1;
@@ -5038,7 +5038,7 @@ output_constructor_regular_field (oc_local_state *local)
 	  fieldsize = array_size_for_constructor (local->val);
 	  /* Given a non-empty initialization, this field had
 	     better be last.  */
-	  gcc_assert (!fieldsize || !TREE_CHAIN (local->field));
+	  gcc_assert (!fieldsize || !DECL_CHAIN (local->field));
 	}
       else if (DECL_SIZE_UNIT (local->field))
 	{
@@ -5303,7 +5303,7 @@ output_constructor (tree exp, unsigned HOST_WIDE_INT size,
 
   for (cnt = 0;
        VEC_iterate (constructor_elt, CONSTRUCTOR_ELTS (exp), cnt, ce);
-       cnt++, local.field = local.field ? TREE_CHAIN (local.field) : 0)
+       cnt++, local.field = local.field ? DECL_CHAIN (local.field) : 0)
     {
       local.val = ce->value;
       local.index = NULL_TREE;