diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 935e4bfd78340eb84b407e1386c233a5c49f8f74..5d432ceabc3cff717244d358e788e09a35a0bebf 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,737 @@
+2006-12-05  Aldy Hernandez  <aldyh@redhat.com>
+
+	Merge from gimple-tuples-branch.
+
+	2006-12-04  Aldy Hernandez  <aldyh@redhat.com>
+
+        * config/s390/s390.c (s390_va_start): Replace MODIFY_EXPR with
+        GIMPLE_MODIFY_STMT.
+        (s390_gimplify_va_arg): Same.
+        * config/sparc/sparc.c (sparc_gimplify_va_arg): Same.
+        * config/sh/sh.c (sh_va_start): Same.
+        (sh_gimplify_va_arg_expr): Same.
+        * config/xtensa/xtensa.c (xtensa_va_start): Same.
+        (xtensa_gimplify_va_arg_expr): Same.
+        * config/ia64/ia64.c (ia64_gimplify_va_arg): Same.
+        * config/pa/pa.c (hppa_gimplify_va_arg_expr): Same.
+        * config/mips/mips.c (mips_va_start): Same.
+        (mips_gimplify_va_arg_expr): Same.
+
+	2006-12-04  Aldy Hernandez  <aldyh@redhat.com>
+
+        * Merge from mainline at revision 119445.
+
+	2006-12-04  Aldy Hernandez  <aldyh@redhat.com>
+
+        * config/spu/spu.c (spu_va_start): Change MODIFY_EXPR to
+        GIMPLE_MODIFY_STMT.
+        (spu_gimplify_va_arg_expr): Same.
+
+	2006-12-04  Aldy Hernandez  <aldyh@redhat.com>
+
+        * config/stormy16/stormy16.c (xstormy16_expand_builtin_va_start): 
+        Change uses of MODIFY_EXPR to GIMPLE_MODIFY_STMT.
+        (xstormy16_expand_builtin_va_arg): Same.
+
+	2006-12-04  Aldy Hernandez  <aldyh@redhat.com>
+
+        * config/frv/frv.c (frv_expand_builtin_va_start): Change MODIFY_EXPR
+        to GIMPLE_MODIFY_STMT.
+
+	2006-12-04  Aldy Hernandez  <aldyh@redhat.com>
+
+        * config/alpha/alpha.c (va_list_skip_additions): Change all
+	occurrences of MODIFY_EXPR to GIMPLE_MODIFY_STMT.
+        (alpha_va_start): Same.
+        (alpha_gimplify_va_arg_1): Same.
+        (alpha_gimplify_va_arg): Same.
+
+	2006-12-01  Aldy Hernandez  <aldyh@redhat.com>
+
+	* gimplify.c (gimplify_modify_expr): Remove FIXME comment.
+
+	2006-12-01  Aldy Hernandez  <aldyh@redhat.com>
+
+        * tree-ssa-loop-im.c: Rename all PROTECTED_TREE_OPERAND to
+        GENERIC_TREE_OPERAND, and all PROTECTED_TREE_TYPE to
+        GENERIC_TREE_TYPE.
+        * tree-complex.c: Same.
+        * tree-pretty-print.c: Same.
+        * tree.c: Same.
+        * tree.h: Same.
+        * builtins.c: Same.
+        * fold-const.c: Same.
+        * tree-ssa-dom.c: Same.
+        * tree-ssa-propagate.c: Same.
+        * tree-ssa-alias.c: Same.
+        * gimple-low.c: Same.
+        * dwarf2out.c: Same.
+        * c-pretty-print.c: Same.
+        * gimplify.c: Same.
+        * tree-inline.c: Same.
+        * tree-outof-ssa.c: Same.
+        * tree-ssa-structalias.c: Same.
+        * tree-ssa-reassoc.c: Same.
+        * stmt.c: Same.
+
+	2006-11-16  Aldy Hernandez  <aldyh@redhat.com>
+
+        * tree.c (build2_stat): Fix comment.
+
+	2006-11-13  Aldy Hernandez  <aldyh@redhat.com>
+
+        * tree-ssa-propagate.c (get_rhs): Use GIMPLE_MODIFY_STMT and
+        TREE_OPERAND when appropriate.
+
+	2006-11-04  Aldy Hernandez  <aldyh@redhat.com>
+
+        * java/java-tree.h (lang_tree_node): Handle gimple tuples.
+        (EXPR_WFL_EMIT_LINE_NOTE): Look inside base.
+        (EXPR_WFL_LINECOL): Use EXPR_LOCUS macro instead of exp.locus.
+        * java/java-gimplify.c (java_gimplify_expr): Comment on why we do
+        not handle GIMPLE_MODIFY_STMT in the switch statement.
+        (java_gimplify_modify_expr): Call build2 with GIMPLE_MODIFY_STMT.
+        (java_gimplify_new_array_init): Same.
+
+	2006-11-03  Aldy Hernandez  <aldyh@redhat.com>
+
+        * gimplify.c (gimplify_omp_for): Allow gimple statements.
+        * tree-outof-ssa.c (check_replaceable): Use PROTECTED_TREE_OPERAND.
+        * fold-const.c (fold_binary): Allow gimple statements.
+        (fold): Same.
+        * fortran/trans-array.c (gfc_conv_descriptor_data_set_internal):
+        Rename from gfc_conv_descriptor_data_set.
+        Call gfc_add_modify instead of gfc_add_modify_expr.
+        * fortran/trans-array.h (gfc_conv_descriptor_data_set_internal):
+        Rename from gfc_conv_descriptor_data_set.
+        (gfc_conv_descriptor_data_set): New macro.
+        (gfc_conv_descriptor_data_set_tuples): New macros.
+        * fortran/trans-openmp.c (gfc_omp_clause_default_ctor): Call
+        gfc_conv_descriptor_data_set_tuples.
+        * fortran/trans.c (gfc_add_modify): Rename from gfc_add_modify_expr.
+        Generate GIMPLE_MODIFY_STMT when appropriate.
+        * fortran/trans.h (gfc_add_modify): Rename from gfc_add_modify_expr.
+        (gfc_add_modify_expr): New macro.
+        (gfc_add_modify_stmt): New macro.
+        * fortran/f95-lang.c (lang_tree_node): Handle gimple statements.
+
+	2006-11-02  Aldy Hernandez  <aldyh@redhat.com>
+
+	* ada/ada-tree.h (lang_tree_node): Handle gimple tuples.
+	* ada/trans.c (gnat_gimplify_expr): Replace MODIFY_EXPR with
+	GIMPLE_MODIFY_STMT.
+
+	2006-11-01  Aldy Hernandez  <aldyh@redhat.com>
+
+	* Merge from mainline at revision 118200.
+
+	2006-10-09  Aldy Hernandez  <aldyh@redhat.com>
+
+	* tree-inline.c (copy_bb): Check for GIMPLE_MODIFY_STMT, and adjust
+	accordingly.
+
+	2006-10-09  Aldy Hernandez  <aldyh@redhat.com>
+
+        * tree.h (TREE_CHAIN, TREE_TYPE): Add versions for non GCC or not
+	enable checking.
+        Also, add __extension__ to GCC versions.
+        * tree-mudflap.c (mf_xform_derefs_1): Add parentheses around TREE_TYPE.
+        * tree-inline.c (copy_tree_r): Initialize chain to assuage the warning
+	patrol.
+
+	2006-10-05  Aldy Hernandez  <aldyh@redhat.com>
+
+	* tree-complex.c (expand_complex_libcall): Adjust for
+	GIMPLE_MODIFY_STMT.
+	(expand_complex_comparison): Same.
+	* tree-pretty-print.c (dump_generic_node): Is_expr should include
+	GIMPLE_STMT_P statements.
+	* value-prof.c (tree_divmod_fixed_value_transform): Adjust for
+	GIMPLE_MODIFY_STMT.
+	(tree_mod_pow2_value_transform): Same.
+	(tree_mod_subtract_transform): Same.
+	* tree.c (build2_stat): Check for gimplified function in cfun.
+	* tree.h (DECL_GIMPLIFIED): Delete.
+	(struct tree_function_decl): Remove gimplified_flag.
+	* omp-low.c (lower_omp_for): Adjust for GIMPLE_MODIFY_STMT.
+	* cp/cp-gimplify.c (cp_gimplify_expr): Adjust for GIMPLE_MODIFY_STMT.
+	(cxx_omp_clause_apply_fn): Adjust for GIMPLE_MODIFY_STMT.
+	(cxx_omp_clause_copy_ctor): Same.
+	(cxx_omp_clause_assign_op): Same.
+	* c-pretty-print.c (pp_c_conditional_expression): Same.
+	(pp_c_expression): Same.
+	* langhooks.c (lhd_omp_predetermined_sharing): Same.
+	* function.h (struct function): Add gimplified field.
+	* tree-if-conv.c (add_to_dst_predicate_list): Adjust for
+	GIMPLE_MODIFY_STMT.
+	(find_phi_replacement_condition): Same.
+	* gimplify.c (gimplify_modify_expr_to_memcpy): Same.
+	(gimplify_modify_expr_to_memset): Same.
+	(gimplify_init_ctor_eval_range): Same.
+	(gimplify_modify_expr_complex_part): Same.
+	(tree_to_gimple_tuple): Same.
+	(gimplify_modify_expr): Same.
+	(gimple_push_cleanup): Same.
+	(gimplify_omp_for): Same.
+	(gimplify_omp_atomic_pipeline): Same.
+	(gimplify_omp_atomic_mutex): Same.
+	(gimplify_expr): Same.
+	(gimplify_one_sizepos): Same.
+	(gimplify_function_tree): Same.
+	* tree-vect-patterns.c (vect_recog_dot_prod_pattern): Same.
+	(vect_recog_widen_sum_pattern): Same.
+	* tree-vect-transform.c (get_initial_def_for_reduction): Same.
+	(vect_create_epilog_for_reduction): Same.
+	(vectorizable_reduction): Same.
+
+	2006-09-28  Aldy Hernandez  <aldyh@redhat.com>
+
+        * tree-ssa-math-opts.c (replace_reciprocal): Use GIMPLE_STMT_OPERAND.
+        * tree-if-conv.c (if_convertible_gimple_modify_stmt_p): Same.
+        (ifc_temp_var): Same.
+        * tree-vect-analyze.c (vect_determine_vectorization_factor): Check
+	for gimple statements.
+        (vect_analyze_operations): Same.
+        (exist_non_indexing_operands_for_use_p): Use GIMPLE_STMT_OPERAND.
+        * gimplify.c (gimplify_return_expr): Handle gimple statements.
+        * lambda-code.c (can_put_in_inner_loop): Same.
+        (can_put_after_inner_loop): Same.
+        * tree-vect-transform.c (vect_create_addr_base_for_vector_ref): Same.
+        (vect_create_data_ref_ptr): Same.
+        (vect_init_vector): Same.
+        (vect_get_vec_def_for_operand): Same.
+        (vect_create_epilog_for_reduction): Same.
+        (vectorizable_reduction): Same.
+        (vectorizable_assignment): Same.
+        (vectorizable_operation): Same.
+        (vectorizable_load): Same.
+        (vectorizable_condition): Same.
+        * config/rs6000/rs6000.c (rs6000_va_start): Do not create MODIFY_EXPRs.
+        (rs6000_gimplify_va_arg): Same.
+
+	2006-09-25  Aldy Hernandez  <aldyh@redhat.com>
+
+        * tree-vrp.c (simplify_div_or_mod_using_ranges): Use
+        GIMPLE_STMT_OPERAND.
+        (simplify_abs_using_ranges): Same.
+        * tree-complex.c (expand_complex_operations_1): Use
+        PROTECTED_TREE_OPERAND.
+        * tree-ssa-loop-niter.c (simplify_replace_tree): Check for gimple
+        stmt.
+        (get_val_for): Use GIMPLE_STMT_OPERAND.
+        * tree-tailcall.c (adjust_accumulator_values): Same.
+        (adjust_return_value): Same.
+        * tree.c (walk_tree): Use IS_GIMPLE_STMT_CODE_CLASS on default
+        case.  Remove special case for tcc_gimple_stmt.
+        * tree.h (CAN_HAVE_LOCATION_P): New.
+        * tree-ssa-loop-ivopts.c (expr_invariant_in_loop_p): Check for
+        GIMPLE_STMT_P.
+        * tree-stdarg.c (va_list_counter_bump): Use GIMPLE_STMT_OPERAND.
+        * tree-ssa-dom.c (propagate_rhs_into_lhs): Same.
+        * tree-nrv.c (execute_return_slot_opt): Same.
+        * tree-ssa-alias.c (count_uses_and_derefs): Check for GIMPLE_STMT_P.
+        * tree-vn.c (set_value_handle): Same.
+        (get_value_handle): Same.
+        * c-decl.c (add_stmt): Use CAN_HAVE_LOCATION_P.
+        * tree-vectorizer.c (find_loop_location): Same.
+        * c-typeck.c (c_process_expr_stmt): Same.
+        (c_finish_stmt_expr): Same.
+        * gimplify.c (should_carry_locus_p): Same.
+        (tree_to_gimple_tuple): Delete definition and use of unecessary
+        variable save_tree_block.
+        * tree-ssa-pre.c (phi_translate): Check for GIMPLE_STMT_P.
+        (create_expression_by_pieces): Use GIMPLE_STMT_OPERAND.
+        (realify_fake_stores): Same.
+        * tree-ssa-forwprop.c (forward_propagate_addr_into_variable_arr):
+        Use TREE_OPERAND.
+        * tree-inline.c (copy_body_r): Check for EXPR_P and GIMPLE_STMT_P.
+        (copy_tree_r): Check for IS_GIMPLE_STMT_CODE_CLASS.
+        * tree-cfg.c (move_stmt_r): Use EXPR_P.  Check for GIMPLE_STMT_P.
+        * c-parser.c (c_parser_typeof_specifier): Use CAN_HAVE_LOCATION_P.
+        (c_parser_statement_after_labels): Same.
+        (c_parser_paren_condition): Same.
+        (c_parser_for_statement): Same.
+        (c_parser_omp_for_loop): Same.
+        * tree-ssa-reassoc.c (linearize_expr): Use GIMPLE_STMT_OPERAND.
+        (linearize_expr_tree): Same.
+        * dwarf2out.c (reference_to_unused): Check for GIMPLE_STMT_P.
+        * function.c (instantiate_expr): Same.
+
+	2006-09-22  Aldy Hernandez  <aldyh@redhat.com>
+
+        * tree.c (expr_location): Use GIMPLE_STMT_LOCUS.
+        (set_expr_location): Same.
+        (expr_locus): Same.
+        (set_expr_locus): Same.
+        (expr_filename): Same.
+        (expr_lineno): Same.
+        (tree_block): Use GIMPLE_STMT_BLOCK.
+        (protected_tree_operand): Use GIMPLE_STMT_OPERAND.
+        * tree.h (struct gimple_stmt): Remove prev and next.
+        (GIMPLE_STMT_OPERAND_CHECK): New.
+        (TREE_TO_GIMPLE_STMT): Delete.
+        (GIMPLE_STMT_TO_TREE): Delete.
+        (GIMPLE_STMT_OPERAND): Use union, not cast.
+        (GIMPLE_STMT_LOCUS): New.
+        (GIMPLE_STMT_BLOCK): New.
+        * gimplify.c (tree_to_gimple_tuple): Use union.  Do not cast
+        to tree_base.
+        * tree-cfg.c (verify_gimple_tuples_1): Call gcc_unreachable.
+
+	2006-09-21  Aldy Hernandez  <aldyh@redhat.com>
+
+        * tree-into-ssa.c (REGISTER_DEFS_IN_STMT): Change common.base
+        to base.
+        * tree-tailcall.c (adjust_return_value): Same.
+        * tree.c (tree_code_size): Remove GIMPLE_STATEMENT_LIST case.
+        (copy_node_stat): Change common.base to base.
+        (tree_node_structure): Return TS_GIMPLE_STATEMENT for tcc_gimple_stmt.
+        Remove GIMPLE_STATEMENT_LIST case.
+        * tree.h (struct gimple_stmt): Make operands of type tree.
+        (TREE_CODE, TREE_SET_CODE, TREE_ADDRESSABLE, CALL_EXPR_TAILCALL,
+        CASE_LOW_SEEN, TREE_STATIC, CLEANUP_EH_ONLY, CASE_HIGH_SEEN,
+        TREE_NO_WARNING, TREE_CONSTANT_OVERFLOW, TREE_SYMBOL_REFERENCED,
+        TYPE_REF_CAN_ALIAS_ALL, TREE_OVERFLOW, TREE_PUBLIC,
+        TYPE_CACHED_VALUES_P, TREE_SIDE_EFFECTS, FORCED_LABEL,
+        TREE_THIS_VOLATILE, TREE_THIS_NOTRAP, TREE_READONLY,
+        TREE_CONSTANT, TYPE_SIZES_GIMPLIFIED, DECL_UNSIGNED,
+        BIT_FIELD_REF_UNSIGNED, TYPE_UNSIGNED, TREE_ASM_WRITTEN, TREE_USED,
+        TREE_NOTHROW, CALL_EXPR_RETURN_SLOT_OPT, DECL_BY_REFERENCE,
+        CALL_FROM_THUNK_P, TYPE_ALIGN_OK, TREE_PRIVATE, TREE_PROTECTED,
+        TREE_DEPRECATED, IDENTIFIER_TRANSPARENT_ALIAS, TREE_INVARIANT,
+        TREE_LANG_FLAG_*, SSA_NAME_OCCURS_IN_ABNORMAL_PHI,
+        SSA_NAME_IN_FREE_LIST, TYPE_VOLATILE, TYPE_READONLY, BINFO_VIRTUAL_P):
+        Change common.base to base.
+        (GIMPLE_STATEMENT_LIST*): Remove.
+        (union tree_node): Add base.  Remove gimple_statement_list.
+        Remove pointer from gstmt.
+        * tree-ssa-propagate.c (set_rhs): Change common.base to base.
+        * treestruct.def: Add TS_BASE.  Remove TS_GIMPLE_STATEMENT_LIST.
+        * tree-vn.c (vn_compute): Change common.base to base.
+        * tree-eh.c (verify_eh_throw_stmt_node): Same.
+        * tree-flow-inline.h (var_ann): Same.
+        (function_ann): Same.
+        (stmt_ann): Same.
+        (mark_non_addressable): Same.
+        * gimplify.c (tree_to_gimple_tuple): Same.
+        * tree.def (DEFTREECODE): Remove GIMPLE_STATEMENT_LIST.
+        * tree-dfa.c (create_var_ann): Change common.base to base.
+        (create_function_ann): Same.
+        (create_stmt_ann): Same.
+        (create_tree_ann): Same.
+        (collect_dfa_stats_r): Same.
+        * tree-ssa-pre.c (NECESSARY): Change common.base to base.
+        * tree-ssa-dce.c (NECESSARY): Same.
+        * tree-ssa.c (delete_tree_ssa): Same.
+        * tree-optimize.c (execute_free_cfg_annotations): Same.
+        * tree-flow.h: Same.
+
+	2006-09-19  Aldy Hernandez  <aldyh@redhat.com>
+
+        * tree.c (tree_code_size): Handle GIMPLE_STATEMENT_LIST.
+        (tree_node_structure): Handle GIMPLE_STATEMENT_LIST and
+	GIMPLE_MODIFY_STMT.
+        * tree.h (struct gimple_stmt): Add prev and next fields.
+	(GIMPLE_STMT_TO_TREE): Cast, do not call GIMPLE_STMT_CHECK.
+	(GIMPLE_STATEMENT_LIST_HEAD): New.
+	(GIMPLE_STATEMENT_LIST_TAIL): New.
+	(struct gimple_statement_list): New.
+	(union tree_node): Add gimple_stmt_list and gstmt.
+        * treestruct.def: Add TS_GIMPLE_STATEMENT_LIST, TS_GIMPLE_STATEMENT.
+        * tree.def: Add GIMPLE_STATEMENT_LIST.
+
+	2006-09-06  Aldy Hernandez  <aldyh@redhat.com>
+
+	* tree-dump.c (dequeue_and_dump): Handle GIMPLE_MODIFY_STMT.
+	* tree-vrp.c (build_assert_expr_for): Change uses of
+	MODIFY_EXPR to GIMPLE_MODIFY_STMT and adjust accordingly.
+	(find_assert_locations): Same.
+	(remove_range_assertions): Same.
+	(stmt_interesting_for_vrp): Same.
+	(vrp_visit_assignment): Same.
+	(vrp_visit_stmt): Same.
+	(simplify_cond_using_ranges): Same.
+	* tree-into-ssa.c (REGISTER_DEFS_IN_THIS_STMT): Adjust for new
+	tree structure.
+	* tree-ssa-loop-im.c (movement_possibility): Change uses of
+	MODIFY_EXPR to GIMPLE_MODIFY_STMT and adjust accordingly.
+	(stmt_cost): Same.
+	(determine_invariantness_stmt): Same.
+	(schedule_sm): Same.
+	(gather_mem_refs_stmt): Same.
+	* tree-complex.c (init_dont_simulate_again): Same.
+	(complex_visit_stmt): Same.
+	(set_component_ssa_name): Same.
+	(expand_complex_move): Same.
+	(expand_complex_div_wide): Same.
+	(expand_complex_comparison): Same.
+	(expand_complex_operations_1): Same.
+	* tree-ssa-loop-niter.c (expand_simple_operations): Same.
+	(chain_of_csts_start): Same.
+	(infer_loop_bounds_from_undefined): Same.
+	* tree-pretty-print.c (dump_generic_node): Same.
+	(op_prio): Same.
+	(op_symbol_1): Same.
+	* tree-ssa-loop-manip.c (create_iv): Same.
+	* value-prof.c (tree_divmod_fixed_value): Same.
+	(tree_divmod_fixed_value_transform): Same.
+	(tree_mod_pow2): Same.
+	(tree_mod_pow2_value_transform): Same.
+	(tree_mod_subtract): Same.
+	(tree_mod_subtract_transform): Same.
+	(tree_divmod_values_to_profile): Same.
+	* tree-tailcall.c (process_assignment): Same.
+	(find_tail_calls): Same.
+	(adjust_accumulator_values): Same.
+	(adjust_return_value): Same.
+	(eliminate_tail_call): Same.
+	* tree.c (tree_code_size): Handle tcc_gimple_stmt.
+	(make_node_stat): Same.
+	(copy_node_stat): Handle gimple tuples.
+	(expr_align): Handle GIMPLE_MODIFY_STMT.  Abort on MODIFY_EXPR.
+	(tree_node_structure): Handle tcc_gimple_stmt.
+	(build2_stat): Abort on MODIFY_EXPR after gimplification.  Handle
+	tcc_gimple_stmt.
+	(build2_gimple_stat): New.
+	(expr_location): New.
+	(set_expr_location): New.
+	(expr_has_location): New.
+	(expr_locus): New.
+	(set_expr_locus): New.
+	(expr_filename): New.
+	(expr_lineno): New.
+	(walk_tree): Handle tcc_gimple_stmt.
+	(tree_block): New.
+	(protected_tree_operand): New.
+	(protected_tree_type): New.
+	(tree_code_kind): Add gimple statements.
+	* tree.h (tree_code_class): Add tcc_gimple_stmt.
+	(IS_GIMPLE_STMT_CODE_CLASS): New.
+	(struct tree_base): New.
+	(struct tree_common): Shrink.
+	(struct gimple_stmt): New.
+	(struct gimple_expr): New.
+	(TREE_SET_CODE, TREE_ADDRESSABLE, CALL_EXPR_TAILCALL,
+	CASE_LOW_SEEN, TREE_STATIC, CLEANUP_EH_ONLY, CASE_HIGH_SEEN,
+	TREE_NO_WARNING, TREE_CONSTANT_OVERFLOW, TREE_SYMBOL_REFERENCED,
+	TYPE_REF_CAN_ALIAS_ALL, TREE_OVERFLOW, TREE_PUBLIC,
+	TYPE_CACHED_VALUES_P, SAVE_EXPR_RESOLVED_P, TREE_SIDE_EFFECTS,
+	FORCED_LABEL, TREE_THIS_VOLATILE, TREE_THIS_NOTRAP, TREE_READONLY,
+	TREE_CONSTANT, TYPE_SIZES_GIMPLIFIED, DECL_UNSIGNED,
+	BIT_FIELD_REF_UNSIGNED, TYPE_UNSIGNED, TREE_ASM_WRITTEN,
+	TREE_USED, TREE_NOTHROW, CALL_EXPR_RETURN_SLOT_OPT,
+	DECL_BY_REFERENCE, CALL_FROM_THUNK_P, TYPE_ALIGN_OK,
+	TREE_PRIVATE, TREE_PROTECTED, TREE_DEPRECATED,
+	IDENTIFIER_TRANSPARENT_ALIAS, TREE_INVARIANT,
+	TREE_LANG_FLAG_[0-6], SSA_NAME_CHECK, SSA_NAME_IN_FREE_LIST,
+	TYPE_VOLATILE, TYPE_READONLY, TREE_VISITED, BINFO_VIRTUAL_P):
+	Adjust for new `common' layout.
+	(struct tree_function_decl): Add gimplified_flag.
+	(DECL_GIMPLIFIED): NEW.
+	(EXPR_LOCATION, SET_EXPR_LOCUS, EXPR_FILENAME, EXPR_LOCUS,
+	SET_EXPR_LOCUS, SET_EXPR_LOCATION, EXPR_LINENO,
+	EXPR_HAS_LOCATION): Call corresponding function.
+	(GIMPLE_STMT_CHECK): New.
+	(TREE_OPERAND_CHECK, TREE_TYPE, TREE_CHAIN): Abort on gimple tuples.
+	(TREE_BLOCK): Call tree_block.
+	(GIMPLE_STMT_P): New.
+	(GIMPLE_TUPLE_P): New.
+	(TREE_TO_GIMPLE_STMT): New.
+	(GIMPLE_STMT_TO_TREE): New.
+	(GIMPLE_STMT_OPERAND): New.
+	(GIMPLE_TUPLE_HAS_LOCUS_P): New.
+	(PROTECTED_TREE_OPERAND): New.
+	(PROTECTED_TREE_TYPE): New.
+	(build2_gimple_stat): Protoize.
+	(build2_gimple): New.
+	(expr_location): Protoize.
+	(set_expr_location): Protoize.
+	(expr_has_location): Protoize.
+	(expr_locus): Protoize.
+	(set_expr_locus): Protoize.
+	(expr_filename): Protoize.
+	(expr_lineno): Protoize.
+	(tree_block): Protoize.
+	(protected_tree_operand): Protoize.
+	(protected_tree_type): Protoize.
+	(enum tree_node_kind): Add gimple_stmt_kind.
+	* c-decl.c (union lang_tree_node): Tuples do not have a
+	TREE_CHAIN.
+	* ipa-cp.c (constant_val_insert): Change uses of MODIFY_EXPR to
+	GIMPLE_MODIFY_STMT and adjust accordingly.
+	* tree-scalar-evolution.c (follow_ssa_edge): Same.
+	(interpret_condition_phi): Same.
+	(pointer_used_p): Same.
+	(analyze_scalar_evolution_1): Same.
+	(scev_const_prop): Same.
+	(interpret_rhs_modify_stmt): Rename from
+	interpret_rhs_modify_expr.
+	* builtins.c (std_expand_builtin_va_start): Change uses of
+	MODIFY_EXPR to GIMPLE_MODIFY_STMT and adjust accordingly.
+	(std_gimplify_va_arg_expr): Same.
+	(expand_builtin_va_copy): Same.
+	(integer_valued_real_p): Same.
+	* fold-const.c (maybe_lvalue_p): Same.
+	(fold_unary): Same.
+	(tree_expr_nonnegative_p): Same.
+	(tree_expr_nonzero_p): Same.
+	* omp-low.c (extract_omp_for_data): Same.
+	(lower_rec_input_clauses): Same.
+	(lower_reduction_clauses): Same.
+	(lower_copyprivate_clauses): Same.
+	(lower_send_clauses): Same.
+	(lower_send_shared_vars): Same.
+	(expand_parallel_call): Same.
+	(expand_omp_parallel): Same.
+	(expand_omp_for_generic): Same.
+	(expand_omp_for_static_nochunk): Same.
+	(expand_omp_for_static_chunk): Same.
+	(expand_omp_sections): Same.
+	(lower_omp_single_copy): Same.
+	(lower_omp_parallel): Same.
+	* tree-ssa-dse.c (memory_address_same): Same.
+	(dse_optimize_stmt): Same.
+	* ipa-reference.c (scan_for_static_refs): Same.
+	* tree-gimple.c (is_gimple_reg_rhs): Same.
+	(get_call_expr_in): Same.
+	(recalculate_side_effects): Same.
+	* cgraphunit.c (cgraph_create_edges): Same.
+	* tree-ssa-copyrename.c (rename_ssa_copies): Same.
+	* tree-ssa-ccp.c (get_default_value): Same.
+	(likely_value): Same.
+	(visit_assignment): Same.
+	(ccp_visit_stmt): Same.
+	(get_maxval_strlen): Same.
+	(ccp_fold_builtin): Same.
+	* tree-ssa-loop-ivopts.c (find_givs_in_stmt_scev): Same.
+	(find_givs_in_stmt): Same.
+	(find_interesting_uses_op): Same.
+	(find_interesting_uses_stmt): Same.
+	(rewrite_use_nonlinear_expr): Same.
+	* ipa-pure-const.c (scan_function): Same.
+	* tree-stdarg.c (va_list_counter_bump): Same.
+	(check_all_va_list_escapes): Same.
+	(execute_optimize_stdarg): Same.
+	* tree-ssa-math-opts.c (compute_merit): Same.
+	(insert_reciprocals): Same.
+	(execute_cse_reciprocals): Same.
+	* tree-ssa-dom.c (initialize_hash_element): Same.
+	(simple_iv_increment_p): Same.
+	(record_equivalences_from_stmt): Same.
+	(optimize_stmt): Same.
+	(remove_stmt_or_phi): Same.
+	(get_rhs_or_phi_arg): Same.
+	(get_lhs_or_phi_result): Same.
+	(propagate_rhs_into_lhs): Same.
+	* tree-nrv.c (tree_nrv): Same.
+	(execute_return_slot_opt): Same.
+	* tree-ssa-propagate.c (get_rhs): Same.
+	(set_rhs): Same.
+	(stmt_makes_single_load): Same.
+	(stmt_makes_single_store): Same.
+	(replace_vuses_in): Same.
+	(fold_predicate_in): Same.
+	(substitute_and_fold): Same.
+	* tree-ssa-alias.c (compute_call_clobbered): Same.
+	(recalculate_used_alone): Same.
+	(count_uses_and_derefs): Same.
+	(is_escape_site): Same.
+	(find_used_portions): Same.
+	* gimple-low.c (lower_stmt): Same.
+	(block_may_fallthru): Same.
+	(lower_return_expr): Same.
+	* tree-ssa-sink.c (is_hidden_global_store): Same.
+	(statement_sink_location): Same.
+	* dwarf2out.c (loc_descriptor_from_tree_1): Same.
+	* expr.c (safe_from_p): Same.
+	(expand_expr_real): Same.
+	(expand_expr_real_1): Same.
+	* tree-ssa-loop-ivcanon.c (empty_loop_p): Same.
+	* predict.c (expr_expected_value): Same.
+	(strip_builtin_expect): Same.
+	(apply_return_prediction): Same.
+	(tree_bb_level_predictions): Same.
+	(tree_estimate_probability): Same.
+	* tree-vn.c (vn_compute): Same.
+	* tree-eh.c (add_stmt_to_eh_region_fn): Same.
+	(remove_stmt_from_eh_region_fn): Same.
+	(do_return_redirection): Same.
+	(honor_protect_cleanup_actions): Same.
+	(lower_try_finally_switch): Same.
+	(lower_eh_constructs_1): Same.
+	(tree_could_throw_p): Same.
+	(verify_eh_throw_stmt_node): Same.
+	* function.c (gimplify_parameters): Same.
+	* tree-vectorizer.c (vect_is_simple_use): Same.
+	(vect_is_simple_reduction): Same.
+	* ipa-type-escape.c (scan_for_refs): Same.
+	* tree-if-conv.c (tree_if_conversion): Same.
+	(tree_if_convert_stmt): Same.
+	(if_convertible_gimplify_modify_stmt_p): Rename from
+	if_convertible_modify_expr_p.
+	(if_convertible_stmt_p): Adjust for GIMPLE_MODIFY_STMT.
+	(ifc_temp_var): Same.
+	(replace_phi_with_cond_modify_stmt): Rename from
+	replace_phi_with_cond_modify_expr.
+	(process_phi_nodes): Call replace_phi_with_cond_modify_stmt.
+	* tree.def (DEFTREECODE): Add GIMPLE_MODIFY_STMT.
+	* tree-data-ref.c (find_data_references_in_loop): Adjust for
+	GIMPLE_MODIFY_STMT.
+	* tree-flow-inline.h (var_ann): Same.
+	(function_ann): Same.
+	(stmt_ann): Same.
+	(mark_non_addressable): Same.
+	* tree-vect-analyze.c (vect_determine_vectorization_factor): Same.
+	* gimplify.c (tree_to_gimple_tuple): New.
+	(build_stack_save_restore): Adjust for GIMPLE_MODIFY_STMT.
+	(gimplify_return_expr): Same.
+	(gimplify_decl_expr): Same.
+	(gimplify_self_mod_expr): Same.
+	(gimplify_cond_expr): Same.
+	(gimplify_init_constructor): Same.
+	(gimplify_modify_expr): Same.
+	(gimplify_expr): Same.
+	(gimplify_function_tree): Same.
+	(force_gimple_operand): Same.
+	* tree-ssa-phiopt.c (conditional_replacement): Same.
+	(minmax_replacement): Same.
+	(abs_replacement): Same.
+	* tree-dfa.c (create_var_ann): Same.
+	(create_function_ann): Same.
+	(create_stmt_ann): Same.
+	(create_tree_ann): Same.
+	(collect_dfa_stats_r): Same.
+	* tree-ssa-pre.c (find_or_generate_expression): Same.
+	(create_expression_by_pieces): Same.
+	(try_look_through_load): Same.
+	(insert_fake_stores): Same.
+	(realify_fake_stores): Same.
+	(compute_avail): Same.
+	(eliminate): Same.
+	(init_pre): Same.
+	(poolify_modify_stmt): Rename from poolify_modify_stmt.
+	Adjust for GIMPLE_MODIFY_STMT.
+	(NECESSARY): Adjust for new `common' layout.
+	* tree-ssa-live.c (build_tree_conflict_graph): Adjust for
+	GIMPLE_MODIFY_STMT.
+	* tree-sra.c (sra_walk_modify_stmt): Rename from
+	sra_walk_modify_expr.
+	(sra_walk_function): Adjust for GIMPLE_MODIFY_STMT.
+	(generate_copy_inout): Same.
+	(generate_element_copy): Same.
+	(generate_element_zero): Same.
+	(scalarize_copy): Same.
+	* tree-mudflap.c (mf_decl_cache_locals): Same.
+	(mf_build_check_statement_for): Same.
+	(mf_xform_derefs): Same.
+	* ipa-prop.c (ipa_method_modify_stmt): Same.
+	* print-tree.c (print_node): Handle gimple tuples.
+	Add case for tcc_gimple_stmt.
+	* tree-ssa-copy.c (stmt_may_generate_copy): Adjust for
+	GIMPLE_MODIFY_STMT.
+	(copy_prop_visit_assignment): Same.
+	(copy_prop_visit_stmt): Same.
+	(init_copy_prop): Same.
+	* tree-ssa-forwprop.c (ssa_name_defined_by_comparison_p): Same.
+	(forward_propagate_into_cond_1): Same.
+	(find_equivalent_equality_comparison): Same.
+	(tidy_after_forward_propagate_addr): Same.
+	(forward_propagate_addr_expr_1): Same.
+	(simplify_not_neg_expr): Same.
+	(simplify_switch_expr): Same.
+	* tree-ssa-dce.c (find_pdom): Same.
+	(mark_stmt_if_obviously_necessary): Same.
+	(NECESSARY): Adjust for new `common' layout.
+	* tree-flow.h: Same.
+	* tree-vect-patterns.c (widened_name_p): Adjust for
+	GIMPLE_MODIFY_STMT.
+	(vect_recog_dot_prod_pattern): Same.
+	(vect_recog_widen_sum_pattern): Same.
+	(vect_pattern_recog_1): Same.
+	* tree-nested.c (init_tmp_var): Same.
+	(save_tmp_var): Same.
+	(walk_stmts): Same.
+	(convert_call_expr): Same.
+	(finalize_nesting_tree_1): Same.
+	* tree-ssa.c (verify_ssa): Same.
+	(delete_tree_ssa): Same.
+	* lambda-code.c (lbv_to_gcc_expression): Same.
+	(lle_to_gcc_expression): Same.
+	(lambda_loopnest_to_gcc_loopnest): Same.
+	(can_put_in_inner_loop): Same.
+	(can_convert_to_perfect_nest): Same.
+	(perfect_nestify): Same.
+	* tree-ssa-loop-prefetch.c (gather_memory_references): Same.
+	* tree-inline.c (copy_body_r): Same.
+	(setup_one_parameter): Same.
+	(initialize_inlined_parameters): Same.
+	(estimate_num_insns_1): Same.
+	(expand_call_inline): Same.
+	(gimple_expand_calls_inline): Same.
+	(copy_tree_r): Same.
+	* tree-optimize.c (execute_free_cfg_annotations): Same.
+	* tree-vect-transform.c (vect_create_addr_base_for_vector_ref): Same.
+	(vect_align_data_ref): Same.
+	(vect_create_data_ref_ptr): Same.
+	(vect_init_vector): Same.
+	(vect_create_epilog_for_reduction): Same.
+	(vectorizable_reduction): Same.
+	(vectorizable_assignment): Same.
+	(vectorizable_operation): Same.
+	(vectorizable_store): Same.
+	(vectorizable_load): Same.
+	(vectorizable_live_operation): Same.
+	(vectorizable_condition): Same.
+	(vect_generate_tmps_on_preheader): Same.
+	(vect_create_cond_for_align_checks): Same.
+	* tree-object-size.c (collect_object_sizes_for): Same.
+	(check_for_plus_in_loops_1): Same.
+	(check_for_plus_in_loops): Same.
+	* tree-outof-ssa.c (insert_copy_on_edge): Same.
+	(replace_use_variable): Same.
+	(check_replaceable): Same.
+	(rewrite_trees): Same.
+	(identical_copies_p): Same.
+	(insert_backedge_copies): Same.
+	* tree-profile.c (tree_gen_edge_profiler): Same.
+	* tree-vect-generic.c (expand_vector_operations_1): Same.
+	* tree-ssa-structalias.c (update_alias_info): Same.
+	(find_func_aliases): Same.
+	* tree-cfg.c (factor_computed_gotos): Same.
+	(make_edges): Same.
+	(make_goto_expr_edges): Same.
+	(tree_merge_blocks): Same.
+	(remove_useless_stmts_cond): Same.
+	(remove_useless_stmts_1): Same.
+	(tree_find_edge_insert_loc): Same.
+	(verify_expr): Same.
+	(gimplify_val): Same.
+	(verify_gimple_tuples_1): New.
+	(verify_gimple_tuples): New.
+	(verify_stmts): Call verify_gimple_tuples.
+	* tree-ssa-reassoc.c (get_rank): Adjust for GIMPLE_MODIFY_STMT.
+	(get_unary_op): Same.
+	(linearize_expr): Same.
+	(get_single_immediate_use): Same.
+	(negate_value): Same.
+	(should_break_up_subtract): Same.
+	(break_up_subtract): Same.
+	(repropagate_negates): Same.
+	(break_up_subtract_bb): Same.
+	(reassociate_bb): Same.
+	* config/i386/i386.c (ix86_va_start): Same.
+	(ix86_gimplify_va_arg): Same.
+	* stmt.c (expand_expr_stmt): Same.
+	(warn_if_unused_value): Same.
+	(expand_return): Same.
+	* tree-ssanames.c (make_ssa_name): Same.
+	* tree-ssa-threadedge.c (lhs_of_dominating_assert): Same.
+	* tree-ssa-operands.c (finalize_ssa_defs): Same.
+	(add_virtual_operand): Same.
+	(get_expr_operands): Same.
+	(parse_ssa_operands): Same.
+	(get_modify_stmt_operands): Rename from get_modify_expr_operands.
+
 2006-12-05  H.J. Lu  <hongjiu.lu@intel.com>
 
 	* config.host: Remove extra blank line.
diff --git a/gcc/ada/ada-tree.h b/gcc/ada/ada-tree.h
index 0bc81e4d71869f08483eadb160494120782da24b..608f75e9df29c9ac66162e5a9393d5098f4eba9c 100644
--- a/gcc/ada/ada-tree.h
+++ b/gcc/ada/ada-tree.h
@@ -36,7 +36,8 @@ enum gnat_tree_code {
 /* Ada uses the lang_decl and lang_type fields to hold a tree.  */
 union lang_tree_node
   GTY((desc ("0"),
-       chain_next ("(union lang_tree_node *)TREE_CHAIN (&%h.t)")))
+       chain_next ("(GIMPLE_STMT_P (&%h.t) ? (union lang_tree_node *) 0 : (union lang_tree_node *)TREE_CHAIN (&%h.t))")))
+
 {
   union tree_node GTY((tag ("0"))) t;
 };
diff --git a/gcc/ada/trans.c b/gcc/ada/trans.c
index 7b9c260ff6b11ad76e97ad8a8108b58bc75fc9c7..b19f2f5f518be680088c80172a1f316eb9cefd47 100644
--- a/gcc/ada/trans.c
+++ b/gcc/ada/trans.c
@@ -4840,7 +4840,7 @@ gnat_gimplify_expr (tree *expr_p, tree *pre_p, tree *post_p ATTRIBUTE_UNUSED)
 	       && TREE_CODE_CLASS (TREE_CODE (op)) != tcc_constant)
 	{
 	  tree new_var = create_tmp_var (TREE_TYPE (op), "A");
-	  tree mod = build2 (MODIFY_EXPR, TREE_TYPE (op), new_var, op);
+	  tree mod = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (op), new_var, op);
 
 	  TREE_ADDRESSABLE (new_var) = 1;
 
diff --git a/gcc/builtins.c b/gcc/builtins.c
index 0cfdb9af12cad61fb7438efd5eb345d0806197e8..fa7ed0133ba034d8090e11249de688b80ece7c52 100644
--- a/gcc/builtins.c
+++ b/gcc/builtins.c
@@ -4319,7 +4319,7 @@ std_expand_builtin_va_start (tree valist, rtx nextarg)
 {
   tree t;
 
-  t = build2 (MODIFY_EXPR, TREE_TYPE (valist), valist,
+  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (valist), valist,
 	      make_tree (ptr_type_node, nextarg));
   TREE_SIDE_EFFECTS (t) = 1;
 
@@ -4390,12 +4390,12 @@ std_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p, tree *post_p)
       && !integer_zerop (TYPE_SIZE (type)))
     {
       t = fold_convert (TREE_TYPE (valist), size_int (boundary - 1));
-      t = build2 (MODIFY_EXPR, TREE_TYPE (valist), valist_tmp,
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (valist), valist_tmp,
 		  build2 (PLUS_EXPR, TREE_TYPE (valist), valist_tmp, t));
       gimplify_and_add (t, pre_p);
 
       t = fold_convert (TREE_TYPE (valist), size_int (-boundary));
-      t = build2 (MODIFY_EXPR, TREE_TYPE (valist), valist_tmp,
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (valist), valist_tmp,
 		  build2 (BIT_AND_EXPR, TREE_TYPE (valist), valist_tmp, t));
       gimplify_and_add (t, pre_p);
     }
@@ -4434,7 +4434,7 @@ std_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p, tree *post_p)
   /* Compute new value for AP.  */
   t = fold_convert (TREE_TYPE (valist), rounded_size);
   t = build2 (PLUS_EXPR, TREE_TYPE (valist), valist_tmp, t);
-  t = build2 (MODIFY_EXPR, TREE_TYPE (valist), valist, t);
+  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (valist), valist, t);
   gimplify_and_add (t, pre_p);
 
   addr = fold_convert (build_pointer_type (type), addr);
@@ -4599,7 +4599,7 @@ expand_builtin_va_copy (tree arglist)
 
   if (TREE_CODE (va_list_type_node) != ARRAY_TYPE)
     {
-      t = build2 (MODIFY_EXPR, va_list_type_node, dst, src);
+      t = build2 (GIMPLE_MODIFY_STMT, va_list_type_node, dst, src);
       TREE_SIDE_EFFECTS (t) = 1;
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
     }
@@ -6738,9 +6738,9 @@ integer_valued_real_p (tree t)
       return integer_valued_real_p (TREE_OPERAND (t, 0));
 
     case COMPOUND_EXPR:
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
     case BIND_EXPR:
-      return integer_valued_real_p (TREE_OPERAND (t, 1));
+      return integer_valued_real_p (GENERIC_TREE_OPERAND (t, 1));
 
     case PLUS_EXPR:
     case MINUS_EXPR:
@@ -8096,7 +8096,7 @@ fold_builtin_memset (tree arglist, tree type, bool ignore)
     }
 
   ret = build_int_cst_type (TREE_TYPE (var), cval);
-  ret = build2 (MODIFY_EXPR, TREE_TYPE (var), var, ret);
+  ret = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (var), var, ret);
   if (ignore)
     return ret;
 
@@ -8251,7 +8251,7 @@ fold_builtin_memory_op (tree arglist, tree type, bool ignore, int endp)
 	expr = fold_convert (TREE_TYPE (destvar), srcvar);
       else
 	expr = fold_build1 (VIEW_CONVERT_EXPR, TREE_TYPE (destvar), srcvar);
-      expr = build2 (MODIFY_EXPR, TREE_TYPE (destvar), destvar, expr);
+      expr = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (destvar), destvar, expr);
     }
 
   if (ignore)
@@ -9474,7 +9474,7 @@ fold_builtin (tree fndecl, tree arglist, bool ignore)
   tree exp = fold_builtin_1 (fndecl, arglist, ignore);
   if (exp && !ignore)
     {
-      exp = build1 (NOP_EXPR, TREE_TYPE (exp), exp);
+      exp = build1 (NOP_EXPR, GENERIC_TREE_TYPE (exp), exp);
       TREE_NO_WARNING (exp) = 1;
     }
 
@@ -11704,9 +11704,11 @@ do_mpfr_sincos (tree arg, tree arg_sinp, tree arg_cosp)
 		  && TYPE_MAIN_VARIANT (TREE_TYPE (arg_cosp)) == TYPE_MAIN_VARIANT (type))
 	        {
 		  /* Set the values. */
-		  result_s = fold_build2 (MODIFY_EXPR, type, arg_sinp, result_s);
+		  result_s = fold_build2 (GIMPLE_MODIFY_STMT, type, arg_sinp,
+		      			  result_s);
 		  TREE_SIDE_EFFECTS (result_s) = 1;
-		  result_c = fold_build2 (MODIFY_EXPR, type, arg_cosp, result_c);
+		  result_c = fold_build2 (GIMPLE_MODIFY_STMT, type, arg_cosp,
+		      			  result_c);
 		  TREE_SIDE_EFFECTS (result_c) = 1;
 		  /* Combine the assignments into a compound expr.  */
 		  result = non_lvalue (fold_build2 (COMPOUND_EXPR, type,
diff --git a/gcc/c-decl.c b/gcc/c-decl.c
index bd737d16e7ce43f9827e72976869cac4449229d7..c95f495398546e909a388a66be743c2e3e097523 100644
--- a/gcc/c-decl.c
+++ b/gcc/c-decl.c
@@ -256,7 +256,7 @@ extern char C_SIZEOF_STRUCT_LANG_IDENTIFIER_isnt_accurate
 
 union lang_tree_node
   GTY((desc ("TREE_CODE (&%h.generic) == IDENTIFIER_NODE"),
-       chain_next ("TREE_CODE (&%h.generic) == INTEGER_TYPE ? (union lang_tree_node *) TYPE_NEXT_VARIANT (&%h.generic) : (union lang_tree_node *) TREE_CHAIN (&%h.generic)")))
+       chain_next ("TREE_CODE (&%h.generic) == INTEGER_TYPE ? (union lang_tree_node *) TYPE_NEXT_VARIANT (&%h.generic) : (GIMPLE_TUPLE_P (&%h.generic) ? (union lang_tree_node *) 0 : (union lang_tree_node *) TREE_CHAIN (&%h.generic))")))
 {
   union tree_node GTY ((tag ("0"),
 			desc ("tree_node_structure (&%h)")))
@@ -434,7 +434,7 @@ add_stmt (tree t)
 {
   enum tree_code code = TREE_CODE (t);
 
-  if (EXPR_P (t) && code != LABEL_EXPR)
+  if (CAN_HAVE_LOCATION_P (t) && code != LABEL_EXPR)
     {
       if (!EXPR_HAS_LOCATION (t))
 	SET_EXPR_LOCATION (t, input_location);
diff --git a/gcc/c-parser.c b/gcc/c-parser.c
index c6be63918f668ba9f82d42afd83056b1d3e4bbaf..a54674ff01dad4c2a47b7a2125d039bb4328dc46 100644
--- a/gcc/c-parser.c
+++ b/gcc/c-parser.c
@@ -2172,7 +2172,7 @@ c_parser_typeof_specifier (c_parser *parser)
 	  if (DECL_P (e) || CONSTANT_CLASS_P (e))
 	    e = build1 (NOP_EXPR, void_type_node, e);
 
-	  if (EXPR_P (e))
+	  if (CAN_HAVE_LOCATION_P (e))
 	    SET_EXPR_LOCATION (e, input_location);
 
 	  add_stmt (e);
@@ -3817,7 +3817,7 @@ c_parser_statement_after_labels (c_parser *parser)
      (recursively) all of the component statements should already have
      line numbers assigned.  ??? Can we discard no-op statements
      earlier?  */
-  if (stmt && EXPR_P (stmt))
+  if (stmt && CAN_HAVE_LOCATION_P (stmt))
     SET_EXPR_LOCATION (stmt, loc);
 }
 
@@ -3836,7 +3836,7 @@ c_parser_paren_condition (c_parser *parser)
   loc = c_parser_peek_token (parser)->location;
   cond = c_objc_common_truthvalue_conversion
     (c_parser_expression_conv (parser).value);
-  if (EXPR_P (cond))
+  if (CAN_HAVE_LOCATION_P (cond))
     SET_EXPR_LOCATION (cond, loc);
   c_parser_skip_until_found (parser, CPP_CLOSE_PAREN, "expected %<)%>");
   return cond;
@@ -4073,7 +4073,7 @@ c_parser_for_statement (c_parser *parser)
 	{
 	  tree ocond = c_parser_expression_conv (parser).value;
 	  cond = c_objc_common_truthvalue_conversion (ocond);
-	  if (EXPR_P (cond))
+	  if (CAN_HAVE_LOCATION_P (cond))
 	    SET_EXPR_LOCATION (cond, loc);
 	  c_parser_skip_until_found (parser, CPP_SEMICOLON, "expected %<;%>");
 	}
@@ -7424,7 +7424,7 @@ c_parser_omp_for_loop (c_parser *parser)
     {
       cond = c_parser_expression_conv (parser).value;
       cond = c_objc_common_truthvalue_conversion (cond);
-      if (EXPR_P (cond))
+      if (CAN_HAVE_LOCATION_P (cond))
 	SET_EXPR_LOCATION (cond, input_location);
     }
   c_parser_skip_until_found (parser, CPP_SEMICOLON, "expected %<;%>");
diff --git a/gcc/c-pretty-print.c b/gcc/c-pretty-print.c
index 5225ea3dd96b287324573ec8d8cbc82dc381c0f7..56b2b47a56960f235b213eeb9385b0fdfdb7fa66 100644
--- a/gcc/c-pretty-print.c
+++ b/gcc/c-pretty-print.c
@@ -1795,13 +1795,15 @@ pp_c_conditional_expression (c_pretty_printer *pp, tree e)
 static void
 pp_c_assignment_expression (c_pretty_printer *pp, tree e)
 {
-  if (TREE_CODE (e) == MODIFY_EXPR || TREE_CODE (e) == INIT_EXPR)
+  if (TREE_CODE (e) == MODIFY_EXPR 
+      || TREE_CODE (e) == GIMPLE_MODIFY_STMT
+      || TREE_CODE (e) == INIT_EXPR)
     {
-      pp_c_unary_expression (pp, TREE_OPERAND (e, 0));
+      pp_c_unary_expression (pp, GENERIC_TREE_OPERAND (e, 0));
       pp_c_whitespace (pp);
       pp_equal (pp);
       pp_space (pp);
-      pp_c_expression (pp, TREE_OPERAND (e, 1));
+      pp_c_expression (pp, GENERIC_TREE_OPERAND (e, 1));
     }
   else
     pp_c_conditional_expression (pp, e);
@@ -1942,6 +1944,7 @@ pp_c_expression (c_pretty_printer *pp, tree e)
       break;
 
     case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
     case INIT_EXPR:
       pp_assignment_expression (pp, e);
       break;
diff --git a/gcc/c-typeck.c b/gcc/c-typeck.c
index 1b0e33a794683afb42e88608818027802b833426..ec145334afaa754df16a20574c5eca6097766e0a 100644
--- a/gcc/c-typeck.c
+++ b/gcc/c-typeck.c
@@ -7450,7 +7450,7 @@ c_process_expr_stmt (tree expr)
   if (DECL_P (expr) || CONSTANT_CLASS_P (expr))
     expr = build1 (NOP_EXPR, TREE_TYPE (expr), expr);
 
-  if (EXPR_P (expr))
+  if (CAN_HAVE_LOCATION_P (expr))
     SET_EXPR_LOCATION (expr, input_location);
 
   return expr;
@@ -7587,7 +7587,7 @@ c_finish_stmt_expr (tree body)
     {
       /* Do not warn if the return value of a statement expression is
 	 unused.  */
-      if (EXPR_P (last))
+      if (CAN_HAVE_LOCATION_P (last))
 	TREE_NO_WARNING (last) = 1;
       return last;
     }
diff --git a/gcc/cgraphunit.c b/gcc/cgraphunit.c
index 1e76777d663585a4393ee8744d2c3c05590766dd..240ac85bd22ec25eb31bdaf2cc02d94f2fb9f403 100644
--- a/gcc/cgraphunit.c
+++ b/gcc/cgraphunit.c
@@ -591,8 +591,8 @@ cgraph_create_edges (struct cgraph_node *node, tree body)
 				bb->loop_depth);
 	    walk_tree (&TREE_OPERAND (call, 1),
 		       record_reference, node, visited_nodes);
-	    if (TREE_CODE (stmt) == MODIFY_EXPR)
-	      walk_tree (&TREE_OPERAND (stmt, 0),
+	    if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
+	      walk_tree (&GIMPLE_STMT_OPERAND (stmt, 0),
 			 record_reference, node, visited_nodes);
 	  }
 	else
diff --git a/gcc/config/alpha/alpha.c b/gcc/config/alpha/alpha.c
index 88fed9266f44ee8bfcf07437fdd4f0a238645762..cf19dc0ed328ced8e9e2cf5932a6c667906e12b8 100644
--- a/gcc/config/alpha/alpha.c
+++ b/gcc/config/alpha/alpha.c
@@ -5921,11 +5921,11 @@ va_list_skip_additions (tree lhs)
       if (TREE_CODE (stmt) == PHI_NODE)
 	return stmt;
 
-      if (TREE_CODE (stmt) != MODIFY_EXPR
-	  || TREE_OPERAND (stmt, 0) != lhs)
+      if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT
+	  || GIMPLE_STMT_OPERAND (stmt, 0) != lhs)
 	return lhs;
 
-      rhs = TREE_OPERAND (stmt, 1);
+      rhs = GIMPLE_STMT_OPERAND (stmt, 1);
       if (TREE_CODE (rhs) == WITH_SIZE_EXPR)
 	rhs = TREE_OPERAND (rhs, 0);
 
@@ -6184,7 +6184,7 @@ alpha_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
     {
       nextarg = plus_constant (nextarg, offset);
       nextarg = plus_constant (nextarg, NUM_ARGS * UNITS_PER_WORD);
-      t = build2 (MODIFY_EXPR, TREE_TYPE (valist), valist,
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (valist), valist,
 		  make_tree (ptr_type_node, nextarg));
       TREE_SIDE_EFFECTS (t) = 1;
 
@@ -6203,12 +6203,13 @@ alpha_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
       t = make_tree (ptr_type_node, virtual_incoming_args_rtx);
       t = build2 (PLUS_EXPR, ptr_type_node, t,
 		  build_int_cst (NULL_TREE, offset));
-      t = build2 (MODIFY_EXPR, TREE_TYPE (base_field), base_field, t);
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (base_field), base_field, t);
       TREE_SIDE_EFFECTS (t) = 1;
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
       t = build_int_cst (NULL_TREE, NUM_ARGS * UNITS_PER_WORD);
-      t = build2 (MODIFY_EXPR, TREE_TYPE (offset_field), offset_field, t);
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (offset_field),
+	  	  offset_field, t);
       TREE_SIDE_EFFECTS (t) = 1;
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
     }
@@ -6224,7 +6225,7 @@ alpha_gimplify_va_arg_1 (tree type, tree base, tree offset, tree *pre_p)
   if (targetm.calls.must_pass_in_stack (TYPE_MODE (type), type))
     {
       t = build_int_cst (TREE_TYPE (offset), 6*8);
-      t = build2 (MODIFY_EXPR, TREE_TYPE (offset), offset,
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (offset), offset,
 		  build2 (MAX_EXPR, TREE_TYPE (offset), offset, t));
       gimplify_and_add (t, pre_p);
     }
@@ -6278,7 +6279,7 @@ alpha_gimplify_va_arg_1 (tree type, tree base, tree offset, tree *pre_p)
       t = size_binop (MULT_EXPR, t, size_int (8));
     }
   t = fold_convert (TREE_TYPE (offset), t);
-  t = build2 (MODIFY_EXPR, void_type_node, offset,
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, offset,
 	      build2 (PLUS_EXPR, TREE_TYPE (offset), offset, t));
   gimplify_and_add (t, pre_p);
 
@@ -6318,7 +6319,7 @@ alpha_gimplify_va_arg (tree valist, tree type, tree *pre_p, tree *post_p)
   r = alpha_gimplify_va_arg_1 (type, base, offset, pre_p);
 
   /* Stuff the offset temporary back into its field.  */
-  t = build2 (MODIFY_EXPR, void_type_node, offset_field,
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, offset_field,
 	      fold_convert (TREE_TYPE (offset_field), offset));
   gimplify_and_add (t, pre_p);
 
diff --git a/gcc/config/frv/frv.c b/gcc/config/frv/frv.c
index d7e06137fec2773d4f3b8f9982ce27c44fbe75d8..942f3c688ede12493929f778f4f5e2e1a6645504 100644
--- a/gcc/config/frv/frv.c
+++ b/gcc/config/frv/frv.c
@@ -2203,7 +2203,7 @@ frv_expand_builtin_va_start (tree valist, rtx nextarg)
       debug_rtx (nextarg);
     }
 
-  t = build2 (MODIFY_EXPR, TREE_TYPE (valist), valist,
+  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (valist), valist,
 	      make_tree (ptr_type_node, nextarg));
   TREE_SIDE_EFFECTS (t) = 1;
 
diff --git a/gcc/config/i386/i386.c b/gcc/config/i386/i386.c
index 40d96a04543236f49e925e7733504a10fd198a24..dd715b4ac1c276fb3664c58d9058b18b7f81c7b3 100644
--- a/gcc/config/i386/i386.c
+++ b/gcc/config/i386/i386.c
@@ -4522,7 +4522,7 @@ ix86_va_start (tree valist, rtx nextarg)
   if (cfun->va_list_gpr_size)
     {
       type = TREE_TYPE (gpr);
-      t = build2 (MODIFY_EXPR, type, gpr,
+      t = build2 (GIMPLE_MODIFY_STMT, type, gpr,
 		  build_int_cst (type, n_gpr * 8));
       TREE_SIDE_EFFECTS (t) = 1;
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
@@ -4531,7 +4531,7 @@ ix86_va_start (tree valist, rtx nextarg)
   if (cfun->va_list_fpr_size)
     {
       type = TREE_TYPE (fpr);
-      t = build2 (MODIFY_EXPR, type, fpr,
+      t = build2 (GIMPLE_MODIFY_STMT, type, fpr,
 		  build_int_cst (type, n_fpr * 16 + 8*REGPARM_MAX));
       TREE_SIDE_EFFECTS (t) = 1;
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
@@ -4543,7 +4543,7 @@ ix86_va_start (tree valist, rtx nextarg)
   if (words != 0)
     t = build2 (PLUS_EXPR, type, t,
 	        build_int_cst (type, words * UNITS_PER_WORD));
-  t = build2 (MODIFY_EXPR, type, ovf, t);
+  t = build2 (GIMPLE_MODIFY_STMT, type, ovf, t);
   TREE_SIDE_EFFECTS (t) = 1;
   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
@@ -4553,7 +4553,7 @@ ix86_va_start (tree valist, rtx nextarg)
 	 Prologue of the function save it right above stack frame.  */
       type = TREE_TYPE (sav);
       t = make_tree (type, frame_pointer_rtx);
-      t = build2 (MODIFY_EXPR, type, sav, t);
+      t = build2 (GIMPLE_MODIFY_STMT, type, sav, t);
       TREE_SIDE_EFFECTS (t) = 1;
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
     }
@@ -4690,7 +4690,7 @@ ix86_gimplify_va_arg (tree valist, tree type, tree *pre_p, tree *post_p)
 	  /* int_addr = gpr + sav; */
 	  t = fold_convert (ptr_type_node, gpr);
 	  t = build2 (PLUS_EXPR, ptr_type_node, sav, t);
-	  t = build2 (MODIFY_EXPR, void_type_node, int_addr, t);
+	  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, int_addr, t);
 	  gimplify_and_add (t, pre_p);
 	}
       if (needed_sseregs)
@@ -4698,7 +4698,7 @@ ix86_gimplify_va_arg (tree valist, tree type, tree *pre_p, tree *post_p)
 	  /* sse_addr = fpr + sav; */
 	  t = fold_convert (ptr_type_node, fpr);
 	  t = build2 (PLUS_EXPR, ptr_type_node, sav, t);
-	  t = build2 (MODIFY_EXPR, void_type_node, sse_addr, t);
+	  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, sse_addr, t);
 	  gimplify_and_add (t, pre_p);
 	}
       if (need_temp)
@@ -4708,7 +4708,7 @@ ix86_gimplify_va_arg (tree valist, tree type, tree *pre_p, tree *post_p)
 
 	  /* addr = &temp; */
 	  t = build1 (ADDR_EXPR, build_pointer_type (type), temp);
-	  t = build2 (MODIFY_EXPR, void_type_node, addr, t);
+	  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, t);
 	  gimplify_and_add (t, pre_p);
 
 	  for (i = 0; i < XVECLEN (container, 0); i++)
@@ -4742,7 +4742,7 @@ ix86_gimplify_va_arg (tree valist, tree type, tree *pre_p, tree *post_p)
 					size_int (INTVAL (XEXP (slot, 1)))));
 	      dest = build_va_arg_indirect_ref (dest_addr);
 
-	      t = build2 (MODIFY_EXPR, void_type_node, dest, src);
+	      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, dest, src);
 	      gimplify_and_add (t, pre_p);
 	    }
 	}
@@ -4751,14 +4751,14 @@ ix86_gimplify_va_arg (tree valist, tree type, tree *pre_p, tree *post_p)
 	{
 	  t = build2 (PLUS_EXPR, TREE_TYPE (gpr), gpr,
 		      build_int_cst (TREE_TYPE (gpr), needed_intregs * 8));
-	  t = build2 (MODIFY_EXPR, TREE_TYPE (gpr), gpr, t);
+	  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (gpr), gpr, t);
 	  gimplify_and_add (t, pre_p);
 	}
       if (needed_sseregs)
 	{
 	  t = build2 (PLUS_EXPR, TREE_TYPE (fpr), fpr,
 		      build_int_cst (TREE_TYPE (fpr), needed_sseregs * 16));
-	  t = build2 (MODIFY_EXPR, TREE_TYPE (fpr), fpr, t);
+	  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (fpr), fpr, t);
 	  gimplify_and_add (t, pre_p);
 	}
 
@@ -4785,12 +4785,12 @@ ix86_gimplify_va_arg (tree valist, tree type, tree *pre_p, tree *post_p)
     }
   gimplify_expr (&t, pre_p, NULL, is_gimple_val, fb_rvalue);
 
-  t2 = build2 (MODIFY_EXPR, void_type_node, addr, t);
+  t2 = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, t);
   gimplify_and_add (t2, pre_p);
 
   t = build2 (PLUS_EXPR, TREE_TYPE (t), t,
 	      build_int_cst (TREE_TYPE (t), rsize * UNITS_PER_WORD));
-  t = build2 (MODIFY_EXPR, TREE_TYPE (ovf), ovf, t);
+  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (ovf), ovf, t);
   gimplify_and_add (t, pre_p);
 
   if (container)
diff --git a/gcc/config/ia64/ia64.c b/gcc/config/ia64/ia64.c
index 53d90d2424922fce2c9036acdcb84b4904a1d382..8915a024ea5a14bcc8824ca5cd9ee36e2ddf06a8 100644
--- a/gcc/config/ia64/ia64.c
+++ b/gcc/config/ia64/ia64.c
@@ -4324,7 +4324,7 @@ ia64_gimplify_va_arg (tree valist, tree type, tree *pre_p, tree *post_p)
 		       build_int_cst (NULL_TREE, 2 * UNITS_PER_WORD - 1));
       t = build2 (BIT_AND_EXPR, TREE_TYPE (t), t,
 		  build_int_cst (NULL_TREE, -2 * UNITS_PER_WORD));
-      t = build2 (MODIFY_EXPR, TREE_TYPE (valist), valist, t);
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (valist), valist, t);
       gimplify_and_add (t, pre_p);
     }
 
diff --git a/gcc/config/mips/mips.c b/gcc/config/mips/mips.c
index 63c19ab99f1e4feff9612f4a89bea27380ceda21..9b4746fe28ea940990a9599ec369dada9c375fef 100644
--- a/gcc/config/mips/mips.c
+++ b/gcc/config/mips/mips.c
@@ -4278,12 +4278,12 @@ mips_va_start (tree valist, rtx nextarg)
 	t = build2 (PLUS_EXPR, TREE_TYPE (ovfl), t,
 		    build_int_cst (NULL_TREE,
 				   cum->stack_words * UNITS_PER_WORD));
-      t = build2 (MODIFY_EXPR, TREE_TYPE (ovfl), ovfl, t);
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (ovfl), ovfl, t);
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
       /* Emit code to initialize GTOP, the top of the GPR save area.  */
       t = make_tree (TREE_TYPE (gtop), virtual_incoming_args_rtx);
-      t = build2 (MODIFY_EXPR, TREE_TYPE (gtop), gtop, t);
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (gtop), gtop, t);
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
       /* Emit code to initialize FTOP, the top of the FPR save area.
@@ -4295,18 +4295,18 @@ mips_va_start (tree valist, rtx nextarg)
       if (fpr_offset)
 	t = build2 (PLUS_EXPR, TREE_TYPE (ftop), t,
 		    build_int_cst (NULL_TREE, -fpr_offset));
-      t = build2 (MODIFY_EXPR, TREE_TYPE (ftop), ftop, t);
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (ftop), ftop, t);
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
       /* Emit code to initialize GOFF, the offset from GTOP of the
 	 next GPR argument.  */
-      t = build2 (MODIFY_EXPR, TREE_TYPE (goff), goff,
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (goff), goff,
 		  build_int_cst (NULL_TREE, gpr_save_area_size));
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
       /* Likewise emit code to initialize FOFF, the offset from FTOP
 	 of the next FPR argument.  */
-      t = build2 (MODIFY_EXPR, TREE_TYPE (foff), foff,
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (foff), foff,
 		  build_int_cst (NULL_TREE, fpr_save_area_size));
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
     }
@@ -4427,7 +4427,7 @@ mips_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p, tree *post_p)
 	      /* [1] Emit code for: off &= -rsize.	*/
 	      t = build2 (BIT_AND_EXPR, TREE_TYPE (off), off,
 			  build_int_cst (NULL_TREE, -rsize));
-	      t = build2 (MODIFY_EXPR, TREE_TYPE (off), off, t);
+	      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (off), off, t);
 	      gimplify_and_add (t, pre_p);
 	    }
 	  osize = rsize;
@@ -4466,7 +4466,7 @@ mips_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p, tree *post_p)
 	  u = fold_convert (TREE_TYPE (ovfl),
 			    build_int_cst (NULL_TREE, -osize));
 	  t = build2 (BIT_AND_EXPR, TREE_TYPE (ovfl), t, u);
-	  align = build2 (MODIFY_EXPR, TREE_TYPE (ovfl), ovfl, t);
+	  align = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (ovfl), ovfl, t);
 	}
       else
 	align = NULL;
diff --git a/gcc/config/pa/pa.c b/gcc/config/pa/pa.c
index 7b274fdc993457f82e27d1ea7bcb7817047aa5e8..26ada7e0600089cd355a55e47f25c8cf544e4348 100644
--- a/gcc/config/pa/pa.c
+++ b/gcc/config/pa/pa.c
@@ -5891,7 +5891,7 @@ hppa_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p, tree *post_p)
       u = build_int_cst (valist_type, (size > 4 ? -8 : -4));
       t = build2 (BIT_AND_EXPR, valist_type, t, u);
 
-      t = build2 (MODIFY_EXPR, valist_type, valist, t);
+      t = build2 (GIMPLE_MODIFY_STMT, valist_type, valist, t);
 
       ofs = (8 - size) % 4;
       if (ofs != 0)
diff --git a/gcc/config/rs6000/rs6000.c b/gcc/config/rs6000/rs6000.c
index 37e30022b5567b4a7a081c5a022244cd73d5f0ce..08b3d01a50e1066ea9c6fdf4fc342880f1bec607 100644
--- a/gcc/config/rs6000/rs6000.c
+++ b/gcc/config/rs6000/rs6000.c
@@ -6013,7 +6013,7 @@ rs6000_va_start (tree valist, rtx nextarg)
 
   if (cfun->va_list_gpr_size)
     {
-      t = build2 (MODIFY_EXPR, TREE_TYPE (gpr), gpr,
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (gpr), gpr,
 		  build_int_cst (NULL_TREE, n_gpr));
       TREE_SIDE_EFFECTS (t) = 1;
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
@@ -6021,7 +6021,7 @@ rs6000_va_start (tree valist, rtx nextarg)
 
   if (cfun->va_list_fpr_size)
     {
-      t = build2 (MODIFY_EXPR, TREE_TYPE (fpr), fpr,
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (fpr), fpr,
 		  build_int_cst (NULL_TREE, n_fpr));
       TREE_SIDE_EFFECTS (t) = 1;
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
@@ -6032,7 +6032,7 @@ rs6000_va_start (tree valist, rtx nextarg)
   if (words != 0)
     t = build2 (PLUS_EXPR, TREE_TYPE (ovf), t,
 	        build_int_cst (NULL_TREE, words * UNITS_PER_WORD));
-  t = build2 (MODIFY_EXPR, TREE_TYPE (ovf), ovf, t);
+  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (ovf), ovf, t);
   TREE_SIDE_EFFECTS (t) = 1;
   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
@@ -6049,7 +6049,7 @@ rs6000_va_start (tree valist, rtx nextarg)
   if (cfun->machine->varargs_save_offset)
     t = build2 (PLUS_EXPR, TREE_TYPE (sav), t,
 	        build_int_cst (NULL_TREE, cfun->machine->varargs_save_offset));
-  t = build2 (MODIFY_EXPR, TREE_TYPE (sav), sav, t);
+  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (sav), sav, t);
   TREE_SIDE_EFFECTS (t) = 1;
   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 }
@@ -6182,7 +6182,7 @@ rs6000_gimplify_va_arg (tree valist, tree type, tree *pre_p, tree *post_p)
       u = build2 (MULT_EXPR, integer_type_node, u, size_int (sav_scale));
       t = build2 (PLUS_EXPR, ptr_type_node, t, u);
 
-      t = build2 (MODIFY_EXPR, void_type_node, addr, t);
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, t);
       gimplify_and_add (t, pre_p);
 
       t = build1 (GOTO_EXPR, void_type_node, lab_over);
@@ -6195,7 +6195,7 @@ rs6000_gimplify_va_arg (tree valist, tree type, tree *pre_p, tree *post_p)
 	{
 	  /* Ensure that we don't find any more args in regs.
 	     Alignment has taken care of the n_reg == 2 gpr case.  */
-	  t = build2 (MODIFY_EXPR, TREE_TYPE (reg), reg, size_int (8));
+	  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (reg), reg, size_int (8));
 	  gimplify_and_add (t, pre_p);
 	}
     }
@@ -6212,11 +6212,11 @@ rs6000_gimplify_va_arg (tree valist, tree type, tree *pre_p, tree *post_p)
     }
   gimplify_expr (&t, pre_p, NULL, is_gimple_val, fb_rvalue);
 
-  u = build2 (MODIFY_EXPR, void_type_node, addr, t);
+  u = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, t);
   gimplify_and_add (u, pre_p);
 
   t = build2 (PLUS_EXPR, TREE_TYPE (t), t, size_int (size));
-  t = build2 (MODIFY_EXPR, TREE_TYPE (ovf), ovf, t);
+  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (ovf), ovf, t);
   gimplify_and_add (t, pre_p);
 
   if (lab_over)
diff --git a/gcc/config/s390/s390.c b/gcc/config/s390/s390.c
index f7a1902ade38a53a6baff4d6ec806321b71a3641..af449f8f92814ac298ed07e4725e18601471b839 100644
--- a/gcc/config/s390/s390.c
+++ b/gcc/config/s390/s390.c
@@ -7931,7 +7931,7 @@ s390_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
 
   if (cfun->va_list_gpr_size)
     {
-      t = build2 (MODIFY_EXPR, TREE_TYPE (gpr), gpr,
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (gpr), gpr,
 	          build_int_cst (NULL_TREE, n_gpr));
       TREE_SIDE_EFFECTS (t) = 1;
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
@@ -7939,7 +7939,7 @@ s390_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
 
   if (cfun->va_list_fpr_size)
     {
-      t = build2 (MODIFY_EXPR, TREE_TYPE (fpr), fpr,
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (fpr), fpr,
 	          build_int_cst (NULL_TREE, n_fpr));
       TREE_SIDE_EFFECTS (t) = 1;
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
@@ -7959,7 +7959,7 @@ s390_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
 
       t = build2 (PLUS_EXPR, TREE_TYPE (ovf), t, build_int_cst (NULL_TREE, off));
 
-      t = build2 (MODIFY_EXPR, TREE_TYPE (ovf), ovf, t);
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (ovf), ovf, t);
       TREE_SIDE_EFFECTS (t) = 1;
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
     }
@@ -7972,7 +7972,7 @@ s390_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
       t = build2 (PLUS_EXPR, TREE_TYPE (sav), t,
 	          build_int_cst (NULL_TREE, -RETURN_REGNUM * UNITS_PER_WORD));
   
-      t = build2 (MODIFY_EXPR, TREE_TYPE (sav), sav, t);
+      t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (sav), sav, t);
       TREE_SIDE_EFFECTS (t) = 1;
       expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
     }
@@ -8105,7 +8105,7 @@ s390_gimplify_va_arg (tree valist, tree type, tree *pre_p,
 	      fold_convert (TREE_TYPE (reg), size_int (sav_scale)));
   t = build2 (PLUS_EXPR, ptr_type_node, t, fold_convert (ptr_type_node, u));
 
-  t = build2 (MODIFY_EXPR, void_type_node, addr, t);
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, t);
   gimplify_and_add (t, pre_p);
 
   t = build1 (GOTO_EXPR, void_type_node, lab_over);
@@ -8124,12 +8124,12 @@ s390_gimplify_va_arg (tree valist, tree type, tree *pre_p,
 
   gimplify_expr (&t, pre_p, NULL, is_gimple_val, fb_rvalue);
 
-  u = build2 (MODIFY_EXPR, void_type_node, addr, t);
+  u = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, t);
   gimplify_and_add (u, pre_p);
 
   t = build2 (PLUS_EXPR, ptr_type_node, t, 
 	      fold_convert (ptr_type_node, size_int (size)));
-  t = build2 (MODIFY_EXPR, ptr_type_node, ovf, t);
+  t = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, ovf, t);
   gimplify_and_add (t, pre_p);
 
   t = build1 (LABEL_EXPR, void_type_node, lab_over);
diff --git a/gcc/config/sh/sh.c b/gcc/config/sh/sh.c
index 11766cbd7adb2c84cf2a7d1fdc5bd5ce9ffc7c20..f9de2a68d77dbe5b0ecd12a3a8326b80a8c40470 100644
--- a/gcc/config/sh/sh.c
+++ b/gcc/config/sh/sh.c
@@ -7117,7 +7117,7 @@ sh_va_start (tree valist, rtx nextarg)
 
   /* Call __builtin_saveregs.  */
   u = make_tree (ptr_type_node, expand_builtin_saveregs ());
-  t = build2 (MODIFY_EXPR, ptr_type_node, next_fp, u);
+  t = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, next_fp, u);
   TREE_SIDE_EFFECTS (t) = 1;
   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
@@ -7128,11 +7128,11 @@ sh_va_start (tree valist, rtx nextarg)
     nfp = 0;
   u = fold_build2 (PLUS_EXPR, ptr_type_node, u,
 		   build_int_cst (NULL_TREE, UNITS_PER_WORD * nfp));
-  t = build2 (MODIFY_EXPR, ptr_type_node, next_fp_limit, u);
+  t = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, next_fp_limit, u);
   TREE_SIDE_EFFECTS (t) = 1;
   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
-  t = build2 (MODIFY_EXPR, ptr_type_node, next_o, u);
+  t = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, next_o, u);
   TREE_SIDE_EFFECTS (t) = 1;
   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
@@ -7143,12 +7143,12 @@ sh_va_start (tree valist, rtx nextarg)
     nint = 0;
   u = fold_build2 (PLUS_EXPR, ptr_type_node, u,
 		   build_int_cst (NULL_TREE, UNITS_PER_WORD * nint));
-  t = build2 (MODIFY_EXPR, ptr_type_node, next_o_limit, u);
+  t = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, next_o_limit, u);
   TREE_SIDE_EFFECTS (t) = 1;
   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
   u = make_tree (ptr_type_node, nextarg);
-  t = build2 (MODIFY_EXPR, ptr_type_node, next_stack, u);
+  t = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, next_stack, u);
   TREE_SIDE_EFFECTS (t) = 1;
   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 }
@@ -7268,10 +7268,10 @@ sh_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p,
 	  bool is_double = size == 8 && TREE_CODE (eff_type) == REAL_TYPE;
 
 	  tmp = build1 (ADDR_EXPR, pptr_type_node, next_fp);
-	  tmp = build2 (MODIFY_EXPR, void_type_node, addr, tmp);
+	  tmp = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, tmp);
 	  gimplify_and_add (tmp, pre_p);
 
-	  tmp = build2 (MODIFY_EXPR, ptr_type_node, next_fp_tmp, valist);
+	  tmp = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, next_fp_tmp, valist);
 	  gimplify_and_add (tmp, pre_p);
 	  tmp = next_fp_limit;
 	  if (size > 4 && !is_double)
@@ -7290,7 +7290,8 @@ sh_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p,
 	      tmp = fold_convert (ptr_type_node, size_int (UNITS_PER_WORD));
 	      tmp = build2 (BIT_AND_EXPR, ptr_type_node, next_fp_tmp, tmp);
 	      tmp = build2 (PLUS_EXPR, ptr_type_node, next_fp_tmp, tmp);
-	      tmp = build2 (MODIFY_EXPR, ptr_type_node, next_fp_tmp, tmp);
+	      tmp = build2 (GIMPLE_MODIFY_STMT, ptr_type_node,
+		  	    next_fp_tmp, tmp);
 	      gimplify_and_add (tmp, pre_p);
 	    }
 	  if (is_double)
@@ -7323,12 +7324,12 @@ sh_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p,
 	  gimplify_and_add (tmp, pre_p);
 
 	  tmp = build1 (ADDR_EXPR, pptr_type_node, next_stack);
-	  tmp = build2 (MODIFY_EXPR, void_type_node, addr, tmp);
+	  tmp = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, tmp);
 	  gimplify_and_add (tmp, pre_p);
-	  tmp = build2 (MODIFY_EXPR, ptr_type_node, next_fp_tmp, valist);
+	  tmp = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, next_fp_tmp, valist);
 	  gimplify_and_add (tmp, pre_p);
 
-	  tmp = build2 (MODIFY_EXPR, ptr_type_node, valist, next_fp_tmp);
+	  tmp = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, valist, next_fp_tmp);
 	  gimplify_and_add (tmp, post_p);
 	  valist = next_fp_tmp;
 	}
@@ -7343,7 +7344,7 @@ sh_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p,
 	  gimplify_and_add (tmp, pre_p);
 
 	  tmp = build1 (ADDR_EXPR, pptr_type_node, next_o);
-	  tmp = build2 (MODIFY_EXPR, void_type_node, addr, tmp);
+	  tmp = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, tmp);
 	  gimplify_and_add (tmp, pre_p);
 
 	  tmp = build1 (GOTO_EXPR, void_type_node, lab_over);
@@ -7354,12 +7355,13 @@ sh_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p,
 
 	  if (size > 4 && ! TARGET_SH4)
 	    {
-	      tmp = build2 (MODIFY_EXPR, ptr_type_node, next_o, next_o_limit);
+	      tmp = build2 (GIMPLE_MODIFY_STMT, ptr_type_node,
+		  	    next_o, next_o_limit);
 	      gimplify_and_add (tmp, pre_p);
 	    }
 
 	  tmp = build1 (ADDR_EXPR, pptr_type_node, next_stack);
-	  tmp = build2 (MODIFY_EXPR, void_type_node, addr, tmp);
+	  tmp = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, tmp);
 	  gimplify_and_add (tmp, pre_p);
 	}
 
@@ -7376,7 +7378,7 @@ sh_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p,
   tmp = std_gimplify_va_arg_expr (valist, type, pre_p, NULL);
   if (result)
     {
-      tmp = build2 (MODIFY_EXPR, void_type_node, result, tmp);
+      tmp = build2 (GIMPLE_MODIFY_STMT, void_type_node, result, tmp);
       gimplify_and_add (tmp, pre_p);
 
       tmp = build1 (LABEL_EXPR, void_type_node, lab_over);
diff --git a/gcc/config/sparc/sparc.c b/gcc/config/sparc/sparc.c
index b26b59ba2ad02287af5fe76a846e032d4a1895e0..75c7de729e686e348504c1cedd0e7839ac6a3026 100644
--- a/gcc/config/sparc/sparc.c
+++ b/gcc/config/sparc/sparc.c
@@ -5716,7 +5716,7 @@ sparc_gimplify_va_arg (tree valist, tree type, tree *pre_p, tree *post_p)
     addr = fold_convert (ptrtype, addr);
 
   incr = fold (build2 (PLUS_EXPR, ptr_type_node, incr, ssize_int (rsize)));
-  incr = build2 (MODIFY_EXPR, ptr_type_node, valist, incr);
+  incr = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, valist, incr);
   gimplify_and_add (incr, post_p);
 
   return build_va_arg_indirect_ref (addr);
diff --git a/gcc/config/spu/spu.c b/gcc/config/spu/spu.c
index 07680b71ae67c09be7efd0272da19d6225226cf2..4aa8e38be9293746773dfddfcfc5307b0bee25d9 100644
--- a/gcc/config/spu/spu.c
+++ b/gcc/config/spu/spu.c
@@ -2801,7 +2801,7 @@ spu_va_start (tree valist, rtx nextarg)
   if (current_function_pretend_args_size > 0)
     t = build2 (PLUS_EXPR, TREE_TYPE (args), t,
 		build_int_cst (integer_type_node, -STACK_POINTER_OFFSET));
-  t = build2 (MODIFY_EXPR, TREE_TYPE (args), args, t);
+  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (args), args, t);
   TREE_SIDE_EFFECTS (t) = 1;
   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
@@ -2811,7 +2811,7 @@ spu_va_start (tree valist, rtx nextarg)
 	      build_int_cst (integer_type_node,
 			     (current_function_pretend_args_size
 			      - STACK_POINTER_OFFSET)));
-  t = build2 (MODIFY_EXPR, TREE_TYPE (skip), skip, t);
+  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (skip), skip, t);
   TREE_SIDE_EFFECTS (t) = 1;
   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 }
@@ -2876,12 +2876,12 @@ spu_gimplify_va_arg_expr (tree valist, tree type, tree * pre_p,
 		build2 (PLUS_EXPR, ptr_type_node, skip,
 			fold_convert (ptr_type_node, size_int (32))), args);
 
-  tmp = build2 (MODIFY_EXPR, ptr_type_node, addr, tmp);
+  tmp = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, addr, tmp);
   gimplify_and_add (tmp, pre_p);
 
   /* update VALIST.__args */
   tmp = build2 (PLUS_EXPR, ptr_type_node, addr, paddedsize);
-  tmp = build2 (MODIFY_EXPR, TREE_TYPE (args), args, tmp);
+  tmp = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (args), args, tmp);
   gimplify_and_add (tmp, pre_p);
 
   addr = fold_convert (build_pointer_type (type), addr);
diff --git a/gcc/config/stormy16/stormy16.c b/gcc/config/stormy16/stormy16.c
index 04617f577299bf0e0bbef638b96893c4c2b8faa2..00b6e643760f3ed5ba2732252eb2535227004724 100644
--- a/gcc/config/stormy16/stormy16.c
+++ b/gcc/config/stormy16/stormy16.c
@@ -1375,11 +1375,11 @@ xstormy16_expand_builtin_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
   t = make_tree (TREE_TYPE (base), virtual_incoming_args_rtx);
   t = build2 (PLUS_EXPR, TREE_TYPE (base), t, 
 	      build_int_cst (NULL_TREE, INCOMING_FRAME_SP_OFFSET));
-  t = build2 (MODIFY_EXPR, TREE_TYPE (base), base, t);
+  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (base), base, t);
   TREE_SIDE_EFFECTS (t) = 1;
   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
-  t = build2 (MODIFY_EXPR, TREE_TYPE (count), count, 
+  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (count), count, 
 	      build_int_cst (NULL_TREE,
 			     current_function_args_info * UNITS_PER_WORD));
   TREE_SIDE_EFFECTS (t) = 1;
@@ -1434,7 +1434,7 @@ xstormy16_expand_builtin_va_arg (tree valist, tree type, tree *pre_p,
   
       t = fold_convert (ptr_type_node, count_tmp);
       t = build2 (PLUS_EXPR, ptr_type_node, base, t);
-      t = build2 (MODIFY_EXPR, void_type_node, addr, t);
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, t);
       gimplify_and_add (t, pre_p);
 
       t = build1 (GOTO_EXPR, void_type_node, lab_gotaddr);
@@ -1453,7 +1453,7 @@ xstormy16_expand_builtin_va_arg (tree valist, tree type, tree *pre_p,
       tree r, u;
 
       r = size_int (NUM_ARGUMENT_REGISTERS * UNITS_PER_WORD);
-      u = build2 (MODIFY_EXPR, void_type_node, count_tmp, r);
+      u = build2 (GIMPLE_MODIFY_STMT, void_type_node, count_tmp, r);
 
       t = fold_convert (TREE_TYPE (count), r);
       t = build2 (GE_EXPR, boolean_type_node, count_tmp, t);
@@ -1469,7 +1469,7 @@ xstormy16_expand_builtin_va_arg (tree valist, tree type, tree *pre_p,
 	      fold_convert (TREE_TYPE (count), size_tree));
   t = fold_convert (TREE_TYPE (base), fold (t));
   t = build2 (MINUS_EXPR, TREE_TYPE (base), base, t);
-  t = build2 (MODIFY_EXPR, void_type_node, addr, t);
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, t);
   gimplify_and_add (t, pre_p);
 
   t = build1 (LABEL_EXPR, void_type_node, lab_gotaddr);
@@ -1477,7 +1477,7 @@ xstormy16_expand_builtin_va_arg (tree valist, tree type, tree *pre_p,
 
   t = fold_convert (TREE_TYPE (count), size_tree);
   t = build2 (PLUS_EXPR, TREE_TYPE (count), count_tmp, t);
-  t = build2 (MODIFY_EXPR, TREE_TYPE (count), count, t);
+  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (count), count, t);
   gimplify_and_add (t, pre_p);
   
   addr = fold_convert (build_pointer_type (type), addr);
diff --git a/gcc/config/xtensa/xtensa.c b/gcc/config/xtensa/xtensa.c
index 011f63cd275d4dc5a301ca5ca7e05e31c6bde078..49a89920239438901f137bcba08a3b4dbe628821 100644
--- a/gcc/config/xtensa/xtensa.c
+++ b/gcc/config/xtensa/xtensa.c
@@ -2102,7 +2102,7 @@ xtensa_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
 
   /* Call __builtin_saveregs; save the result in __va_reg */
   u = make_tree (ptr_type_node, expand_builtin_saveregs ());
-  t = build2 (MODIFY_EXPR, ptr_type_node, reg, u);
+  t = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, reg, u);
   TREE_SIDE_EFFECTS (t) = 1;
   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
@@ -2110,7 +2110,7 @@ xtensa_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
   u = make_tree (ptr_type_node, virtual_incoming_args_rtx);
   u = fold_build2 (PLUS_EXPR, ptr_type_node, u,
 		   build_int_cst (NULL_TREE, -32));
-  t = build2 (MODIFY_EXPR, ptr_type_node, stk, u);
+  t = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, stk, u);
   TREE_SIDE_EFFECTS (t) = 1;
   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 
@@ -2120,7 +2120,7 @@ xtensa_va_start (tree valist, rtx nextarg ATTRIBUTE_UNUSED)
   if (arg_words >= MAX_ARGS_IN_REGISTERS)
     arg_words += 2;
   u = build_int_cst (NULL_TREE, arg_words * UNITS_PER_WORD);
-  t = build2 (MODIFY_EXPR, integer_type_node, ndx, u);
+  t = build2 (GIMPLE_MODIFY_STMT, integer_type_node, ndx, u);
   TREE_SIDE_EFFECTS (t) = 1;
   expand_expr (t, const0_rtx, VOIDmode, EXPAND_NORMAL);
 }
@@ -2189,7 +2189,7 @@ xtensa_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p,
 		  build_int_cst (NULL_TREE, align - 1));
       t = build2 (BIT_AND_EXPR, integer_type_node, t,
 		  build_int_cst (NULL_TREE, -align));
-      t = build2 (MODIFY_EXPR, integer_type_node, orig_ndx, t);
+      t = build2 (GIMPLE_MODIFY_STMT, integer_type_node, orig_ndx, t);
       gimplify_and_add (t, pre_p);
     }
 
@@ -2200,7 +2200,7 @@ xtensa_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p,
 
   t = fold_convert (integer_type_node, va_size);
   t = build2 (PLUS_EXPR, integer_type_node, orig_ndx, t);
-  t = build2 (MODIFY_EXPR, integer_type_node, ndx, t);
+  t = build2 (GIMPLE_MODIFY_STMT, integer_type_node, ndx, t);
   gimplify_and_add (t, pre_p);
 
 
@@ -2225,7 +2225,7 @@ xtensa_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p,
 		  NULL_TREE);
       gimplify_and_add (t, pre_p);
 
-      t = build2 (MODIFY_EXPR, void_type_node, array, reg);
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, array, reg);
       gimplify_and_add (t, pre_p);
 
       t = build1 (GOTO_EXPR, void_type_node, lab_over);
@@ -2257,13 +2257,13 @@ xtensa_gimplify_va_arg_expr (tree valist, tree type, tree *pre_p,
 
   t = size_binop (PLUS_EXPR, va_size, size_int (32));
   t = fold_convert (integer_type_node, t);
-  t = build2 (MODIFY_EXPR, integer_type_node, ndx, t);
+  t = build2 (GIMPLE_MODIFY_STMT, integer_type_node, ndx, t);
   gimplify_and_add (t, pre_p);
 
   t = build1 (LABEL_EXPR, void_type_node, lab_false2);
   gimplify_and_add (t, pre_p);
 
-  t = build2 (MODIFY_EXPR, void_type_node, array, stk);
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, array, stk);
   gimplify_and_add (t, pre_p);
 
   if (lab_over)
diff --git a/gcc/cp/ChangeLog b/gcc/cp/ChangeLog
index 31c87e20af88c7cf0a15895657f62fc3bbf7cd64..8c57d4fffa31a8e632a7a6699bd768ed2d0dc9d1 100644
--- a/gcc/cp/ChangeLog
+++ b/gcc/cp/ChangeLog
@@ -1,3 +1,20 @@
+2006-12-05  Aldy Hernandez  <aldyh@redhat.com>
+
+	Merge from gimple-tuples-branch.
+	
+	2006-10-05  Aldy Hernandez  <aldyh@redhat.com>
+
+	* cp-gimplify.c (cp_gimplify_expr): Adjust for GIMPLE_MODIFY_STMT.
+	(cxx_omp_clause_apply_fn): Adjust for GIMPLE_MODIFY_STMT.
+	(cxx_omp_clause_copy_ctor): Same.
+	(cxx_omp_clause_assign_op): Same.
+
+	2006-09-28  Aldy Hernandez  <aldyh@redhat.com>
+
+        * cp-tree.h (union lang_tree_node): Gimple statements do not
+	have a TREE_CHAIN.
+	(TREE_INDIRECT_USING): Look in base.
+
 2006-12-04  Jan Hubicka  <jh@suse.cz>
 
 	* cp-objcp-common.c (cp_expr_size): Return NULL in the case
diff --git a/gcc/cp/cp-gimplify.c b/gcc/cp/cp-gimplify.c
index bdb2edf2f41687863194706d9da73b88ecfbcdad..b6ca617ab30c5e90d00044bad313376899d8bfd2 100644
--- a/gcc/cp/cp-gimplify.c
+++ b/gcc/cp/cp-gimplify.c
@@ -483,7 +483,7 @@ cp_gimplify_expr (tree *expr_p, tree *pre_p, tree *post_p)
       ret = GS_OK;
       break;
 
-      /* We used to do this for MODIFY_EXPR as well, but that's unsafe; the
+      /* We used to do this for GIMPLE_MODIFY_STMT as well, but that's unsafe; the
 	 LHS of an assignment might also be involved in the RHS, as in bug
 	 25979.  */
     case INIT_EXPR:
@@ -784,13 +784,13 @@ cxx_omp_clause_apply_fn (tree fn, tree arg1, tree arg2)
       end1 = build2 (PLUS_EXPR, TREE_TYPE (start1), start1, end1);
 
       p1 = create_tmp_var (TREE_TYPE (start1), NULL);
-      t = build2 (MODIFY_EXPR, void_type_node, p1, start1);
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, p1, start1);
       append_to_statement_list (t, &ret);
 
       if (arg2)
 	{
 	  p2 = create_tmp_var (TREE_TYPE (start2), NULL);
-	  t = build2 (MODIFY_EXPR, void_type_node, p2, start2);
+	  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, p2, start2);
 	  append_to_statement_list (t, &ret);
 	}
 
@@ -812,14 +812,14 @@ cxx_omp_clause_apply_fn (tree fn, tree arg1, tree arg2)
 
       t = fold_convert (TREE_TYPE (p1), TYPE_SIZE_UNIT (inner_type));
       t = build2 (PLUS_EXPR, TREE_TYPE (p1), p1, t);
-      t = build2 (MODIFY_EXPR, void_type_node, p1, t);
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, p1, t);
       append_to_statement_list (t, &ret);
 
       if (arg2)
 	{
 	  t = fold_convert (TREE_TYPE (p2), TYPE_SIZE_UNIT (inner_type));
 	  t = build2 (PLUS_EXPR, TREE_TYPE (p2), p2, t);
-	  t = build2 (MODIFY_EXPR, void_type_node, p2, t);
+	  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, p2, t);
 	  append_to_statement_list (t, &ret);
 	}
 
@@ -870,7 +870,7 @@ cxx_omp_clause_copy_ctor (tree clause, tree dst, tree src)
   if (info)
     ret = cxx_omp_clause_apply_fn (TREE_VEC_ELT (info, 0), dst, src);
   if (ret == NULL)
-    ret = build2 (MODIFY_EXPR, void_type_node, dst, src);
+    ret = build2 (GIMPLE_MODIFY_STMT, void_type_node, dst, src);
 
   return ret;
 }
@@ -886,7 +886,7 @@ cxx_omp_clause_assign_op (tree clause, tree dst, tree src)
   if (info)
     ret = cxx_omp_clause_apply_fn (TREE_VEC_ELT (info, 2), dst, src);
   if (ret == NULL)
-    ret = build2 (MODIFY_EXPR, void_type_node, dst, src);
+    ret = build2 (GIMPLE_MODIFY_STMT, void_type_node, dst, src);
 
   return ret;
 }
diff --git a/gcc/cp/cp-tree.h b/gcc/cp/cp-tree.h
index 0270eb3a6c2fc52ddcf1fddd4fa091e403807704..ae250bfbdfef4b14846b42baa47876c72f79c3a4 100644
--- a/gcc/cp/cp-tree.h
+++ b/gcc/cp/cp-tree.h
@@ -486,7 +486,7 @@ enum cp_tree_node_structure_enum {
 
 /* The resulting tree type.  */
 union lang_tree_node GTY((desc ("cp_tree_node_structure (&%h)"),
-       chain_next ("(union lang_tree_node *)TREE_CHAIN (&%h.generic)")))
+       chain_next ("(GIMPLE_STMT_P (&%h.generic) ? (union lang_tree_node *) 0 : (union lang_tree_node *)TREE_CHAIN (&%h.generic))")))
 {
   union tree_node GTY ((tag ("TS_CP_GENERIC"),
 			desc ("tree_node_structure (&%h)"))) generic;
@@ -2067,7 +2067,7 @@ struct lang_decl GTY(())
 
 /* In a TREE_LIST concatenating using directives, indicate indirect
    directives  */
-#define TREE_INDIRECT_USING(NODE) (TREE_LIST_CHECK (NODE)->common.lang_flag_0)
+#define TREE_INDIRECT_USING(NODE) (TREE_LIST_CHECK (NODE)->base.lang_flag_0)
 
 extern tree decl_shadowed_for_var_lookup (tree);
 extern void decl_shadowed_for_var_insert (tree, tree);
diff --git a/gcc/dwarf2out.c b/gcc/dwarf2out.c
index e853b2fde2e8720611d5b88557d4f65bc7759568..9a4903bdb48e8c4ef3f3ab145ef72d6f9a04390e 100644
--- a/gcc/dwarf2out.c
+++ b/gcc/dwarf2out.c
@@ -9266,8 +9266,9 @@ loc_descriptor_from_tree_1 (tree loc, int want_address)
     case NON_LVALUE_EXPR:
     case VIEW_CONVERT_EXPR:
     case SAVE_EXPR:
-    case MODIFY_EXPR:
-      return loc_descriptor_from_tree_1 (TREE_OPERAND (loc, 0), want_address);
+    case GIMPLE_MODIFY_STMT:
+      return loc_descriptor_from_tree_1 (GENERIC_TREE_OPERAND (loc, 0),
+					 want_address);
 
     case COMPONENT_REF:
     case BIT_FIELD_REF:
@@ -10040,7 +10041,7 @@ static tree
 reference_to_unused (tree * tp, int * walk_subtrees,
 		     void * data ATTRIBUTE_UNUSED)
 {
-  if (! EXPR_P (*tp) && ! CONSTANT_CLASS_P (*tp))
+  if (! EXPR_P (*tp) && ! GIMPLE_STMT_P (*tp) && ! CONSTANT_CLASS_P (*tp))
     *walk_subtrees = 0;
   
   if (DECL_P (*tp) && ! TREE_PUBLIC (*tp) && ! TREE_USED (*tp)
diff --git a/gcc/expr.c b/gcc/expr.c
index 7182b57442350af311db9dbefba68215cce70638..05bb9b80f6c735e18988aa29100e53242b18b335 100644
--- a/gcc/expr.c
+++ b/gcc/expr.c
@@ -6247,6 +6247,9 @@ safe_from_p (rtx x, tree exp, int top_p)
     case tcc_type:
       /* Should never get a type here.  */
       gcc_unreachable ();
+
+    case tcc_gimple_stmt:
+      gcc_unreachable ();
     }
 
   /* If we have an rtl, find any enclosed object.  Then see if we conflict
@@ -6667,7 +6670,7 @@ expand_expr_real (tree exp, rtx target, enum machine_mode tmode,
 
   /* Handle ERROR_MARK before anybody tries to access its type.  */
   if (TREE_CODE (exp) == ERROR_MARK
-      || TREE_CODE (TREE_TYPE (exp)) == ERROR_MARK)
+      || (!GIMPLE_TUPLE_P (exp) && TREE_CODE (TREE_TYPE (exp)) == ERROR_MARK))
     {
       ret = CONST0_RTX (tmode);
       return ret ? ret : const0_rtx;
@@ -6737,7 +6740,7 @@ expand_expr_real_1 (tree exp, rtx target, enum machine_mode tmode,
 		    enum expand_modifier modifier, rtx *alt_rtl)
 {
   rtx op0, op1, temp, decl_rtl;
-  tree type = TREE_TYPE (exp);
+  tree type;
   int unsignedp;
   enum machine_mode mode;
   enum tree_code code = TREE_CODE (exp);
@@ -6752,8 +6755,18 @@ expand_expr_real_1 (tree exp, rtx target, enum machine_mode tmode,
 								  type)	  \
 				 : (expr))
 
-  mode = TYPE_MODE (type);
-  unsignedp = TYPE_UNSIGNED (type);
+  if (GIMPLE_STMT_P (exp))
+    {
+      type = void_type_node;
+      mode = VOIDmode;
+      unsignedp = 0;
+    }
+  else
+    {
+      type = TREE_TYPE (exp);
+      mode = TYPE_MODE (type);
+      unsignedp = TYPE_UNSIGNED (type);
+    }
   if (lang_hooks.reduce_bit_field_operations
       && TREE_CODE (type) == INTEGER_TYPE
       && GET_MODE_PRECISION (mode) > TYPE_PRECISION (type))
@@ -8563,10 +8576,10 @@ expand_expr_real_1 (tree exp, rtx target, enum machine_mode tmode,
 	target = expand_vec_cond_expr (exp, target);
 	return target;
 
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       {
-	tree lhs = TREE_OPERAND (exp, 0);
-	tree rhs = TREE_OPERAND (exp, 1);
+	tree lhs = GIMPLE_STMT_OPERAND (exp, 0);
+	tree rhs = GIMPLE_STMT_OPERAND (exp, 1);
 
 	gcc_assert (ignore);
 
diff --git a/gcc/fold-const.c b/gcc/fold-const.c
index 93dee15ce287955caec97e1964f1cc34a8e74f50..0908e2840f2f0dbe69201ee34a6b62a16eb73f1c 100644
--- a/gcc/fold-const.c
+++ b/gcc/fold-const.c
@@ -41,7 +41,11 @@ Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
 
    force_fit_type takes a constant, an overflowable flag and prior
    overflow indicators.  It forces the value to fit the type and sets
-   TREE_OVERFLOW and TREE_CONSTANT_OVERFLOW as appropriate.  */
+   TREE_OVERFLOW and TREE_CONSTANT_OVERFLOW as appropriate.
+   
+   Note: Since the folders get called on non-gimple code as well as
+   gimple code, we need to handle GIMPLE tuples as well as their
+   corresponding tree equivalents.  */
 
 #include "config.h"
 #include "system.h"
@@ -2181,6 +2185,7 @@ maybe_lvalue_p (tree x)
   case WITH_CLEANUP_EXPR:
   case COMPOUND_EXPR:
   case MODIFY_EXPR:
+  case GIMPLE_MODIFY_STMT:
   case TARGET_EXPR:
   case COND_EXPR:
   case BIND_EXPR:
@@ -7474,15 +7479,17 @@ fold_unary (enum tree_code code, tree type, tree op0)
 	    return fold_convert (type, build_fold_addr_expr (base));
         }
 
-      if (TREE_CODE (op0) == MODIFY_EXPR
-	  && TREE_CONSTANT (TREE_OPERAND (op0, 1))
+      if ((TREE_CODE (op0) == MODIFY_EXPR
+	   || TREE_CODE (op0) == GIMPLE_MODIFY_STMT)
+	  && TREE_CONSTANT (GENERIC_TREE_OPERAND (op0, 1))
 	  /* Detect assigning a bitfield.  */
-	  && !(TREE_CODE (TREE_OPERAND (op0, 0)) == COMPONENT_REF
-	       && DECL_BIT_FIELD (TREE_OPERAND (TREE_OPERAND (op0, 0), 1))))
+	  && !(TREE_CODE (GENERIC_TREE_OPERAND (op0, 0)) == COMPONENT_REF
+	       && DECL_BIT_FIELD
+	       (TREE_OPERAND (GENERIC_TREE_OPERAND (op0, 0), 1))))
 	{
 	  /* Don't leave an assignment inside a conversion
 	     unless assigning a bitfield.  */
-	  tem = fold_build1 (code, type, TREE_OPERAND (op0, 1));
+	  tem = fold_build1 (code, type, GENERIC_TREE_OPERAND (op0, 1));
 	  /* First do the assignment, then return converted constant.  */
 	  tem = build2 (COMPOUND_EXPR, TREE_TYPE (tem), op0, tem);
 	  TREE_NO_WARNING (tem) = 1;
@@ -8461,7 +8468,8 @@ fold_binary (enum tree_code code, tree type, tree op0, tree op1)
   tree arg0, arg1, tem;
   tree t1 = NULL_TREE;
 
-  gcc_assert (IS_EXPR_CODE_CLASS (kind)
+  gcc_assert ((IS_EXPR_CODE_CLASS (kind)
+	       || IS_GIMPLE_STMT_CODE_CLASS (kind))
 	      && TREE_CODE_LENGTH (code) == 2
 	      && op0 != NULL_TREE
 	      && op1 != NULL_TREE);
@@ -11673,7 +11681,8 @@ fold (tree expr)
   if (kind == tcc_constant)
     return t;
 
-  if (IS_EXPR_CODE_CLASS (kind))
+  if (IS_EXPR_CODE_CLASS (kind)
+      || IS_GIMPLE_STMT_CODE_CLASS (kind))
     {
       tree type = TREE_TYPE (t);
       tree op0, op1, op2;
@@ -12359,7 +12368,8 @@ tree_expr_nonnegative_p (tree t)
 
     case COMPOUND_EXPR:
     case MODIFY_EXPR:
-      return tree_expr_nonnegative_p (TREE_OPERAND (t, 1));
+    case GIMPLE_MODIFY_STMT:
+      return tree_expr_nonnegative_p (GENERIC_TREE_OPERAND (t, 1));
 
     case BIND_EXPR:
       return tree_expr_nonnegative_p (expr_last (TREE_OPERAND (t, 1)));
@@ -12419,9 +12429,10 @@ tree_expr_nonnegative_p (tree t)
 	    else
 	      break;
 	  }
-	if (TREE_CODE (t) == MODIFY_EXPR
-	    && TREE_OPERAND (t, 0) == temp)
-	  return tree_expr_nonnegative_p (TREE_OPERAND (t, 1));
+	if ((TREE_CODE (t) == MODIFY_EXPR
+	     || TREE_CODE (t) == GIMPLE_MODIFY_STMT)
+	    && GENERIC_TREE_OPERAND (t, 0) == temp)
+	  return tree_expr_nonnegative_p (GENERIC_TREE_OPERAND (t, 1));
 
 	return false;
       }
@@ -12657,8 +12668,9 @@ tree_expr_nonzero_p (tree t)
 
     case COMPOUND_EXPR:
     case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
     case BIND_EXPR:
-      return tree_expr_nonzero_p (TREE_OPERAND (t, 1));
+      return tree_expr_nonzero_p (GENERIC_TREE_OPERAND (t, 1));
 
     case SAVE_EXPR:
     case NON_LVALUE_EXPR:
diff --git a/gcc/fortran/f95-lang.c b/gcc/fortran/f95-lang.c
index 52c0b5f5adbb2c4ce5c639ab79a92bdaa235c2e8..11513186c046869c0ad37ff213475c7c55243a72 100644
--- a/gcc/fortran/f95-lang.c
+++ b/gcc/fortran/f95-lang.c
@@ -62,7 +62,8 @@ GTY(())
 
 union lang_tree_node
 GTY((desc ("TREE_CODE (&%h.generic) == IDENTIFIER_NODE"),
-     chain_next ("(union lang_tree_node *)TREE_CHAIN (&%h.generic)")))
+     chain_next ("(GIMPLE_STMT_P (&%h.generic) ? (union lang_tree_node *) 0 : (union lang_tree_node *)TREE_CHAIN (&%h.generic))")))
+
 {
   union tree_node GTY((tag ("0"),
 		       desc ("tree_node_structure (&%h)"))) generic;
diff --git a/gcc/fortran/resolve.c b/gcc/fortran/resolve.c
index e31ecbd5909e8f6cb3c2f88037f188bc9fb703d4..8cbcac93dab20b8f85bc6a9156b961ca1d12cc48 100644
--- a/gcc/fortran/resolve.c
+++ b/gcc/fortran/resolve.c
@@ -5741,6 +5741,19 @@ resolve_fl_derived (gfc_symbol *sym)
       sym->ns->derived_types = dt_list;
     }
 
+  /* Add derived type to the derived type list.  */
+  for (dt_list = sym->ns->derived_types; dt_list; dt_list = dt_list->next)
+    if (sym == dt_list->derived)
+      break;
+
+  if (dt_list == NULL)
+    {
+      dt_list = gfc_get_dt_list ();
+      dt_list->next = sym->ns->derived_types;
+      dt_list->derived = sym;
+      sym->ns->derived_types = dt_list;
+    }
+
   return SUCCESS;
 }
 
diff --git a/gcc/fortran/trans-array.c b/gcc/fortran/trans-array.c
index 991fa1c18ea916c5b39c61f706012cf3f150a2f9..0049ad5b54b86c081ed5757a058815dc03fe1dfe 100644
--- a/gcc/fortran/trans-array.c
+++ b/gcc/fortran/trans-array.c
@@ -156,10 +156,18 @@ gfc_conv_descriptor_data_get (tree desc)
   return t;
 }
 
-/* This provides WRITE access to the data field.  */
+/* This provides WRITE access to the data field.
+
+   TUPLES_P is true if we are generating tuples.
+   
+   This function gets called through the following macros:
+     gfc_conv_descriptor_data_set
+     gfc_conv_descriptor_data_set_tuples.  */
 
 void
-gfc_conv_descriptor_data_set (stmtblock_t *block, tree desc, tree value)
+gfc_conv_descriptor_data_set_internal (stmtblock_t *block,
+				       tree desc, tree value,
+				       bool tuples_p)
 {
   tree field, type, t;
 
@@ -170,7 +178,7 @@ gfc_conv_descriptor_data_set (stmtblock_t *block, tree desc, tree value)
   gcc_assert (DATA_FIELD == 0);
 
   t = build3 (COMPONENT_REF, TREE_TYPE (field), desc, field, NULL_TREE);
-  gfc_add_modify_expr (block, t, fold_convert (TREE_TYPE (field), value));
+  gfc_add_modify (block, t, fold_convert (TREE_TYPE (field), value), tuples_p);
 }
 
 
diff --git a/gcc/fortran/trans-array.h b/gcc/fortran/trans-array.h
index 3374c4ceac9eb14cd34778e7226f3e8573f5f87c..38ad123624b291f8674363ded33256c5b2fb6b1d 100644
--- a/gcc/fortran/trans-array.h
+++ b/gcc/fortran/trans-array.h
@@ -118,7 +118,11 @@ tree gfc_conv_array_ubound (tree, int);
 
 /* Build expressions for accessing components of an array descriptor.  */
 tree gfc_conv_descriptor_data_get (tree);
-void gfc_conv_descriptor_data_set (stmtblock_t *, tree, tree);
+void gfc_conv_descriptor_data_set_internal (stmtblock_t *, tree, tree, bool);
+#define gfc_conv_descriptor_data_set(BLOCK, T1, T2)			\
+  gfc_conv_descriptor_data_set_internal ((BLOCK), (T1), (T2), false)
+#define gfc_conv_descriptor_data_set_tuples(BLOCK, T1, T2)		\
+  gfc_conv_descriptor_data_set_internal ((BLOCK), (T1), (T2), true)
 tree gfc_conv_descriptor_data_addr (tree);
 tree gfc_conv_descriptor_offset (tree);
 tree gfc_conv_descriptor_dtype (tree);
diff --git a/gcc/fortran/trans-openmp.c b/gcc/fortran/trans-openmp.c
index fa8be1d72ecfd2ab09d66e51aaa6d9f56f8c922a..827631612772aff6d990aa5c49f41dcc12d9b14a 100644
--- a/gcc/fortran/trans-openmp.c
+++ b/gcc/fortran/trans-openmp.c
@@ -111,7 +111,7 @@ gfc_omp_clause_default_ctor (tree clause ATTRIBUTE_UNUSED, tree decl)
      "not currently allocated" allocation status.  */
   gfc_init_block (&block);
 
-  gfc_conv_descriptor_data_set (&block, decl, null_pointer_node);
+  gfc_conv_descriptor_data_set_tuples (&block, decl, null_pointer_node);
 
   return gfc_finish_block (&block);
 }
@@ -832,7 +832,7 @@ gfc_trans_omp_atomic (gfc_code *code)
 	  tree accum = gfc_create_var (TREE_TYPE (rse.expr), NULL);
 	  gfc_actual_arglist *arg;
 
-	  gfc_add_modify_expr (&block, accum, rse.expr);
+	  gfc_add_modify_stmt (&block, accum, rse.expr);
 	  for (arg = expr2->value.function.actual->next->next; arg;
 	       arg = arg->next)
 	    {
@@ -840,7 +840,7 @@ gfc_trans_omp_atomic (gfc_code *code)
 	      gfc_conv_expr (&rse, arg->expr);
 	      gfc_add_block_to_block (&block, &rse.pre);
 	      x = fold_build2 (op, TREE_TYPE (accum), accum, rse.expr);
-	      gfc_add_modify_expr (&block, accum, x);
+	      gfc_add_modify_stmt (&block, accum, x);
 	    }
 
 	  rse.expr = accum;
@@ -957,11 +957,11 @@ gfc_trans_omp_do (gfc_code *code, stmtblock_t *pblock,
   /* Loop body.  */
   if (simple)
     {
-      init = build2_v (MODIFY_EXPR, dovar, from);
+      init = build2_v (GIMPLE_MODIFY_STMT, dovar, from);
       cond = build2 (simple > 0 ? LE_EXPR : GE_EXPR, boolean_type_node,
 		     dovar, to);
       incr = fold_build2 (PLUS_EXPR, type, dovar, step);
-      incr = fold_build2 (MODIFY_EXPR, type, dovar, incr);
+      incr = fold_build2 (GIMPLE_MODIFY_STMT, type, dovar, incr);
       if (pblock != &block)
 	{
 	  pushlevel (0);
@@ -983,10 +983,10 @@ gfc_trans_omp_do (gfc_code *code, stmtblock_t *pblock,
       tmp = fold_build2 (TRUNC_DIV_EXPR, type, tmp, step);
       tmp = gfc_evaluate_now (tmp, pblock);
       count = gfc_create_var (type, "count");
-      init = build2_v (MODIFY_EXPR, count, build_int_cst (type, 0));
+      init = build2_v (GIMPLE_MODIFY_STMT, count, build_int_cst (type, 0));
       cond = build2 (LT_EXPR, boolean_type_node, count, tmp);
       incr = fold_build2 (PLUS_EXPR, type, count, build_int_cst (type, 1));
-      incr = fold_build2 (MODIFY_EXPR, type, count, incr);
+      incr = fold_build2 (GIMPLE_MODIFY_STMT, type, count, incr);
 
       if (pblock != &block)
 	{
@@ -998,7 +998,7 @@ gfc_trans_omp_do (gfc_code *code, stmtblock_t *pblock,
       /* Initialize DOVAR.  */
       tmp = fold_build2 (MULT_EXPR, type, count, step);
       tmp = build2 (PLUS_EXPR, type, from, tmp);
-      gfc_add_modify_expr (&body, dovar, tmp);
+      gfc_add_modify_stmt (&body, dovar, tmp);
     }
 
   if (!dovar_found)
diff --git a/gcc/fortran/trans.c b/gcc/fortran/trans.c
index 69a702e6034e0c8c9444343944f349827b6ec6ee..3040319f14ea99253b0b15a7532958e1b18cc094 100644
--- a/gcc/fortran/trans.c
+++ b/gcc/fortran/trans.c
@@ -140,11 +140,13 @@ gfc_evaluate_now (tree expr, stmtblock_t * pblock)
 }
 
 
-/* Build a MODIFY_EXPR node and add it to a given statement block PBLOCK.
-   A MODIFY_EXPR is an assignment: LHS <- RHS.  */
+/* Build a MODIFY_EXPR (or GIMPLE_MODIFY_STMT) node and add it to a
+   given statement block PBLOCK.  A MODIFY_EXPR is an assignment:
+   LHS <- RHS.  */
 
 void
-gfc_add_modify_expr (stmtblock_t * pblock, tree lhs, tree rhs)
+gfc_add_modify (stmtblock_t * pblock, tree lhs, tree rhs,
+		bool tuples_p)
 {
   tree tmp;
 
@@ -157,7 +159,8 @@ gfc_add_modify_expr (stmtblock_t * pblock, tree lhs, tree rhs)
 	      || AGGREGATE_TYPE_P (TREE_TYPE (lhs)));
 #endif
 
-  tmp = fold_build2 (MODIFY_EXPR, void_type_node, lhs, rhs);
+  tmp = fold_build2 (tuples_p ? GIMPLE_MODIFY_STMT : MODIFY_EXPR,
+		     void_type_node, lhs, rhs);
   gfc_add_expr_to_block (pblock, tmp);
 }
 
diff --git a/gcc/fortran/trans.h b/gcc/fortran/trans.h
index f471f093af99311e1591c9a6dcace85965df1aa7..ed96838608307e54758c1de86993e050ac9ae334 100644
--- a/gcc/fortran/trans.h
+++ b/gcc/fortran/trans.h
@@ -334,8 +334,12 @@ void gfc_trans_vla_type_sizes (gfc_symbol *, stmtblock_t *);
 void gfc_add_expr_to_block (stmtblock_t *, tree);
 /* Add a block to the end of a block.  */
 void gfc_add_block_to_block (stmtblock_t *, stmtblock_t *);
-/* Add a MODIFY_EXPR to a block.  */
-void gfc_add_modify_expr (stmtblock_t *, tree, tree);
+/* Add a MODIFY_EXPR or a GIMPLE_MODIFY_STMT to a block.  */
+void gfc_add_modify (stmtblock_t *, tree, tree, bool);
+#define gfc_add_modify_expr(BLOCK, LHS, RHS) \
+       gfc_add_modify ((BLOCK), (LHS), (RHS), false)
+#define gfc_add_modify_stmt(BLOCK, LHS, RHS) \
+       gfc_add_modify ((BLOCK), (LHS), (RHS), true)
 
 /* Initialize a statement block.  */
 void gfc_init_block (stmtblock_t *);
diff --git a/gcc/function.c b/gcc/function.c
index da93fa2af6ec5b812c4260915c75c866b59724f3..b61b9004a78cbc60dbbb1db1cf9123788d711299 100644
--- a/gcc/function.c
+++ b/gcc/function.c
@@ -1609,7 +1609,7 @@ static tree
 instantiate_expr (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
 {
   tree t = *tp;
-  if (! EXPR_P (t))
+  if (! EXPR_P (t) && ! GIMPLE_STMT_P (t))
     {
       *walk_subtrees = 0;
       if (DECL_P (t) && DECL_RTL_SET_P (t))
@@ -3227,11 +3227,11 @@ gimplify_parameters (void)
 		  t = built_in_decls[BUILT_IN_ALLOCA];
 		  t = build_function_call_expr (t, args);
 		  t = fold_convert (ptr_type, t);
-		  t = build2 (MODIFY_EXPR, void_type_node, addr, t);
+		  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, t);
 		  gimplify_and_add (t, &stmts);
 		}
 
-	      t = build2 (MODIFY_EXPR, void_type_node, local, parm);
+	      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, local, parm);
 	      gimplify_and_add (t, &stmts);
 
 	      SET_DECL_VALUE_EXPR (parm, local);
diff --git a/gcc/function.h b/gcc/function.h
index 63d42dcc79f211d6423a9c1aa43d8c7dc078ac98..b37907cc41615a0ae4b4adad104b1fea6e7ef7d1 100644
--- a/gcc/function.h
+++ b/gcc/function.h
@@ -469,6 +469,11 @@ struct function GTY(())
   /* Number of units of floating point registers that need saving in stdarg
      function.  */
   unsigned int va_list_fpr_size : 8;
+
+  /* FIXME tuples: This bit is temporarily here to mark when a
+     function has been gimplified, so we can make sure we're not
+     creating non GIMPLE tuples after gimplification.  */
+  unsigned gimplified : 1;
 };
 
 /* If va_list_[gf]pr_size is set to this, it means we don't know how
diff --git a/gcc/gimple-low.c b/gcc/gimple-low.c
index c6a0312a2bea88bd7a934778832a257034ddb28a..9c68447206c3a0b2ba7e73918bd264f5869cbb9d 100644
--- a/gcc/gimple-low.c
+++ b/gcc/gimple-low.c
@@ -138,7 +138,7 @@ lower_function_body (void)
       arg = tree_cons (NULL, t, NULL);
       t = implicit_built_in_decls[BUILT_IN_SETJMP_DISPATCHER];
       t = build_function_call_expr (t,arg);
-      x = build2 (MODIFY_EXPR, void_type_node, disp_var, t);
+      x = build2 (GIMPLE_MODIFY_STMT, void_type_node, disp_var, t);
 
       /* Build 'goto DISP_VAR;' and insert.  */
       tsi_link_after (&i, x, TSI_CONTINUE_LINKING);
@@ -254,9 +254,9 @@ lower_stmt (tree_stmt_iterator *tsi, struct lower_data *data)
     case OMP_CONTINUE:
       break;
 
-    case MODIFY_EXPR:
-      if (TREE_CODE (TREE_OPERAND (stmt, 1)) == CALL_EXPR)
-	stmt = TREE_OPERAND (stmt, 1);
+    case GIMPLE_MODIFY_STMT:
+      if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == CALL_EXPR)
+	stmt = GIMPLE_STMT_OPERAND (stmt, 1);
       else
 	break;
       /* FALLTHRU */
@@ -436,9 +436,9 @@ block_may_fallthru (tree block)
       return (block_may_fallthru (TREE_OPERAND (stmt, 0))
 	      && block_may_fallthru (TREE_OPERAND (stmt, 1)));
 
-    case MODIFY_EXPR:
-      if (TREE_CODE (TREE_OPERAND (stmt, 1)) == CALL_EXPR)
-	stmt = TREE_OPERAND (stmt, 1);
+    case GIMPLE_MODIFY_STMT:
+      if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == CALL_EXPR)
+	stmt = GIMPLE_STMT_OPERAND (stmt, 1);
       else
 	return true;
       /* FALLTHRU */
@@ -560,15 +560,15 @@ lower_return_expr (tree_stmt_iterator *tsi, struct lower_data *data)
 
   /* Extract the value being returned.  */
   value = TREE_OPERAND (stmt, 0);
-  if (value && TREE_CODE (value) == MODIFY_EXPR)
-    value = TREE_OPERAND (value, 1);
+  if (value && TREE_CODE (value) == GIMPLE_MODIFY_STMT)
+    value = GIMPLE_STMT_OPERAND (value, 1);
 
   /* Match this up with an existing return statement that's been created.  */
   for (t = data->return_statements; t ; t = TREE_CHAIN (t))
     {
       tree tvalue = TREE_OPERAND (TREE_VALUE (t), 0);
-      if (tvalue && TREE_CODE (tvalue) == MODIFY_EXPR)
-	tvalue = TREE_OPERAND (tvalue, 1);
+      if (tvalue && TREE_CODE (tvalue) == GIMPLE_MODIFY_STMT)
+	tvalue = GIMPLE_STMT_OPERAND (tvalue, 1);
 
       if (value == tvalue)
 	{
@@ -654,10 +654,10 @@ lower_builtin_setjmp (tree_stmt_iterator *tsi)
      passed to both __builtin_setjmp_setup and __builtin_setjmp_receiver.  */
   FORCED_LABEL (next_label) = 1;
 
-  if (TREE_CODE (stmt) == MODIFY_EXPR)
+  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
     {
-      dest = TREE_OPERAND (stmt, 0);
-      stmt = TREE_OPERAND (stmt, 1);
+      dest = GIMPLE_STMT_OPERAND (stmt, 0);
+      stmt = GIMPLE_STMT_OPERAND (stmt, 1);
     }
   else
     dest = NULL_TREE;
@@ -665,7 +665,7 @@ lower_builtin_setjmp (tree_stmt_iterator *tsi)
   /* Build '__builtin_setjmp_setup (BUF, NEXT_LABEL)' and insert.  */
   t = build_addr (next_label, current_function_decl);
   arg = tree_cons (NULL, t, NULL);
-  t = TREE_VALUE (TREE_OPERAND (stmt, 1));
+  t = TREE_VALUE (GENERIC_TREE_OPERAND (stmt, 1));
   arg = tree_cons (NULL, t, arg);
   t = implicit_built_in_decls[BUILT_IN_SETJMP_SETUP];
   t = build_function_call_expr (t, arg);
@@ -675,7 +675,7 @@ lower_builtin_setjmp (tree_stmt_iterator *tsi)
   /* Build 'DEST = 0' and insert.  */
   if (dest)
     {
-      t = build2 (MODIFY_EXPR, void_type_node, dest, integer_zero_node);
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, dest, integer_zero_node);
       SET_EXPR_LOCUS (t, EXPR_LOCUS (stmt));
       tsi_link_before (tsi, t, TSI_SAME_STMT);
     }
@@ -699,7 +699,7 @@ lower_builtin_setjmp (tree_stmt_iterator *tsi)
   /* Build 'DEST = 1' and insert.  */
   if (dest)
     {
-      t = build2 (MODIFY_EXPR, void_type_node, dest, integer_one_node);
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, dest, integer_one_node);
       SET_EXPR_LOCUS (t, EXPR_LOCUS (stmt));
       tsi_link_before (tsi, t, TSI_SAME_STMT);
     }
diff --git a/gcc/gimplify.c b/gcc/gimplify.c
index ce91852eea3d8b039c7dffb029fef9f6d95400f1..efe6b96dcdf6205648d32a48e466457956ee8f22 100644
--- a/gcc/gimplify.c
+++ b/gcc/gimplify.c
@@ -769,7 +769,8 @@ should_carry_locus_p (tree stmt)
 static void
 annotate_one_with_locus (tree t, location_t locus)
 {
-  if (EXPR_P (t) && ! EXPR_HAS_LOCATION (t) && should_carry_locus_p (t))
+  if (CAN_HAVE_LOCATION_P (t)
+      && ! EXPR_HAS_LOCATION (t) && should_carry_locus_p (t))
     SET_EXPR_LOCATION (t, locus);
 }
 
@@ -1040,7 +1041,7 @@ build_stack_save_restore (tree *save, tree *restore)
 				NULL_TREE);
   tmp_var = create_tmp_var (ptr_type_node, "saved_stack");
 
-  *save = build2 (MODIFY_EXPR, ptr_type_node, tmp_var, save_call);
+  *save = build2 (GIMPLE_MODIFY_STMT, ptr_type_node, tmp_var, save_call);
   *restore =
     build_function_call_expr (implicit_built_in_decls[BUILT_IN_STACK_RESTORE],
 			      tree_cons (NULL_TREE, tmp_var, NULL_TREE));
@@ -1141,12 +1142,13 @@ gimplify_return_expr (tree stmt, tree *pre_p)
     result_decl = NULL_TREE;
   else
     {
-      result_decl = TREE_OPERAND (ret_expr, 0);
+      result_decl = GENERIC_TREE_OPERAND (ret_expr, 0);
       if (TREE_CODE (result_decl) == INDIRECT_REF)
 	/* See through a return by reference.  */
 	result_decl = TREE_OPERAND (result_decl, 0);
 
       gcc_assert ((TREE_CODE (ret_expr) == MODIFY_EXPR
+	    	   || TREE_CODE (ret_expr) == GIMPLE_MODIFY_STMT
 		   || TREE_CODE (ret_expr) == INIT_EXPR)
 		  && TREE_CODE (result_decl) == RESULT_DECL);
     }
@@ -1177,10 +1179,10 @@ gimplify_return_expr (tree stmt, tree *pre_p)
       gimplify_ctxp->return_temp = result;
     }
 
-  /* Smash the lhs of the MODIFY_EXPR to the temporary we plan to use.
+  /* Smash the lhs of the GIMPLE_MODIFY_STMT to the temporary we plan to use.
      Then gimplify the whole thing.  */
   if (result != result_decl)
-    TREE_OPERAND (ret_expr, 0) = result;
+    GENERIC_TREE_OPERAND (ret_expr, 0) = result;
 
   gimplify_and_add (TREE_OPERAND (stmt, 0), pre_p);
 
@@ -1189,7 +1191,8 @@ gimplify_return_expr (tree stmt, tree *pre_p)
   if (result == result_decl)
     ret_expr = result;
   else
-    ret_expr = build2 (MODIFY_EXPR, TREE_TYPE (result), result_decl, result);
+    ret_expr = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (result), result_decl,
+		       result);
   TREE_OPERAND (stmt, 0) = ret_expr;
 
   return GS_ALL_DONE;
@@ -1244,7 +1247,7 @@ gimplify_decl_expr (tree *stmt_p)
 	  t = built_in_decls[BUILT_IN_ALLOCA];
 	  t = build_function_call_expr (t, args);
 	  t = fold_convert (ptr_type, t);
-	  t = build2 (MODIFY_EXPR, void_type_node, addr, t);
+	  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, addr, t);
 
 	  gimplify_and_add (t, stmt_p);
 
@@ -1943,7 +1946,7 @@ gimplify_self_mod_expr (tree *expr_p, tree *pre_p, tree *post_p,
     }
 
   t1 = build2 (arith_code, TREE_TYPE (*expr_p), lhs, rhs);
-  t1 = build2 (MODIFY_EXPR, TREE_TYPE (lvalue), lvalue, t1);
+  t1 = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (lvalue), lvalue, t1);
 
   if (postfix)
     {
@@ -2466,12 +2469,14 @@ gimplify_cond_expr (tree *expr_p, tree *pre_p, fallback_t fallback)
 	 if this branch is void; in C++ it can be, if it's a throw.  */
       if (TREE_TYPE (TREE_OPERAND (expr, 1)) != void_type_node)
 	TREE_OPERAND (expr, 1)
-	  = build2 (MODIFY_EXPR, void_type_node, tmp, TREE_OPERAND (expr, 1));
+	  = build2 (GIMPLE_MODIFY_STMT, void_type_node, tmp,
+	      	    TREE_OPERAND (expr, 1));
 
       /* Build the else clause, 't1 = b;'.  */
       if (TREE_TYPE (TREE_OPERAND (expr, 2)) != void_type_node)
 	TREE_OPERAND (expr, 2)
-	  = build2 (MODIFY_EXPR, void_type_node, tmp2, TREE_OPERAND (expr, 2));
+	  = build2 (GIMPLE_MODIFY_STMT, void_type_node, tmp2,
+	      	    TREE_OPERAND (expr, 2));
 
       TREE_TYPE (expr) = void_type_node;
       recalculate_side_effects (expr);
@@ -2551,8 +2556,8 @@ gimplify_modify_expr_to_memcpy (tree *expr_p, tree size, bool want_value)
 {
   tree args, t, to, to_ptr, from;
 
-  to = TREE_OPERAND (*expr_p, 0);
-  from = TREE_OPERAND (*expr_p, 1);
+  to = GENERIC_TREE_OPERAND (*expr_p, 0);
+  from = GENERIC_TREE_OPERAND (*expr_p, 1);
 
   args = tree_cons (NULL, size, NULL);
 
@@ -2583,7 +2588,7 @@ gimplify_modify_expr_to_memset (tree *expr_p, tree size, bool want_value)
 {
   tree args, t, to, to_ptr;
 
-  to = TREE_OPERAND (*expr_p, 0);
+  to = GENERIC_TREE_OPERAND (*expr_p, 0);
 
   args = tree_cons (NULL, size, NULL);
 
@@ -2746,7 +2751,8 @@ gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
   /* Create and initialize the index variable.  */
   var_type = TREE_TYPE (upper);
   var = create_tmp_var (var_type, NULL);
-  append_to_statement_list (build2 (MODIFY_EXPR, var_type, var, lower), pre_p);
+  append_to_statement_list (build2 (GIMPLE_MODIFY_STMT, var_type, var, lower),
+			    pre_p);
 
   /* Add the loop entry label.  */
   append_to_statement_list (build1 (LABEL_EXPR,
@@ -2767,7 +2773,7 @@ gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
     gimplify_init_ctor_eval (cref, CONSTRUCTOR_ELTS (value),
 			     pre_p, cleared);
   else
-    append_to_statement_list (build2 (MODIFY_EXPR, TREE_TYPE (cref),
+    append_to_statement_list (build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (cref),
 				      cref, value),
 			      pre_p);
 
@@ -2782,7 +2788,7 @@ gimplify_init_ctor_eval_range (tree object, tree lower, tree upper,
 		    pre_p);
 
   /* Otherwise, increment the index var...  */
-  append_to_statement_list (build2 (MODIFY_EXPR, var_type, var,
+  append_to_statement_list (build2 (GIMPLE_MODIFY_STMT, var_type, var,
 				    build2 (PLUS_EXPR, var_type, var,
 					    fold_convert (var_type,
 							  integer_one_node))),
@@ -2918,7 +2924,7 @@ gimplify_init_constructor (tree *expr_p, tree *pre_p,
 			   tree *post_p, bool want_value)
 {
   tree object;
-  tree ctor = TREE_OPERAND (*expr_p, 1);
+  tree ctor = GENERIC_TREE_OPERAND (*expr_p, 1);
   tree type = TREE_TYPE (ctor);
   enum gimplify_status ret;
   VEC(constructor_elt,gc) *elts;
@@ -2926,11 +2932,11 @@ gimplify_init_constructor (tree *expr_p, tree *pre_p,
   if (TREE_CODE (ctor) != CONSTRUCTOR)
     return GS_UNHANDLED;
 
-  ret = gimplify_expr (&TREE_OPERAND (*expr_p, 0), pre_p, post_p,
+  ret = gimplify_expr (&GENERIC_TREE_OPERAND (*expr_p, 0), pre_p, post_p,
 		       is_gimple_lvalue, fb_lvalue);
   if (ret == GS_ERROR)
     return ret;
-  object = TREE_OPERAND (*expr_p, 0);
+  object = GENERIC_TREE_OPERAND (*expr_p, 0);
 
   elts = CONSTRUCTOR_ELTS (ctor);
 
@@ -3056,7 +3062,7 @@ gimplify_init_constructor (tree *expr_p, tree *pre_p,
 		  }
 	        walk_tree (&DECL_INITIAL (new), force_labels_r, NULL, NULL);
 
-		TREE_OPERAND (*expr_p, 1) = new;
+		GENERIC_TREE_OPERAND (*expr_p, 1) = new;
 
 		/* This is no longer an assignment of a CONSTRUCTOR, but
 		   we still may have processing to do on the LHS.  So
@@ -3075,7 +3081,7 @@ gimplify_init_constructor (tree *expr_p, tree *pre_p,
 	      preeval_data.lhs_base_decl = NULL;
 	    preeval_data.lhs_alias_set = get_alias_set (object);
 
-	    gimplify_init_ctor_preeval (&TREE_OPERAND (*expr_p, 1),
+	    gimplify_init_ctor_preeval (&GENERIC_TREE_OPERAND (*expr_p, 1),
 					pre_p, post_p, &preeval_data);
 	  }
 
@@ -3462,8 +3468,8 @@ gimplify_modify_expr_complex_part (tree *expr_p, tree *pre_p, bool want_value)
   enum tree_code code, ocode;
   tree lhs, rhs, new_rhs, other, realpart, imagpart;
 
-  lhs = TREE_OPERAND (*expr_p, 0);
-  rhs = TREE_OPERAND (*expr_p, 1);
+  lhs = GENERIC_TREE_OPERAND (*expr_p, 0);
+  rhs = GENERIC_TREE_OPERAND (*expr_p, 1);
   code = TREE_CODE (lhs);
   lhs = TREE_OPERAND (lhs, 0);
 
@@ -3479,8 +3485,8 @@ gimplify_modify_expr_complex_part (tree *expr_p, tree *pre_p, bool want_value)
   else
     new_rhs = build2 (COMPLEX_EXPR, TREE_TYPE (lhs), realpart, imagpart);
 
-  TREE_OPERAND (*expr_p, 0) = lhs;
-  TREE_OPERAND (*expr_p, 1) = new_rhs;
+  GENERIC_TREE_OPERAND (*expr_p, 0) = lhs;
+  GENERIC_TREE_OPERAND (*expr_p, 1) = new_rhs;
 
   if (want_value)
     {
@@ -3491,6 +3497,53 @@ gimplify_modify_expr_complex_part (tree *expr_p, tree *pre_p, bool want_value)
   return GS_ALL_DONE;
 }
 
+
+/* Destructively convert the TREE pointer in TP into a gimple tuple if
+   appropriate.  */
+
+static void
+tree_to_gimple_tuple (tree *tp)
+{
+
+  switch (TREE_CODE (*tp))
+    {
+    case GIMPLE_MODIFY_STMT:
+      return;
+    case MODIFY_EXPR:
+      {
+        struct gimple_stmt *gs;
+	tree lhs = TREE_OPERAND (*tp, 0);
+	bool def_stmt_self_p = false;
+
+	if (TREE_CODE (lhs) == SSA_NAME)
+	  {
+	    if (SSA_NAME_DEF_STMT (lhs) == *tp)
+	      def_stmt_self_p = true;
+	  }
+
+        gs = &make_node (GIMPLE_MODIFY_STMT)->gstmt;
+        gs->base = (*tp)->base;
+        /* The set to base above overwrites the CODE.  */
+        TREE_SET_CODE ((tree) gs, GIMPLE_MODIFY_STMT);
+
+        gs->locus = EXPR_LOCUS (*tp);
+        gs->operands[0] = TREE_OPERAND (*tp, 0);
+        gs->operands[1] = TREE_OPERAND (*tp, 1);
+        gs->block = TREE_BLOCK (*tp);
+        *tp = (tree)gs;
+
+	/* If we re-gimplify a set to an SSA_NAME, we must change the
+	   SSA name's DEF_STMT link.  */
+	if (def_stmt_self_p)
+	  SSA_NAME_DEF_STMT (GIMPLE_STMT_OPERAND (*tp, 0)) = *tp;
+
+        return;
+      }
+    default:
+      break;
+    }
+}
+
 /* Gimplify the MODIFY_EXPR node pointed to by EXPR_P.
 
       modify_expr
@@ -3509,11 +3562,12 @@ gimplify_modify_expr_complex_part (tree *expr_p, tree *pre_p, bool want_value)
 static enum gimplify_status
 gimplify_modify_expr (tree *expr_p, tree *pre_p, tree *post_p, bool want_value)
 {
-  tree *from_p = &TREE_OPERAND (*expr_p, 1);
-  tree *to_p = &TREE_OPERAND (*expr_p, 0);
+  tree *from_p = &GENERIC_TREE_OPERAND (*expr_p, 1);
+  tree *to_p = &GENERIC_TREE_OPERAND (*expr_p, 0);
   enum gimplify_status ret = GS_UNHANDLED;
 
   gcc_assert (TREE_CODE (*expr_p) == MODIFY_EXPR
+	      || TREE_CODE (*expr_p) == GIMPLE_MODIFY_STMT
 	      || TREE_CODE (*expr_p) == INIT_EXPR);
 
   /* For zero sized types only gimplify the left hand side and right hand side
@@ -3592,6 +3646,8 @@ gimplify_modify_expr (tree *expr_p, tree *pre_p, tree *post_p, bool want_value)
 
   if (want_value)
     {
+      tree_to_gimple_tuple (expr_p);
+
       append_to_statement_list (*expr_p, pre_p);
       *expr_p = *to_p;
       return GS_OK;
@@ -4182,9 +4238,9 @@ gimple_push_cleanup (tree var, tree cleanup, bool eh_only, tree *pre_p)
       */
 
       tree flag = create_tmp_var (boolean_type_node, "cleanup");
-      tree ffalse = build2 (MODIFY_EXPR, void_type_node, flag,
+      tree ffalse = build2 (GIMPLE_MODIFY_STMT, void_type_node, flag,
 			    boolean_false_node);
-      tree ftrue = build2 (MODIFY_EXPR, void_type_node, flag,
+      tree ftrue = build2 (GIMPLE_MODIFY_STMT, void_type_node, flag,
 			   boolean_true_node);
       cleanup = build3 (COND_EXPR, void_type_node, flag, cleanup, NULL);
       wce = build1 (WITH_CLEANUP_EXPR, void_type_node, cleanup);
@@ -4883,8 +4939,9 @@ gimplify_omp_for (tree *expr_p, tree *pre_p)
   gimplify_scan_omp_clauses (&OMP_FOR_CLAUSES (for_stmt), pre_p, false, false);
 
   t = OMP_FOR_INIT (for_stmt);
-  gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
-  decl = TREE_OPERAND (t, 0);
+  gcc_assert (TREE_CODE (t) == MODIFY_EXPR
+	      || TREE_CODE (t) == GIMPLE_MODIFY_STMT);
+  decl = GENERIC_TREE_OPERAND (t, 0);
   gcc_assert (DECL_P (decl));
   gcc_assert (INTEGRAL_TYPE_P (TREE_TYPE (decl)));
 
@@ -4894,16 +4951,21 @@ gimplify_omp_for (tree *expr_p, tree *pre_p)
   else
     omp_add_variable (gimplify_omp_ctxp, decl, GOVD_PRIVATE | GOVD_SEEN);
 
-  ret |= gimplify_expr (&TREE_OPERAND (t, 1), &OMP_FOR_PRE_BODY (for_stmt),
+  ret |= gimplify_expr (&GENERIC_TREE_OPERAND (t, 1),
+			&OMP_FOR_PRE_BODY (for_stmt),
 			NULL, is_gimple_val, fb_rvalue);
 
+  tree_to_gimple_tuple (&OMP_FOR_INIT (for_stmt));
+
   t = OMP_FOR_COND (for_stmt);
   gcc_assert (COMPARISON_CLASS_P (t));
-  gcc_assert (TREE_OPERAND (t, 0) == decl);
+  gcc_assert (GENERIC_TREE_OPERAND (t, 0) == decl);
 
-  ret |= gimplify_expr (&TREE_OPERAND (t, 1), &OMP_FOR_PRE_BODY (for_stmt),
+  ret |= gimplify_expr (&GENERIC_TREE_OPERAND (t, 1),
+			&OMP_FOR_PRE_BODY (for_stmt),
 			NULL, is_gimple_val, fb_rvalue);
 
+  tree_to_gimple_tuple (&OMP_FOR_INCR (for_stmt));
   t = OMP_FOR_INCR (for_stmt);
   switch (TREE_CODE (t))
     {
@@ -4917,13 +4979,13 @@ gimplify_omp_for (tree *expr_p, tree *pre_p)
       goto build_modify;
     build_modify:
       t = build2 (PLUS_EXPR, TREE_TYPE (decl), decl, t);
-      t = build2 (MODIFY_EXPR, void_type_node, decl, t);
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, decl, t);
       OMP_FOR_INCR (for_stmt) = t;
       break;
       
-    case MODIFY_EXPR:
-      gcc_assert (TREE_OPERAND (t, 0) == decl);
-      t = TREE_OPERAND (t, 1);
+    case GIMPLE_MODIFY_STMT:
+      gcc_assert (GIMPLE_STMT_OPERAND (t, 0) == decl);
+      t = GIMPLE_STMT_OPERAND (t, 1);
       switch (TREE_CODE (t))
 	{
 	case PLUS_EXPR:
@@ -5133,7 +5195,7 @@ gimplify_omp_atomic_pipeline (tree *expr_p, tree *pre_p, tree addr,
     return GS_ERROR;
 
   x = build_fold_indirect_ref (addr);
-  x = build2 (MODIFY_EXPR, void_type_node, oldval, x);
+  x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldval, x);
   gimplify_and_add (x, pre_p);
 
   /* For floating-point values, we'll need to view-convert them to integers
@@ -5151,7 +5213,7 @@ gimplify_omp_atomic_pipeline (tree *expr_p, tree *pre_p, tree addr,
       newival = create_tmp_var (itype, NULL);
 
       x = build1 (VIEW_CONVERT_EXPR, itype, oldval);
-      x = build2 (MODIFY_EXPR, void_type_node, oldival, x);
+      x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldival, x);
       gimplify_and_add (x, pre_p);
       iaddr = fold_convert (build_pointer_type (itype), addr);
     }
@@ -5162,17 +5224,17 @@ gimplify_omp_atomic_pipeline (tree *expr_p, tree *pre_p, tree addr,
   x = build1 (LABEL_EXPR, void_type_node, label);
   gimplify_and_add (x, pre_p);
 
-  x = build2 (MODIFY_EXPR, void_type_node, newval, rhs);
+  x = build2 (GIMPLE_MODIFY_STMT, void_type_node, newval, rhs);
   gimplify_and_add (x, pre_p);
 
   if (newval != newival)
     {
       x = build1 (VIEW_CONVERT_EXPR, itype, newval);
-      x = build2 (MODIFY_EXPR, void_type_node, newival, x);
+      x = build2 (GIMPLE_MODIFY_STMT, void_type_node, newival, x);
       gimplify_and_add (x, pre_p);
     }
 
-  x = build2 (MODIFY_EXPR, void_type_node, oldival2,
+  x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldival2,
 	      fold_convert (itype, oldival));
   gimplify_and_add (x, pre_p);
 
@@ -5182,14 +5244,14 @@ gimplify_omp_atomic_pipeline (tree *expr_p, tree *pre_p, tree addr,
   x = build_function_call_expr (cmpxchg, args);
   if (oldval == oldival)
     x = fold_convert (type, x);
-  x = build2 (MODIFY_EXPR, void_type_node, oldival, x);
+  x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldival, x);
   gimplify_and_add (x, pre_p);
 
   /* For floating point, be prepared for the loop backedge.  */
   if (oldval != oldival)
     {
       x = build1 (VIEW_CONVERT_EXPR, type, oldival);
-      x = build2 (MODIFY_EXPR, void_type_node, oldval, x);
+      x = build2 (GIMPLE_MODIFY_STMT, void_type_node, oldval, x);
       gimplify_and_add (x, pre_p);
     }
 
@@ -5227,7 +5289,7 @@ gimplify_omp_atomic_mutex (tree *expr_p, tree *pre_p, tree addr, tree rhs)
   gimplify_and_add (t, pre_p);
 
   t = build_fold_indirect_ref (addr);
-  t = build2 (MODIFY_EXPR, void_type_node, t, rhs);
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, t, rhs);
   gimplify_and_add (t, pre_p);
   
   t = built_in_decls[BUILT_IN_GOMP_ATOMIC_END];
@@ -5362,7 +5424,8 @@ gimplify_expr (tree *expr_p, tree *pre_p, tree *post_p,
 
       /* Die, die, die, my darling.  */
       if (save_expr == error_mark_node
-	  || (TREE_TYPE (save_expr)
+	  || (!GIMPLE_STMT_P (save_expr)
+	      && TREE_TYPE (save_expr)
 	      && TREE_TYPE (save_expr) == error_mark_node))
 	{
 	  ret = GS_ERROR;
@@ -5438,14 +5501,23 @@ gimplify_expr (tree *expr_p, tree *pre_p, tree *post_p,
 	  break;
 
 	case MODIFY_EXPR:
+	case GIMPLE_MODIFY_STMT:
 	case INIT_EXPR:
 	  ret = gimplify_modify_expr (expr_p, pre_p, post_p,
 				      fallback != fb_none);
 
-	  /* The distinction between MODIFY_EXPR and INIT_EXPR is no longer
-	     useful.  */
-	  if (*expr_p && TREE_CODE (*expr_p) == INIT_EXPR)
-	    TREE_SET_CODE (*expr_p, MODIFY_EXPR);
+	  if (*expr_p)
+	    {
+	      /* The distinction between MODIFY_EXPR and INIT_EXPR is no longer
+		 useful.  */
+	      if (TREE_CODE (*expr_p) == INIT_EXPR)
+		TREE_SET_CODE (*expr_p, MODIFY_EXPR);
+
+	      /* Convert MODIFY_EXPR to GIMPLE_MODIFY_STMT.  */
+	      if (TREE_CODE (*expr_p) == MODIFY_EXPR)
+		tree_to_gimple_tuple (expr_p);
+	    }
+
 	  break;
 
 	case TRUTH_ANDIF_EXPR:
@@ -5885,7 +5957,7 @@ gimplify_expr (tree *expr_p, tree *pre_p, tree *post_p,
 	     given a TREE_ADDRESSABLE type.  */
 	  tree tmp = create_tmp_var_raw (type, "vol");
 	  gimple_add_tmp_var (tmp);
-	  *expr_p = build2 (MODIFY_EXPR, type, tmp, *expr_p);
+	  *expr_p = build2 (GIMPLE_MODIFY_STMT, type, tmp, *expr_p);
 	}
       else
 	/* We can't do anything useful with a volatile reference to
@@ -6117,7 +6189,7 @@ gimplify_one_sizepos (tree *expr_p, tree *stmt_p)
 
       *expr_p = create_tmp_var (type, NULL);
       tmp = build1 (NOP_EXPR, type, expr);
-      tmp = build2 (MODIFY_EXPR, type, *expr_p, tmp);
+      tmp = build2 (GIMPLE_MODIFY_STMT, type, *expr_p, tmp);
       if (EXPR_HAS_LOCATION (expr))
 	SET_EXPR_LOCUS (tmp, EXPR_LOCUS (expr));
       else
@@ -6340,10 +6412,10 @@ gimplify_function_tree (tree fndecl)
       DECL_SAVED_TREE (fndecl) = bind;
     }
 
+  cfun->gimplified = true;
   current_function_decl = oldfn;
   cfun = oldfn ? DECL_STRUCT_FUNCTION (oldfn) : NULL;
 }
-
 
 /* Expands EXPR to list of gimple statements STMTS.  If SIMPLE is true,
    force the result to be either ssa_name or an invariant, otherwise
@@ -6368,7 +6440,7 @@ force_gimple_operand (tree expr, tree *stmts, bool simple, tree var)
   gimplify_ctxp->into_ssa = gimple_in_ssa_p (cfun);
 
   if (var)
-    expr = build2 (MODIFY_EXPR, TREE_TYPE (var), var, expr);
+    expr = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (var), var, expr);
 
   ret = gimplify_expr (&expr, stmts, NULL,
 		       gimple_test_f, fb_rvalue);
diff --git a/gcc/ipa-cp.c b/gcc/ipa-cp.c
index 3837bfdc97ad326a7d5a6317aebf00153acbb76e..305b1a5f4e27dab8c8b53d13f92ffba948d7ebe9 100644
--- a/gcc/ipa-cp.c
+++ b/gcc/ipa-cp.c
@@ -446,7 +446,7 @@ constant_val_insert (tree fn, tree parm1, tree val)
   edge e_step;
   edge_iterator ei;
 
-  init_stmt = build2 (MODIFY_EXPR, void_type_node, parm1, val);
+  init_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, parm1, val);
   func = DECL_STRUCT_FUNCTION (fn);
   cfun = func;
   current_function_decl = fn;
diff --git a/gcc/ipa-prop.c b/gcc/ipa-prop.c
index 58fe8507a608fae011762d34d315aa2c699aafb5..91eff199337909bfd829d173f33df2013c19a1fd 100644
--- a/gcc/ipa-prop.c
+++ b/gcc/ipa-prop.c
@@ -247,10 +247,10 @@ ipa_method_modify_stmt (struct cgraph_node *mt, tree stmt)
 
   switch (TREE_CODE (stmt))
     {
-    case MODIFY_EXPR:
-      if (TREE_CODE (TREE_OPERAND (stmt, 0)) == PARM_DECL)
+    case GIMPLE_MODIFY_STMT:
+      if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) == PARM_DECL)
 	{
-	  i = ipa_method_tree_map (mt, TREE_OPERAND (stmt, 0));
+	  i = ipa_method_tree_map (mt, GIMPLE_STMT_OPERAND (stmt, 0));
 	  if (i >= 0)
             ipa_method_modify_set (mt, i, true);
 	}
diff --git a/gcc/ipa-pure-const.c b/gcc/ipa-pure-const.c
index fdaff50d573b87dce8fba14bcc9ecad92f18c4c3..bd1d72b75067368ee0ba3664d05c79ae3de00f85 100644
--- a/gcc/ipa-pure-const.c
+++ b/gcc/ipa-pure-const.c
@@ -412,11 +412,11 @@ scan_function (tree *tp,
       *walk_subtrees = 0;
       break;
 
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       {
 	/* First look on the lhs and see what variable is stored to */
-	tree lhs = TREE_OPERAND (t, 0);
-	tree rhs = TREE_OPERAND (t, 1);
+	tree lhs = GIMPLE_STMT_OPERAND (t, 0);
+	tree rhs = GIMPLE_STMT_OPERAND (t, 1);
 	check_lhs_var (local, lhs);
 
 	/* For the purposes of figuring out what the cast affects */
diff --git a/gcc/ipa-reference.c b/gcc/ipa-reference.c
index 077aa18d72377ae476a7c919105d8381a5e032e1..9780acf74700cc0cef3b43f2ecee562397509e6d 100644
--- a/gcc/ipa-reference.c
+++ b/gcc/ipa-reference.c
@@ -494,11 +494,11 @@ scan_for_static_refs (tree *tp,
       *walk_subtrees = 0;
       break;
 
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       {
 	/* First look on the lhs and see what variable is stored to */
-	tree lhs = TREE_OPERAND (t, 0);
-	tree rhs = TREE_OPERAND (t, 1);
+	tree lhs = GIMPLE_STMT_OPERAND (t, 0);
+	tree rhs = GIMPLE_STMT_OPERAND (t, 1);
 	check_lhs_var (local, lhs);
 
 	/* For the purposes of figuring out what the cast affects */
diff --git a/gcc/ipa-type-escape.c b/gcc/ipa-type-escape.c
index b2ee148268ed0b5c5dbafa83228e7ccb3f2d5c52..0b0c19a7e91de8adbdc264667430936b47f48eab 100644
--- a/gcc/ipa-type-escape.c
+++ b/gcc/ipa-type-escape.c
@@ -1184,11 +1184,11 @@ scan_for_refs (tree *tp, int *walk_subtrees, void *data)
       *walk_subtrees = 0;
       break;
 
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       {
 	/* First look on the lhs and see what variable is stored to */
-	tree lhs = TREE_OPERAND (t, 0);
-	tree rhs = TREE_OPERAND (t, 1);
+	tree lhs = GIMPLE_STMT_OPERAND (t, 0);
+	tree rhs = GIMPLE_STMT_OPERAND (t, 1);
 
 	check_lhs_var (lhs);
  	check_cast (TREE_TYPE (lhs), rhs);
diff --git a/gcc/java/java-gimplify.c b/gcc/java/java-gimplify.c
index 54900d3f9ab45126976da2201c5730d480933148..76d299f947f96d2be8f635cf6dcf5a348718ffab 100644
--- a/gcc/java/java-gimplify.c
+++ b/gcc/java/java-gimplify.c
@@ -120,6 +120,9 @@ java_gimplify_expr (tree *expr_p, tree *pre_p ATTRIBUTE_UNUSED,
       *expr_p = java_replace_reference (*expr_p, /* want_lvalue */ false);
       return GS_UNHANDLED;
 
+      /* We don't handle GIMPLE_MODIFY_STMT, as MODIFY_EXPRs with java
+         semantics should only be generated by the front-end, and never
+         by anything after gimplification.  */
     case MODIFY_EXPR:
       return java_gimplify_modify_expr (expr_p, pre_p, post_p);
 
@@ -326,7 +329,7 @@ java_gimplify_modify_expr (tree *modify_expr_p, tree *pre_p, tree *post_p)
     {
       tree new_lhs = java_replace_reference (lhs, /* want_lvalue */ true);
       tree new_rhs = build1 (NOP_EXPR, TREE_TYPE (new_lhs), rhs);
-      modify_expr = build2 (MODIFY_EXPR, TREE_TYPE (new_lhs),
+      modify_expr = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (new_lhs),
 			    new_lhs, new_rhs);
       modify_expr = build1 (NOP_EXPR, lhs_type, modify_expr);
     }
@@ -424,7 +427,7 @@ java_gimplify_new_array_init (tree exp)
 
   tree array_ptr_type = build_pointer_type (array_type);
   tree tmp = create_tmp_var (array_ptr_type, "array");
-  tree body = build2 (MODIFY_EXPR, array_ptr_type, tmp,
+  tree body = build2 (GIMPLE_MODIFY_STMT, array_ptr_type, tmp,
 		      build_new_array (element_type, length));
 
   int index = 0;
@@ -437,7 +440,7 @@ java_gimplify_new_array_init (tree exp)
       tree lhs = build3 (COMPONENT_REF, TREE_TYPE (data_field),    
 			 build_java_indirect_ref (array_type, tmp, 0),
 			 data_field, NULL_TREE);
-      tree assignment = build2 (MODIFY_EXPR, element_type,
+      tree assignment = build2 (GIMPLE_MODIFY_STMT, element_type,
 				build4 (ARRAY_REF, element_type, lhs,
 					build_int_cst (NULL_TREE, index++),
 					NULL_TREE, NULL_TREE),
diff --git a/gcc/java/java-tree.h b/gcc/java/java-tree.h
index a064ab0575acc5c07a29ccc0838aafee3ae63463..a7bfa38eb574e7cf04bab82b872c97c4bb94c193 100644
--- a/gcc/java/java-tree.h
+++ b/gcc/java/java-tree.h
@@ -725,7 +725,8 @@ struct lang_identifier GTY(())
 /* The resulting tree type.  */
 union lang_tree_node 
   GTY((desc ("TREE_CODE (&%h.generic) == IDENTIFIER_NODE"),
-       chain_next ("(union lang_tree_node *)TREE_CHAIN (&%h.generic)")))
+       chain_next ("(GIMPLE_STMT_P (&%h.generic) ? (union lang_tree_node *) 0 : (union lang_tree_node *)TREE_CHAIN (&%h.generic))")))
+
 {
   union tree_node GTY ((tag ("0"), 
 			desc ("tree_node_structure (&%h)"))) 
@@ -1881,12 +1882,12 @@ enum
 
 /* In an EXPR_WITH_FILE_LOCATION node.  */
 #define EXPR_WFL_EMIT_LINE_NOTE(NODE) \
-  (EXPR_WITH_FILE_LOCATION_CHECK (NODE)->common.public_flag)
+  (EXPR_WITH_FILE_LOCATION_CHECK (NODE)->base.public_flag)
 #undef EXPR_WFL_NODE
 #define EXPR_WFL_NODE(NODE) \
   TREE_OPERAND (EXPR_WITH_FILE_LOCATION_CHECK (NODE), 0)
 #ifdef USE_MAPPED_LOCATION
-#define EXPR_WFL_LINECOL(NODE) ((NODE)->exp.locus)
+#define EXPR_WFL_LINECOL(NODE) EXPR_LOCUS(NODE)
 #define EXPR_WFL_FILENAME(NODE) EXPR_FILENAME (NODE)
 #define EXPR_WFL_LINENO(NODE) EXPR_LINENO (NODE)
 extern tree build_expr_wfl (tree, source_location);
diff --git a/gcc/lambda-code.c b/gcc/lambda-code.c
index f16937b3cbdbdfa8556842b0eaf26511408d1ce4..0eb3286503b491e99fd6e5498f753abe2c5cd5d6 100644
--- a/gcc/lambda-code.c
+++ b/gcc/lambda-code.c
@@ -1540,9 +1540,10 @@ lbv_to_gcc_expression (lambda_body_vector lbv,
   add_referenced_var (resvar);
 
   /* Start at 0.  */
-  stmt = build2 (MODIFY_EXPR, void_type_node, resvar, integer_zero_node);
+  stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, resvar,
+      		 integer_zero_node);
   name = make_ssa_name (resvar, stmt);
-  TREE_OPERAND (stmt, 0) = name;
+  GIMPLE_STMT_OPERAND (stmt, 0) = name;
   tsi = tsi_last (stmts);
   tsi_link_after (&tsi, stmt, TSI_CONTINUE_LINKING);
 
@@ -1555,20 +1556,20 @@ lbv_to_gcc_expression (lambda_body_vector lbv,
 	  
 	  /* newname = coefficient * induction_variable */
 	  coeffmult = build_int_cst (type, LBV_COEFFICIENTS (lbv)[i]);
-	  stmt = build2 (MODIFY_EXPR, void_type_node, resvar,
+	  stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, resvar,
 			 fold_build2 (MULT_EXPR, type, iv, coeffmult));
 
 	  newname = make_ssa_name (resvar, stmt);
-	  TREE_OPERAND (stmt, 0) = newname;
+	  GIMPLE_STMT_OPERAND (stmt, 0) = newname;
 	  fold_stmt (&stmt);
 	  tsi = tsi_last (stmts);
 	  tsi_link_after (&tsi, stmt, TSI_CONTINUE_LINKING);
 
 	  /* name = name + newname */
-	  stmt = build2 (MODIFY_EXPR, void_type_node, resvar,
+	  stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, resvar,
 			 build2 (PLUS_EXPR, type, name, newname));
 	  name = make_ssa_name (resvar, stmt);
-	  TREE_OPERAND (stmt, 0) = name;
+	  GIMPLE_STMT_OPERAND (stmt, 0) = name;
 	  fold_stmt (&stmt);
 	  tsi = tsi_last (stmts);
 	  tsi_link_after (&tsi, stmt, TSI_CONTINUE_LINKING);
@@ -1580,10 +1581,10 @@ lbv_to_gcc_expression (lambda_body_vector lbv,
   if (LBV_DENOMINATOR (lbv) != 1)
     {
       tree denominator = build_int_cst (type, LBV_DENOMINATOR (lbv));
-      stmt = build2 (MODIFY_EXPR, void_type_node, resvar,
+      stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, resvar,
 		     build2 (CEIL_DIV_EXPR, type, name, denominator));
       name = make_ssa_name (resvar, stmt);
-      TREE_OPERAND (stmt, 0) = name;
+      GIMPLE_STMT_OPERAND (stmt, 0) = name;
       fold_stmt (&stmt);
       tsi = tsi_last (stmts);
       tsi_link_after (&tsi, stmt, TSI_CONTINUE_LINKING);
@@ -1631,9 +1632,10 @@ lle_to_gcc_expression (lambda_linear_expression lle,
   for (; lle != NULL; lle = LLE_NEXT (lle))
     {
       /* Start at name = 0.  */
-      stmt = build2 (MODIFY_EXPR, void_type_node, resvar, integer_zero_node);
+      stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, resvar,
+	  	     integer_zero_node);
       name = make_ssa_name (resvar, stmt);
-      TREE_OPERAND (stmt, 0) = name;
+      GIMPLE_STMT_OPERAND (stmt, 0) = name;
       fold_stmt (&stmt);
       tsi = tsi_last (stmts);
       tsi_link_after (&tsi, stmt, TSI_CONTINUE_LINKING);
@@ -1662,18 +1664,18 @@ lle_to_gcc_expression (lambda_linear_expression lle,
 		}
 
 	      /* newname = mult */
-	      stmt = build2 (MODIFY_EXPR, void_type_node, resvar, mult);
+	      stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, resvar, mult);
 	      newname = make_ssa_name (resvar, stmt);
-	      TREE_OPERAND (stmt, 0) = newname;
+	      GIMPLE_STMT_OPERAND (stmt, 0) = newname;
 	      fold_stmt (&stmt);
 	      tsi = tsi_last (stmts);
 	      tsi_link_after (&tsi, stmt, TSI_CONTINUE_LINKING);
 
 	      /* name = name + newname */
-	      stmt = build2 (MODIFY_EXPR, void_type_node, resvar,
+	      stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, resvar,
 			     build2 (PLUS_EXPR, type, name, newname));
 	      name = make_ssa_name (resvar, stmt);
-	      TREE_OPERAND (stmt, 0) = name;
+	      GIMPLE_STMT_OPERAND (stmt, 0) = name;
 	      fold_stmt (&stmt);
 	      tsi = tsi_last (stmts);
 	      tsi_link_after (&tsi, stmt, TSI_CONTINUE_LINKING);
@@ -1703,18 +1705,18 @@ lle_to_gcc_expression (lambda_linear_expression lle,
 		}
 
 	      /* newname = mult */
-	      stmt = build2 (MODIFY_EXPR, void_type_node, resvar, mult);
+	      stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, resvar, mult);
 	      newname = make_ssa_name (resvar, stmt);
-	      TREE_OPERAND (stmt, 0) = newname;
+	      GIMPLE_STMT_OPERAND (stmt, 0) = newname;
 	      fold_stmt (&stmt);
 	      tsi = tsi_last (stmts);
 	      tsi_link_after (&tsi, stmt, TSI_CONTINUE_LINKING);
 
 	      /* name = name + newname */
-	      stmt = build2 (MODIFY_EXPR, void_type_node, resvar,
+	      stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, resvar,
 			     build2 (PLUS_EXPR, type, name, newname));
 	      name = make_ssa_name (resvar, stmt);
-	      TREE_OPERAND (stmt, 0) = name;
+	      GIMPLE_STMT_OPERAND (stmt, 0) = name;
 	      fold_stmt (&stmt);
 	      tsi = tsi_last (stmts);
 	      tsi_link_after (&tsi, stmt, TSI_CONTINUE_LINKING);
@@ -1725,11 +1727,11 @@ lle_to_gcc_expression (lambda_linear_expression lle,
          name = name + constant.  */
       if (LLE_CONSTANT (lle) != 0)
 	{
-	  stmt = build2 (MODIFY_EXPR, void_type_node, resvar,
+	  stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, resvar,
 			 build2 (PLUS_EXPR, type, name, 
 			         build_int_cst (type, LLE_CONSTANT (lle))));
 	  name = make_ssa_name (resvar, stmt);
-	  TREE_OPERAND (stmt, 0) = name;
+	  GIMPLE_STMT_OPERAND (stmt, 0) = name;
 	  fold_stmt (&stmt);
 	  tsi = tsi_last (stmts);
 	  tsi_link_after (&tsi, stmt, TSI_CONTINUE_LINKING);
@@ -1739,11 +1741,11 @@ lle_to_gcc_expression (lambda_linear_expression lle,
          name = name + linear offset.  */
       if (LLE_CONSTANT (offset) != 0)
 	{
-	  stmt = build2 (MODIFY_EXPR, void_type_node, resvar,
+	  stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, resvar,
 			 build2 (PLUS_EXPR, type, name, 
 			         build_int_cst (type, LLE_CONSTANT (offset))));
 	  name = make_ssa_name (resvar, stmt);
-	  TREE_OPERAND (stmt, 0) = name;
+	  GIMPLE_STMT_OPERAND (stmt, 0) = name;
 	  fold_stmt (&stmt);
 	  tsi = tsi_last (stmts);
 	  tsi_link_after (&tsi, stmt, TSI_CONTINUE_LINKING);
@@ -1755,11 +1757,11 @@ lle_to_gcc_expression (lambda_linear_expression lle,
 	  stmt = build_int_cst (type, LLE_DENOMINATOR (lle));
 	  stmt = build2 (wrap == MAX_EXPR ? CEIL_DIV_EXPR : FLOOR_DIV_EXPR,
 			 type, name, stmt);
-	  stmt = build2 (MODIFY_EXPR, void_type_node, resvar, stmt);
+	  stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, resvar, stmt);
 
 	  /* name = {ceil, floor}(name/denominator) */
 	  name = make_ssa_name (resvar, stmt);
-	  TREE_OPERAND (stmt, 0) = name;
+	  GIMPLE_STMT_OPERAND (stmt, 0) = name;
 	  tsi = tsi_last (stmts);
 	  tsi_link_after (&tsi, stmt, TSI_CONTINUE_LINKING);
 	}
@@ -1775,10 +1777,10 @@ lle_to_gcc_expression (lambda_linear_expression lle,
     {
       tree op1 = VEC_index (tree, results, 0);
       tree op2 = VEC_index (tree, results, 1);
-      stmt = build2 (MODIFY_EXPR, void_type_node, resvar,
+      stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, resvar,
 		     build2 (wrap, type, op1, op2));
       name = make_ssa_name (resvar, stmt);
-      TREE_OPERAND (stmt, 0) = name;
+      GIMPLE_STMT_OPERAND (stmt, 0) = name;
       tsi = tsi_last (stmts);
       tsi_link_after (&tsi, stmt, TSI_CONTINUE_LINKING);
     }
@@ -1893,10 +1895,10 @@ lambda_loopnest_to_gcc_loopnest (struct loop *old_loopnest,
 	 test,  and let redundancy elimination sort it out.  */
       inc_stmt = build2 (PLUS_EXPR, type, 
 			 ivvar, build_int_cst (type, LL_STEP (newloop)));
-      inc_stmt = build2 (MODIFY_EXPR, void_type_node, SSA_NAME_VAR (ivvar),
-			 inc_stmt);
+      inc_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node,
+	  		 SSA_NAME_VAR (ivvar), inc_stmt);
       ivvarinced = make_ssa_name (SSA_NAME_VAR (ivvar), inc_stmt);
-      TREE_OPERAND (inc_stmt, 0) = ivvarinced;
+      GIMPLE_STMT_OPERAND (inc_stmt, 0) = ivvarinced;
       bsi = bsi_for_stmt (exitcond);
       bsi_insert_before (&bsi, inc_stmt, BSI_SAME_STMT);
 
@@ -2185,9 +2187,9 @@ replace_uses_equiv_to_x_with_y (struct loop *loop, tree stmt, tree x,
       var = create_tmp_var (TREE_TYPE (use), "perfecttmp");
       add_referenced_var (var);
       val = force_gimple_operand_bsi (firstbsi, val, false, NULL);
-      setstmt = build2 (MODIFY_EXPR, void_type_node, var, val);
+      setstmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, var, val);
       var = make_ssa_name (var, setstmt);
-      TREE_OPERAND (setstmt, 0) = var;
+      GIMPLE_STMT_OPERAND (setstmt, 0) = var;
       bsi_insert_before (firstbsi, setstmt, BSI_SAME_STMT);
       update_stmt (setstmt);
       SET_USE (use_p, var);
@@ -2224,12 +2226,12 @@ can_put_in_inner_loop (struct loop *inner, tree stmt)
   imm_use_iterator imm_iter;
   use_operand_p use_p;
   
-  gcc_assert (TREE_CODE (stmt) == MODIFY_EXPR);
+  gcc_assert (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT);
   if (!ZERO_SSA_OPERANDS (stmt, SSA_OP_ALL_VIRTUALS)
-      || !expr_invariant_in_loop_p (inner, TREE_OPERAND (stmt, 1)))
+      || !expr_invariant_in_loop_p (inner, GIMPLE_STMT_OPERAND (stmt, 1)))
     return false;
   
-  FOR_EACH_IMM_USE_FAST (use_p, imm_iter, TREE_OPERAND (stmt, 0))
+  FOR_EACH_IMM_USE_FAST (use_p, imm_iter, GIMPLE_STMT_OPERAND (stmt, 0))
     {
       if (!exit_phi_for_loop_p (inner, USE_STMT (use_p)))
 	{
@@ -2252,7 +2254,7 @@ can_put_after_inner_loop (struct loop *loop, tree stmt)
   if (!ZERO_SSA_OPERANDS (stmt, SSA_OP_ALL_VIRTUALS))
     return false;
   
-  FOR_EACH_IMM_USE_FAST (use_p, imm_iter, TREE_OPERAND (stmt, 0))
+  FOR_EACH_IMM_USE_FAST (use_p, imm_iter, GIMPLE_STMT_OPERAND (stmt, 0))
     {
       if (!exit_phi_for_loop_p (loop, USE_STMT (use_p)))
 	{
@@ -2310,12 +2312,12 @@ can_convert_to_perfect_nest (struct loop *loop)
 		 win we get from rearranging the memory walk
 		 the loop is doing so that it has better
 		 cache behavior.  */
-	      if (TREE_CODE (stmt) == MODIFY_EXPR)
+	      if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
 		{
 		  use_operand_p use_a, use_b;
 		  imm_use_iterator imm_iter;
 		  ssa_op_iter op_iter, op_iter1;
-		  tree op0 = TREE_OPERAND (stmt, 0);
+		  tree op0 = GIMPLE_STMT_OPERAND (stmt, 0);
 		  tree scev = instantiate_parameters
 		    (loop, analyze_scalar_evolution (loop, op0));
 
@@ -2538,10 +2540,10 @@ perfect_nestify (struct loop *loop,
   exit_condition = get_loop_exit_condition (newloop);
   uboundvar = create_tmp_var (integer_type_node, "uboundvar");
   add_referenced_var (uboundvar);
-  stmt = build2 (MODIFY_EXPR, void_type_node, uboundvar, 
+  stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, uboundvar, 
 		 VEC_index (tree, ubounds, 0));
   uboundvar = make_ssa_name (uboundvar, stmt);
-  TREE_OPERAND (stmt, 0) = uboundvar;
+  GIMPLE_STMT_OPERAND (stmt, 0) = uboundvar;
 
   if (insert_after)
     bsi_insert_after (&bsi, stmt, BSI_SAME_STMT);
diff --git a/gcc/langhooks.c b/gcc/langhooks.c
index 7fca436e89dbaf0c4d3372e8b074cc23427b7010..5b0e09f471c2b2eeb87a5fd00d5a05c2d1470720 100644
--- a/gcc/langhooks.c
+++ b/gcc/langhooks.c
@@ -577,7 +577,7 @@ lhd_omp_predetermined_sharing (tree decl ATTRIBUTE_UNUSED)
 tree
 lhd_omp_assignment (tree clause ATTRIBUTE_UNUSED, tree dst, tree src)
 {
-  return build2 (MODIFY_EXPR, void_type_node, dst, src);
+  return build2 (GIMPLE_MODIFY_STMT, void_type_node, dst, src);
 }
 
 /* Register language specific type size variables as potentially OpenMP
diff --git a/gcc/omp-low.c b/gcc/omp-low.c
index f58ee1f1b6f6a0bb8cd8eaacd9590128a85e62e4..625ac37496784a82138952381b02d22eeca79cbe 100644
--- a/gcc/omp-low.c
+++ b/gcc/omp-low.c
@@ -157,11 +157,11 @@ extract_omp_for_data (tree for_stmt, struct omp_for_data *fd)
   fd->pre = NULL;
 
   t = OMP_FOR_INIT (for_stmt);
-  gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
-  fd->v = TREE_OPERAND (t, 0);
+  gcc_assert (TREE_CODE (t) == GIMPLE_MODIFY_STMT);
+  fd->v = GIMPLE_STMT_OPERAND (t, 0);
   gcc_assert (DECL_P (fd->v));
   gcc_assert (TREE_CODE (TREE_TYPE (fd->v)) == INTEGER_TYPE);
-  fd->n1 = TREE_OPERAND (t, 1);
+  fd->n1 = GIMPLE_STMT_OPERAND (t, 1);
 
   t = OMP_FOR_COND (for_stmt);
   fd->cond_code = TREE_CODE (t);
@@ -187,9 +187,9 @@ extract_omp_for_data (tree for_stmt, struct omp_for_data *fd)
     }
 
   t = OMP_FOR_INCR (fd->for_stmt);
-  gcc_assert (TREE_CODE (t) == MODIFY_EXPR);
-  gcc_assert (TREE_OPERAND (t, 0) == fd->v);
-  t = TREE_OPERAND (t, 1);
+  gcc_assert (TREE_CODE (t) == GIMPLE_MODIFY_STMT);
+  gcc_assert (GIMPLE_STMT_OPERAND (t, 0) == fd->v);
+  t = GIMPLE_STMT_OPERAND (t, 1);
   gcc_assert (TREE_OPERAND (t, 0) == fd->v);
   switch (TREE_CODE (t))
     {
@@ -1680,7 +1680,7 @@ lower_rec_input_clauses (tree clauses, tree *ilist, tree *dlist,
 	      x = built_in_decls[BUILT_IN_ALLOCA];
 	      x = build_function_call_expr (x, args);
 	      x = fold_convert (TREE_TYPE (ptr), x);
-	      x = build2 (MODIFY_EXPR, void_type_node, ptr, x);
+	      x = build2 (GIMPLE_MODIFY_STMT, void_type_node, ptr, x);
 	      gimplify_and_add (x, ilist);
 	    }
 	  else if (is_reference (var))
@@ -1716,7 +1716,7 @@ lower_rec_input_clauses (tree clauses, tree *ilist, tree *dlist,
 		  x = fold_convert (TREE_TYPE (new_var), x);
 		}
 
-	      x = build2 (MODIFY_EXPR, void_type_node, new_var, x);
+	      x = build2 (GIMPLE_MODIFY_STMT, void_type_node, new_var, x);
 	      gimplify_and_add (x, ilist);
 
 	      new_var = build_fold_indirect_ref (new_var);
@@ -1799,7 +1799,7 @@ lower_rec_input_clauses (tree clauses, tree *ilist, tree *dlist,
 		{
 		  x = omp_reduction_init (c, TREE_TYPE (new_var));
 		  gcc_assert (TREE_CODE (TREE_TYPE (new_var)) != ARRAY_TYPE);
-		  x = build2 (MODIFY_EXPR, void_type_node, new_var, x);
+		  x = build2 (GIMPLE_MODIFY_STMT, void_type_node, new_var, x);
 		  gimplify_and_add (x, ilist);
 		}
 	      break;
@@ -1964,7 +1964,7 @@ lower_reduction_clauses (tree clauses, tree *stmt_list, omp_context *ctx)
 	{
 	  x = build2 (code, TREE_TYPE (ref), ref, new_var);
 	  ref = build_outer_var_ref (var, ctx);
-	  x = build2 (MODIFY_EXPR, void_type_node, ref, x);
+	  x = build2 (GIMPLE_MODIFY_STMT, void_type_node, ref, x);
 	  append_to_statement_list (x, &sub_list);
 	}
     }
@@ -2003,7 +2003,7 @@ lower_copyprivate_clauses (tree clauses, tree *slist, tree *rlist,
       ref = build_sender_ref (var, ctx);
       x = (ctx->is_nested) ? lookup_decl_in_outer_ctx (var, ctx) : var;
       x = by_ref ? build_fold_addr_expr (x) : x;
-      x = build2 (MODIFY_EXPR, void_type_node, ref, x);
+      x = build2 (GIMPLE_MODIFY_STMT, void_type_node, ref, x);
       gimplify_and_add (x, slist);
 
       ref = build_receiver_ref (var, by_ref, ctx);
@@ -2084,14 +2084,14 @@ lower_send_clauses (tree clauses, tree *ilist, tree *olist, omp_context *ctx)
 	{
 	  ref = build_sender_ref (val, ctx);
 	  x = by_ref ? build_fold_addr_expr (var) : var;
-	  x = build2 (MODIFY_EXPR, void_type_node, ref, x);
+	  x = build2 (GIMPLE_MODIFY_STMT, void_type_node, ref, x);
 	  gimplify_and_add (x, ilist);
 	}
 
       if (do_out)
 	{
 	  ref = build_sender_ref (val, ctx);
-	  x = build2 (MODIFY_EXPR, void_type_node, var, ref);
+	  x = build2 (GIMPLE_MODIFY_STMT, void_type_node, var, ref);
 	  gimplify_and_add (x, olist);
 	}
     }
@@ -2128,17 +2128,17 @@ lower_send_shared_vars (tree *ilist, tree *olist, omp_context *ctx)
 	{
 	  x = build_sender_ref (ovar, ctx);
 	  var = build_fold_addr_expr (var);
-	  x = build2 (MODIFY_EXPR, void_type_node, x, var);
+	  x = build2 (GIMPLE_MODIFY_STMT, void_type_node, x, var);
 	  gimplify_and_add (x, ilist);
 	}
       else
 	{
 	  x = build_sender_ref (ovar, ctx);
-	  x = build2 (MODIFY_EXPR, void_type_node, x, var);
+	  x = build2 (GIMPLE_MODIFY_STMT, void_type_node, x, var);
 	  gimplify_and_add (x, ilist);
 
 	  x = build_sender_ref (ovar, ctx);
-	  x = build2 (MODIFY_EXPR, void_type_node, var, x);
+	  x = build2 (GIMPLE_MODIFY_STMT, void_type_node, var, x);
 	  gimplify_and_add (x, olist);
 	}
     }
@@ -2236,13 +2236,13 @@ expand_parallel_call (struct omp_region *region, basic_block bb,
 	  si = bsi_start (then_bb);
 	  t = build1 (LABEL_EXPR, void_type_node, then_lab);
 	  bsi_insert_after (&si, t, BSI_CONTINUE_LINKING);
-	  t = build2 (MODIFY_EXPR, void_type_node, tmp, val);
+	  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, tmp, val);
 	  bsi_insert_after (&si, t, BSI_CONTINUE_LINKING);
 
 	  si = bsi_start (else_bb);
 	  t = build1 (LABEL_EXPR, void_type_node, else_lab);
 	  bsi_insert_after (&si, t, BSI_CONTINUE_LINKING);
-	  t = build2 (MODIFY_EXPR, void_type_node, tmp, 
+	  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, tmp, 
 	              build_int_cst (unsigned_type_node, 1));
 	  bsi_insert_after (&si, t, BSI_CONTINUE_LINKING);
 
@@ -2483,19 +2483,20 @@ expand_omp_parallel (struct omp_region *region)
 
 	      gcc_assert (!bsi_end_p (si));
 	      stmt = bsi_stmt (si);
-	      if (TREE_CODE (stmt) != MODIFY_EXPR)
+	      if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
 		continue;
 
-	      arg = TREE_OPERAND (stmt, 1);
+	      arg = GIMPLE_STMT_OPERAND (stmt, 1);
 	      STRIP_NOPS (arg);
 	      if (TREE_CODE (arg) == ADDR_EXPR
 		  && TREE_OPERAND (arg, 0)
 		     == OMP_PARALLEL_DATA_ARG (entry_stmt))
 		{
-		  if (TREE_OPERAND (stmt, 0) == DECL_ARGUMENTS (child_fn))
+		  if (GIMPLE_STMT_OPERAND (stmt, 0)
+		      == DECL_ARGUMENTS (child_fn))
 		    bsi_remove (&si, true);
 		  else
-		    TREE_OPERAND (stmt, 1) = DECL_ARGUMENTS (child_fn);
+		    GIMPLE_STMT_OPERAND (stmt, 1) = DECL_ARGUMENTS (child_fn);
 		  break;
 		}
 	    }
@@ -2651,11 +2652,11 @@ expand_omp_for_generic (struct omp_region *region,
   /* Iteration setup for sequential loop goes in L0_BB.  */
   list = alloc_stmt_list ();
   t = fold_convert (type, istart0);
-  t = build2 (MODIFY_EXPR, void_type_node, fd->v, t);
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, fd->v, t);
   gimplify_and_add (t, &list);
 
   t = fold_convert (type, iend0);
-  t = build2 (MODIFY_EXPR, void_type_node, iend, t);
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, iend, t);
   gimplify_and_add (t, &list);
 
   si = bsi_start (l0_bb);
@@ -2677,7 +2678,7 @@ expand_omp_for_generic (struct omp_region *region,
   list = alloc_stmt_list ();
 
   t = build2 (PLUS_EXPR, type, fd->v, fd->step);
-  t = build2 (MODIFY_EXPR, void_type_node, fd->v, t);
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, fd->v, t);
   gimplify_and_add (t, &list);
   
   t = build2 (fd->cond_code, boolean_type_node, fd->v, iend);
@@ -2856,7 +2857,7 @@ expand_omp_for_static_nochunk (struct omp_region *region,
   t = fold_convert (type, s0);
   t = build2 (MULT_EXPR, type, t, fd->step);
   t = build2 (PLUS_EXPR, type, t, fd->n1);
-  t = build2 (MODIFY_EXPR, void_type_node, fd->v, t);
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, fd->v, t);
   gimplify_and_add (t, &list);
 
   t = fold_convert (type, e0);
@@ -2871,7 +2872,7 @@ expand_omp_for_static_nochunk (struct omp_region *region,
   list = alloc_stmt_list ();
 
   t = build2 (PLUS_EXPR, type, fd->v, fd->step);
-  t = build2 (MODIFY_EXPR, void_type_node, fd->v, t);
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, fd->v, t);
   gimplify_and_add (t, &list);
 
   t = build2 (fd->cond_code, boolean_type_node, fd->v, e);
@@ -3040,7 +3041,7 @@ expand_omp_for_static_chunk (struct omp_region *region, struct omp_for_data *fd)
   t = fold_convert (type, s0);
   t = build2 (MULT_EXPR, type, t, fd->step);
   t = build2 (PLUS_EXPR, type, t, fd->n1);
-  t = build2 (MODIFY_EXPR, void_type_node, fd->v, t);
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, fd->v, t);
   gimplify_and_add (t, &list);
 
   t = fold_convert (type, e0);
@@ -3056,7 +3057,7 @@ expand_omp_for_static_chunk (struct omp_region *region, struct omp_for_data *fd)
   list = alloc_stmt_list ();
 
   t = build2 (PLUS_EXPR, type, fd->v, fd->step);
-  t = build2 (MODIFY_EXPR, void_type_node, fd->v, t);
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, fd->v, t);
   gimplify_and_add (t, &list);
 
   t = build2 (fd->cond_code, boolean_type_node, fd->v, e);
@@ -3075,7 +3076,7 @@ expand_omp_for_static_chunk (struct omp_region *region, struct omp_for_data *fd)
 
   t = build_int_cst (type, 1);
   t = build2 (PLUS_EXPR, type, trip, t);
-  t = build2 (MODIFY_EXPR, void_type_node, trip, t);
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, trip, t);
   gimplify_and_add (t, &list);
 
   si = bsi_start (trip_update_bb);
@@ -3224,7 +3225,7 @@ expand_omp_sections (struct omp_region *region)
       t = tree_cons (NULL, t, NULL);
       u = built_in_decls[BUILT_IN_GOMP_SECTIONS_START];
       t = build_function_call_expr (u, t);
-      t = build2 (MODIFY_EXPR, void_type_node, v, t);
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, v, t);
       bsi_insert_after (&si, t, BSI_SAME_STMT);
     }
   bsi_remove (&si, true);
@@ -3293,7 +3294,7 @@ expand_omp_sections (struct omp_region *region)
 
       t = built_in_decls[BUILT_IN_GOMP_SECTIONS_NEXT];
       t = build_function_call_expr (t, NULL);
-      t = build2 (MODIFY_EXPR, void_type_node, v, t);
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, v, t);
       bsi_insert_after (&si, t, BSI_SAME_STMT);
       bsi_remove (&si, true);
     }
@@ -3731,7 +3732,7 @@ lower_omp_single_copy (tree single_stmt, tree *pre_p, omp_context *ctx)
   t = built_in_decls[BUILT_IN_GOMP_SINGLE_COPY_START];
   t = build_function_call_expr (t, NULL);
   t = fold_convert (ptr_type, t);
-  t = build2 (MODIFY_EXPR, void_type_node, ctx->receiver_decl, t);
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, ctx->receiver_decl, t);
   gimplify_and_add (t, pre_p);
 
   t = build2 (EQ_EXPR, boolean_type_node, ctx->receiver_decl,
@@ -4048,7 +4049,7 @@ lower_omp_for (tree *stmt_p, omp_context *ctx)
 
      We just need to make sure that VAL1, VAL2 and VAL3 are lowered
      using the .omp_data_s mapping, if needed.  */
-  rhs_p = &TREE_OPERAND (OMP_FOR_INIT (stmt), 1);
+  rhs_p = &GIMPLE_STMT_OPERAND (OMP_FOR_INIT (stmt), 1);
   if (!is_gimple_min_invariant (*rhs_p))
     *rhs_p = get_formal_tmp_var (*rhs_p, body_p);
 
@@ -4056,7 +4057,7 @@ lower_omp_for (tree *stmt_p, omp_context *ctx)
   if (!is_gimple_min_invariant (*rhs_p))
     *rhs_p = get_formal_tmp_var (*rhs_p, body_p);
 
-  rhs_p = &TREE_OPERAND (TREE_OPERAND (OMP_FOR_INCR (stmt), 1), 1);
+  rhs_p = &TREE_OPERAND (GIMPLE_STMT_OPERAND (OMP_FOR_INCR (stmt), 1), 1);
   if (!is_gimple_min_invariant (*rhs_p))
     *rhs_p = get_formal_tmp_var (*rhs_p, body_p);
 
@@ -4144,7 +4145,7 @@ lower_omp_parallel (tree *stmt_p, omp_context *ctx)
       t = build_fold_addr_expr (ctx->sender_decl);
       /* fixup_child_record_type might have changed receiver_decl's type.  */
       t = fold_convert (TREE_TYPE (ctx->receiver_decl), t);
-      t = build2 (MODIFY_EXPR, void_type_node, ctx->receiver_decl, t);
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, ctx->receiver_decl, t);
       append_to_statement_list (t, &new_body);
     }
 
diff --git a/gcc/predict.c b/gcc/predict.c
index d28e515386a0764540cfde19cf254beb63ea5992..4b5344b7481f8f5eee1317934ed46a41d4b68967 100644
--- a/gcc/predict.c
+++ b/gcc/predict.c
@@ -902,9 +902,10 @@ expr_expected_value (tree expr, bitmap visited)
 	    }
 	  return val;
 	}
-      if (TREE_CODE (def) != MODIFY_EXPR || TREE_OPERAND (def, 0) != expr)
+      if (TREE_CODE (def) != GIMPLE_MODIFY_STMT
+	  || GIMPLE_STMT_OPERAND (def, 0) != expr)
 	return NULL;
-      return expr_expected_value (TREE_OPERAND (def, 1), visited);
+      return expr_expected_value (GIMPLE_STMT_OPERAND (def, 1), visited);
     }
   else if (TREE_CODE (expr) == CALL_EXPR)
     {
@@ -968,15 +969,15 @@ strip_builtin_expect (void)
 	  tree fndecl;
 	  tree arglist;
 
-	  if (TREE_CODE (stmt) == MODIFY_EXPR
-	      && TREE_CODE (TREE_OPERAND (stmt, 1)) == CALL_EXPR
-	      && (fndecl = get_callee_fndecl (TREE_OPERAND (stmt, 1)))
+	  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+	      && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == CALL_EXPR
+	      && (fndecl = get_callee_fndecl (GIMPLE_STMT_OPERAND (stmt, 1)))
 	      && DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_NORMAL
 	      && DECL_FUNCTION_CODE (fndecl) == BUILT_IN_EXPECT
-	      && (arglist = TREE_OPERAND (TREE_OPERAND (stmt, 1), 1))
+	      && (arglist = TREE_OPERAND (GIMPLE_STMT_OPERAND (stmt, 1), 1))
 	      && TREE_CHAIN (arglist))
 	    {
-	      TREE_OPERAND (stmt, 1) = TREE_VALUE (arglist);
+	      GIMPLE_STMT_OPERAND (stmt, 1) = TREE_VALUE (arglist);
 	      update_stmt (stmt);
 	    }
 	}
@@ -1167,8 +1168,8 @@ apply_return_prediction (int *heads)
   return_val = TREE_OPERAND (return_stmt, 0);
   if (!return_val)
     return;
-  if (TREE_CODE (return_val) == MODIFY_EXPR)
-    return_val = TREE_OPERAND (return_val, 1);
+  if (TREE_CODE (return_val) == GIMPLE_MODIFY_STMT)
+    return_val = GIMPLE_STMT_OPERAND (return_val, 1);
   if (TREE_CODE (return_val) != SSA_NAME
       || !SSA_NAME_DEF_STMT (return_val)
       || TREE_CODE (SSA_NAME_DEF_STMT (return_val)) != PHI_NODE)
@@ -1221,10 +1222,10 @@ tree_bb_level_predictions (void)
 	  tree stmt = bsi_stmt (bsi);
 	  switch (TREE_CODE (stmt))
 	    {
-	      case MODIFY_EXPR:
-		if (TREE_CODE (TREE_OPERAND (stmt, 1)) == CALL_EXPR)
+	      case GIMPLE_MODIFY_STMT:
+		if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == CALL_EXPR)
 		  {
-		    stmt = TREE_OPERAND (stmt, 1);
+		    stmt = GIMPLE_STMT_OPERAND (stmt, 1);
 		    goto call_expr;
 		  }
 		break;
@@ -1306,8 +1307,9 @@ tree_estimate_probability (void)
 		{
 		  tree stmt = bsi_stmt (bi);
 		  if ((TREE_CODE (stmt) == CALL_EXPR
-		       || (TREE_CODE (stmt) == MODIFY_EXPR
-			   && TREE_CODE (TREE_OPERAND (stmt, 1)) == CALL_EXPR))
+		       || (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+			   && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1))
+			      == CALL_EXPR))
 		      /* Constant and pure calls are hardly used to signalize
 			 something exceptional.  */
 		      && TREE_SIDE_EFFECTS (stmt))
diff --git a/gcc/print-tree.c b/gcc/print-tree.c
index 57b07ace4bb6352416bbf9436b9f2642b3273257..1ed17de864117180a759e4413e7d0ad53d5ed0b1 100644
--- a/gcc/print-tree.c
+++ b/gcc/print-tree.c
@@ -263,7 +263,7 @@ print_node (FILE *file, const char *prefix, tree node, int indent)
       if (indent <= 4)
 	print_node_brief (file, "type", TREE_TYPE (node), indent + 4);
     }
-  else
+  else if (!GIMPLE_TUPLE_P (node))
     {
       print_node (file, "type", TREE_TYPE (node), indent + 4);
       if (TREE_TYPE (node))
@@ -679,6 +679,18 @@ print_node (FILE *file, const char *prefix, tree node, int indent)
       print_node (file, "chain", TREE_CHAIN (node), indent + 4);
       break;
 
+    case tcc_gimple_stmt:
+      len = TREE_CODE_LENGTH (TREE_CODE (node));
+
+      for (i = 0; i < len; i++)
+	{
+	  char temp[10];
+
+	  sprintf (temp, "arg %d", i);
+	  print_node (file, temp, GIMPLE_STMT_OPERAND (node, i), indent + 4);
+	}
+      break;
+
     case tcc_constant:
     case tcc_exceptional:
       switch (TREE_CODE (node))
diff --git a/gcc/stmt.c b/gcc/stmt.c
index d5a181b9d2d997c8d04b1b02c424e693b9e9d0d4..819d9be85b6b8bb517ae1742abb0167e1b8c79da 100644
--- a/gcc/stmt.c
+++ b/gcc/stmt.c
@@ -1362,6 +1362,9 @@ expand_expr_stmt (tree exp)
   tree type;
 
   value = expand_expr (exp, const0_rtx, VOIDmode, 0);
+  if (GIMPLE_TUPLE_P (exp))
+    type = void_type_node;
+  else
   type = TREE_TYPE (exp);
 
   /* If all we do is reference a volatile value in memory,
@@ -1415,6 +1418,7 @@ warn_if_unused_value (tree exp, location_t locus)
     case PREDECREMENT_EXPR:
     case POSTDECREMENT_EXPR:
     case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
     case INIT_EXPR:
     case TARGET_EXPR:
     case CALL_EXPR:
@@ -1582,10 +1586,10 @@ expand_return (tree retval)
       expand_null_return ();
       return;
     }
-  else if ((TREE_CODE (retval) == MODIFY_EXPR
+  else if ((TREE_CODE (retval) == GIMPLE_MODIFY_STMT
 	    || TREE_CODE (retval) == INIT_EXPR)
-	   && TREE_CODE (TREE_OPERAND (retval, 0)) == RESULT_DECL)
-    retval_rhs = TREE_OPERAND (retval, 1);
+	   && TREE_CODE (GENERIC_TREE_OPERAND (retval, 0)) == RESULT_DECL)
+    retval_rhs = GENERIC_TREE_OPERAND (retval, 1);
   else
     retval_rhs = retval;
 
@@ -1604,7 +1608,7 @@ expand_return (tree retval)
      (and in expand_call).  */
 
   else if (retval_rhs != 0
-	   && TYPE_MODE (TREE_TYPE (retval_rhs)) == BLKmode
+	   && TYPE_MODE (GENERIC_TREE_TYPE (retval_rhs)) == BLKmode
 	   && REG_P (result_rtl))
     {
       int i;
diff --git a/gcc/tree-cfg.c b/gcc/tree-cfg.c
index bdbff33fdead71ca4726a3c23ce72d7eb212cc10..e4733a2012f5a3979adf5c87e7c97f35d8ee87a1 100644
--- a/gcc/tree-cfg.c
+++ b/gcc/tree-cfg.c
@@ -314,8 +314,8 @@ factor_computed_gotos (void)
 	    }
 
 	  /* Copy the original computed goto's destination into VAR.  */
-	  assignment = build2 (MODIFY_EXPR, ptr_type_node,
-			       var, GOTO_DESTINATION (last));
+	  assignment = build2_gimple (GIMPLE_MODIFY_STMT,
+			              var, GOTO_DESTINATION (last));
 	  bsi_insert_before (&bsi, assignment, BSI_SAME_STMT);
 
 	  /* And re-vector the computed goto to the new destination.  */
@@ -501,11 +501,14 @@ make_edges (void)
 	      break;
 
 	    case MODIFY_EXPR:
+	      gcc_unreachable ();
+
+	    case GIMPLE_MODIFY_STMT:
 	      if (is_ctrl_altering_stmt (last))
 		{
-		  /* A MODIFY_EXPR may have a CALL_EXPR on its RHS and the
-		     CALL_EXPR may have an abnormal edge.  Search the RHS for
-		     this case and create any required edges.  */
+		  /* A GIMPLE_MODIFY_STMT may have a CALL_EXPR on its RHS and
+		     the CALL_EXPR may have an abnormal edge.  Search the RHS
+		     for this case and create any required edges.  */
 		  if (tree_can_make_abnormal_goto (last))
 		    make_abnormal_goto_edges (bb, true);  
 
@@ -1330,7 +1333,7 @@ tree_merge_blocks (basic_block a, basic_block b)
 	     with ordering of phi nodes.  This is because A is the single
 	     predecessor of B, therefore results of the phi nodes cannot
 	     appear as arguments of the phi nodes.  */
-	  copy = build2 (MODIFY_EXPR, void_type_node, def, use);
+	  copy = build2_gimple (GIMPLE_MODIFY_STMT, def, use);
 	  bsi_insert_after (&bsi, copy, BSI_NEW_STMT);
 	  SET_PHI_RESULT (phi, NULL_TREE);
 	  SSA_NAME_DEF_STMT (def) = copy;
@@ -1559,9 +1562,9 @@ remove_useless_stmts_cond (tree *stmt_p, struct rus_data *data)
       else if (TREE_CODE (cond) == VAR_DECL || TREE_CODE (cond) == PARM_DECL)
 	{
 	  if (else_stmt
-	      && TREE_CODE (else_stmt) == MODIFY_EXPR
-	      && TREE_OPERAND (else_stmt, 0) == cond
-	      && integer_zerop (TREE_OPERAND (else_stmt, 1)))
+	      && TREE_CODE (else_stmt) == GIMPLE_MODIFY_STMT
+	      && GIMPLE_STMT_OPERAND (else_stmt, 0) == cond
+	      && integer_zerop (GIMPLE_STMT_OPERAND (else_stmt, 1)))
 	    COND_EXPR_ELSE (*stmt_p) = alloc_stmt_list ();
 	}
       else if ((TREE_CODE (cond) == EQ_EXPR || TREE_CODE (cond) == NE_EXPR)
@@ -1576,9 +1579,9 @@ remove_useless_stmts_cond (tree *stmt_p, struct rus_data *data)
 			    : &COND_EXPR_ELSE (*stmt_p));
 
 	  if (stmt
-	      && TREE_CODE (stmt) == MODIFY_EXPR
-	      && TREE_OPERAND (stmt, 0) == TREE_OPERAND (cond, 0)
-	      && TREE_OPERAND (stmt, 1) == TREE_OPERAND (cond, 1))
+	      && TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+	      && GIMPLE_STMT_OPERAND (stmt, 0) == TREE_OPERAND (cond, 0)
+	      && GIMPLE_STMT_OPERAND (stmt, 1) == TREE_OPERAND (cond, 1))
 	    *location = alloc_stmt_list ();
 	}
     }
@@ -1871,6 +1874,9 @@ remove_useless_stmts_1 (tree *tp, struct rus_data *data)
       break;
 
     case MODIFY_EXPR:
+      gcc_unreachable ();
+
+    case GIMPLE_MODIFY_STMT:
       data->last_goto = NULL;
       fold_stmt (tp);
       op = get_call_expr_in (t);
@@ -2508,8 +2514,8 @@ tree_can_make_abnormal_goto (tree t)
 {
   if (computed_goto_p (t))
     return true;
-  if (TREE_CODE (t) == MODIFY_EXPR)
-    t = TREE_OPERAND (t, 1);
+  if (TREE_CODE (t) == GIMPLE_MODIFY_STMT)
+    t = GIMPLE_STMT_OPERAND (t, 1);
   if (TREE_CODE (t) == WITH_SIZE_EXPR)
     t = TREE_OPERAND (t, 0);
   if (TREE_CODE (t) == CALL_EXPR)
@@ -3011,9 +3017,9 @@ tree_find_edge_insert_loc (edge e, block_stmt_iterator *bsi,
 	  tree op = TREE_OPERAND (tmp, 0);
 	  if (op && !is_gimple_val (op))
 	    {
-	      gcc_assert (TREE_CODE (op) == MODIFY_EXPR);
+	      gcc_assert (TREE_CODE (op) == GIMPLE_MODIFY_STMT);
 	      bsi_insert_before (bsi, op, BSI_NEW_STMT);
-	      TREE_OPERAND (tmp, 0) = TREE_OPERAND (op, 0);
+	      TREE_OPERAND (tmp, 0) = GIMPLE_STMT_OPERAND (op, 0);
 	    }
 	  bsi_prev (bsi);
 	  return true;
@@ -3232,7 +3238,10 @@ verify_expr (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
       break;
 
     case MODIFY_EXPR:
-      x = TREE_OPERAND (t, 0);
+      gcc_unreachable ();
+
+    case GIMPLE_MODIFY_STMT:
+      x = GIMPLE_STMT_OPERAND (t, 0);
       if (TREE_CODE (x) == BIT_FIELD_REF
 	  && is_gimple_reg (TREE_OPERAND (x, 0)))
 	{
@@ -3536,6 +3545,35 @@ verify_node_sharing (tree * tp, int *walk_subtrees, void *data)
 }
 
 
+/* Helper function for verify_gimple_tuples.  */
+
+static tree
+verify_gimple_tuples_1 (tree *tp, int *walk_subtrees ATTRIBUTE_UNUSED,
+			 void *data ATTRIBUTE_UNUSED)
+{
+  switch (TREE_CODE (*tp))
+    {
+    case MODIFY_EXPR:
+      error ("unexpected non-tuple");
+      debug_tree (*tp);
+      gcc_unreachable ();
+      return NULL_TREE;
+
+    default:
+      return NULL_TREE;
+    }
+}
+
+/* Verify that there are no trees that should have been converted to
+   gimple tuples.  Return true if T contains a node that should have
+   been converted to a gimple tuple, but hasn't.  */
+
+static bool
+verify_gimple_tuples (tree t)
+{
+  return walk_tree (&t, verify_gimple_tuples_1, NULL, NULL) != NULL;
+}
+
 /* Verify the GIMPLE statement chain.  */
 
 void
@@ -3604,6 +3642,8 @@ verify_stmts (void)
 	{
 	  tree stmt = bsi_stmt (bsi);
 
+	  err |= verify_gimple_tuples (stmt);
+
 	  if (bb_for_stmt (stmt) != bb)
 	    {
 	      error ("bb_for_stmt (stmt) is set to a wrong basic block");
@@ -4570,7 +4610,8 @@ move_stmt_r (tree *tp, int *walk_subtrees, void *data)
   struct move_stmt_d *p = (struct move_stmt_d *) data;
   tree t = *tp;
 
-  if (p->block && IS_EXPR_CODE_CLASS (TREE_CODE_CLASS (TREE_CODE (t))))
+  if (p->block
+      && (EXPR_P (t) || GIMPLE_STMT_P (t)))
     TREE_BLOCK (t) = p->block;
 
   if (OMP_DIRECTIVE_P (t)
@@ -5638,7 +5679,7 @@ gimplify_val (block_stmt_iterator *bsi, tree type, tree exp)
     return exp;
 
   t = make_rename_temp (type, NULL);
-  new_stmt = build2 (MODIFY_EXPR, type, t, exp);
+  new_stmt = build2_gimple (GIMPLE_MODIFY_STMT, t, exp);
 
   orig_stmt = bsi_stmt (*bsi);
   SET_EXPR_LOCUS (new_stmt, EXPR_LOCUS (orig_stmt));
diff --git a/gcc/tree-complex.c b/gcc/tree-complex.c
index d3909ae0acc18b678783fe672f7327341e1910e2..38b2101d33c281990534d474fa2c90e63ff50451 100644
--- a/gcc/tree-complex.c
+++ b/gcc/tree-complex.c
@@ -206,13 +206,13 @@ init_dont_simulate_again (void)
 		 since it's never used as an input to another computation.  */
 	      dsa = true;
 	      stmt = TREE_OPERAND (stmt, 0);
-	      if (!stmt || TREE_CODE (stmt) != MODIFY_EXPR)
+	      if (!stmt || TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
 		break;
 	      /* FALLTHRU */
 
-	    case MODIFY_EXPR:
-	      dsa = !is_complex_reg (TREE_OPERAND (stmt, 0));
-	      rhs = TREE_OPERAND (stmt, 1);
+	    case GIMPLE_MODIFY_STMT:
+	      dsa = !is_complex_reg (GIMPLE_STMT_OPERAND (stmt, 0));
+	      rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 	      break;
 
 	    case COND_EXPR:
@@ -267,11 +267,11 @@ complex_visit_stmt (tree stmt, edge *taken_edge_p ATTRIBUTE_UNUSED,
   unsigned int ver;
   tree lhs, rhs;
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return SSA_PROP_VARYING;
 
-  lhs = TREE_OPERAND (stmt, 0);
-  rhs = TREE_OPERAND (stmt, 1);
+  lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+  rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
   /* These conditions should be satisfied due to the initial filter
      set up in init_dont_simulate_again.  */
@@ -532,7 +532,7 @@ set_component_ssa_name (tree ssa_name, bool imag_p, tree value)
   
   /* Do all the work to assign VALUE to COMP.  */
   value = force_gimple_operand (value, &list, false, NULL);
-  last = build2 (MODIFY_EXPR, TREE_TYPE (comp), comp, value);
+  last = build2_gimple (GIMPLE_MODIFY_STMT, comp, value);
   append_to_statement_list (last, &list);
 
   gcc_assert (SSA_NAME_DEF_STMT (comp) == NULL);
@@ -588,7 +588,7 @@ extract_component (block_stmt_iterator *bsi, tree t, bool imagpart_p,
 static void
 update_complex_components (block_stmt_iterator *bsi, tree stmt, tree r, tree i)
 {
-  tree lhs = TREE_OPERAND (stmt, 0);
+  tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
   tree list;
 
   list = set_component_ssa_name (lhs, false, r);
@@ -628,8 +628,8 @@ update_complex_assignment (block_stmt_iterator *bsi, tree r, tree i)
   else if (gimple_in_ssa_p (cfun))
     update_complex_components (bsi, stmt, r, i);
   
-  type = TREE_TYPE (TREE_OPERAND (mod, 1));
-  TREE_OPERAND (mod, 1) = build2 (COMPLEX_EXPR, type, r, i);
+  type = TREE_TYPE (GIMPLE_STMT_OPERAND (mod, 1));
+  GIMPLE_STMT_OPERAND (mod, 1) = build2 (COMPLEX_EXPR, type, r, i);
   update_stmt (stmt);
 }
 
@@ -773,25 +773,24 @@ expand_complex_move (block_stmt_iterator *bsi, tree stmt, tree type,
       i = extract_component (bsi, rhs, 1, false);
 
       x = build1 (REALPART_EXPR, inner_type, unshare_expr (lhs));
-      x = build2 (MODIFY_EXPR, inner_type, x, r);
+      x = build2_gimple (GIMPLE_MODIFY_STMT, x, r);
       bsi_insert_before (bsi, x, BSI_SAME_STMT);
 
       if (stmt == bsi_stmt (*bsi))
 	{
 	  x = build1 (IMAGPART_EXPR, inner_type, unshare_expr (lhs));
-	  TREE_OPERAND (stmt, 0) = x;
-	  TREE_OPERAND (stmt, 1) = i;
-	  TREE_TYPE (stmt) = inner_type;
+	  GIMPLE_STMT_OPERAND (stmt, 0) = x;
+	  GIMPLE_STMT_OPERAND (stmt, 1) = i;
 	}
       else
 	{
 	  x = build1 (IMAGPART_EXPR, inner_type, unshare_expr (lhs));
-	  x = build2 (MODIFY_EXPR, inner_type, x, i);
+	  x = build2_gimple (GIMPLE_MODIFY_STMT, x, i);
 	  bsi_insert_before (bsi, x, BSI_SAME_STMT);
 
 	  stmt = bsi_stmt (*bsi);
 	  gcc_assert (TREE_CODE (stmt) == RETURN_EXPR);
-	  TREE_OPERAND (stmt, 0) = lhs;
+	  GIMPLE_STMT_OPERAND (stmt, 0) = lhs;
 	}
 
       update_all_vops (stmt);
@@ -894,7 +893,7 @@ expand_complex_libcall (block_stmt_iterator *bsi, tree ar, tree ai,
   args = tree_cons (NULL, ar, args);
 
   stmt = bsi_stmt (*bsi);
-  type = TREE_TYPE (TREE_OPERAND (stmt, 1));
+  type = TREE_TYPE (GIMPLE_STMT_OPERAND (stmt, 1));
 
   mode = TYPE_MODE (type);
   gcc_assert (GET_MODE_CLASS (mode) == MODE_COMPLEX_FLOAT);
@@ -906,13 +905,13 @@ expand_complex_libcall (block_stmt_iterator *bsi, tree ar, tree ai,
     gcc_unreachable ();
   fn = built_in_decls[bcode];
 
-  TREE_OPERAND (stmt, 1)
+  GIMPLE_STMT_OPERAND (stmt, 1)
     = build3 (CALL_EXPR, type, build_fold_addr_expr (fn), args, NULL);
   update_stmt (stmt);
 
   if (gimple_in_ssa_p (cfun))
     {
-      tree lhs = TREE_OPERAND (stmt, 0);
+      tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
       type = TREE_TYPE (type);
       update_complex_components (bsi, stmt,
 				 build1 (REALPART_EXPR, type, lhs),
@@ -1122,9 +1121,9 @@ expand_complex_div_wide (block_stmt_iterator *bsi, tree inner_type,
 
      if (bb_true)
        {
-	 t1 = build2 (MODIFY_EXPR, inner_type, rr, tr);
+	 t1 = build2_gimple (GIMPLE_MODIFY_STMT, rr, tr);
 	 bsi_insert_before (bsi, t1, BSI_SAME_STMT);
-	 t1 = build2 (MODIFY_EXPR, inner_type, ri, ti);
+	 t1 = build2_gimple (GIMPLE_MODIFY_STMT, ri, ti);
 	 bsi_insert_before (bsi, t1, BSI_SAME_STMT);
 	 bsi_remove (bsi, true);
        }
@@ -1161,9 +1160,9 @@ expand_complex_div_wide (block_stmt_iterator *bsi, tree inner_type,
 
      if (bb_false)
        {
-	 t1 = build2 (MODIFY_EXPR, inner_type, rr, tr);
+	 t1 = build2_gimple (GIMPLE_MODIFY_STMT, rr, tr);
 	 bsi_insert_before (bsi, t1, BSI_SAME_STMT);
-	 t1 = build2 (MODIFY_EXPR, inner_type, ri, ti);
+	 t1 = build2_gimple (GIMPLE_MODIFY_STMT, ri, ti);
 	 bsi_insert_before (bsi, t1, BSI_SAME_STMT);
 	 bsi_remove (bsi, true);
        }
@@ -1307,9 +1306,9 @@ expand_complex_comparison (block_stmt_iterator *bsi, tree ar, tree ai,
     case RETURN_EXPR:
       expr = TREE_OPERAND (stmt, 0);
       /* FALLTHRU */
-    case MODIFY_EXPR:
-      type = TREE_TYPE (TREE_OPERAND (expr, 1));
-      TREE_OPERAND (expr, 1) = fold_convert (type, cc);
+    case GIMPLE_MODIFY_STMT:
+      type = TREE_TYPE (GIMPLE_STMT_OPERAND (expr, 1));
+      GIMPLE_STMT_OPERAND (expr, 1) = fold_convert (type, cc);
       break;
     case COND_EXPR:
       TREE_OPERAND (stmt, 0) = cc;
@@ -1338,12 +1337,12 @@ expand_complex_operations_1 (block_stmt_iterator *bsi)
       stmt = TREE_OPERAND (stmt, 0);
       if (!stmt)
 	return;
-      if (TREE_CODE (stmt) != MODIFY_EXPR)
+      if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
 	return;
       /* FALLTHRU */
 
-    case MODIFY_EXPR:
-      rhs = TREE_OPERAND (stmt, 1);
+    case GIMPLE_MODIFY_STMT:
+      rhs = GIMPLE_STMT_OPERAND (stmt, 1);
       break;
 
     case COND_EXPR:
@@ -1384,8 +1383,8 @@ expand_complex_operations_1 (block_stmt_iterator *bsi)
 
     default:
       {
-	tree lhs = TREE_OPERAND (stmt, 0);
-	tree rhs = TREE_OPERAND (stmt, 1);
+	tree lhs = GENERIC_TREE_OPERAND (stmt, 0);
+	tree rhs = GENERIC_TREE_OPERAND (stmt, 1);
 
 	if (TREE_CODE (type) == COMPLEX_TYPE)
 	  expand_complex_move (bsi, stmt, type, lhs, rhs);
@@ -1393,7 +1392,7 @@ expand_complex_operations_1 (block_stmt_iterator *bsi)
 		  || TREE_CODE (rhs) == IMAGPART_EXPR)
 		 && TREE_CODE (TREE_OPERAND (rhs, 0)) == SSA_NAME)
 	  {
-	    TREE_OPERAND (stmt, 1)
+	    GENERIC_TREE_OPERAND (stmt, 1)
 	      = extract_component (bsi, TREE_OPERAND (rhs, 0),
 				   TREE_CODE (rhs) == IMAGPART_EXPR, false);
 	    update_stmt (stmt);
diff --git a/gcc/tree-data-ref.c b/gcc/tree-data-ref.c
index 3734058bbbf163ac7ee9e6486a4dd5e7db167476..7ed14f0e55a960c73733d0c1dbe1a9f68505f075 100644
--- a/gcc/tree-data-ref.c
+++ b/gcc/tree-data-ref.c
@@ -4019,10 +4019,10 @@ get_references_in_stmt (tree stmt, VEC (data_ref_loc, heap) **references)
   if (ZERO_SSA_OPERANDS (stmt, SSA_OP_ALL_VIRTUALS))
     return clobbers_memory;
 
-  if (TREE_CODE (stmt) ==  MODIFY_EXPR)
+  if (TREE_CODE (stmt) ==  GIMPLE_MODIFY_STMT)
     {
-      op0 = &TREE_OPERAND (stmt, 0);
-      op1 = &TREE_OPERAND (stmt, 1);
+      op0 = &GIMPLE_STMT_OPERAND (stmt, 0);
+      op1 = &GIMPLE_STMT_OPERAND (stmt, 1);
 		
       if (DECL_P (*op1)
 	  || REFERENCE_CLASS_P (*op1))
diff --git a/gcc/tree-dfa.c b/gcc/tree-dfa.c
index 3330624c19f8e27cfc59637b2f6800ef98140cd6..b2d09f4b031bd2c788263b4789761637b6a55aee 100644
--- a/gcc/tree-dfa.c
+++ b/gcc/tree-dfa.c
@@ -128,13 +128,13 @@ create_var_ann (tree t)
 
   gcc_assert (t);
   gcc_assert (DECL_P (t));
-  gcc_assert (!t->common.ann || t->common.ann->common.type == VAR_ANN);
+  gcc_assert (!t->base.ann || t->base.ann->common.type == VAR_ANN);
 
   ann = GGC_CNEW (struct var_ann_d);
 
   ann->common.type = VAR_ANN;
 
-  t->common.ann = (tree_ann_t) ann;
+  t->base.ann = (tree_ann_t) ann;
 
   return ann;
 }
@@ -148,14 +148,14 @@ create_function_ann (tree t)
 
   gcc_assert (t);
   gcc_assert (TREE_CODE (t) == FUNCTION_DECL);
-  gcc_assert (!t->common.ann || t->common.ann->common.type == FUNCTION_ANN);
+  gcc_assert (!t->base.ann || t->base.ann->common.type == FUNCTION_ANN);
 
   ann = ggc_alloc (sizeof (*ann));
   memset ((void *) ann, 0, sizeof (*ann));
 
   ann->common.type = FUNCTION_ANN;
 
-  t->common.ann = (tree_ann_t) ann;
+  t->base.ann = (tree_ann_t) ann;
 
   return ann;
 }
@@ -168,7 +168,7 @@ create_stmt_ann (tree t)
   stmt_ann_t ann;
 
   gcc_assert (is_gimple_stmt (t));
-  gcc_assert (!t->common.ann || t->common.ann->common.type == STMT_ANN);
+  gcc_assert (!t->base.ann || t->base.ann->common.type == STMT_ANN);
 
   ann = GGC_CNEW (struct stmt_ann_d);
 
@@ -177,7 +177,7 @@ create_stmt_ann (tree t)
   /* Since we just created the annotation, mark the statement modified.  */
   ann->modified = true;
 
-  t->common.ann = (tree_ann_t) ann;
+  t->base.ann = (tree_ann_t) ann;
 
   return ann;
 }
@@ -190,12 +190,12 @@ create_tree_common_ann (tree t)
   tree_ann_common_t ann;
 
   gcc_assert (t);
-  gcc_assert (!t->common.ann || t->common.ann->common.type == TREE_ANN_COMMON);
+  gcc_assert (!t->base.ann || t->base.ann->common.type == TREE_ANN_COMMON);
 
   ann = GGC_CNEW (struct tree_ann_common_d);
 
   ann->type = TREE_ANN_COMMON;
-  t->common.ann = (tree_ann_t) ann;
+  t->base.ann = (tree_ann_t) ann;
 
   return ann;
 }
@@ -540,9 +540,9 @@ collect_dfa_stats_r (tree *tp, int *walk_subtrees ATTRIBUTE_UNUSED,
   tree t = *tp;
   struct dfa_stats_d *dfa_stats_p = (struct dfa_stats_d *)data;
 
-  if (t->common.ann)
+  if (t->base.ann)
     {
-      switch (ann_type (t->common.ann))
+      switch (ann_type (t->base.ann))
 	{
 	case STMT_ANN:
 	  {
diff --git a/gcc/tree-dump.c b/gcc/tree-dump.c
index 8c008ab705c88d5fa7f0f04402c928594e01128d..2cea58248837ae25b3b4d0d5ba72816047e249de 100644
--- a/gcc/tree-dump.c
+++ b/gcc/tree-dump.c
@@ -576,6 +576,11 @@ dequeue_and_dump (dump_info_p di)
       dump_child ("op 1", TREE_OPERAND (t, 1));
       break;
 
+    case GIMPLE_MODIFY_STMT:
+      dump_child ("op 0", GIMPLE_STMT_OPERAND (t, 0));
+      dump_child ("op 1", GIMPLE_STMT_OPERAND (t, 1));
+      break;
+
     case COMPONENT_REF:
       dump_child ("op 0", TREE_OPERAND (t, 0));
       dump_child ("op 1", TREE_OPERAND (t, 1));
diff --git a/gcc/tree-eh.c b/gcc/tree-eh.c
index 2a723b303b7025465676ab863a1aa03ca2af3b90..760cdc3da108899a85652b703e59b610db3194c0 100644
--- a/gcc/tree-eh.c
+++ b/gcc/tree-eh.c
@@ -115,7 +115,7 @@ add_stmt_to_eh_region_fn (struct function *ifun, tree t, int num)
   /* ??? For the benefit of calls.c, converting all this to rtl,
      we need to record the call expression, not just the outer
      modify statement.  */
-  if (TREE_CODE (t) == MODIFY_EXPR
+  if (TREE_CODE (t) == GIMPLE_MODIFY_STMT
       && (t = get_call_expr_in (t)))
     add_stmt_to_eh_region_fn (ifun, t, num);
 }
@@ -144,7 +144,7 @@ remove_stmt_from_eh_region_fn (struct function *ifun, tree t)
       /* ??? For the benefit of calls.c, converting all this to rtl,
 	 we need to record the call expression, not just the outer
 	 modify statement.  */
-      if (TREE_CODE (t) == MODIFY_EXPR
+      if (TREE_CODE (t) == GIMPLE_MODIFY_STMT
 	  && (t = get_call_expr_in (t)))
 	remove_stmt_from_eh_region_fn (ifun, t);
       return true;
@@ -624,10 +624,10 @@ do_return_redirection (struct goto_queue_node *q, tree finlab, tree mod,
 	  q->cont_stmt = q->stmt;
 	  break;
 
-	case MODIFY_EXPR:
+	case GIMPLE_MODIFY_STMT:
 	  {
-	    tree result = TREE_OPERAND (ret_expr, 0);
-	    tree new, old = TREE_OPERAND (ret_expr, 1);
+	    tree result = GIMPLE_STMT_OPERAND (ret_expr, 0);
+	    tree new, old = GIMPLE_STMT_OPERAND (ret_expr, 1);
 
 	    if (!*return_value_p)
 	      {
@@ -646,13 +646,13 @@ do_return_redirection (struct goto_queue_node *q, tree finlab, tree mod,
 	    else
 	      new = *return_value_p;
 
-	    x = build2 (MODIFY_EXPR, TREE_TYPE (new), new, old);
+	    x = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (new), new, old);
 	    append_to_statement_list (x, &q->repl_stmt);
 
 	    if (new == result)
 	      x = result;
 	    else
-	      x = build2 (MODIFY_EXPR, TREE_TYPE (result), result, new);
+	      x = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (result), result, new);
 	    q->cont_stmt = build1 (RETURN_EXPR, void_type_node, x);
 	  }
 
@@ -842,20 +842,20 @@ honor_protect_cleanup_actions (struct leh_state *outer_state,
 
       i = tsi_start (finally);
       x = build0 (EXC_PTR_EXPR, ptr_type_node);
-      x = build2 (MODIFY_EXPR, void_type_node, save_eptr, x);
+      x = build2 (GIMPLE_MODIFY_STMT, void_type_node, save_eptr, x);
       tsi_link_before (&i, x, TSI_CONTINUE_LINKING);
 
       x = build0 (FILTER_EXPR, integer_type_node);
-      x = build2 (MODIFY_EXPR, void_type_node, save_filt, x);
+      x = build2 (GIMPLE_MODIFY_STMT, void_type_node, save_filt, x);
       tsi_link_before (&i, x, TSI_CONTINUE_LINKING);
 
       i = tsi_last (finally);
       x = build0 (EXC_PTR_EXPR, ptr_type_node);
-      x = build2 (MODIFY_EXPR, void_type_node, x, save_eptr);
+      x = build2 (GIMPLE_MODIFY_STMT, void_type_node, x, save_eptr);
       tsi_link_after (&i, x, TSI_CONTINUE_LINKING);
 
       x = build0 (FILTER_EXPR, integer_type_node);
-      x = build2 (MODIFY_EXPR, void_type_node, x, save_filt);
+      x = build2 (GIMPLE_MODIFY_STMT, void_type_node, x, save_filt);
       tsi_link_after (&i, x, TSI_CONTINUE_LINKING);
 
       x = build_resx (get_eh_region_number (tf->region));
@@ -1177,7 +1177,7 @@ lower_try_finally_switch (struct leh_state *state, struct leh_tf_state *tf)
 
   if (tf->may_fallthru)
     {
-      x = build2 (MODIFY_EXPR, void_type_node, finally_tmp,
+      x = build2 (GIMPLE_MODIFY_STMT, void_type_node, finally_tmp,
 		  build_int_cst (NULL_TREE, fallthru_index));
       append_to_statement_list (x, tf->top_p);
 
@@ -1207,7 +1207,7 @@ lower_try_finally_switch (struct leh_state *state, struct leh_tf_state *tf)
       x = build1 (LABEL_EXPR, void_type_node, tf->eh_label);
       append_to_statement_list (x, tf->top_p);
 
-      x = build2 (MODIFY_EXPR, void_type_node, finally_tmp,
+      x = build2 (GIMPLE_MODIFY_STMT, void_type_node, finally_tmp,
 		  build_int_cst (NULL_TREE, eh_index));
       append_to_statement_list (x, tf->top_p);
 
@@ -1239,14 +1239,14 @@ lower_try_finally_switch (struct leh_state *state, struct leh_tf_state *tf)
 
       if (q->index < 0)
 	{
-	  mod = build2 (MODIFY_EXPR, void_type_node, finally_tmp,
+	  mod = build2 (GIMPLE_MODIFY_STMT, void_type_node, finally_tmp,
 		        build_int_cst (NULL_TREE, return_index));
 	  do_return_redirection (q, finally_label, mod, &return_val);
 	  switch_id = return_index;
 	}
       else
 	{
-	  mod = build2 (MODIFY_EXPR, void_type_node, finally_tmp,
+	  mod = build2 (GIMPLE_MODIFY_STMT, void_type_node, finally_tmp,
 		        build_int_cst (NULL_TREE, q->index));
 	  do_goto_redirection (q, finally_label, mod);
 	  switch_id = q->index;
@@ -1612,7 +1612,7 @@ lower_eh_constructs_1 (struct leh_state *state, tree *tp)
 	}
       break;
 
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       /* Look for things that can throw exceptions, and record them.  */
       if (state->cur_region && tree_could_throw_p (t))
 	{
@@ -1997,12 +1997,12 @@ tree_could_throw_p (tree t)
 {
   if (!flag_exceptions)
     return false;
-  if (TREE_CODE (t) == MODIFY_EXPR)
+  if (TREE_CODE (t) == GIMPLE_MODIFY_STMT)
     {
       if (flag_non_call_exceptions
-	  && tree_could_trap_p (TREE_OPERAND (t, 0)))
+	  && tree_could_trap_p (GIMPLE_STMT_OPERAND (t, 0)))
 	return true;
-      t = TREE_OPERAND (t, 1);
+      t = GIMPLE_STMT_OPERAND (t, 1);
     }
 
   if (TREE_CODE (t) == WITH_SIZE_EXPR)
@@ -2081,7 +2081,7 @@ verify_eh_throw_stmt_node (void **slot, void *data ATTRIBUTE_UNUSED)
 {
   struct throw_stmt_node *node = (struct throw_stmt_node *)*slot;
 
-  gcc_assert (node->stmt->common.ann == NULL);
+  gcc_assert (node->stmt->base.ann == NULL);
   return 1;
 }
 
diff --git a/gcc/tree-flow-inline.h b/gcc/tree-flow-inline.h
index 5040375bf76f107b960c87e7cfb1a45dd3213096..f19faa1c4ff22adf73433531be733f9f48416424 100644
--- a/gcc/tree-flow-inline.h
+++ b/gcc/tree-flow-inline.h
@@ -194,9 +194,10 @@ var_ann (tree t)
   gcc_assert (t);
   gcc_assert (DECL_P (t));
   gcc_assert (TREE_CODE (t) != FUNCTION_DECL);
-  gcc_assert (!t->common.ann || t->common.ann->common.type == VAR_ANN);
+  gcc_assert (!t->base.ann
+	      || t->base.ann->common.type == VAR_ANN);
 
-  return (var_ann_t) t->common.ann;
+  return (var_ann_t) t->base.ann;
 }
 
 /* Return the variable annotation for T, which must be a _DECL node.
@@ -215,9 +216,10 @@ function_ann (tree t)
 {
   gcc_assert (t);
   gcc_assert (TREE_CODE (t) == FUNCTION_DECL);
-  gcc_assert (!t->common.ann || t->common.ann->common.type == FUNCTION_ANN);
+  gcc_assert (!t->base.ann
+	      || t->base.ann->common.type == FUNCTION_ANN);
 
-  return (function_ann_t) t->common.ann;
+  return (function_ann_t) t->base.ann;
 }
 
 /* Return the function annotation for T, which must be a FUNCTION_DECL node.
@@ -226,7 +228,7 @@ static inline function_ann_t
 get_function_ann (tree var)
 {
   function_ann_t ann = function_ann (var);
-  gcc_assert (!var->common.ann || var->common.ann->common.type == FUNCTION_ANN);
+  gcc_assert (!var->base.ann || var->base.ann->common.type == FUNCTION_ANN);
   return (ann) ? ann : create_function_ann (var);
 }
 
@@ -238,7 +240,7 @@ has_stmt_ann (tree t)
 #ifdef ENABLE_CHECKING
   gcc_assert (is_gimple_stmt (t));
 #endif
-  return t->common.ann && t->common.ann->common.type == STMT_ANN;
+  return t->base.ann && t->base.ann->common.type == STMT_ANN;
 }
 
 /* Return the statement annotation for T, which must be a statement
@@ -249,8 +251,8 @@ stmt_ann (tree t)
 #ifdef ENABLE_CHECKING
   gcc_assert (is_gimple_stmt (t));
 #endif
-  gcc_assert (!t->common.ann || t->common.ann->common.type == STMT_ANN);
-  return (stmt_ann_t) t->common.ann;
+  gcc_assert (!t->base.ann || t->base.ann->common.type == STMT_ANN);
+  return (stmt_ann_t) t->base.ann;
 }
 
 /* Return the statement annotation for T, which must be a statement
@@ -868,7 +870,7 @@ mark_non_addressable (tree var)
 static inline tree_ann_common_t
 tree_common_ann (tree t)
 {
-  return &t->common.ann->common;
+  return &t->base.ann->common;
 }
 
 /* Return a common annotation for T.  Create the constant annotation if it
diff --git a/gcc/tree-flow.h b/gcc/tree-flow.h
index 3be370ce4033231524c17e0ec53e22b6c20b937d..bee5cd94794ca02af691725e834f213fcaf64a28 100644
--- a/gcc/tree-flow.h
+++ b/gcc/tree-flow.h
@@ -156,7 +156,7 @@ struct ptr_info_def GTY(())
 
 
 /*---------------------------------------------------------------------------
-		   Tree annotations stored in tree_common.ann
+		   Tree annotations stored in tree_base.ann
 ---------------------------------------------------------------------------*/
 enum tree_ann_type { TREE_ANN_COMMON, VAR_ANN, FUNCTION_ANN, STMT_ANN };
 
diff --git a/gcc/tree-gimple.c b/gcc/tree-gimple.c
index 3dab75de74d49c450a7f2de045b7b8a5034ec058..eda454186655fa69ca8eccc35254ae452ad6d4bf 100644
--- a/gcc/tree-gimple.c
+++ b/gcc/tree-gimple.c
@@ -87,7 +87,7 @@ is_gimple_formal_tmp_rhs (tree t)
 bool
 is_gimple_reg_rhs (tree t)
 {
-  /* If the RHS of the MODIFY_EXPR may throw or make a nonlocal goto
+  /* If the RHS of the GIMPLE_MODIFY_STMT may throw or make a nonlocal goto
      and the LHS is a user variable, then we need to introduce a formal
      temporary.  This way the optimizers can determine that the user
      variable is only modified if evaluation of the RHS does not throw.
@@ -233,7 +233,7 @@ is_gimple_stmt (tree t)
       return true;
 
     case CALL_EXPR:
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       /* These are valid regardless of their type.  */
       return true;
 
@@ -427,8 +427,10 @@ is_gimple_call_addr (tree t)
 tree
 get_call_expr_in (tree t)
 {
-  if (TREE_CODE (t) == MODIFY_EXPR)
-    t = TREE_OPERAND (t, 1);
+  /* FIXME tuples: delete the assertion below when conversion complete.  */
+  gcc_assert (TREE_CODE (t) != MODIFY_EXPR);
+  if (TREE_CODE (t) == GIMPLE_MODIFY_STMT)
+    t = GIMPLE_STMT_OPERAND (t, 1);
   if (TREE_CODE (t) == WITH_SIZE_EXPR)
     t = TREE_OPERAND (t, 0);
   if (TREE_CODE (t) == CALL_EXPR)
@@ -473,7 +475,7 @@ recalculate_side_effects (tree t)
       switch (code)
 	{
 	case INIT_EXPR:
-	case MODIFY_EXPR:
+	case GIMPLE_MODIFY_STMT:
 	case VA_ARG_EXPR:
 	case PREDECREMENT_EXPR:
 	case PREINCREMENT_EXPR:
diff --git a/gcc/tree-if-conv.c b/gcc/tree-if-conv.c
index 7ccb48c927374a3939edd07b16392459f8b2cce1..2f304356efb61206a7a400f7795172b982b26a9d 100644
--- a/gcc/tree-if-conv.c
+++ b/gcc/tree-if-conv.c
@@ -108,7 +108,8 @@ static tree tree_if_convert_stmt (struct loop *loop, tree, tree,
 static void tree_if_convert_cond_expr (struct loop *, tree, tree,
 				       block_stmt_iterator *);
 static bool if_convertible_phi_p (struct loop *, basic_block, tree);
-static bool if_convertible_modify_expr_p (struct loop *, basic_block, tree);
+static bool if_convertible_gimple_modify_stmt_p (struct loop *, basic_block,
+    						 tree);
 static bool if_convertible_stmt_p (struct loop *, basic_block, tree);
 static bool if_convertible_bb_p (struct loop *, basic_block, basic_block);
 static bool if_convertible_loop_p (struct loop *, bool);
@@ -119,7 +120,7 @@ static void clean_predicate_lists (struct loop *loop);
 static basic_block find_phi_replacement_condition (struct loop *loop,
 						   basic_block, tree *,
 						   block_stmt_iterator *);
-static void replace_phi_with_cond_modify_expr (tree, tree, basic_block,
+static void replace_phi_with_cond_gimple_modify_stmt (tree, tree, basic_block,
                                                block_stmt_iterator *);
 static void process_phi_nodes (struct loop *);
 static void combine_blocks (struct loop *);
@@ -209,7 +210,7 @@ tree_if_conversion (struct loop *loop, bool for_vectorizer)
 }
 
 /* if-convert stmt T which is part of LOOP.
-   If T is a MODIFY_EXPR than it is converted into conditional modify
+   If T is a GIMPLE_MODIFY_STMT than it is converted into conditional modify
    expression using COND.  For conditional expressions, add condition in the
    destination basic block's predicate list and remove conditional
    expression itself. BSI is the iterator used to traverse statements of
@@ -232,12 +233,12 @@ tree_if_convert_stmt (struct loop *  loop, tree t, tree cond,
     case LABEL_EXPR:
       break;
 
-    case MODIFY_EXPR:
-      /* This modify_expr is killing previous value of LHS. Appropriate value will
-	 be selected by PHI node based on condition. It is possible that before
-	 this transformation, PHI nodes was selecting default value and now it will
-	 use this new value. This is OK because it does not change validity the
-	 program.  */
+    case GIMPLE_MODIFY_STMT:
+      /* This GIMPLE_MODIFY_STMT is killing previous value of LHS. Appropriate
+	 value will be selected by PHI node based on condition. It is possible
+	 that before this transformation, PHI nodes was selecting default
+	 value and now it will use this new value. This is OK because it does 
+	 not change validity the program.  */
       break;
 
     case COND_EXPR:
@@ -334,15 +335,16 @@ if_convertible_phi_p (struct loop *loop, basic_block bb, tree phi)
 }
 
 /* Return true, if M_EXPR is if-convertible.
-   MODIFY_EXPR is not if-convertible if,
+   GIMPLE_MODIFY_STMT is not if-convertible if,
    - It is not movable.
    - It could trap.
    - LHS is not var decl.
-  MODIFY_EXPR is part of block BB, which is inside loop LOOP.
+  GIMPLE_MODIFY_STMT is part of block BB, which is inside loop LOOP.
 */
 
 static bool
-if_convertible_modify_expr_p (struct loop *loop, basic_block bb, tree m_expr)
+if_convertible_gimple_modify_stmt_p (struct loop *loop, basic_block bb,
+    				     tree m_expr)
 {
   if (dump_file && (dump_flags & TDF_DETAILS))
     {
@@ -360,21 +362,21 @@ if_convertible_modify_expr_p (struct loop *loop, basic_block bb, tree m_expr)
 
   /* See if it needs speculative loading or not.  */
   if (bb != loop->header
-      && tree_could_trap_p (TREE_OPERAND (m_expr, 1)))
+      && tree_could_trap_p (GIMPLE_STMT_OPERAND (m_expr, 1)))
     {
       if (dump_file && (dump_flags & TDF_DETAILS))
 	fprintf (dump_file, "tree could trap...\n");
       return false;
     }
 
-  if (TREE_CODE (TREE_OPERAND (m_expr, 1)) == CALL_EXPR)
+  if (TREE_CODE (GIMPLE_STMT_OPERAND (m_expr, 1)) == CALL_EXPR)
     {
       if (dump_file && (dump_flags & TDF_DETAILS))
 	fprintf (dump_file, "CALL_EXPR \n");
       return false;
     }
 
-  if (TREE_CODE (TREE_OPERAND (m_expr, 0)) != SSA_NAME
+  if (TREE_CODE (GIMPLE_STMT_OPERAND (m_expr, 0)) != SSA_NAME
       && bb != loop->header
       && !bb_with_exit_edge_p (loop, bb))
     {
@@ -392,7 +394,7 @@ if_convertible_modify_expr_p (struct loop *loop, basic_block bb, tree m_expr)
 
 /* Return true, iff STMT is if-convertible.
    Statement is if-convertible if,
-   - It is if-convertible MODIFY_EXPR
+   - It is if-convertible GIMPLE_MODIFY_STMT
    - IT is LABEL_EXPR or COND_EXPR.
    STMT is inside block BB, which is inside loop LOOP.  */
 
@@ -404,9 +406,9 @@ if_convertible_stmt_p (struct loop *loop, basic_block bb, tree stmt)
     case LABEL_EXPR:
       break;
 
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
 
-      if (!if_convertible_modify_expr_p (loop, bb, stmt))
+      if (!if_convertible_gimple_modify_stmt_p (loop, bb, stmt))
 	return false;
       break;
 
@@ -634,7 +636,7 @@ add_to_dst_predicate_list (struct loop * loop, basic_block bb,
 		    unshare_expr (prev_cond), cond);
       tmp_stmt = ifc_temp_var (boolean_type_node, tmp);
       bsi_insert_before (bsi, tmp_stmt, BSI_SAME_STMT);
-      new_cond = TREE_OPERAND (tmp_stmt, 0);
+      new_cond = GIMPLE_STMT_OPERAND (tmp_stmt, 0);
     }
   add_to_predicate_list (bb, new_cond);
   return new_cond;
@@ -741,7 +743,7 @@ find_phi_replacement_condition (struct loop *loop,
 
       new_stmt = ifc_temp_var (TREE_TYPE (*cond), unshare_expr (*cond));
       bsi_insert_before (bsi, new_stmt, BSI_SAME_STMT);
-      *cond = TREE_OPERAND (new_stmt, 0);
+      *cond = GIMPLE_STMT_OPERAND (new_stmt, 0);
     }
 
   gcc_assert (*cond);
@@ -761,8 +763,9 @@ find_phi_replacement_condition (struct loop *loop,
 */
 
 static void
-replace_phi_with_cond_modify_expr (tree phi, tree cond, basic_block true_bb,
-                                   block_stmt_iterator *bsi)
+replace_phi_with_cond_gimple_modify_stmt (tree phi, tree cond,
+    					  basic_block true_bb,
+                                   	  block_stmt_iterator *bsi)
 {
   tree new_stmt;
   basic_block bb;
@@ -799,7 +802,7 @@ replace_phi_with_cond_modify_expr (tree phi, tree cond, basic_block true_bb,
 	        unshare_expr (arg_1));
 
   /* Create new MODIFY expression using RHS.  */
-  new_stmt = build2 (MODIFY_EXPR, TREE_TYPE (PHI_RESULT (phi)),
+  new_stmt = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (PHI_RESULT (phi)),
 		     unshare_expr (PHI_RESULT (phi)), rhs);
 
   /* Make new statement definition of the original phi result.  */
@@ -848,7 +851,7 @@ process_phi_nodes (struct loop *loop)
       while (phi)
 	{
 	  tree next = PHI_CHAIN (phi);
-	  replace_phi_with_cond_modify_expr (phi, cond, true_bb, &bsi);
+	  replace_phi_with_cond_gimple_modify_stmt (phi, cond, true_bb, &bsi);
 	  release_phi_node (phi);
 	  phi = next;
 	}
@@ -963,7 +966,7 @@ combine_blocks (struct loop *loop)
     merge_blocks (loop->header, exit_bb);
 }
 
-/* Make new  temp variable of type TYPE. Add MODIFY_EXPR to assign EXP
+/* Make new  temp variable of type TYPE. Add GIMPLE_MODIFY_STMT to assign EXP
    to the new variable.  */
 
 static tree
@@ -980,12 +983,12 @@ ifc_temp_var (tree type, tree exp)
   add_referenced_var (var);
 
   /* Build new statement to assign EXP to new variable.  */
-  stmt = build2 (MODIFY_EXPR, type, var, exp);
+  stmt = build2 (GIMPLE_MODIFY_STMT, type, var, exp);
 
   /* Get SSA name for the new variable and set make new statement
      its definition statement.  */
   new_name = make_ssa_name (var, stmt);
-  TREE_OPERAND (stmt, 0) = new_name;
+  GIMPLE_STMT_OPERAND (stmt, 0) = new_name;
   SSA_NAME_DEF_STMT (new_name) = stmt;
 
   return stmt;
diff --git a/gcc/tree-inline.c b/gcc/tree-inline.c
index 4b1c70919f5a084c7de68755ec61a61e814b7c13..429cc2cb0f6d1704b8bcaa19a5a32b54b09f5c39 100644
--- a/gcc/tree-inline.c
+++ b/gcc/tree-inline.c
@@ -58,7 +58,7 @@ Boston, MA 02110-1301, USA.  */
 
    Inlining: a function body is duplicated, but the PARM_DECLs are
    remapped into VAR_DECLs, and non-void RETURN_EXPRs become
-   MODIFY_EXPRs that store to a dedicated returned-value variable.
+   GIMPLE_MODIFY_STMTs that store to a dedicated returned-value variable.
    The duplicated eh_region info of the copy will later be appended
    to the info for the caller; the eh_region info in copied throwing
    statements and RESX_EXPRs is adjusted accordingly.
@@ -476,7 +476,7 @@ copy_body_r (tree *tp, int *walk_subtrees, void *data)
      duplicated and/or tweaked.  */
 
   /* When requested, RETURN_EXPRs should be transformed to just the
-     contained MODIFY_EXPR.  The branch semantics of the return will
+     contained GIMPLE_MODIFY_STMT.  The branch semantics of the return will
      be handled elsewhere by manipulating the CFG rather than a statement.  */
   if (TREE_CODE (*tp) == RETURN_EXPR && id->transform_return_to_modify)
     {
@@ -487,10 +487,10 @@ copy_body_r (tree *tp, int *walk_subtrees, void *data)
 	 If the "assignment" is just the result decl, the result
 	 decl has already been set (e.g. a recent "foo (&result_decl,
 	 ...)"); just toss the entire RETURN_EXPR.  */
-      if (assignment && TREE_CODE (assignment) == MODIFY_EXPR)
+      if (assignment && TREE_CODE (assignment) == GIMPLE_MODIFY_STMT)
 	{
 	  /* Replace the RETURN_EXPR with (a copy of) the
-	     MODIFY_EXPR hanging underneath.  */
+	     GIMPLE_MODIFY_STMT hanging underneath.  */
 	  *tp = copy_node (assignment);
 	}
       else /* Else the RETURN_EXPR returns no value.  */
@@ -557,15 +557,15 @@ copy_body_r (tree *tp, int *walk_subtrees, void *data)
       /* Here we handle trees that are not completely rewritten.
 	 First we detect some inlining-induced bogosities for
 	 discarding.  */
-      if (TREE_CODE (*tp) == MODIFY_EXPR
-	  && TREE_OPERAND (*tp, 0) == TREE_OPERAND (*tp, 1)
+      if (TREE_CODE (*tp) == GIMPLE_MODIFY_STMT
+	  && GIMPLE_STMT_OPERAND (*tp, 0) == GIMPLE_STMT_OPERAND (*tp, 1)
 	  && (lang_hooks.tree_inlining.auto_var_in_fn_p
-	      (TREE_OPERAND (*tp, 0), fn)))
+	      (GIMPLE_STMT_OPERAND (*tp, 0), fn)))
 	{
 	  /* Some assignments VAR = VAR; don't generate any rtl code
 	     and thus don't count as variable modification.  Avoid
 	     keeping bogosities like 0 = 0.  */
-	  tree decl = TREE_OPERAND (*tp, 0), value;
+	  tree decl = GIMPLE_STMT_OPERAND (*tp, 0), value;
 	  splay_tree_node n;
 
 	  n = splay_tree_lookup (id->decl_map, (splay_tree_key) decl);
@@ -624,7 +624,7 @@ copy_body_r (tree *tp, int *walk_subtrees, void *data)
       /* If EXPR has block defined, map it to newly constructed block.
          When inlining we want EXPRs without block appear in the block
 	 of function call.  */
-      if (IS_EXPR_CODE_CLASS (TREE_CODE_CLASS (TREE_CODE (*tp))))
+      if (EXPR_P (*tp) || GIMPLE_STMT_P (*tp))
 	{
 	  new_block = id->block;
 	  if (TREE_BLOCK (*tp))
@@ -644,7 +644,8 @@ copy_body_r (tree *tp, int *walk_subtrees, void *data)
 	    (NULL_TREE,
 	     id->eh_region_offset + TREE_INT_CST_LOW (TREE_OPERAND (*tp, 0)));
 
-      TREE_TYPE (*tp) = remap_type (TREE_TYPE (*tp), id);
+      if (!GIMPLE_TUPLE_P (*tp))
+	TREE_TYPE (*tp) = remap_type (TREE_TYPE (*tp), id);
 
       /* The copied TARGET_EXPR has never been expanded, even if the
 	 original node was expanded already.  */
@@ -708,9 +709,9 @@ copy_bb (copy_body_data *id, basic_block bb, int frequency_scale, int count_scal
 
 	  /* With return slot optimization we can end up with
 	     non-gimple (foo *)&this->m, fix that here.  */
-	  if (TREE_CODE (stmt) == MODIFY_EXPR
-	      && TREE_CODE (TREE_OPERAND (stmt, 1)) == NOP_EXPR
-	      && !is_gimple_val (TREE_OPERAND (TREE_OPERAND (stmt, 1), 0)))
+	  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+	      && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == NOP_EXPR
+	      && !is_gimple_val (TREE_OPERAND (GIMPLE_STMT_OPERAND (stmt, 1), 0)))
 	    gimplify_stmt (&stmt);
 
           bsi_insert_after (&copy_bsi, stmt, BSI_NEW_STMT);
@@ -1093,9 +1094,9 @@ setup_one_parameter (copy_body_data *id, tree p, tree value, tree fn,
 
       STRIP_USELESS_TYPE_CONVERSION (rhs);
 
-      /* We want to use MODIFY_EXPR, not INIT_EXPR here so that we
+      /* We want to use GIMPLE_MODIFY_STMT, not INIT_EXPR here so that we
 	 keep our trees in gimple form.  */
-      init_stmt = build2 (MODIFY_EXPR, TREE_TYPE (var), var, rhs);
+      init_stmt = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (var), var, rhs);
 
       /* If we did not create a gimple value and we did not create a gimple
 	 cast of a gimple value, then we will need to gimplify INIT_STMTS
@@ -1167,7 +1168,7 @@ initialize_inlined_parameters (copy_body_data *id, tree args, tree static_chain,
 
    RETURN_SLOT_ADDR, if non-null, was a fake parameter that
    took the address of the result.  MODIFY_DEST, if non-null, was the LHS of
-   the MODIFY_EXPR to which this call is the RHS.
+   the GIMPLE_MODIFY_STMT to which this call is the RHS.
 
    The return value is a (possibly null) value that is the result of the
    function as seen by the callee.  *USE_P is a (possibly null) value that
@@ -1657,30 +1658,32 @@ estimate_num_insns_1 (tree *tp, int *walk_subtrees, void *data)
 	3) TARGET_EXPRs.
 
        Let us look at the first two cases, assuming we have "a = b + C":
-       <modify_expr <var_decl "a"> <plus_expr <var_decl "b"> <constant C>>
+       <GIMPLE_MODIFY_STMT <var_decl "a">
+       			   <plus_expr <var_decl "b"> <constant C>>
        If "a" is a GIMPLE register, the assignment to it is free on almost
        any target, because "a" usually ends up in a real register.  Hence
        the only cost of this expression comes from the PLUS_EXPR, and we
-       can ignore the MODIFY_EXPR.
+       can ignore the GIMPLE_MODIFY_STMT.
        If "a" is not a GIMPLE register, the assignment to "a" will most
-       likely be a real store, so the cost of the MODIFY_EXPR is the cost
+       likely be a real store, so the cost of the GIMPLE_MODIFY_STMT is the cost
        of moving something into "a", which we compute using the function
        estimate_move_cost.
 
        The third case deals with TARGET_EXPRs, for which the semantics are
        that a temporary is assigned, unless the TARGET_EXPR itself is being
        assigned to something else.  In the latter case we do not need the
-       temporary.  E.g. in <modify_expr <var_decl "a"> <target_expr>>, the
-       MODIFY_EXPR is free.  */
+       temporary.  E.g. in:
+       		<GIMPLE_MODIFY_STMT <var_decl "a"> <target_expr>>, the
+       GIMPLE_MODIFY_STMT is free.  */
     case INIT_EXPR:
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       /* Is the right and side a TARGET_EXPR?  */
-      if (TREE_CODE (TREE_OPERAND (x, 1)) == TARGET_EXPR)
+      if (TREE_CODE (GENERIC_TREE_OPERAND (x, 1)) == TARGET_EXPR)
 	break;
       /* ... fall through ...  */
 
     case TARGET_EXPR:
-      x = TREE_OPERAND (x, 0);
+      x = GENERIC_TREE_OPERAND (x, 0);
       /* Is this an assignments to a register?  */
       if (is_gimple_reg (x))
 	break;
@@ -2100,9 +2103,9 @@ expand_call_inline (basic_block bb, tree stmt, tree *tp, void *data)
 
   /* Find the lhs to which the result of this call is assigned.  */
   return_slot_addr = NULL;
-  if (TREE_CODE (stmt) == MODIFY_EXPR)
+  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
     {
-      modify_dest = TREE_OPERAND (stmt, 0);
+      modify_dest = GIMPLE_STMT_OPERAND (stmt, 0);
 
       /* The function which we are inlining might not return a value,
 	 in which case we should issue a warning that the function
@@ -2189,7 +2192,7 @@ expand_call_inline (basic_block bb, tree stmt, tree *tp, void *data)
 
 /* Expand call statements reachable from STMT_P.
    We can only have CALL_EXPRs as the "toplevel" tree code or nested
-   in a MODIFY_EXPR.  See tree-gimple.c:get_call_expr_in().  We can
+   in a GIMPLE_MODIFY_STMT.  See tree-gimple.c:get_call_expr_in().  We can
    unfortunately not use that function here because we need a pointer
    to the CALL_EXPR, not the tree itself.  */
 
@@ -2205,8 +2208,8 @@ gimple_expand_calls_inline (basic_block bb, copy_body_data *id)
       tree *expr_p = bsi_stmt_ptr (bsi);
       tree stmt = *expr_p;
 
-      if (TREE_CODE (*expr_p) == MODIFY_EXPR)
-	expr_p = &TREE_OPERAND (*expr_p, 1);
+      if (TREE_CODE (*expr_p) == GIMPLE_MODIFY_STMT)
+	expr_p = &GIMPLE_STMT_OPERAND (*expr_p, 1);
       if (TREE_CODE (*expr_p) == WITH_SIZE_EXPR)
 	expr_p = &TREE_OPERAND (*expr_p, 0);
       if (TREE_CODE (*expr_p) == CALL_EXPR)
@@ -2320,9 +2323,11 @@ tree
 copy_tree_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
 {
   enum tree_code code = TREE_CODE (*tp);
+  enum tree_code_class cl = TREE_CODE_CLASS (code);
 
   /* We make copies of most nodes.  */
-  if (IS_EXPR_CODE_CLASS (TREE_CODE_CLASS (code))
+  if (IS_EXPR_CODE_CLASS (cl)
+      || IS_GIMPLE_STMT_CODE_CLASS (cl)
       || code == TREE_LIST
       || code == TREE_VEC
       || code == TYPE_DECL
@@ -2330,8 +2335,10 @@ copy_tree_r (tree *tp, int *walk_subtrees, void *data ATTRIBUTE_UNUSED)
     {
       /* Because the chain gets clobbered when we make a copy, we save it
 	 here.  */
-      tree chain = TREE_CHAIN (*tp);
-      tree new;
+      tree chain = NULL_TREE, new;
+
+      if (!GIMPLE_TUPLE_P (*tp))
+	chain = TREE_CHAIN (*tp);
 
       /* Copy the node.  */
       new = copy_node (*tp);
diff --git a/gcc/tree-into-ssa.c b/gcc/tree-into-ssa.c
index 3fb2c53181741a5e894131cc14f3e6681ae1deb8..90f3dd359d3b10841b9f7ff1f7e69385d0073daf 100644
--- a/gcc/tree-into-ssa.c
+++ b/gcc/tree-into-ssa.c
@@ -245,7 +245,7 @@ enum rewrite_mode {
    processed from those that only need to have their defs processed.
    Statements that define new SSA names only need to have their defs
    registered, but they don't need to have their uses renamed.  */
-#define REGISTER_DEFS_IN_THIS_STMT(T)	(T)->common.unsigned_flag
+#define REGISTER_DEFS_IN_THIS_STMT(T)	(T)->base.unsigned_flag
 
 
 /* Prototypes for debugging functions.  */
diff --git a/gcc/tree-mudflap.c b/gcc/tree-mudflap.c
index 54cedb844a3dcd6f69fe34b6cb6fb3e9f40417bf..4d80c19d385d63b7c8ba3bd7de4d281e972e47f3 100644
--- a/gcc/tree-mudflap.c
+++ b/gcc/tree-mudflap.c
@@ -458,13 +458,13 @@ mf_decl_cache_locals (void)
 
   /* Build initialization nodes for the cache vars.  We just load the
      globals into the cache variables.  */
-  t = build2 (MODIFY_EXPR, TREE_TYPE (mf_cache_shift_decl_l),
+  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (mf_cache_shift_decl_l),
               mf_cache_shift_decl_l, mf_cache_shift_decl);
   SET_EXPR_LOCATION (t, DECL_SOURCE_LOCATION (current_function_decl));
   gimplify_to_stmt_list (&t);
   shift_init_stmts = t;
 
-  t = build2 (MODIFY_EXPR, TREE_TYPE (mf_cache_mask_decl_l),
+  t = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (mf_cache_mask_decl_l),
               mf_cache_mask_decl_l, mf_cache_mask_decl);
   SET_EXPR_LOCATION (t, DECL_SOURCE_LOCATION (current_function_decl));
   gimplify_to_stmt_list (&t);
@@ -553,7 +553,7 @@ mf_build_check_statement_for (tree base, tree limit,
   mf_limit = create_tmp_var (mf_uintptr_type, "__mf_limit");
 
   /* Build: __mf_base = (uintptr_t) <base address expression>.  */
-  t = build2 (MODIFY_EXPR, void_type_node, mf_base,
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, mf_base,
               convert (mf_uintptr_type, unshare_expr (base)));
   SET_EXPR_LOCUS (t, locus);
   gimplify_to_stmt_list (&t);
@@ -561,7 +561,7 @@ mf_build_check_statement_for (tree base, tree limit,
   tsi = tsi_last (t);
 
   /* Build: __mf_limit = (uintptr_t) <limit address expression>.  */
-  t = build2 (MODIFY_EXPR, void_type_node, mf_limit,
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, mf_limit,
               convert (mf_uintptr_type, unshare_expr (limit)));
   SET_EXPR_LOCUS (t, locus);
   gimplify_to_stmt_list (&t);
@@ -577,7 +577,7 @@ mf_build_check_statement_for (tree base, tree limit,
               TREE_TYPE (TREE_TYPE (mf_cache_array_decl)),
               mf_cache_array_decl, t, NULL_TREE, NULL_TREE);
   t = build1 (ADDR_EXPR, mf_cache_structptr_type, t);
-  t = build2 (MODIFY_EXPR, void_type_node, mf_elem, t);
+  t = build2 (GIMPLE_MODIFY_STMT, void_type_node, mf_elem, t);
   SET_EXPR_LOCUS (t, locus);
   gimplify_to_stmt_list (&t);
   tsi_link_after (&tsi, t, TSI_CONTINUE_LINKING);
@@ -623,7 +623,7 @@ mf_build_check_statement_for (tree base, tree limit,
      can use as the condition for the conditional jump.  */
   t = build2 (TRUTH_OR_EXPR, boolean_type_node, t, u);
   cond = create_tmp_var (boolean_type_node, "__mf_unlikely_cond");
-  t = build2 (MODIFY_EXPR, boolean_type_node, cond, t);
+  t = build2 (GIMPLE_MODIFY_STMT, boolean_type_node, cond, t);
   gimplify_to_stmt_list (&t);
   tsi_link_after (&tsi, t, TSI_CONTINUE_LINKING);
 
@@ -676,11 +676,11 @@ mf_build_check_statement_for (tree base, tree limit,
 
   if (! flag_mudflap_threads)
     {
-      t = build2 (MODIFY_EXPR, void_type_node,
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node,
                   mf_cache_shift_decl_l, mf_cache_shift_decl);
       tsi_link_after (&tsi, t, TSI_CONTINUE_LINKING);
 
-      t = build2 (MODIFY_EXPR, void_type_node,
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node,
                   mf_cache_mask_decl_l, mf_cache_mask_decl);
       tsi_link_after (&tsi, t, TSI_CONTINUE_LINKING);
     }
@@ -912,18 +912,19 @@ mf_xform_derefs (void)
           /* Only a few GIMPLE statements can reference memory.  */
           switch (TREE_CODE (s))
             {
-            case MODIFY_EXPR:
-              mf_xform_derefs_1 (&i, &TREE_OPERAND (s, 0), EXPR_LOCUS (s),
-                                 integer_one_node);
-              mf_xform_derefs_1 (&i, &TREE_OPERAND (s, 1), EXPR_LOCUS (s),
-                                 integer_zero_node);
+            case GIMPLE_MODIFY_STMT:
+              mf_xform_derefs_1 (&i, &GIMPLE_STMT_OPERAND (s, 0),
+		  		 EXPR_LOCUS (s), integer_one_node);
+              mf_xform_derefs_1 (&i, &GIMPLE_STMT_OPERAND (s, 1),
+		  		 EXPR_LOCUS (s), integer_zero_node);
               break;
 
             case RETURN_EXPR:
               if (TREE_OPERAND (s, 0) != NULL_TREE)
                 {
-                  if (TREE_CODE (TREE_OPERAND (s, 0)) == MODIFY_EXPR)
-                    mf_xform_derefs_1 (&i, &TREE_OPERAND (TREE_OPERAND (s, 0), 1),
+                  if (TREE_CODE (TREE_OPERAND (s, 0)) == GIMPLE_MODIFY_STMT)
+                    mf_xform_derefs_1 (&i, &GIMPLE_STMT_OPERAND
+					     (TREE_OPERAND (s, 0), 1),
                                        EXPR_LOCUS (s), integer_zero_node);
                   else
                     mf_xform_derefs_1 (&i, &TREE_OPERAND (s, 0), EXPR_LOCUS (s),
diff --git a/gcc/tree-nested.c b/gcc/tree-nested.c
index 7467dca84e6a2611849d9317ead2849291fa6d87..ed4a1ae664706b01060d90469603d407cbda7287 100644
--- a/gcc/tree-nested.c
+++ b/gcc/tree-nested.c
@@ -388,7 +388,7 @@ init_tmp_var (struct nesting_info *info, tree exp, tree_stmt_iterator *tsi)
   tree t, stmt;
 
   t = create_tmp_var_for (info, TREE_TYPE (exp), NULL);
-  stmt = build2 (MODIFY_EXPR, TREE_TYPE (t), t, exp);
+  stmt = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (t), t, exp);
   SET_EXPR_LOCUS (stmt, EXPR_LOCUS (tsi_stmt (*tsi)));
   tsi_link_before (tsi, stmt, TSI_SAME_STMT);
 
@@ -416,7 +416,7 @@ save_tmp_var (struct nesting_info *info, tree exp,
   tree t, stmt;
 
   t = create_tmp_var_for (info, TREE_TYPE (exp), NULL);
-  stmt = build2 (MODIFY_EXPR, TREE_TYPE (t), exp, t);
+  stmt = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (t), exp, t);
   SET_EXPR_LOCUS (stmt, EXPR_LOCUS (tsi_stmt (*tsi)));
   tsi_link_after (tsi, stmt, TSI_SAME_STMT);
 
@@ -613,16 +613,16 @@ walk_stmts (struct walk_stmt_info *wi, tree *tp)
       walk_stmts (wi, &TREE_OPERAND (t, 0));
       break;
 
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       /* A formal temporary lhs may use a COMPONENT_REF rhs.  */
-      wi->val_only = !is_gimple_formal_tmp_var (TREE_OPERAND (t, 0));
-      walk_tree (&TREE_OPERAND (t, 1), wi->callback, wi, NULL);
+      wi->val_only = !is_gimple_formal_tmp_var (GIMPLE_STMT_OPERAND (t, 0));
+      walk_tree (&GIMPLE_STMT_OPERAND (t, 1), wi->callback, wi, NULL);
 
       /* If the rhs is appropriate for a memory, we may use a
 	 COMPONENT_REF on the lhs.  */
-      wi->val_only = !is_gimple_mem_rhs (TREE_OPERAND (t, 1));
+      wi->val_only = !is_gimple_mem_rhs (GIMPLE_STMT_OPERAND (t, 1));
       wi->is_lhs = true;
-      walk_tree (&TREE_OPERAND (t, 0), wi->callback, wi, NULL);
+      walk_tree (&GIMPLE_STMT_OPERAND (t, 0), wi->callback, wi, NULL);
 
       wi->val_only = true;
       wi->is_lhs = false;
@@ -1648,7 +1648,7 @@ convert_call_expr (tree *tp, int *walk_subtrees, void *data)
       break;
 
     case RETURN_EXPR:
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
     case WITH_SIZE_EXPR:
       /* Only return modify and with_size_expr may contain calls.  */
       *walk_subtrees = 1;
@@ -1770,7 +1770,7 @@ finalize_nesting_tree_1 (struct nesting_info *root)
 
 	  y = build3 (COMPONENT_REF, TREE_TYPE (field),
 		      root->frame_decl, field, NULL_TREE);
-	  x = build2 (MODIFY_EXPR, TREE_TYPE (field), y, x);
+	  x = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (field), y, x);
 	  append_to_statement_list (x, &stmt_list);
 	}
     }
@@ -1781,7 +1781,7 @@ finalize_nesting_tree_1 (struct nesting_info *root)
     {
       tree x = build3 (COMPONENT_REF, TREE_TYPE (root->chain_field),
 		       root->frame_decl, root->chain_field, NULL_TREE);
-      x = build2 (MODIFY_EXPR, TREE_TYPE (x), x, get_chain_decl (root));
+      x = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (x), x, get_chain_decl (root));
       append_to_statement_list (x, &stmt_list);
     }
 
diff --git a/gcc/tree-nrv.c b/gcc/tree-nrv.c
index f51afdb258c2d9d554ad4bd2e95772ce4be5a00a..c33ff0ea31aba54b5aaaa3e0252384e2920e7682 100644
--- a/gcc/tree-nrv.c
+++ b/gcc/tree-nrv.c
@@ -133,10 +133,10 @@ tree_nrv (void)
 	      if (ret_expr)
 		gcc_assert (ret_expr == result);
 	    }
-	  else if (TREE_CODE (stmt) == MODIFY_EXPR
-		   && TREE_OPERAND (stmt, 0) == result)
+	  else if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+		   && GIMPLE_STMT_OPERAND (stmt, 0) == result)
 	    {
-	      ret_expr = TREE_OPERAND (stmt, 1);
+	      ret_expr = GIMPLE_STMT_OPERAND (stmt, 1);
 
 	      /* Now verify that this return statement uses the same value
 		 as any previously encountered return statement.  */
@@ -197,9 +197,9 @@ tree_nrv (void)
 	{
 	  tree *tp = bsi_stmt_ptr (bsi);
 	  /* If this is a copy from VAR to RESULT, remove it.  */
-	  if (TREE_CODE (*tp) == MODIFY_EXPR
-	      && TREE_OPERAND (*tp, 0) == result
-	      && TREE_OPERAND (*tp, 1) == found)
+	  if (TREE_CODE (*tp) == GIMPLE_MODIFY_STMT
+	      && GIMPLE_STMT_OPERAND (*tp, 0) == result
+	      && GIMPLE_STMT_OPERAND (*tp, 1) == found)
 	    bsi_remove (&bsi, true);
 	  else
 	    {
@@ -264,7 +264,7 @@ dest_safe_for_nrv_p (tree dest)
     }
 }
 
-/* Walk through the function looking for MODIFY_EXPRs with calls that
+/* Walk through the function looking for GIMPLE_MODIFY_STMTs with calls that
    return in memory on the RHS.  For each of these, determine whether it is
    safe to pass the address of the LHS as the return slot, and mark the
    call appropriately if so.
@@ -289,15 +289,15 @@ execute_return_slot_opt (void)
 	  tree stmt = bsi_stmt (i);
 	  tree call;
 
-	  if (TREE_CODE (stmt) == MODIFY_EXPR
-	      && (call = TREE_OPERAND (stmt, 1),
+	  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+	      && (call = GIMPLE_STMT_OPERAND (stmt, 1),
 		  TREE_CODE (call) == CALL_EXPR)
 	      && !CALL_EXPR_RETURN_SLOT_OPT (call)
 	      && aggregate_value_p (call, call))
 	    /* Check if the location being assigned to is
 	       call-clobbered.  */
 	    CALL_EXPR_RETURN_SLOT_OPT (call) =
-	      dest_safe_for_nrv_p (TREE_OPERAND (stmt, 0)) ? 1 : 0;
+	      dest_safe_for_nrv_p (GIMPLE_STMT_OPERAND (stmt, 0)) ? 1 : 0;
 	}
     }
   return 0;
diff --git a/gcc/tree-object-size.c b/gcc/tree-object-size.c
index 7a3d77571864e837719b94b4b4635012e6f6b401..7ae87d67539810bb2bab2a297d79a0d7a960d691 100644
--- a/gcc/tree-object-size.c
+++ b/gcc/tree-object-size.c
@@ -688,13 +688,13 @@ collect_object_sizes_for (struct object_size_info *osi, tree var)
   switch (TREE_CODE (stmt))
     {
     case RETURN_EXPR:
-      gcc_assert (TREE_CODE (TREE_OPERAND (stmt, 0)) == MODIFY_EXPR);
+      gcc_assert (TREE_CODE (TREE_OPERAND (stmt, 0)) == GIMPLE_MODIFY_STMT);
       stmt = TREE_OPERAND (stmt, 0);
       /* FALLTHRU  */
 
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       {
-	tree rhs = TREE_OPERAND (stmt, 1), arg;
+	tree rhs = GIMPLE_STMT_OPERAND (stmt, 1), arg;
 	STRIP_NOPS (rhs);
 
 	if (TREE_CODE (rhs) == CALL_EXPR)
@@ -814,13 +814,13 @@ check_for_plus_in_loops_1 (struct object_size_info *osi, tree var,
   switch (TREE_CODE (stmt))
     {
     case RETURN_EXPR:
-      gcc_assert (TREE_CODE (TREE_OPERAND (stmt, 0)) == MODIFY_EXPR);
+      gcc_assert (TREE_CODE (TREE_OPERAND (stmt, 0)) == GIMPLE_MODIFY_STMT);
       stmt = TREE_OPERAND (stmt, 0);
       /* FALLTHRU  */
 
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       {
-	tree rhs = TREE_OPERAND (stmt, 1), arg;
+	tree rhs = GIMPLE_STMT_OPERAND (stmt, 1), arg;
 	STRIP_NOPS (rhs);
 
 	if (TREE_CODE (rhs) == CALL_EXPR)
@@ -892,13 +892,13 @@ check_for_plus_in_loops (struct object_size_info *osi, tree var)
   switch (TREE_CODE (stmt))
     {
     case RETURN_EXPR:
-      gcc_assert (TREE_CODE (TREE_OPERAND (stmt, 0)) == MODIFY_EXPR);
+      gcc_assert (TREE_CODE (TREE_OPERAND (stmt, 0)) == GIMPLE_MODIFY_STMT);
       stmt = TREE_OPERAND (stmt, 0);
       /* FALLTHRU  */
 
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       {
-	tree rhs = TREE_OPERAND (stmt, 1), arg;
+	tree rhs = GIMPLE_STMT_OPERAND (stmt, 1), arg;
 	STRIP_NOPS (rhs);
 
 	if (TREE_CODE (rhs) == CALL_EXPR)
diff --git a/gcc/tree-optimize.c b/gcc/tree-optimize.c
index 50dd22b451fa4f3872ddfc1967510ca56d0cb2f3..9e4af19bbad66a0865d9fa7e5f77f3cab32a6a24 100644
--- a/gcc/tree-optimize.c
+++ b/gcc/tree-optimize.c
@@ -206,8 +206,8 @@ execute_free_cfg_annotations (void)
     for (bsi = bsi_start (bb); !bsi_end_p (bsi); bsi_next (&bsi))
       {
 	tree stmt = bsi_stmt (bsi);
-	ggc_free (stmt->common.ann);
-	stmt->common.ann = NULL;
+	ggc_free (stmt->base.ann);
+	stmt->base.ann = NULL;
       }
 
   /* And get rid of annotations we no longer need.  */
diff --git a/gcc/tree-outof-ssa.c b/gcc/tree-outof-ssa.c
index 3a7d0171b636127a5c597f01dc4400f2f5b77051..279934d98e638dac55b23f6f477a0563998b5a27 100644
--- a/gcc/tree-outof-ssa.c
+++ b/gcc/tree-outof-ssa.c
@@ -188,7 +188,7 @@ insert_copy_on_edge (edge e, tree dest, tree src)
 {
   tree copy;
 
-  copy = build2 (MODIFY_EXPR, TREE_TYPE (dest), dest, src);
+  copy = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (dest), dest, src);
   set_is_used (dest);
 
   if (TREE_CODE (src) == ADDR_EXPR)
@@ -1026,10 +1026,10 @@ replace_use_variable (var_map map, use_operand_p p, tree *expr)
       int version = SSA_NAME_VERSION (var);
       if (expr[version])
         {
-	  tree new_expr = TREE_OPERAND (expr[version], 1);
+	  tree new_expr = GIMPLE_STMT_OPERAND (expr[version], 1);
 	  SET_USE (p, new_expr);
 	  /* Clear the stmt's RHS, or GC might bite us.  */
-	  TREE_OPERAND (expr[version], 1) = NULL_TREE;
+	  GIMPLE_STMT_OPERAND (expr[version], 1) = NULL_TREE;
 	  return true;
 	}
     }
@@ -1437,7 +1437,7 @@ check_replaceable (temp_expr_table_p tab, tree stmt)
   tree call_expr;
   bitmap def_vars, use_vars;
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
   
   /* Punt if there is more than 1 def, or more than 1 use.  */
@@ -1453,7 +1453,8 @@ check_replaceable (temp_expr_table_p tab, tree stmt)
     return false;
 
   /* Float expressions must go through memory if float-store is on.  */
-  if (flag_float_store && FLOAT_TYPE_P (TREE_TYPE (TREE_OPERAND (stmt, 1))))
+  if (flag_float_store && FLOAT_TYPE_P (TREE_TYPE
+					(GENERIC_TREE_OPERAND (stmt, 1))))
     return false;
 
   /* Calls to functions with side-effects cannot be replaced.  */
@@ -1793,8 +1794,8 @@ rewrite_trees (var_map map, tree *values)
 	  ann = stmt_ann (stmt);
 	  changed = false;
 
-	  if (TREE_CODE (stmt) == MODIFY_EXPR 
-	      && (TREE_CODE (TREE_OPERAND (stmt, 1)) == SSA_NAME))
+	  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT 
+	      && (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == SSA_NAME))
 	    is_copy = true;
 
 	  copy_use_p = NULL_USE_OPERAND_P;
@@ -1877,17 +1878,17 @@ static inline bool
 identical_copies_p (tree s1, tree s2)
 {
 #ifdef ENABLE_CHECKING
-  gcc_assert (TREE_CODE (s1) == MODIFY_EXPR);
-  gcc_assert (TREE_CODE (s2) == MODIFY_EXPR);
-  gcc_assert (DECL_P (TREE_OPERAND (s1, 0)));
-  gcc_assert (DECL_P (TREE_OPERAND (s2, 0)));
+  gcc_assert (TREE_CODE (s1) == GIMPLE_MODIFY_STMT);
+  gcc_assert (TREE_CODE (s2) == GIMPLE_MODIFY_STMT);
+  gcc_assert (DECL_P (GIMPLE_STMT_OPERAND (s1, 0)));
+  gcc_assert (DECL_P (GIMPLE_STMT_OPERAND (s2, 0)));
 #endif
 
-  if (TREE_OPERAND (s1, 0) != TREE_OPERAND (s2, 0))
+  if (GIMPLE_STMT_OPERAND (s1, 0) != GIMPLE_STMT_OPERAND (s2, 0))
     return false;
 
-  s1 = TREE_OPERAND (s1, 1);
-  s2 = TREE_OPERAND (s2, 1);
+  s1 = GIMPLE_STMT_OPERAND (s1, 1);
+  s2 = GIMPLE_STMT_OPERAND (s2, 1);
 
   if (s1 != s2)
     return false;
@@ -2343,10 +2344,10 @@ insert_backedge_copies (void)
 
 		  /* Create a new instance of the underlying
 		     variable of the PHI result.  */
-		  stmt = build2 (MODIFY_EXPR, TREE_TYPE (result_var),
+		  stmt = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (result_var),
 				 NULL_TREE, PHI_ARG_DEF (phi, i));
 		  name = make_ssa_name (result_var, stmt);
-		  TREE_OPERAND (stmt, 0) = name;
+		  GIMPLE_STMT_OPERAND (stmt, 0) = name;
 
 		  /* Insert the new statement into the block and update
 		     the PHI node.  */
diff --git a/gcc/tree-pretty-print.c b/gcc/tree-pretty-print.c
index d33d8315adae0130c48def3129903279ae80e839..2c9a8c8a2cba0d7adb38a2d1a281eb5196e8ecef 100644
--- a/gcc/tree-pretty-print.c
+++ b/gcc/tree-pretty-print.c
@@ -419,7 +419,7 @@ dump_generic_node (pretty_printer *buffer, tree node, int spc, int flags,
   if (node == NULL_TREE)
     return spc;
 
-  is_expr = EXPR_P (node);
+  is_expr = EXPR_P (node) || GIMPLE_STMT_P (node);
 
   /* We use has_stmt_ann because CALL_EXPR can be both an expression
      and a statement, and we have no guarantee that it will have a
@@ -1024,12 +1024,15 @@ dump_generic_node (pretty_printer *buffer, tree node, int spc, int flags,
       break;
 
     case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
     case INIT_EXPR:
-      dump_generic_node (buffer, TREE_OPERAND (node, 0), spc, flags, false);
+      dump_generic_node (buffer, GENERIC_TREE_OPERAND (node, 0), spc, flags,
+	  		 false);
       pp_space (buffer);
       pp_character (buffer, '=');
       pp_space (buffer);
-      dump_generic_node (buffer, TREE_OPERAND (node, 1), spc, flags, false);
+      dump_generic_node (buffer, GENERIC_TREE_OPERAND (node, 1), spc, flags,
+	  		 false);
       break;
 
     case TARGET_EXPR:
@@ -1485,8 +1488,10 @@ dump_generic_node (pretty_printer *buffer, tree node, int spc, int flags,
       if (op0)
 	{
 	  pp_space (buffer);
-	  if (TREE_CODE (op0) == MODIFY_EXPR)
-	    dump_generic_node (buffer, TREE_OPERAND (op0, 1), spc, flags, false);
+	  if (TREE_CODE (op0) == MODIFY_EXPR
+	      || TREE_CODE (op0) == GIMPLE_MODIFY_STMT)
+	    dump_generic_node (buffer, GENERIC_TREE_OPERAND (op0, 1),
+			       spc, flags, false);
 	  else
 	    dump_generic_node (buffer, op0, spc, flags, false);
 	}
@@ -2180,6 +2185,7 @@ op_prio (tree op)
       return 1;
 
     case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
     case INIT_EXPR:
       return 2;
 
@@ -2311,6 +2317,7 @@ op_symbol_1 (enum tree_code code)
   switch (code)
     {
     case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       return "=";
 
     case TRUTH_OR_EXPR:
diff --git a/gcc/tree-profile.c b/gcc/tree-profile.c
index fe42309ccc7d3e0f171ddce2e43ae07eabc80782..329ebcd4b6e7e4e4751243ca2db6825a62354601 100644
--- a/gcc/tree-profile.c
+++ b/gcc/tree-profile.c
@@ -106,11 +106,11 @@ tree_gen_edge_profiler (int edgeno, edge e)
   tree tmp1 = create_tmp_var (gcov_type_node, "PROF");
   tree tmp2 = create_tmp_var (gcov_type_node, "PROF");
   tree ref = tree_coverage_counter_ref (GCOV_COUNTER_ARCS, edgeno);
-  tree stmt1 = build2 (MODIFY_EXPR, gcov_type_node, tmp1, ref);
-  tree stmt2 = build2 (MODIFY_EXPR, gcov_type_node, tmp2,
+  tree stmt1 = build2 (GIMPLE_MODIFY_STMT, gcov_type_node, tmp1, ref);
+  tree stmt2 = build2 (GIMPLE_MODIFY_STMT, gcov_type_node, tmp2,
 		       build2 (PLUS_EXPR, gcov_type_node, 
 			      tmp1, integer_one_node));
-  tree stmt3 = build2 (MODIFY_EXPR, gcov_type_node, ref, tmp2);
+  tree stmt3 = build2 (GIMPLE_MODIFY_STMT, gcov_type_node, ref, tmp2);
   bsi_insert_on_edge (e, stmt1);
   bsi_insert_on_edge (e, stmt2);
   bsi_insert_on_edge (e, stmt3);
diff --git a/gcc/tree-scalar-evolution.c b/gcc/tree-scalar-evolution.c
index 0c5955796181b30f514d44554b0c3c0ac58c0744..b882d458b882ec8fccde3a271ae5779da70b31f3 100644
--- a/gcc/tree-scalar-evolution.c
+++ b/gcc/tree-scalar-evolution.c
@@ -48,7 +48,7 @@ Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
    Given a scalar variable to be analyzed, follow the SSA edge to
    its definition:
      
-   - When the definition is a MODIFY_EXPR: if the right hand side
+   - When the definition is a GIMPLE_MODIFY_STMT: if the right hand side
    (RHS) of the definition cannot be statically analyzed, the answer
    of the analyzer is: "don't know".  
    Otherwise, for all the variables that are not yet analyzed in the
@@ -1405,15 +1405,15 @@ follow_ssa_edge (struct loop *loop, tree def, tree halting_phi,
       /* Outer loop.  */
       return t_false;
 
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       return follow_ssa_edge_in_rhs (loop, def,
-				     TREE_OPERAND (def, 1), 
+				     GIMPLE_STMT_OPERAND (def, 1), 
 				     halting_phi, 
 				     evolution_of_loop, limit);
       
     default:
       /* At this level of abstraction, the program is just a set
-	 of MODIFY_EXPRs and PHI_NODEs.  In principle there is no
+	 of GIMPLE_MODIFY_STMTs and PHI_NODEs.  In principle there is no
 	 other node to be handled.  */
       return t_false;
     }
@@ -1607,16 +1607,16 @@ interpret_condition_phi (struct loop *loop, tree condition_phi)
   return res;
 }
 
-/* Interpret the right hand side of a modify_expr OPND1.  If we didn't
+/* Interpret the right hand side of a GIMPLE_MODIFY_STMT OPND1.  If we didn't
    analyze this node before, follow the definitions until ending
-   either on an analyzed modify_expr, or on a loop-phi-node.  On the
+   either on an analyzed GIMPLE_MODIFY_STMT, or on a loop-phi-node.  On the
    return path, this function propagates evolutions (ala constant copy
    propagation).  OPND1 is not a GIMPLE expression because we could
    analyze the effect of an inner loop: see interpret_loop_phi.  */
 
 static tree
-interpret_rhs_modify_expr (struct loop *loop, tree at_stmt,
-			   tree opnd1, tree type)
+interpret_rhs_modify_stmt (struct loop *loop, tree at_stmt,
+			   	  tree opnd1, tree type)
 {
   tree res, opnd10, opnd11, chrec10, chrec11;
 
@@ -1883,15 +1883,15 @@ pointer_used_p (tree ptr)
       if (TREE_CODE (stmt) == COND_EXPR)
 	return true;
 
-      if (TREE_CODE (stmt) != MODIFY_EXPR)
+      if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
 	continue;
 
-      rhs = TREE_OPERAND (stmt, 1);
+      rhs = GIMPLE_STMT_OPERAND (stmt, 1);
       if (!COMPARISON_CLASS_P (rhs))
 	continue;
 
-      if (TREE_OPERAND (stmt, 0) == ptr
-	  || TREE_OPERAND (stmt, 1) == ptr)
+      if (GIMPLE_STMT_OPERAND (stmt, 0) == ptr
+	  || GIMPLE_STMT_OPERAND (stmt, 1) == ptr)
 	return true;
     }
 
@@ -1911,7 +1911,7 @@ analyze_scalar_evolution_1 (struct loop *loop, tree var, tree res)
     return chrec_dont_know;
 
   if (TREE_CODE (var) != SSA_NAME)
-    return interpret_rhs_modify_expr (loop, NULL_TREE, var, type);
+    return interpret_rhs_modify_stmt (loop, NULL_TREE, var, type);
 
   def = SSA_NAME_DEF_STMT (var);
   bb = bb_for_stmt (def);
@@ -1944,8 +1944,9 @@ analyze_scalar_evolution_1 (struct loop *loop, tree var, tree res)
 
   switch (TREE_CODE (def))
     {
-    case MODIFY_EXPR:
-      res = interpret_rhs_modify_expr (loop, def, TREE_OPERAND (def, 1), type);
+    case GIMPLE_MODIFY_STMT:
+      res = interpret_rhs_modify_stmt (loop, def,
+	  			       GIMPLE_STMT_OPERAND (def, 1), type);
 
       if (POINTER_TYPE_P (type)
 	  && !automatically_generated_chrec_p (res)
@@ -3005,14 +3006,14 @@ scev_const_prop (void)
 	  SET_PHI_RESULT (phi, NULL_TREE);
 	  remove_phi_node (phi, NULL_TREE);
 
-	  ass = build2 (MODIFY_EXPR, void_type_node, rslt, NULL_TREE);
+	  ass = build2 (GIMPLE_MODIFY_STMT, void_type_node, rslt, NULL_TREE);
 	  SSA_NAME_DEF_STMT (rslt) = ass;
 	  {
 	    block_stmt_iterator dest = bsi;
 	    bsi_insert_before (&dest, ass, BSI_NEW_STMT);
 	    def = force_gimple_operand_bsi (&dest, def, false, NULL_TREE);
 	  }
-	  TREE_OPERAND (ass, 1) = def;
+	  GIMPLE_STMT_OPERAND (ass, 1) = def;
 	  update_stmt (ass);
 	}
     }
diff --git a/gcc/tree-sra.c b/gcc/tree-sra.c
index a5ed161ed3e9d1260c5867fc2856ef808fc70947..2db1925013ce7ae7220b1afcdce1e43a6d4bdd48 100644
--- a/gcc/tree-sra.c
+++ b/gcc/tree-sra.c
@@ -851,17 +851,17 @@ sra_walk_asm_expr (tree expr, block_stmt_iterator *bsi,
   sra_walk_tree_list (ASM_OUTPUTS (expr), bsi, true, fns);
 }
 
-/* Walk a MODIFY_EXPR and categorize the assignment appropriately.  */
+/* Walk a GIMPLE_MODIFY_STMT and categorize the assignment appropriately.  */
 
 static void
-sra_walk_modify_expr (tree expr, block_stmt_iterator *bsi,
+sra_walk_gimple_modify_stmt (tree expr, block_stmt_iterator *bsi,
 		      const struct sra_walk_fns *fns)
 {
   struct sra_elt *lhs_elt, *rhs_elt;
   tree lhs, rhs;
 
-  lhs = TREE_OPERAND (expr, 0);
-  rhs = TREE_OPERAND (expr, 1);
+  lhs = GIMPLE_STMT_OPERAND (expr, 0);
+  rhs = GIMPLE_STMT_OPERAND (expr, 1);
   lhs_elt = maybe_lookup_element_for_expr (lhs);
   rhs_elt = maybe_lookup_element_for_expr (rhs);
 
@@ -878,7 +878,7 @@ sra_walk_modify_expr (tree expr, block_stmt_iterator *bsi,
       if (!rhs_elt->is_scalar)
 	fns->ldst (rhs_elt, lhs, bsi, false);
       else
-	fns->use (rhs_elt, &TREE_OPERAND (expr, 1), bsi, false, false);
+	fns->use (rhs_elt, &GIMPLE_STMT_OPERAND (expr, 1), bsi, false, false);
     }
 
   /* If it isn't scalarizable, there may be scalarizable variables within, so
@@ -892,7 +892,7 @@ sra_walk_modify_expr (tree expr, block_stmt_iterator *bsi,
       if (call)
 	sra_walk_call_expr (call, bsi, fns);
       else
-	sra_walk_expr (&TREE_OPERAND (expr, 1), bsi, false, fns);
+	sra_walk_expr (&GIMPLE_STMT_OPERAND (expr, 1), bsi, false, fns);
     }
 
   /* Likewise, handle the LHS being scalarizable.  We have cases similar
@@ -924,14 +924,14 @@ sra_walk_modify_expr (tree expr, block_stmt_iterator *bsi,
       /* Otherwise we're being used in some context that requires the
 	 aggregate to be seen as a whole.  Invoke USE.  */
       else
-	fns->use (lhs_elt, &TREE_OPERAND (expr, 0), bsi, true, false);
+	fns->use (lhs_elt, &GIMPLE_STMT_OPERAND (expr, 0), bsi, true, false);
     }
 
   /* Similarly to above, LHS_ELT being null only means that the LHS as a
      whole is not a scalarizable reference.  There may be occurrences of
      scalarizable variables within, which implies a USE.  */
   else
-    sra_walk_expr (&TREE_OPERAND (expr, 0), bsi, true, fns);
+    sra_walk_expr (&GIMPLE_STMT_OPERAND (expr, 0), bsi, true, fns);
 }
 
 /* Entry point to the walk functions.  Search the entire function,
@@ -977,14 +977,14 @@ sra_walk_function (const struct sra_walk_fns *fns)
 	       as a USE of the variable on the RHS of this assignment.  */
 
 	    t = TREE_OPERAND (stmt, 0);
-	    if (TREE_CODE (t) == MODIFY_EXPR)
-	      sra_walk_expr (&TREE_OPERAND (t, 1), &si, false, fns);
+	    if (TREE_CODE (t) == GIMPLE_MODIFY_STMT)
+	      sra_walk_expr (&GIMPLE_STMT_OPERAND (t, 1), &si, false, fns);
 	    else
 	      sra_walk_expr (&TREE_OPERAND (stmt, 0), &si, false, fns);
 	    break;
 
-	  case MODIFY_EXPR:
-	    sra_walk_modify_expr (stmt, &si, fns);
+	  case GIMPLE_MODIFY_STMT:
+	    sra_walk_gimple_modify_stmt (stmt, &si, fns);
 	    break;
 	  case CALL_EXPR:
 	    sra_walk_call_expr (stmt, &si, fns);
@@ -1689,16 +1689,16 @@ generate_copy_inout (struct sra_elt *elt, bool copy_out, tree expr,
       i = c->replacement;
 
       t = build2 (COMPLEX_EXPR, elt->type, r, i);
-      t = build2 (MODIFY_EXPR, void_type_node, expr, t);
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, expr, t);
       SSA_NAME_DEF_STMT (expr) = t;
       append_to_statement_list (t, list_p);
     }
   else if (elt->replacement)
     {
       if (copy_out)
-	t = build2 (MODIFY_EXPR, void_type_node, elt->replacement, expr);
+	t = build2 (GIMPLE_MODIFY_STMT, void_type_node, elt->replacement, expr);
       else
-	t = build2 (MODIFY_EXPR, void_type_node, expr, elt->replacement);
+	t = build2 (GIMPLE_MODIFY_STMT, void_type_node, expr, elt->replacement);
       append_to_statement_list (t, list_p);
     }
   else
@@ -1733,7 +1733,7 @@ generate_element_copy (struct sra_elt *dst, struct sra_elt *src, tree *list_p)
 
       gcc_assert (src->replacement);
 
-      t = build2 (MODIFY_EXPR, void_type_node, dst->replacement,
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, dst->replacement,
 		  src->replacement);
       append_to_statement_list (t, list_p);
     }
@@ -1765,7 +1765,7 @@ generate_element_zero (struct sra_elt *elt, tree *list_p)
       gcc_assert (elt->is_scalar);
       t = fold_convert (elt->type, integer_zero_node);
 
-      t = build2 (MODIFY_EXPR, void_type_node, elt->replacement, t);
+      t = build2 (GIMPLE_MODIFY_STMT, void_type_node, elt->replacement, t);
       append_to_statement_list (t, list_p);
     }
 }
@@ -1777,7 +1777,7 @@ static void
 generate_one_element_init (tree var, tree init, tree *list_p)
 {
   /* The replacement can be almost arbitrarily complex.  Gimplify.  */
-  tree stmt = build2 (MODIFY_EXPR, void_type_node, var, init);
+  tree stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, var, init);
   gimplify_and_add (stmt, list_p);
 }
 
@@ -2024,10 +2024,10 @@ scalarize_copy (struct sra_elt *lhs_elt, struct sra_elt *rhs_elt,
 
       /* See the commentary in sra_walk_function concerning
 	 RETURN_EXPR, and why we should never see one here.  */
-      gcc_assert (TREE_CODE (stmt) == MODIFY_EXPR);
+      gcc_assert (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT);
 
-      TREE_OPERAND (stmt, 0) = lhs_elt->replacement;
-      TREE_OPERAND (stmt, 1) = rhs_elt->replacement;
+      GIMPLE_STMT_OPERAND (stmt, 0) = lhs_elt->replacement;
+      GIMPLE_STMT_OPERAND (stmt, 1) = rhs_elt->replacement;
       update_stmt (stmt);
     }
   else if (lhs_elt->use_block_copy || rhs_elt->use_block_copy)
diff --git a/gcc/tree-ssa-alias.c b/gcc/tree-ssa-alias.c
index 163c78d91836b079598fef6645ef6ed1393f4640..6853ea14712c115568e04fc94d9a2a298331f4a7 100644
--- a/gcc/tree-ssa-alias.c
+++ b/gcc/tree-ssa-alias.c
@@ -408,7 +408,7 @@ compute_call_clobbered (struct alias_info *ai)
 static bool
 lhs_may_store_to (tree stmt, tree sym ATTRIBUTE_UNUSED)
 {
-  tree lhs = TREE_OPERAND (stmt, 0);
+  tree lhs = GENERIC_TREE_OPERAND (stmt, 0);
   
   lhs = get_base_address (lhs);
   
@@ -459,8 +459,8 @@ recalculate_used_alone (void)
 	  stmt = bsi_stmt (bsi);
 	  
 	  if (TREE_CODE (stmt) == CALL_EXPR
-	      || (TREE_CODE (stmt) == MODIFY_EXPR 
-		  && TREE_CODE (TREE_OPERAND (stmt, 1)) == CALL_EXPR))
+	      || (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT 
+		  && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == CALL_EXPR))
 	    {
 	      iscall = true;
 	      VEC_safe_push (tree, heap, calls, stmt);	    
@@ -786,24 +786,24 @@ count_uses_and_derefs (tree ptr, tree stmt, unsigned *num_uses_p,
      find all the indirect and direct uses of x_1 inside.  The only
      shortcut we can take is the fact that GIMPLE only allows
      INDIRECT_REFs inside the expressions below.  */
-  if (TREE_CODE (stmt) == MODIFY_EXPR
+  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
       || (TREE_CODE (stmt) == RETURN_EXPR
-	  && TREE_CODE (TREE_OPERAND (stmt, 0)) == MODIFY_EXPR)
+	  && TREE_CODE (TREE_OPERAND (stmt, 0)) == GIMPLE_MODIFY_STMT)
       || TREE_CODE (stmt) == ASM_EXPR
       || TREE_CODE (stmt) == CALL_EXPR)
     {
       tree lhs, rhs;
 
-      if (TREE_CODE (stmt) == MODIFY_EXPR)
+      if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
 	{
-	  lhs = TREE_OPERAND (stmt, 0);
-	  rhs = TREE_OPERAND (stmt, 1);
+	  lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+	  rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 	}
       else if (TREE_CODE (stmt) == RETURN_EXPR)
 	{
 	  tree e = TREE_OPERAND (stmt, 0);
-	  lhs = TREE_OPERAND (e, 0);
-	  rhs = TREE_OPERAND (e, 1);
+	  lhs = GIMPLE_STMT_OPERAND (e, 0);
+	  rhs = GIMPLE_STMT_OPERAND (e, 1);
 	}
       else if (TREE_CODE (stmt) == ASM_EXPR)
 	{
@@ -816,7 +816,8 @@ count_uses_and_derefs (tree ptr, tree stmt, unsigned *num_uses_p,
 	  rhs = stmt;
 	}
 
-      if (lhs && (TREE_CODE (lhs) == TREE_LIST || EXPR_P (lhs)))
+      if (lhs && (TREE_CODE (lhs) == TREE_LIST
+		  || EXPR_P (lhs) || GIMPLE_STMT_P (lhs)))
 	{
 	  struct count_ptr_d count;
 	  count.ptr = ptr;
@@ -826,7 +827,8 @@ count_uses_and_derefs (tree ptr, tree stmt, unsigned *num_uses_p,
 	  *num_derefs_p = count.count;
 	}
 
-      if (rhs && (TREE_CODE (rhs) == TREE_LIST || EXPR_P (rhs)))
+      if (rhs && (TREE_CODE (rhs) == TREE_LIST
+		  || EXPR_P (rhs) || GIMPLE_STMT_P (rhs)))
 	{
 	  struct count_ptr_d count;
 	  count.ptr = ptr;
@@ -2167,9 +2169,9 @@ is_escape_site (tree stmt)
     }
   else if (TREE_CODE (stmt) == ASM_EXPR)
     return ESCAPE_TO_ASM;
-  else if (TREE_CODE (stmt) == MODIFY_EXPR)
+  else if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
     {
-      tree lhs = TREE_OPERAND (stmt, 0);
+      tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
 
       /* Get to the base of _REF nodes.  */
       if (TREE_CODE (lhs) != SSA_NAME)
@@ -2180,12 +2182,13 @@ is_escape_site (tree stmt)
       if (lhs == NULL_TREE)
 	return ESCAPE_UNKNOWN;
 
-      if (TREE_CODE (TREE_OPERAND (stmt, 1)) == NOP_EXPR
-	  || TREE_CODE (TREE_OPERAND (stmt, 1)) == CONVERT_EXPR
-	  || TREE_CODE (TREE_OPERAND (stmt, 1)) == VIEW_CONVERT_EXPR)
+      if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == NOP_EXPR
+	  || TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == CONVERT_EXPR
+	  || TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == VIEW_CONVERT_EXPR)
 	{
-	  tree from = TREE_TYPE (TREE_OPERAND (TREE_OPERAND (stmt, 1), 0));
-	  tree to = TREE_TYPE (TREE_OPERAND (stmt, 1));
+	  tree from
+	    = TREE_TYPE (TREE_OPERAND (GIMPLE_STMT_OPERAND (stmt, 1), 0));
+	  tree to = TREE_TYPE (GIMPLE_STMT_OPERAND (stmt, 1));
 
 	  /* If the RHS is a conversion between a pointer and an integer, the
 	     pointer escapes since we can't track the integer.  */
@@ -3173,11 +3176,12 @@ find_used_portions (tree *tp, int *walk_subtrees, void *lhs_p)
 {
   switch (TREE_CODE (*tp))
     {
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       /* Recurse manually here to track whether the use is in the
 	 LHS of an assignment.  */
-      find_used_portions (&TREE_OPERAND (*tp, 0), walk_subtrees, tp);
-      return find_used_portions (&TREE_OPERAND (*tp, 1), walk_subtrees, NULL);
+      find_used_portions (&GIMPLE_STMT_OPERAND (*tp, 0), walk_subtrees, tp);
+      return find_used_portions (&GIMPLE_STMT_OPERAND (*tp, 1),
+	  			 walk_subtrees, NULL);
     case REALPART_EXPR:
     case IMAGPART_EXPR:
     case COMPONENT_REF:
diff --git a/gcc/tree-ssa-ccp.c b/gcc/tree-ssa-ccp.c
index 8da29e4be51ffea9a020ce6f8140c1f861f0c2b7..c8ec228e244c1b859dcdd2366a963f32c01cafde 100644
--- a/gcc/tree-ssa-ccp.c
+++ b/gcc/tree-ssa-ccp.c
@@ -375,7 +375,7 @@ get_default_value (tree var)
 	  else
 	    val.lattice_val = VARYING;
 	}
-      else if (TREE_CODE (stmt) == MODIFY_EXPR
+      else if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
 	       || TREE_CODE (stmt) == PHI_NODE)
 	{
 	  /* Any other variable defined by an assignment or a PHI node
@@ -543,7 +543,7 @@ likely_value (tree stmt)
 
   /* Anything other than assignments and conditional jumps are not
      interesting for CCP.  */
-  if (TREE_CODE (stmt) != MODIFY_EXPR
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT
       && !(TREE_CODE (stmt) == RETURN_EXPR && get_rhs (stmt) != NULL_TREE)
       && TREE_CODE (stmt) != COND_EXPR
       && TREE_CODE (stmt) != SWITCH_EXPR)
@@ -601,7 +601,7 @@ surely_varying_stmt_p (tree stmt)
 
   /* Anything other than assignments and conditional jumps are not
      interesting for CCP.  */
-  if (TREE_CODE (stmt) != MODIFY_EXPR
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT
       && !(TREE_CODE (stmt) == RETURN_EXPR && get_rhs (stmt) != NULL_TREE)
       && TREE_CODE (stmt) != COND_EXPR
       && TREE_CODE (stmt) != SWITCH_EXPR)
@@ -1184,8 +1184,8 @@ visit_assignment (tree stmt, tree *output_p)
   tree lhs, rhs;
   enum ssa_prop_result retval;
 
-  lhs = TREE_OPERAND (stmt, 0);
-  rhs = TREE_OPERAND (stmt, 1);
+  lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+  rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
   if (TREE_CODE (rhs) == SSA_NAME)
     {
@@ -1219,7 +1219,7 @@ visit_assignment (tree stmt, tree *output_p)
      the constant value into the type of the destination variable.  This
      should not be necessary if GCC represented bitfields properly.  */
   {
-    tree orig_lhs = TREE_OPERAND (stmt, 0);
+    tree orig_lhs = GIMPLE_STMT_OPERAND (stmt, 0);
 
     if (TREE_CODE (orig_lhs) == VIEW_CONVERT_EXPR
 	&& val.lattice_val == CONSTANT)
@@ -1364,7 +1364,7 @@ ccp_visit_stmt (tree stmt, edge *taken_edge_p, tree *output_p)
       fprintf (dump_file, "\n");
     }
 
-  if (TREE_CODE (stmt) == MODIFY_EXPR)
+  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
     {
       /* If the statement is an assignment that produces a single
 	 output value, evaluate its RHS to see if the lattice value of
@@ -2145,14 +2145,14 @@ get_maxval_strlen (tree arg, tree *length, bitmap visited, int type)
 
   switch (TREE_CODE (def_stmt))
     {
-      case MODIFY_EXPR:
+      case GIMPLE_MODIFY_STMT:
 	{
 	  tree rhs;
 
 	  /* The RHS of the statement defining VAR must either have a
 	     constant length or come from another SSA_NAME with a constant
 	     length.  */
-	  rhs = TREE_OPERAND (def_stmt, 1);
+	  rhs = GIMPLE_STMT_OPERAND (def_stmt, 1);
 	  STRIP_NOPS (rhs);
 	  return get_maxval_strlen (rhs, length, visited, type);
 	}
@@ -2204,7 +2204,7 @@ ccp_fold_builtin (tree stmt, tree fn)
   bitmap visited;
   bool ignore;
 
-  ignore = TREE_CODE (stmt) != MODIFY_EXPR;
+  ignore = TREE_CODE (stmt) != GIMPLE_MODIFY_STMT;
 
   /* First try the generic builtin folder.  If that succeeds, return the
      result directly.  */
@@ -2308,13 +2308,13 @@ ccp_fold_builtin (tree stmt, tree fn)
 
     case BUILT_IN_FPUTS:
       result = fold_builtin_fputs (arglist,
-				   TREE_CODE (stmt) != MODIFY_EXPR, 0,
+				   TREE_CODE (stmt) != GIMPLE_MODIFY_STMT, 0,
 				   val[0]);
       break;
 
     case BUILT_IN_FPUTS_UNLOCKED:
       result = fold_builtin_fputs (arglist,
-				   TREE_CODE (stmt) != MODIFY_EXPR, 1,
+				   TREE_CODE (stmt) != GIMPLE_MODIFY_STMT, 1,
 				   val[0]);
       break;
 
@@ -2578,7 +2578,7 @@ execute_fold_all_builtins (void)
 	    {
 	      result = convert_to_gimple_builtin (&i, result,
 			      			  TREE_CODE (old_stmt)
-						  != MODIFY_EXPR);
+						  != GIMPLE_MODIFY_STMT);
 	      if (result)
 		{
 		  bool ok = set_rhs (stmtp, result);
diff --git a/gcc/tree-ssa-copy.c b/gcc/tree-ssa-copy.c
index 43172d78e4e27a2f8227943d2605cb9f6cd508ad..6b9f353034601afc4bcb732421b6cce16fca01bf 100644
--- a/gcc/tree-ssa-copy.c
+++ b/gcc/tree-ssa-copy.c
@@ -370,11 +370,11 @@ stmt_may_generate_copy (tree stmt)
   if (TREE_CODE (stmt) == PHI_NODE)
     return !SSA_NAME_OCCURS_IN_ABNORMAL_PHI (PHI_RESULT (stmt));
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
 
-  lhs = TREE_OPERAND (stmt, 0);
-  rhs = TREE_OPERAND (stmt, 1);
+  lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+  rhs = GIMPLE_STMT_OPERAND (stmt, 1);
   ann = stmt_ann (stmt);
 
   /* If the statement has volatile operands, it won't generate a
@@ -554,8 +554,8 @@ copy_prop_visit_assignment (tree stmt, tree *result_p)
   tree lhs, rhs;
   prop_value_t *rhs_val;
 
-  lhs = TREE_OPERAND (stmt, 0);
-  rhs = TREE_OPERAND (stmt, 1);
+  lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+  rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
   gcc_assert (TREE_CODE (rhs) == SSA_NAME);
 
@@ -690,17 +690,17 @@ copy_prop_visit_stmt (tree stmt, edge *taken_edge_p, tree *result_p)
       fprintf (dump_file, "\n");
     }
 
-  if (TREE_CODE (stmt) == MODIFY_EXPR
-      && TREE_CODE (TREE_OPERAND (stmt, 1)) == SSA_NAME
+  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+      && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == SSA_NAME
       && (do_store_copy_prop
-	  || TREE_CODE (TREE_OPERAND (stmt, 0)) == SSA_NAME))
+	  || TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) == SSA_NAME))
     {
       /* If the statement is a copy assignment, evaluate its RHS to
 	 see if the lattice value of its output has changed.  */
       retval = copy_prop_visit_assignment (stmt, result_p);
     }
-  else if (TREE_CODE (stmt) == MODIFY_EXPR
-	   && TREE_CODE (TREE_OPERAND (stmt, 0)) == SSA_NAME
+  else if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+	   && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) == SSA_NAME
 	   && do_store_copy_prop
 	   && stmt_makes_single_load (stmt))
     {
@@ -711,14 +711,14 @@ copy_prop_visit_stmt (tree stmt, edge *taken_edge_p, tree *result_p)
       if (val
 	  && val->mem_ref
 	  && is_gimple_reg (val->value)
-	  && operand_equal_p (val->mem_ref, TREE_OPERAND (stmt, 1), 0))
+	  && operand_equal_p (val->mem_ref, GIMPLE_STMT_OPERAND (stmt, 1), 0))
         {
 	  bool changed;
-	  changed = set_copy_of_val (TREE_OPERAND (stmt, 0),
+	  changed = set_copy_of_val (GIMPLE_STMT_OPERAND (stmt, 0),
 				     val->value, val->mem_ref);
 	  if (changed)
 	    {
-	      *result_p = TREE_OPERAND (stmt, 0);
+	      *result_p = GIMPLE_STMT_OPERAND (stmt, 0);
 	      retval = SSA_PROP_INTERESTING;
 	    }
 	  else
@@ -910,7 +910,7 @@ init_copy_prop (void)
 	  if (stmt_ends_bb_p (stmt))
 	    DONT_SIMULATE_AGAIN (stmt) = false;
 	  else if (stmt_may_generate_copy (stmt)
-		   && loop_depth_of_name (TREE_OPERAND (stmt, 1)) <= depth)
+		   && loop_depth_of_name (GIMPLE_STMT_OPERAND (stmt, 1)) <= depth)
 	    DONT_SIMULATE_AGAIN (stmt) = false;
 	  else
 	    DONT_SIMULATE_AGAIN (stmt) = true;
diff --git a/gcc/tree-ssa-copyrename.c b/gcc/tree-ssa-copyrename.c
index b2921a2b9eb2ec3d073f612a9687ff2619c8530d..a2423a02ff8dc78f72096ad3d3bd37d499484276 100644
--- a/gcc/tree-ssa-copyrename.c
+++ b/gcc/tree-ssa-copyrename.c
@@ -315,10 +315,10 @@ rename_ssa_copies (void)
       for (bsi = bsi_start (bb); !bsi_end_p (bsi); bsi_next (&bsi))
 	{
 	  stmt = bsi_stmt (bsi); 
-	  if (TREE_CODE (stmt) == MODIFY_EXPR)
+	  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
 	    {
-	      tree lhs = TREE_OPERAND (stmt, 0);
-	      tree rhs = TREE_OPERAND (stmt, 1);
+	      tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+	      tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
               if (TREE_CODE (lhs) == SSA_NAME && TREE_CODE (rhs) == SSA_NAME)
 		copy_rename_partition_coalesce (map, lhs, rhs, debug);
diff --git a/gcc/tree-ssa-dce.c b/gcc/tree-ssa-dce.c
index 7b492b23e46d032f51ce6b2b55854d6f9ceee936..3b205629e33da41ae495e50e6bfd7b9d3edad629 100644
--- a/gcc/tree-ssa-dce.c
+++ b/gcc/tree-ssa-dce.c
@@ -216,7 +216,7 @@ find_pdom (basic_block block)
     }
 }
 
-#define NECESSARY(stmt)		stmt->common.asm_written_flag
+#define NECESSARY(stmt)		stmt->base.asm_written_flag
 
 /* If STMT is not already marked necessary, mark it, and add it to the
    worklist if ADD_TO_WORKLIST is true.  */
@@ -318,7 +318,7 @@ mark_stmt_if_obviously_necessary (tree stmt, bool aggressive)
 	mark_stmt_necessary (stmt, true);
       return;
 
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       op = get_call_expr_in (stmt);
       if (op && TREE_SIDE_EFFECTS (op))
 	{
@@ -329,8 +329,8 @@ mark_stmt_if_obviously_necessary (tree stmt, bool aggressive)
       /* These values are mildly magic bits of the EH runtime.  We can't
 	 see the entire lifetime of these values until landing pads are
 	 generated.  */
-      if (TREE_CODE (TREE_OPERAND (stmt, 0)) == EXC_PTR_EXPR
-	  || TREE_CODE (TREE_OPERAND (stmt, 0)) == FILTER_EXPR)
+      if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) == EXC_PTR_EXPR
+	  || TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) == FILTER_EXPR)
 	{
 	  mark_stmt_necessary (stmt, true);
 	  return;
diff --git a/gcc/tree-ssa-dom.c b/gcc/tree-ssa-dom.c
index b277068934ecb7b86db431a8ff24fa2b8c31dc86..134cfe934e8d052a69efd13d359c45580a30991f 100644
--- a/gcc/tree-ssa-dom.c
+++ b/gcc/tree-ssa-dom.c
@@ -489,7 +489,7 @@ initialize_hash_element (tree expr, tree lhs, struct expr_hash_elt *element)
   else if (TREE_CODE (expr) == RETURN_EXPR && TREE_OPERAND (expr, 0))
     {
       element->stmt = expr;
-      element->rhs = TREE_OPERAND (TREE_OPERAND (expr, 0), 1);
+      element->rhs = GIMPLE_STMT_OPERAND (TREE_OPERAND (expr, 0), 1);
     }
   else if (TREE_CODE (expr) == GOTO_EXPR)
     {
@@ -499,7 +499,7 @@ initialize_hash_element (tree expr, tree lhs, struct expr_hash_elt *element)
   else
     {
       element->stmt = expr;
-      element->rhs = TREE_OPERAND (expr, 1);
+      element->rhs = GENERIC_TREE_OPERAND (expr, 1);
     }
 
   element->lhs = lhs;
@@ -1183,14 +1183,14 @@ simple_iv_increment_p (tree stmt)
   tree lhs, rhs, preinc, phi;
   unsigned i;
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
 
-  lhs = TREE_OPERAND (stmt, 0);
+  lhs = GIMPLE_STMT_OPERAND (stmt, 0);
   if (TREE_CODE (lhs) != SSA_NAME)
     return false;
 
-  rhs = TREE_OPERAND (stmt, 1);
+  rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
   if (TREE_CODE (rhs) != PLUS_EXPR
       && TREE_CODE (rhs) != MINUS_EXPR)
@@ -1473,8 +1473,8 @@ eliminate_redundant_computations (tree stmt)
   bool retval = false;
   bool modify_expr_p = false;
 
-  if (TREE_CODE (stmt) == MODIFY_EXPR)
-    def = TREE_OPERAND (stmt, 0);
+  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
+    def = GIMPLE_STMT_OPERAND (stmt, 0);
 
   /* Certain expressions on the RHS can be optimized away, but can not
      themselves be entered into the hash tables.  */
@@ -1499,12 +1499,12 @@ eliminate_redundant_computations (tree stmt)
     expr_p = &SWITCH_COND (stmt);
   else if (TREE_CODE (stmt) == RETURN_EXPR && TREE_OPERAND (stmt, 0))
     {
-      expr_p = &TREE_OPERAND (TREE_OPERAND (stmt, 0), 1);
+      expr_p = &GIMPLE_STMT_OPERAND (TREE_OPERAND (stmt, 0), 1);
       modify_expr_p = true;
     }
   else
     {
-      expr_p = &TREE_OPERAND (stmt, 1);
+      expr_p = &GENERIC_TREE_OPERAND (stmt, 1);
       modify_expr_p = true;
     }
 
@@ -1552,7 +1552,7 @@ eliminate_redundant_computations (tree stmt)
   return retval;
 }
 
-/* STMT, a MODIFY_EXPR, may create certain equivalences, in either
+/* STMT, a GIMPLE_MODIFY_STMT, may create certain equivalences, in either
    the available expressions table or the const_and_copies table.
    Detect and record those equivalences.  */
 
@@ -1561,12 +1561,12 @@ record_equivalences_from_stmt (tree stmt,
 			       int may_optimize_p,
 			       stmt_ann_t ann)
 {
-  tree lhs = TREE_OPERAND (stmt, 0);
+  tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
   enum tree_code lhs_code = TREE_CODE (lhs);
 
   if (lhs_code == SSA_NAME)
     {
-      tree rhs = TREE_OPERAND (stmt, 1);
+      tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
       /* Strip away any useless type conversions.  */
       STRIP_USELESS_TYPE_CONVERSION (rhs);
@@ -1588,11 +1588,11 @@ record_equivalences_from_stmt (tree stmt,
      vops and recording the result in the available expression table,
      we may be able to expose more redundant loads.  */
   if (!ann->has_volatile_ops
-      && (TREE_CODE (TREE_OPERAND (stmt, 1)) == SSA_NAME
-	  || is_gimple_min_invariant (TREE_OPERAND (stmt, 1)))
+      && (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == SSA_NAME
+	  || is_gimple_min_invariant (GIMPLE_STMT_OPERAND (stmt, 1)))
       && !is_gimple_reg (lhs))
     {
-      tree rhs = TREE_OPERAND (stmt, 1);
+      tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
       tree new;
 
       /* FIXME: If the LHS of the assignment is a bitfield and the RHS
@@ -1619,7 +1619,7 @@ record_equivalences_from_stmt (tree stmt,
       if (rhs)
 	{
 	  /* Build a new statement with the RHS and LHS exchanged.  */
-	  new = build2 (MODIFY_EXPR, TREE_TYPE (stmt), rhs, lhs);
+	  new = build2_gimple (GIMPLE_MODIFY_STMT, rhs, lhs);
 
 	  create_ssa_artficial_load_stmt (new, stmt);
 
@@ -1840,11 +1840,14 @@ optimize_stmt (struct dom_walk_data *walk_data ATTRIBUTE_UNUSED,
   may_optimize_p = (!ann->has_volatile_ops
 		    && ((TREE_CODE (stmt) == RETURN_EXPR
 			 && TREE_OPERAND (stmt, 0)
-			 && TREE_CODE (TREE_OPERAND (stmt, 0)) == MODIFY_EXPR
+			 && TREE_CODE (TREE_OPERAND (stmt, 0))
+			    == GIMPLE_MODIFY_STMT
 			 && ! (TREE_SIDE_EFFECTS
-			       (TREE_OPERAND (TREE_OPERAND (stmt, 0), 1))))
-			|| (TREE_CODE (stmt) == MODIFY_EXPR
-			    && ! TREE_SIDE_EFFECTS (TREE_OPERAND (stmt, 1)))
+			       (GIMPLE_STMT_OPERAND
+				(TREE_OPERAND (stmt, 0), 1))))
+			|| (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+			    && ! TREE_SIDE_EFFECTS (GIMPLE_STMT_OPERAND (stmt,
+									 1)))
 			|| TREE_CODE (stmt) == COND_EXPR
 			|| TREE_CODE (stmt) == SWITCH_EXPR));
 
@@ -1852,7 +1855,7 @@ optimize_stmt (struct dom_walk_data *walk_data ATTRIBUTE_UNUSED,
     may_have_exposed_new_symbols |= eliminate_redundant_computations (stmt);
 
   /* Record any additional equivalences created by this statement.  */
-  if (TREE_CODE (stmt) == MODIFY_EXPR)
+  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
     record_equivalences_from_stmt (stmt,
 				   may_optimize_p,
 				   ann);
@@ -1917,7 +1920,7 @@ optimize_stmt (struct dom_walk_data *walk_data ATTRIBUTE_UNUSED,
    is also added to the stack pointed to by BLOCK_AVAIL_EXPRS_P, so that they
    can be removed when we finish processing this block and its children.
 
-   NOTE: This function assumes that STMT is a MODIFY_EXPR node that
+   NOTE: This function assumes that STMT is a GIMPLE_MODIFY_STMT node that
    contains no CALL_EXPR on its RHS and makes no volatile nor
    aliased references.  */
 
@@ -1929,7 +1932,8 @@ lookup_avail_expr (tree stmt, bool insert)
   tree temp;
   struct expr_hash_elt *element = XNEW (struct expr_hash_elt);
 
-  lhs = TREE_CODE (stmt) == MODIFY_EXPR ? TREE_OPERAND (stmt, 0) : NULL;
+  lhs = TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+    			    ? GIMPLE_STMT_OPERAND (stmt, 0) : NULL;
 
   initialize_hash_element (stmt, lhs, element);
 
@@ -1978,8 +1982,8 @@ lookup_avail_expr (tree stmt, bool insert)
 }
 
 /* Hashing and equality functions for AVAIL_EXPRS.  The table stores
-   MODIFY_EXPR statements.  We compute a value number for expressions using
-   the code of the expression and the SSA numbers of its operands.  */
+   GIMPLE_MODIFY_STMT statements.  We compute a value number for expressions
+   using the code of the expression and the SSA numbers of its operands.  */
 
 static hashval_t
 avail_expr_hash (const void *p)
@@ -2078,7 +2082,7 @@ degenerate_phi_result (tree phi)
   return (i == PHI_NUM_ARGS (phi) ? val : NULL);
 }
 
-/* Given a tree node T, which is either a PHI_NODE or MODIFY_EXPR,
+/* Given a tree node T, which is either a PHI_NODE or GIMPLE_MODIFY_STMT,
    remove it from the IL.  */
 
 static void
@@ -2093,7 +2097,7 @@ remove_stmt_or_phi (tree t)
     }
 }
 
-/* Given a tree node T, which is either a PHI_NODE or MODIFY_EXPR,
+/* Given a tree node T, which is either a PHI_NODE or GIMPLE_MODIFY_STMT,
    return the "rhs" of the node, in the case of a non-degenerate
    PHI, NULL is returned.  */
 
@@ -2102,13 +2106,13 @@ get_rhs_or_phi_arg (tree t)
 {
   if (TREE_CODE (t) == PHI_NODE)
     return degenerate_phi_result (t);
-  else if (TREE_CODE (t) == MODIFY_EXPR)
-    return TREE_OPERAND (t, 1);
+  else if (TREE_CODE (t) == GIMPLE_MODIFY_STMT)
+    return GIMPLE_STMT_OPERAND (t, 1);
   gcc_unreachable ();
 }
 
 
-/* Given a tree node T, which is either a PHI_NODE or a MODIFY_EXPR,
+/* Given a tree node T, which is either a PHI_NODE or a GIMPLE_MODIFY_STMT,
    return the "lhs" of the node.  */
 
 static tree
@@ -2116,8 +2120,8 @@ get_lhs_or_phi_result (tree t)
 {
   if (TREE_CODE (t) == PHI_NODE)
     return PHI_RESULT (t);
-  else if (TREE_CODE (t) == MODIFY_EXPR)
-    return TREE_OPERAND (t, 0);
+  else if (TREE_CODE (t) == GIMPLE_MODIFY_STMT)
+    return GIMPLE_STMT_OPERAND (t, 0);
   gcc_unreachable ();
 }
 
@@ -2239,9 +2243,10 @@ propagate_rhs_into_lhs (tree stmt, tree lhs, tree rhs, bitmap interesting_names)
 
 	  /* If we replaced a variable index with a constant, then
 	     we would need to update the invariant flag for ADDR_EXPRs.  */
-	  if (TREE_CODE (use_stmt) == MODIFY_EXPR
-	      && TREE_CODE (TREE_OPERAND (use_stmt, 1)) == ADDR_EXPR)
-	    recompute_tree_invariant_for_addr_expr (TREE_OPERAND (use_stmt, 1));
+	  if (TREE_CODE (use_stmt) == GIMPLE_MODIFY_STMT
+	      && TREE_CODE (GIMPLE_STMT_OPERAND (use_stmt, 1)) == ADDR_EXPR)
+	    recompute_tree_invariant_for_addr_expr
+	      (GIMPLE_STMT_OPERAND (use_stmt, 1));
 
 	  /* If we cleaned up EH information from the statement,
 	     mark its containing block as needing EH cleanups.  */
@@ -2254,10 +2259,11 @@ propagate_rhs_into_lhs (tree stmt, tree lhs, tree rhs, bitmap interesting_names)
 
 	  /* Propagation may expose new trivial copy/constant propagation
 	     opportunities.  */
-	  if (TREE_CODE (use_stmt) == MODIFY_EXPR
-	      && TREE_CODE (TREE_OPERAND (use_stmt, 0)) == SSA_NAME
-	      && (TREE_CODE (TREE_OPERAND (use_stmt, 1)) == SSA_NAME
-		  || is_gimple_min_invariant (TREE_OPERAND (use_stmt, 1))))
+	  if (TREE_CODE (use_stmt) == GIMPLE_MODIFY_STMT
+	      && TREE_CODE (GIMPLE_STMT_OPERAND (use_stmt, 0)) == SSA_NAME
+	      && (TREE_CODE (GIMPLE_STMT_OPERAND (use_stmt, 1)) == SSA_NAME
+		  || is_gimple_min_invariant (GIMPLE_STMT_OPERAND (use_stmt,
+		      						   1))))
 	    {
 	      tree result = get_lhs_or_phi_result (use_stmt);
 	      bitmap_set_bit (interesting_names, SSA_NAME_VERSION (result));
diff --git a/gcc/tree-ssa-dse.c b/gcc/tree-ssa-dse.c
index f7f333f0b2cf37b8c948b7e01841807e105002c6..8cc4762ea04fd919e3dfd11b643fc563c39ba7da 100644
--- a/gcc/tree-ssa-dse.c
+++ b/gcc/tree-ssa-dse.c
@@ -205,7 +205,7 @@ memory_address_same (tree store1, tree store2)
   walk_data.store1_bb = bb_for_stmt (store1);
   walk_data.store2_bb = bb_for_stmt (store2);
 
-  return (walk_tree (&TREE_OPERAND (store1, 0), memory_ssa_name_same,
+  return (walk_tree (&GIMPLE_STMT_OPERAND (store1, 0), memory_ssa_name_same,
 		     &walk_data, NULL)
 	  == NULL);
 }
@@ -237,15 +237,15 @@ dse_optimize_stmt (struct dom_walk_data *walk_data,
   if (ZERO_SSA_OPERANDS (stmt, (SSA_OP_VMAYDEF|SSA_OP_VMUSTDEF)))
     return;
 
-  /* We know we have virtual definitions.  If this is a MODIFY_EXPR that's
-     not also a function call, then record it into our table.  */
+  /* We know we have virtual definitions.  If this is a GIMPLE_MODIFY_STMT
+     that's not also a function call, then record it into our table.  */
   if (get_call_expr_in (stmt))
     return;
 
   if (ann->has_volatile_ops)
     return;
 
-  if (TREE_CODE (stmt) == MODIFY_EXPR)
+  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
     {
       use_operand_p first_use_p = NULL_USE_OPERAND_P;
       use_operand_p use_p = NULL;
@@ -328,8 +328,8 @@ dse_optimize_stmt (struct dom_walk_data *walk_data,
 	 SSA-form variables in the address will have the same values.  */
       if (use_p != NULL_USE_OPERAND_P
 	  && bitmap_bit_p (dse_gd->stores, get_stmt_uid (use_stmt))
-	  && operand_equal_p (TREE_OPERAND (stmt, 0),
-			      TREE_OPERAND (use_stmt, 0), 0)
+	  && operand_equal_p (GIMPLE_STMT_OPERAND (stmt, 0),
+			      GIMPLE_STMT_OPERAND (use_stmt, 0), 0)
 	  && memory_address_same (stmt, use_stmt))
 	{
 	  /* Make sure we propagate the ABNORMAL bit setting.  */
diff --git a/gcc/tree-ssa-forwprop.c b/gcc/tree-ssa-forwprop.c
index a3caf235062e8ce6e184bcb2053152737ade011e..dd20d00bf228e84fa9140f3f5cdd88fb9f2ee2f0 100644
--- a/gcc/tree-ssa-forwprop.c
+++ b/gcc/tree-ssa-forwprop.c
@@ -162,9 +162,9 @@ ssa_name_defined_by_comparison_p (tree var)
 {
   tree def = SSA_NAME_DEF_STMT (var);
 
-  if (TREE_CODE (def) == MODIFY_EXPR)
+  if (TREE_CODE (def) == GIMPLE_MODIFY_STMT)
     {
-      tree rhs = TREE_OPERAND (def, 1);
+      tree rhs = GIMPLE_STMT_OPERAND (def, 1);
       return COMPARISON_CLASS_P (rhs);
     }
 
@@ -203,12 +203,12 @@ forward_propagate_into_cond_1 (tree cond, tree *test_var_p)
     test_var = TREE_OPERAND (cond, 0);
 
   /* Now get the defining statement for TEST_VAR.  Skip this case if
-     it's not defined by some MODIFY_EXPR.  */
+     it's not defined by some GIMPLE_MODIFY_STMT.  */
   def = SSA_NAME_DEF_STMT (test_var);
-  if (TREE_CODE (def) != MODIFY_EXPR)
+  if (TREE_CODE (def) != GIMPLE_MODIFY_STMT)
     return NULL_TREE;
 
-  def_rhs = TREE_OPERAND (def, 1);
+  def_rhs = GIMPLE_STMT_OPERAND (def, 1);
 
   /* If TEST_VAR is set by adding or subtracting a constant
      from an SSA_NAME, then it is interesting to us as we
@@ -429,15 +429,15 @@ find_equivalent_equality_comparison (tree cond)
   tree def_stmt = SSA_NAME_DEF_STMT (op0);
 
   while (def_stmt
-	 && TREE_CODE (def_stmt) == MODIFY_EXPR
-	 && TREE_CODE (TREE_OPERAND (def_stmt, 1)) == SSA_NAME)
-    def_stmt = SSA_NAME_DEF_STMT (TREE_OPERAND (def_stmt, 1));
+	 && TREE_CODE (def_stmt) == GIMPLE_MODIFY_STMT
+	 && TREE_CODE (GIMPLE_STMT_OPERAND (def_stmt, 1)) == SSA_NAME)
+    def_stmt = SSA_NAME_DEF_STMT (GIMPLE_STMT_OPERAND (def_stmt, 1));
 
   /* OP0 might have been a parameter, so first make sure it
-     was defined by a MODIFY_EXPR.  */
-  if (def_stmt && TREE_CODE (def_stmt) == MODIFY_EXPR)
+     was defined by a GIMPLE_MODIFY_STMT.  */
+  if (def_stmt && TREE_CODE (def_stmt) == GIMPLE_MODIFY_STMT)
     {
-      tree def_rhs = TREE_OPERAND (def_stmt, 1);
+      tree def_rhs = GIMPLE_STMT_OPERAND (def_stmt, 1);
 
       /* If either operand to the comparison is a pointer to
 	 a function, then we can not apply this optimization
@@ -450,7 +450,7 @@ find_equivalent_equality_comparison (tree cond)
 	      && TREE_CODE (TREE_TYPE (TREE_TYPE (op1))) == FUNCTION_TYPE))
 	return NULL;
 	      
-      /* Now make sure the RHS of the MODIFY_EXPR is a typecast.  */
+      /* Now make sure the RHS of the GIMPLE_MODIFY_STMT is a typecast.  */
       if ((TREE_CODE (def_rhs) == NOP_EXPR
 	   || TREE_CODE (def_rhs) == CONVERT_EXPR)
 	  && TREE_CODE (TREE_OPERAND (def_rhs, 0)) == SSA_NAME)
@@ -583,8 +583,8 @@ tidy_after_forward_propagate_addr (tree stmt)
       && tree_purge_dead_eh_edges (bb_for_stmt (stmt)))
     cfg_changed = true;
 
-  if (TREE_CODE (TREE_OPERAND (stmt, 1)) == ADDR_EXPR)
-     recompute_tree_invariant_for_addr_expr (TREE_OPERAND (stmt, 1));
+  if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == ADDR_EXPR)
+     recompute_tree_invariant_for_addr_expr (GIMPLE_STMT_OPERAND (stmt, 1));
 
   mark_new_vars_to_rename (stmt);
 }
@@ -610,13 +610,13 @@ forward_propagate_addr_into_variable_array_index (tree offset, tree lhs,
 {
   tree index;
 
-  /* The offset must be defined by a simple MODIFY_EXPR statement.  */
-  if (TREE_CODE (offset) != MODIFY_EXPR)
+  /* The offset must be defined by a simple GIMPLE_MODIFY_STMT statement.  */
+  if (TREE_CODE (offset) != GIMPLE_MODIFY_STMT)
     return false;
 
   /* The RHS of the statement which defines OFFSET must be a gimple
      cast of another SSA_NAME.  */
-  offset = TREE_OPERAND (offset, 1);
+  offset = GIMPLE_STMT_OPERAND (offset, 1);
   if (!is_gimple_cast (offset))
     return false;
 
@@ -629,15 +629,15 @@ forward_propagate_addr_into_variable_array_index (tree offset, tree lhs,
   offset = SSA_NAME_DEF_STMT (offset);
 
   /* The statement which defines OFFSET before type conversion
-     must be a simple MODIFY_EXPR.  */
-  if (TREE_CODE (offset) != MODIFY_EXPR)
+     must be a simple GIMPLE_MODIFY_STMT.  */
+  if (TREE_CODE (offset) != GIMPLE_MODIFY_STMT)
     return false;
 
   /* The RHS of the statement which defines OFFSET must be a
      multiplication of an object by the size of the array elements. 
      This implicitly verifies that the size of the array elements
      is constant.  */
-  offset = TREE_OPERAND (offset, 1);
+  offset = GIMPLE_STMT_OPERAND (offset, 1);
   if (TREE_CODE (offset) != MULT_EXPR
       || TREE_CODE (TREE_OPERAND (offset, 1)) != INTEGER_CST
       || !simple_cst_equal (TREE_OPERAND (offset, 1),
@@ -648,8 +648,10 @@ forward_propagate_addr_into_variable_array_index (tree offset, tree lhs,
   index = TREE_OPERAND (offset, 0);
 
   /* Replace the pointer addition with array indexing.  */
-  TREE_OPERAND (use_stmt, 1) = unshare_expr (TREE_OPERAND (stmt, 1));
-  TREE_OPERAND (TREE_OPERAND (TREE_OPERAND (use_stmt, 1), 0), 1) = index;
+  GIMPLE_STMT_OPERAND (use_stmt, 1)
+    = unshare_expr (GIMPLE_STMT_OPERAND (stmt, 1));
+  TREE_OPERAND (TREE_OPERAND (GIMPLE_STMT_OPERAND (use_stmt, 1), 0), 1)
+    = index;
 
   /* That should have created gimple, so there is no need to
      record information to undo the propagation.  */
@@ -673,12 +675,12 @@ forward_propagate_addr_into_variable_array_index (tree offset, tree lhs,
 static bool
 forward_propagate_addr_expr_1 (tree stmt, tree use_stmt, bool *changed)
 {
-  tree name = TREE_OPERAND (stmt, 0);
+  tree name = GIMPLE_STMT_OPERAND (stmt, 0);
   tree lhs, rhs, array_ref;
 
   /* Strip away any outer COMPONENT_REF/ARRAY_REF nodes from the LHS. 
      ADDR_EXPR will not appear on the LHS.  */
-  lhs = TREE_OPERAND (use_stmt, 0);
+  lhs = GIMPLE_STMT_OPERAND (use_stmt, 0);
   while (TREE_CODE (lhs) == COMPONENT_REF || TREE_CODE (lhs) == ARRAY_REF)
     lhs = TREE_OPERAND (lhs, 0);
 
@@ -688,7 +690,7 @@ forward_propagate_addr_expr_1 (tree stmt, tree use_stmt, bool *changed)
     {
       /* This should always succeed in creating gimple, so there is
 	 no need to save enough state to undo this propagation.  */
-      TREE_OPERAND (lhs, 0) = unshare_expr (TREE_OPERAND (stmt, 1));
+      TREE_OPERAND (lhs, 0) = unshare_expr (GIMPLE_STMT_OPERAND (stmt, 1));
       fold_stmt_inplace (use_stmt);
       tidy_after_forward_propagate_addr (use_stmt);
       if (changed)
@@ -702,9 +704,11 @@ forward_propagate_addr_expr_1 (tree stmt, tree use_stmt, bool *changed)
      we can catch some cascading effects, ie the single use is
      in a copy, and the copy is used later by a single INDIRECT_REF
      for example.  */
-  else if (TREE_CODE (lhs) == SSA_NAME && TREE_OPERAND (use_stmt, 1) == name)
+  else if (TREE_CODE (lhs) == SSA_NAME
+      	   && GIMPLE_STMT_OPERAND (use_stmt, 1) == name)
     {
-      TREE_OPERAND (use_stmt, 1) = unshare_expr (TREE_OPERAND (stmt, 1));
+      GIMPLE_STMT_OPERAND (use_stmt, 1)
+	= unshare_expr (GIMPLE_STMT_OPERAND (stmt, 1));
       tidy_after_forward_propagate_addr (use_stmt);
       if (changed)
 	*changed = true;
@@ -713,7 +717,7 @@ forward_propagate_addr_expr_1 (tree stmt, tree use_stmt, bool *changed)
 
   /* Strip away any outer COMPONENT_REF, ARRAY_REF or ADDR_EXPR
      nodes from the RHS.  */
-  rhs = TREE_OPERAND (use_stmt, 1);
+  rhs = GIMPLE_STMT_OPERAND (use_stmt, 1);
   while (TREE_CODE (rhs) == COMPONENT_REF
 	 || TREE_CODE (rhs) == ARRAY_REF
 	 || TREE_CODE (rhs) == ADDR_EXPR)
@@ -725,7 +729,7 @@ forward_propagate_addr_expr_1 (tree stmt, tree use_stmt, bool *changed)
     {
       /* This should always succeed in creating gimple, so there is
          no need to save enough state to undo this propagation.  */
-      TREE_OPERAND (rhs, 0) = unshare_expr (TREE_OPERAND (stmt, 1));
+      TREE_OPERAND (rhs, 0) = unshare_expr (GIMPLE_STMT_OPERAND (stmt, 1));
       fold_stmt_inplace (use_stmt);
       tidy_after_forward_propagate_addr (use_stmt);
       if (changed)
@@ -737,7 +741,7 @@ forward_propagate_addr_expr_1 (tree stmt, tree use_stmt, bool *changed)
      array indexing.  They only apply when we have the address of
      element zero in an array.  If that is not the case then there
      is nothing to do.  */
-  array_ref = TREE_OPERAND (TREE_OPERAND (stmt, 1), 0);
+  array_ref = TREE_OPERAND (GIMPLE_STMT_OPERAND (stmt, 1), 0);
   if (TREE_CODE (array_ref) != ARRAY_REF
       || TREE_CODE (TREE_TYPE (TREE_OPERAND (array_ref, 0))) != ARRAY_TYPE
       || !integer_zerop (TREE_OPERAND (array_ref, 1)))
@@ -754,7 +758,7 @@ forward_propagate_addr_expr_1 (tree stmt, tree use_stmt, bool *changed)
       && TREE_CODE (TREE_OPERAND (rhs, 1)) == INTEGER_CST)
     {
       tree orig = unshare_expr (rhs);
-      TREE_OPERAND (rhs, 0) = unshare_expr (TREE_OPERAND (stmt, 1));
+      TREE_OPERAND (rhs, 0) = unshare_expr (GIMPLE_STMT_OPERAND (stmt, 1));
 
       /* If folding succeeds, then we have just exposed new variables
 	 in USE_STMT which will need to be renamed.  If folding fails,
@@ -768,7 +772,7 @@ forward_propagate_addr_expr_1 (tree stmt, tree use_stmt, bool *changed)
 	}
       else
 	{
-	  TREE_OPERAND (use_stmt, 1) = orig;
+	  GIMPLE_STMT_OPERAND (use_stmt, 1) = orig;
 	  update_stmt (use_stmt);
 	  return false;
 	}
@@ -826,7 +830,7 @@ static bool
 forward_propagate_addr_expr (tree stmt, bool *some)
 {
   int stmt_loop_depth = bb_for_stmt (stmt)->loop_depth;
-  tree name = TREE_OPERAND (stmt, 0);
+  tree name = GIMPLE_STMT_OPERAND (stmt, 0);
   imm_use_iterator iter;
   tree use_stmt;
   bool all = true;
@@ -837,7 +841,7 @@ forward_propagate_addr_expr (tree stmt, bool *some)
 
       /* If the use is not in a simple assignment statement, then
 	 there is nothing we can do.  */
-      if (TREE_CODE (use_stmt) != MODIFY_EXPR)
+      if (TREE_CODE (use_stmt) != GIMPLE_MODIFY_STMT)
 	{
 	  all = false;
 	  continue;
@@ -877,20 +881,21 @@ forward_propagate_addr_expr (tree stmt, bool *some)
 static void
 simplify_not_neg_expr (tree stmt)
 {
-  tree rhs = TREE_OPERAND (stmt, 1);
+  tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
   tree rhs_def_stmt = SSA_NAME_DEF_STMT (TREE_OPERAND (rhs, 0));
 
   /* See if the RHS_DEF_STMT has the same form as our statement.  */
-  if (TREE_CODE (rhs_def_stmt) == MODIFY_EXPR
-      && TREE_CODE (TREE_OPERAND (rhs_def_stmt, 1)) == TREE_CODE (rhs))
+  if (TREE_CODE (rhs_def_stmt) == GIMPLE_MODIFY_STMT
+      && TREE_CODE (GIMPLE_STMT_OPERAND (rhs_def_stmt, 1)) == TREE_CODE (rhs))
     {
-      tree rhs_def_operand = TREE_OPERAND (TREE_OPERAND (rhs_def_stmt, 1), 0);
+      tree rhs_def_operand =
+	TREE_OPERAND (GIMPLE_STMT_OPERAND (rhs_def_stmt, 1), 0);
 
       /* Verify that RHS_DEF_OPERAND is a suitable SSA_NAME.  */
       if (TREE_CODE (rhs_def_operand) == SSA_NAME
 	  && ! SSA_NAME_OCCURS_IN_ABNORMAL_PHI (rhs_def_operand))
 	{
-	  TREE_OPERAND (stmt, 1) = rhs_def_operand;
+	  GIMPLE_STMT_OPERAND (stmt, 1) = rhs_def_operand;
 	  update_stmt (stmt);
 	}
     }
@@ -911,9 +916,9 @@ simplify_switch_expr (tree stmt)
   if (TREE_CODE (cond) == SSA_NAME)
     {
       def = SSA_NAME_DEF_STMT (cond);
-      if (TREE_CODE (def) == MODIFY_EXPR)
+      if (TREE_CODE (def) == GIMPLE_MODIFY_STMT)
 	{
-	  def = TREE_OPERAND (def, 1);
+	  def = GIMPLE_STMT_OPERAND (def, 1);
 	  if (TREE_CODE (def) == NOP_EXPR)
 	    {
 	      int need_precision;
@@ -974,10 +979,10 @@ tree_ssa_forward_propagate_single_use_vars (void)
 
 	  /* If this statement sets an SSA_NAME to an address,
 	     try to propagate the address into the uses of the SSA_NAME.  */
-	  if (TREE_CODE (stmt) == MODIFY_EXPR)
+	  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
 	    {
-	      tree lhs = TREE_OPERAND (stmt, 0);
-	      tree rhs = TREE_OPERAND (stmt, 1);
+	      tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+	      tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
 
 	      if (TREE_CODE (lhs) != SSA_NAME)
diff --git a/gcc/tree-ssa-live.c b/gcc/tree-ssa-live.c
index f7665cde557f000281ed8f503bc616a47c272c0a..277e2763bc505768469569835311d1a0bc0f78df 100644
--- a/gcc/tree-ssa-live.c
+++ b/gcc/tree-ssa-live.c
@@ -1331,10 +1331,10 @@ build_tree_conflict_graph (tree_live_info_p liveinfo, tpa_p tpa,
 	     be interested in trying to coalesce SSA_NAME variables with
 	     root variables in some cases.  */
 
-	  if (TREE_CODE (stmt) == MODIFY_EXPR)
+	  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
 	    {
-	      tree lhs = TREE_OPERAND (stmt, 0);
-	      tree rhs = TREE_OPERAND (stmt, 1);
+	      tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+	      tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 	      int p1, p2;
 	      int bit;
 
diff --git a/gcc/tree-ssa-loop-im.c b/gcc/tree-ssa-loop-im.c
index 5b8d6038bcf4967b6f6b9c3ad574746b654806f2..9fd0eba16a09ed1d75e0659e7a871d8486b8739f 100644
--- a/gcc/tree-ssa-loop-im.c
+++ b/gcc/tree-ssa-loop-im.c
@@ -244,7 +244,7 @@ movement_possibility (tree stmt)
       return MOVE_POSSIBLE;
     }
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return MOVE_IMPOSSIBLE;
 
   if (stmt_ends_bb_p (stmt))
@@ -253,12 +253,12 @@ movement_possibility (tree stmt)
   if (stmt_ann (stmt)->has_volatile_ops)
     return MOVE_IMPOSSIBLE;
 
-  lhs = TREE_OPERAND (stmt, 0);
+  lhs = GIMPLE_STMT_OPERAND (stmt, 0);
   if (TREE_CODE (lhs) == SSA_NAME
       && SSA_NAME_OCCURS_IN_ABNORMAL_PHI (lhs))
     return MOVE_IMPOSSIBLE;
 
-  rhs = TREE_OPERAND (stmt, 1);
+  rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
   if (TREE_SIDE_EFFECTS (rhs))
     return MOVE_IMPOSSIBLE;
@@ -423,7 +423,7 @@ stmt_cost (tree stmt)
   if (TREE_CODE (stmt) == COND_EXPR)
     return LIM_EXPENSIVE;
 
-  rhs = TREE_OPERAND (stmt, 1);
+  rhs = GENERIC_TREE_OPERAND (stmt, 1);
 
   /* Hoisting memory references out should almost surely be a win.  */
   if (stmt_references_memory_p (stmt))
@@ -609,7 +609,7 @@ determine_invariantness_stmt (struct dom_walk_data *dw_data ATTRIBUTE_UNUSED,
       /* If divisor is invariant, convert a/b to a*(1/b), allowing reciprocal
 	 to be hoisted out of loop, saving expensive divide.  */
       if (pos == MOVE_POSSIBLE
-	  && (rhs = TREE_OPERAND (stmt, 1)) != NULL
+	  && (rhs = GENERIC_TREE_OPERAND (stmt, 1)) != NULL
 	  && TREE_CODE (rhs) == RDIV_EXPR
 	  && flag_unsafe_math_optimizations
 	  && !flag_trapping_math
@@ -620,19 +620,19 @@ determine_invariantness_stmt (struct dom_walk_data *dw_data ATTRIBUTE_UNUSED,
 	{
 	  tree lhs, stmt1, stmt2, var, name;
 
-	  lhs = TREE_OPERAND (stmt, 0);
+	  lhs = GENERIC_TREE_OPERAND (stmt, 0);
 
-	  /* stmt must be MODIFY_EXPR.  */
+	  /* stmt must be GIMPLE_MODIFY_STMT.  */
 	  var = create_tmp_var (TREE_TYPE (rhs), "reciptmp");
 	  add_referenced_var (var);
 
-	  stmt1 = build2 (MODIFY_EXPR, void_type_node, var,
+	  stmt1 = build2 (GIMPLE_MODIFY_STMT, void_type_node, var,
 			  build2 (RDIV_EXPR, TREE_TYPE (rhs),
 				  build_real (TREE_TYPE (rhs), dconst1),
 				  TREE_OPERAND (rhs, 1)));
 	  name = make_ssa_name (var, stmt1);
-	  TREE_OPERAND (stmt1, 0) = name;
-	  stmt2 = build2 (MODIFY_EXPR, void_type_node, lhs,
+	  GIMPLE_STMT_OPERAND (stmt1, 0) = name;
+	  stmt2 = build2 (GIMPLE_MODIFY_STMT, void_type_node, lhs,
 			  build2 (MULT_EXPR, TREE_TYPE (rhs),
 				  name, TREE_OPERAND (rhs, 0)));
 
@@ -1051,7 +1051,7 @@ schedule_sm (struct loop *loop, VEC (edge, heap) *exits, tree ref,
       LIM_DATA (aref->stmt)->sm_done = true;
 
   /* Emit the load & stores.  */
-  load = build2 (MODIFY_EXPR, void_type_node, tmp_var, ref);
+  load = build2_gimple (GIMPLE_MODIFY_STMT, tmp_var, ref);
   get_stmt_ann (load)->common.aux = xcalloc (1, sizeof (struct lim_aux_data));
   LIM_DATA (load)->max_loop = loop;
   LIM_DATA (load)->tgt_loop = loop;
@@ -1062,8 +1062,7 @@ schedule_sm (struct loop *loop, VEC (edge, heap) *exits, tree ref,
 
   for (i = 0; VEC_iterate (edge, exits, i, ex); i++)
     {
-      store = build2 (MODIFY_EXPR, void_type_node,
-		      unshare_expr (ref), tmp_var);
+      store = build2_gimple (GIMPLE_MODIFY_STMT, unshare_expr (ref), tmp_var);
       bsi_insert_on_edge (ex, store);
     }
 }
@@ -1201,11 +1200,11 @@ gather_mem_refs_stmt (struct loop *loop, htab_t mem_refs,
     return;
 
   /* Recognize MEM = (SSA_NAME | invariant) and SSA_NAME = MEM patterns.  */
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     goto fail;
 
-  lhs = &TREE_OPERAND (stmt, 0);
-  rhs = &TREE_OPERAND (stmt, 1);
+  lhs = &GIMPLE_STMT_OPERAND (stmt, 0);
+  rhs = &GIMPLE_STMT_OPERAND (stmt, 1);
 
   if (TREE_CODE (*lhs) == SSA_NAME)
     {
diff --git a/gcc/tree-ssa-loop-ivcanon.c b/gcc/tree-ssa-loop-ivcanon.c
index c4d857302afc4461bd36f55de3c14f50dd05cb57..7dcb0da01dafb6166e07109c1caf5218d84ecd92 100644
--- a/gcc/tree-ssa-loop-ivcanon.c
+++ b/gcc/tree-ssa-loop-ivcanon.c
@@ -455,7 +455,7 @@ empty_loop_p (struct loop *loop)
 	  switch (TREE_CODE (stmt))
 	    {
 	    case RETURN_EXPR:
-	    case MODIFY_EXPR:
+	    case GIMPLE_MODIFY_STMT:
 	      stmt = get_call_expr_in (stmt);
 	      if (!stmt)
 		break;
diff --git a/gcc/tree-ssa-loop-ivopts.c b/gcc/tree-ssa-loop-ivopts.c
index 40b39f9b3db4ec968e986f1ecb8a851713fc2c2f..0132fc9cdb47987db9203d9498f57596f5f978bc 100644
--- a/gcc/tree-ssa-loop-ivopts.c
+++ b/gcc/tree-ssa-loop-ivopts.c
@@ -1037,14 +1037,14 @@ find_givs_in_stmt_scev (struct ivopts_data *data, tree stmt, affine_iv *iv)
   iv->base = NULL_TREE;
   iv->step = NULL_TREE;
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
 
-  lhs = TREE_OPERAND (stmt, 0);
+  lhs = GIMPLE_STMT_OPERAND (stmt, 0);
   if (TREE_CODE (lhs) != SSA_NAME)
     return false;
 
-  if (!simple_iv (loop, stmt, TREE_OPERAND (stmt, 1), iv, true))
+  if (!simple_iv (loop, stmt, GIMPLE_STMT_OPERAND (stmt, 1), iv, true))
     return false;
   iv->base = expand_simple_operations (iv->base);
 
@@ -1065,7 +1065,7 @@ find_givs_in_stmt (struct ivopts_data *data, tree stmt)
   if (!find_givs_in_stmt_scev (data, stmt, &iv))
     return;
 
-  set_iv (data, TREE_OPERAND (stmt, 0), iv.base, iv.step);
+  set_iv (data, GIMPLE_STMT_OPERAND (stmt, 0), iv.base, iv.step);
 }
 
 /* Finds general ivs in basic block BB.  */
@@ -1222,7 +1222,7 @@ find_interesting_uses_op (struct ivopts_data *data, tree op)
 
   stmt = SSA_NAME_DEF_STMT (op);
   gcc_assert (TREE_CODE (stmt) == PHI_NODE
-	      || TREE_CODE (stmt) == MODIFY_EXPR);
+	      || TREE_CODE (stmt) == GIMPLE_MODIFY_STMT);
 
   use = record_use (data, NULL, civ, stmt, USE_NONLINEAR_EXPR);
   iv->use_id = use->id;
@@ -1314,7 +1314,7 @@ expr_invariant_in_loop_p (struct loop *loop, tree expr)
       return true;
     }
 
-  if (!EXPR_P (expr))
+  if (!EXPR_P (expr) && !GIMPLE_STMT_P (expr))
     return false;
 
   len = TREE_CODE_LENGTH (TREE_CODE (expr));
@@ -1636,10 +1636,10 @@ find_interesting_uses_stmt (struct ivopts_data *data, tree stmt)
       return;
     }
 
-  if (TREE_CODE (stmt) == MODIFY_EXPR)
+  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
     {
-      lhs = TREE_OPERAND (stmt, 0);
-      rhs = TREE_OPERAND (stmt, 1);
+      lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+      rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
       if (TREE_CODE (lhs) == SSA_NAME)
 	{
@@ -1655,13 +1655,16 @@ find_interesting_uses_stmt (struct ivopts_data *data, tree stmt)
       switch (TREE_CODE_CLASS (TREE_CODE (rhs)))
 	{
 	case tcc_comparison:
-	  find_interesting_uses_cond (data, stmt, &TREE_OPERAND (stmt, 1));
+	  find_interesting_uses_cond (data, stmt,
+	      			      &GIMPLE_STMT_OPERAND (stmt, 1));
 	  return;
 
 	case tcc_reference:
-	  find_interesting_uses_address (data, stmt, &TREE_OPERAND (stmt, 1));
+	  find_interesting_uses_address (data, stmt,
+					 &GIMPLE_STMT_OPERAND (stmt, 1));
 	  if (REFERENCE_CLASS_P (lhs))
-	    find_interesting_uses_address (data, stmt, &TREE_OPERAND (stmt, 0));
+	    find_interesting_uses_address (data, stmt,
+					   &GIMPLE_STMT_OPERAND (stmt, 0));
 	  return;
 
 	default: ;
@@ -1670,7 +1673,8 @@ find_interesting_uses_stmt (struct ivopts_data *data, tree stmt)
       if (REFERENCE_CLASS_P (lhs)
 	  && is_gimple_val (rhs))
 	{
-	  find_interesting_uses_address (data, stmt, &TREE_OPERAND (stmt, 0));
+	  find_interesting_uses_address (data, stmt,
+					 &GIMPLE_STMT_OPERAND (stmt, 0));
 	  find_interesting_uses_op (data, rhs);
 	  return;
 	}
@@ -5383,8 +5387,8 @@ rewrite_use_nonlinear_expr (struct ivopts_data *data,
       tree step, ctype, utype;
       enum tree_code incr_code = PLUS_EXPR;
 
-      gcc_assert (TREE_CODE (use->stmt) == MODIFY_EXPR);
-      gcc_assert (TREE_OPERAND (use->stmt, 0) == cand->var_after);
+      gcc_assert (TREE_CODE (use->stmt) == GIMPLE_MODIFY_STMT);
+      gcc_assert (GIMPLE_STMT_OPERAND (use->stmt, 0) == cand->var_after);
 
       step = cand->iv->step;
       ctype = TREE_TYPE (step);
@@ -5400,7 +5404,7 @@ rewrite_use_nonlinear_expr (struct ivopts_data *data,
 	 computations in the loop -- otherwise, the computation
 	 we rely upon may be removed in remove_unused_ivs,
 	 thus leading to ICE.  */
-      op = TREE_OPERAND (use->stmt, 1);
+      op = GIMPLE_STMT_OPERAND (use->stmt, 1);
       if (TREE_CODE (op) == PLUS_EXPR
 	  || TREE_CODE (op) == MINUS_EXPR)
 	{
@@ -5448,8 +5452,8 @@ rewrite_use_nonlinear_expr (struct ivopts_data *data,
 	}
       break;
 
-    case MODIFY_EXPR:
-      tgt = TREE_OPERAND (use->stmt, 0);
+    case GIMPLE_MODIFY_STMT:
+      tgt = GIMPLE_STMT_OPERAND (use->stmt, 0);
       bsi = bsi_for_stmt (use->stmt);
       break;
 
@@ -5463,7 +5467,7 @@ rewrite_use_nonlinear_expr (struct ivopts_data *data,
     {
       if (stmts)
 	bsi_insert_after (&bsi, stmts, BSI_CONTINUE_LINKING);
-      ass = build2 (MODIFY_EXPR, TREE_TYPE (tgt), tgt, op);
+      ass = build2_gimple (GIMPLE_MODIFY_STMT, tgt, op);
       bsi_insert_after (&bsi, ass, BSI_NEW_STMT);
       remove_statement (use->stmt, false);
       SSA_NAME_DEF_STMT (tgt) = ass;
@@ -5472,7 +5476,7 @@ rewrite_use_nonlinear_expr (struct ivopts_data *data,
     {
       if (stmts)
 	bsi_insert_before (&bsi, stmts, BSI_SAME_STMT);
-      TREE_OPERAND (use->stmt, 1) = op;
+      GIMPLE_STMT_OPERAND (use->stmt, 1) = op;
     }
 }
 
diff --git a/gcc/tree-ssa-loop-manip.c b/gcc/tree-ssa-loop-manip.c
index d92f6e91ba51d891e536cacea7083bae3f3eabb1..7cfb9e1301abb6a40cf0fa9baa6796c786616ff6 100644
--- a/gcc/tree-ssa-loop-manip.c
+++ b/gcc/tree-ssa-loop-manip.c
@@ -100,9 +100,8 @@ create_iv (tree base, tree step, tree var, struct loop *loop,
   if (stmts)
     bsi_insert_on_edge_immediate (pe, stmts);
 
-  stmt = build2 (MODIFY_EXPR, void_type_node, va,
-		 build2 (incr_op, TREE_TYPE (base),
-			 vb, step));
+  stmt = build2_gimple (GIMPLE_MODIFY_STMT, va,
+		        build2 (incr_op, TREE_TYPE (base), vb, step));
   SSA_NAME_DEF_STMT (va) = stmt;
   if (after)
     bsi_insert_after (incr_pos, stmt, BSI_NEW_STMT);
diff --git a/gcc/tree-ssa-loop-niter.c b/gcc/tree-ssa-loop-niter.c
index 862f993f3b686aea7c493003a6657db982ba1129..de9ce1c2ea48def14ae7178dd22e81555c6ae232 100644
--- a/gcc/tree-ssa-loop-niter.c
+++ b/gcc/tree-ssa-loop-niter.c
@@ -684,7 +684,7 @@ simplify_replace_tree (tree expr, tree old, tree new)
       || operand_equal_p (expr, old, 0))
     return unshare_expr (new);
 
-  if (!EXPR_P (expr))
+  if (!EXPR_P (expr) && !GIMPLE_STMT_P (expr))
     return expr;
 
   n = TREE_CODE_LENGTH (TREE_CODE (expr));
@@ -744,10 +744,10 @@ expand_simple_operations (tree expr)
     return expr;
 
   stmt = SSA_NAME_DEF_STMT (expr);
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return expr;
 
-  e = TREE_OPERAND (stmt, 1);
+  e = GIMPLE_STMT_OPERAND (stmt, 1);
   if (/* Casts are simple.  */
       TREE_CODE (e) != NOP_EXPR
       && TREE_CODE (e) != CONVERT_EXPR
@@ -1255,7 +1255,7 @@ chain_of_csts_start (struct loop *loop, tree x)
       return NULL_TREE;
     }
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return NULL_TREE;
 
   if (!ZERO_SSA_OPERANDS (stmt, SSA_OP_ALL_VIRTUALS))
@@ -1337,7 +1337,7 @@ get_val_for (tree x, tree base)
       nx = USE_FROM_PTR (op);
       val = get_val_for (nx, base);
       SET_USE (op, val);
-      val = fold (TREE_OPERAND (stmt, 1));
+      val = fold (GIMPLE_STMT_OPERAND (stmt, 1));
       SET_USE (op, nx);
       /* only iterate loop once.  */
       return val;
@@ -1655,10 +1655,11 @@ derive_constant_upper_bound (tree val, tree additional)
 
     case SSA_NAME:
       stmt = SSA_NAME_DEF_STMT (val);
-      if (TREE_CODE (stmt) != MODIFY_EXPR
-	  || TREE_OPERAND (stmt, 0) != val)
+      if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT
+	  || GIMPLE_STMT_OPERAND (stmt, 0) != val)
 	return max;
-      return derive_constant_upper_bound (TREE_OPERAND (stmt, 1), additional);
+      return derive_constant_upper_bound (GIMPLE_STMT_OPERAND (stmt, 1),
+	  				  additional);
 
     default: 
       return max;
@@ -1872,10 +1873,10 @@ infer_loop_bounds_from_array (struct loop *loop, tree stmt)
 {
   tree call;
 
-  if (TREE_CODE (stmt) == MODIFY_EXPR)
+  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
     {
-      tree op0 = TREE_OPERAND (stmt, 0);
-      tree op1 = TREE_OPERAND (stmt, 1);
+      tree op0 = GIMPLE_STMT_OPERAND (stmt, 0);
+      tree op1 = GIMPLE_STMT_OPERAND (stmt, 1);
 
       /* For each memory access, analyze its access function
 	 and record a bound on the loop iteration domain.  */
@@ -1906,10 +1907,10 @@ infer_loop_bounds_from_signedness (struct loop *loop, tree stmt)
 {
   tree def, base, step, scev, type, low, high;
 
-  if (flag_wrapv || TREE_CODE (stmt) != MODIFY_EXPR)
+  if (flag_wrapv || TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return;
 
-  def = TREE_OPERAND (stmt, 0);
+  def = GIMPLE_STMT_OPERAND (stmt, 0);
 
   if (TREE_CODE (def) != SSA_NAME)
     return;
diff --git a/gcc/tree-ssa-loop-prefetch.c b/gcc/tree-ssa-loop-prefetch.c
index 07f35cf5d0ce92a0e368edf09bf3293e14ef7c31..114d0e3ebe05b4e1fb9368b7e1e7db52dc3e01e7 100644
--- a/gcc/tree-ssa-loop-prefetch.c
+++ b/gcc/tree-ssa-loop-prefetch.c
@@ -461,11 +461,11 @@ gather_memory_references (struct loop *loop)
       for (bsi = bsi_start (bb); !bsi_end_p (bsi); bsi_next (&bsi))
 	{
 	  stmt = bsi_stmt (bsi);
-	  if (TREE_CODE (stmt) != MODIFY_EXPR)
+	  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
 	    continue;
 
-	  lhs = TREE_OPERAND (stmt, 0);
-	  rhs = TREE_OPERAND (stmt, 1);
+	  lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+	  rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
 	  if (REFERENCE_CLASS_P (rhs))
 	    gather_memory_references_ref (loop, &refs, rhs, false, stmt);
diff --git a/gcc/tree-ssa-math-opts.c b/gcc/tree-ssa-math-opts.c
index 76b0c3ea9b3da7868f29176aa5bb49921dc94a93..5b2834089ec7107590681b467467c5d3dbd83a0f 100644
--- a/gcc/tree-ssa-math-opts.c
+++ b/gcc/tree-ssa-math-opts.c
@@ -111,7 +111,7 @@ struct occurrence {
      inserted in BB.  */
   tree recip_def;
 
-  /* If non-NULL, the MODIFY_EXPR for a reciprocal computation that
+  /* If non-NULL, the GIMPLE_MODIFY_STMT for a reciprocal computation that
      was inserted in BB.  */
   tree recip_def_stmt;
 
@@ -274,9 +274,9 @@ compute_merit (struct occurrence *occ)
 static inline bool
 is_division_by (tree use_stmt, tree def)
 {
-  return TREE_CODE (use_stmt) == MODIFY_EXPR
-	 && TREE_CODE (TREE_OPERAND (use_stmt, 1)) == RDIV_EXPR
-	 && TREE_OPERAND (TREE_OPERAND (use_stmt, 1), 1) == def;
+  return TREE_CODE (use_stmt) == GIMPLE_MODIFY_STMT
+	 && TREE_CODE (GIMPLE_STMT_OPERAND (use_stmt, 1)) == RDIV_EXPR
+	 && TREE_OPERAND (GIMPLE_STMT_OPERAND (use_stmt, 1), 1) == def;
 }
 
 /* Walk the subset of the dominator tree rooted at OCC, setting the
@@ -303,7 +303,7 @@ insert_reciprocals (block_stmt_iterator *def_bsi, struct occurrence *occ,
       /* Make a variable with the replacement and substitute it.  */
       type = TREE_TYPE (def);
       recip_def = make_rename_temp (type, "reciptmp");
-      new_stmt = build2 (MODIFY_EXPR, void_type_node, recip_def,
+      new_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, recip_def,
 		         fold_build2 (RDIV_EXPR, type, build_one_cst (type),
 				      def));
   
@@ -353,7 +353,7 @@ replace_reciprocal (use_operand_p use_p)
 
   if (occ->recip_def && use_stmt != occ->recip_def_stmt)
     {
-      TREE_SET_CODE (TREE_OPERAND (use_stmt, 1), MULT_EXPR);
+      TREE_SET_CODE (GIMPLE_STMT_OPERAND (use_stmt, 1), MULT_EXPR);
       SET_USE (use_p, occ->recip_def);
       fold_stmt_inplace (use_stmt);
       update_stmt (use_stmt);
@@ -490,7 +490,7 @@ execute_cse_reciprocals (void)
       for (bsi = bsi_after_labels (bb); !bsi_end_p (bsi); bsi_next (&bsi))
         {
 	  tree stmt = bsi_stmt (bsi);
-	  if (TREE_CODE (stmt) == MODIFY_EXPR
+	  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
 	      && (def = SINGLE_SSA_TREE_OPERAND (stmt, SSA_OP_DEF)) != NULL
 	      && FLOAT_TYPE_P (TREE_TYPE (def))
 	      && TREE_CODE (def) == SSA_NAME)
diff --git a/gcc/tree-ssa-operands.c b/gcc/tree-ssa-operands.c
index 5c4e100595d914584ac945b75cfa46a2aa5324de..05876846a35d2ef52ff81c543000878fe13d3111 100644
--- a/gcc/tree-ssa-operands.c
+++ b/gcc/tree-ssa-operands.c
@@ -98,7 +98,7 @@ Boston, MA 02110-1301, USA.  */
 
 /* Operand is a "non-specific" kill for call-clobbers and such.  This
    is used to distinguish "reset the world" events from explicit
-   MODIFY_EXPRs.  */
+   GIMPLE_MODIFY_STMTs.  */
 #define opf_non_specific  (1 << 3)
 
 /* Array for building all the def operands.  */
@@ -533,7 +533,7 @@ finalize_ssa_defs (tree stmt)
   unsigned int num = VEC_length (tree, build_defs);
 
   /* There should only be a single real definition per assignment.  */
-  gcc_assert ((stmt && TREE_CODE (stmt) != MODIFY_EXPR) || num <= 1);
+  gcc_assert ((stmt && TREE_CODE (stmt) != GIMPLE_MODIFY_STMT) || num <= 1);
 
   /* If there is an old list, often the new list is identical, or close, so
      find the elements at the beginning that are the same as the vector.  */
@@ -1230,7 +1230,7 @@ add_virtual_operand (tree var, stmt_ann_t s_ann, int flags,
      check that this only happens on non-specific stores.
 
      Note that if this is a specific store, i.e. associated with a
-     modify_expr, then we can't suppress the V_MAY_DEF, lest we run
+     gimple_modify_stmt, then we can't suppress the V_MAY_DEF, lest we run
      into validation problems.
 
      This can happen when programs cast away const, leaving us with a
@@ -1814,10 +1814,10 @@ get_asm_expr_operands (tree stmt)
 /* Scan operands for the assignment expression EXPR in statement STMT.  */
 
 static void
-get_modify_expr_operands (tree stmt, tree expr)
+get_modify_stmt_operands (tree stmt, tree expr)
 {
   /* First get operands from the RHS.  */
-  get_expr_operands (stmt, &TREE_OPERAND (expr, 1), opf_none);
+  get_expr_operands (stmt, &GIMPLE_STMT_OPERAND (expr, 1), opf_none);
 
   /* For the LHS, use a regular definition (OPF_IS_DEF) for GIMPLE
      registers.  If the LHS is a store to memory, we will either need
@@ -1832,7 +1832,8 @@ get_modify_expr_operands (tree stmt, tree expr)
      The determination of whether to use a preserving or a killing
      definition is done while scanning the LHS of the assignment.  By
      default, assume that we will emit a V_MUST_DEF.  */
-  get_expr_operands (stmt, &TREE_OPERAND (expr, 0), opf_is_def|opf_kill_def);
+  get_expr_operands (stmt, &GIMPLE_STMT_OPERAND (expr, 0),
+      		     opf_is_def|opf_kill_def);
 }
 
 
@@ -2005,8 +2006,8 @@ get_expr_operands (tree stmt, tree *expr_p, int flags)
       get_expr_operands (stmt, &TREE_OPERAND (expr, 2), opf_none);
       return;
 
-    case MODIFY_EXPR:
-      get_modify_expr_operands (stmt, expr);
+    case GIMPLE_MODIFY_STMT:
+      get_modify_stmt_operands (stmt, expr);
       return;
 
     case CONSTRUCTOR:
@@ -2106,8 +2107,8 @@ parse_ssa_operands (tree stmt)
   code = TREE_CODE (stmt);
   switch (code)
     {
-    case MODIFY_EXPR:
-      get_modify_expr_operands (stmt, stmt);
+    case GIMPLE_MODIFY_STMT:
+      get_modify_stmt_operands (stmt, stmt);
       break;
 
     case COND_EXPR:
diff --git a/gcc/tree-ssa-phiopt.c b/gcc/tree-ssa-phiopt.c
index edad768d864fd00946b8a3cd1eeb526bd972f612..2cc7ad794252772b9483ad039fae2c67e55a3147 100644
--- a/gcc/tree-ssa-phiopt.c
+++ b/gcc/tree-ssa-phiopt.c
@@ -439,7 +439,7 @@ conditional_replacement (basic_block cond_bb, basic_block middle_bb,
 		     TREE_OPERAND (old_result, 0),
 		     TREE_OPERAND (old_result, 1));
 
-      new1 = build2 (MODIFY_EXPR, TREE_TYPE (old_result), new_var, new1);
+      new1 = build2_gimple (GIMPLE_MODIFY_STMT, new_var, new1);
       SSA_NAME_DEF_STMT (new_var) = new1;
 
       bsi_insert_after (&bsi, new1, BSI_NEW_STMT);
@@ -470,7 +470,7 @@ conditional_replacement (basic_block cond_bb, basic_block middle_bb,
       || (e1 == true_edge && integer_onep (arg1))
       || (e1 == false_edge && integer_zerop (arg1)))
     {
-      new = build2 (MODIFY_EXPR, TREE_TYPE (new_var1), new_var1, cond);
+      new = build2_gimple (GIMPLE_MODIFY_STMT, new_var1, cond);
     }
   else
     {
@@ -514,14 +514,14 @@ conditional_replacement (basic_block cond_bb, basic_block middle_bb,
 	  tmp = create_tmp_var (TREE_TYPE (op0), NULL);
 	  add_referenced_var (tmp);
 	  cond_tmp = make_ssa_name (tmp, NULL);
-	  new = build2 (MODIFY_EXPR, TREE_TYPE (cond_tmp), cond_tmp, op0);
+	  new = build2_gimple (GIMPLE_MODIFY_STMT, cond_tmp, op0);
 	  SSA_NAME_DEF_STMT (cond_tmp) = new;
 
 	  bsi_insert_after (&bsi, new, BSI_NEW_STMT);
 	  cond = fold_convert (TREE_TYPE (result), cond_tmp);
 	}
 
-      new = build2 (MODIFY_EXPR, TREE_TYPE (new_var1), new_var1, cond);
+      new = build2_gimple (GIMPLE_MODIFY_STMT, new_var1, cond);
     }
 
   bsi_insert_after (&bsi, new, BSI_NEW_STMT);
@@ -715,11 +715,11 @@ minmax_replacement (basic_block cond_bb, basic_block middle_bb,
       tree lhs, rhs, op0, op1, bound;
 
       if (!assign
-	  || TREE_CODE (assign) != MODIFY_EXPR)
+	  || TREE_CODE (assign) != GIMPLE_MODIFY_STMT)
 	return false;
 
-      lhs = TREE_OPERAND (assign, 0);
-      rhs = TREE_OPERAND (assign, 1);
+      lhs = GIMPLE_STMT_OPERAND (assign, 0);
+      rhs = GIMPLE_STMT_OPERAND (assign, 1);
       ass_code = TREE_CODE (rhs);
       if (ass_code != MAX_EXPR && ass_code != MIN_EXPR)
 	return false;
@@ -853,8 +853,8 @@ minmax_replacement (basic_block cond_bb, basic_block middle_bb,
 
   /* Emit the statement to compute min/max.  */
   result = duplicate_ssa_name (PHI_RESULT (phi), NULL);
-  new = build2 (MODIFY_EXPR, type, result,
-		build2 (minmax, type, arg0, arg1));
+  new = build2_gimple (GIMPLE_MODIFY_STMT, result,
+		       build2 (minmax, type, arg0, arg1));
   SSA_NAME_DEF_STMT (result) = new;
   bsi = bsi_last (cond_bb);
   bsi_insert_before (&bsi, new, BSI_NEW_STMT);
@@ -901,11 +901,11 @@ abs_replacement (basic_block cond_bb, basic_block middle_bb,
   /* If we got here, then we have found the only executable statement
      in OTHER_BLOCK.  If it is anything other than arg = -arg1 or
      arg1 = -arg0, then we can not optimize.  */
-  if (TREE_CODE (assign) != MODIFY_EXPR)
+  if (TREE_CODE (assign) != GIMPLE_MODIFY_STMT)
     return false;
 
-  lhs = TREE_OPERAND (assign, 0);
-  rhs = TREE_OPERAND (assign, 1);
+  lhs = GIMPLE_STMT_OPERAND (assign, 0);
+  rhs = GIMPLE_STMT_OPERAND (assign, 1);
 
   if (TREE_CODE (rhs) != NEGATE_EXPR)
     return false;
@@ -966,8 +966,8 @@ abs_replacement (basic_block cond_bb, basic_block middle_bb,
     lhs = result;
 
   /* Build the modify expression with abs expression.  */
-  new = build2 (MODIFY_EXPR, TREE_TYPE (lhs),
-		lhs, build1 (ABS_EXPR, TREE_TYPE (lhs), rhs));
+  new = build2_gimple (GIMPLE_MODIFY_STMT,
+		       lhs, build1 (ABS_EXPR, TREE_TYPE (lhs), rhs));
   SSA_NAME_DEF_STMT (lhs) = new;
 
   bsi = bsi_last (cond_bb);
@@ -978,8 +978,8 @@ abs_replacement (basic_block cond_bb, basic_block middle_bb,
       /* Get the right BSI.  We want to insert after the recently
 	 added ABS_EXPR statement (which we know is the first statement
 	 in the block.  */
-      new = build2 (MODIFY_EXPR, TREE_TYPE (result),
-		    result, build1 (NEGATE_EXPR, TREE_TYPE (lhs), lhs));
+      new = build2_gimple (GIMPLE_MODIFY_STMT,
+		           result, build1 (NEGATE_EXPR, TREE_TYPE (lhs), lhs));
       SSA_NAME_DEF_STMT (result) = new;
 
       bsi_insert_after (&bsi, new, BSI_NEW_STMT);
diff --git a/gcc/tree-ssa-pre.c b/gcc/tree-ssa-pre.c
index 1bbd77e96c8b77d4ae3056419abd61209be2e815..492b42d1551136de757ef2322863df1ece2950f5 100644
--- a/gcc/tree-ssa-pre.c
+++ b/gcc/tree-ssa-pre.c
@@ -61,9 +61,9 @@ Boston, MA 02110-1301, USA.  */
 */
 
 /* For ease of terminology, "expression node" in the below refers to
-   every expression node but MODIFY_EXPR, because MODIFY_EXPR's represent
-   the actual statement containing the expressions we care about, and
-   we cache the value number by putting it in the expression.  */
+   every expression node but GIMPLE_MODIFY_STMT, because GIMPLE_MODIFY_STMT's
+   represent the actual statement containing the expressions we care about,
+   and we cache the value number by putting it in the expression.  */
 
 /* Basic algorithm
 
@@ -986,7 +986,7 @@ phi_translate (tree expr, bitmap_set_t set1, bitmap_set_t set2,
     return expr;
 
   /* Phi translations of a given expression don't change.  */
-  if (EXPR_P (expr))
+  if (EXPR_P (expr) || GIMPLE_STMT_P (expr))
     {
       tree vh;
 
@@ -1115,7 +1115,7 @@ phi_translate (tree expr, bitmap_set_t set1, bitmap_set_t set2,
 		TREE_OPERAND (newexpr, 0) = newop0 == oldop0 ? oldval0 : get_value_handle (newop0);
 		TREE_OPERAND (newexpr, 1) = listchanged ? newarglist : oldarglist;
 		TREE_OPERAND (newexpr, 2) = newop2 == oldop2 ? oldval2 : get_value_handle (newop2);
-		newexpr->common.ann = NULL;
+		newexpr->base.ann = NULL;
 		vn_lookup_or_add_with_vuses (newexpr, tvuses);
 		expr = newexpr;
 		phi_trans_add (oldexpr, newexpr, pred, tvuses);
@@ -1227,7 +1227,7 @@ phi_translate (tree expr, bitmap_set_t set1, bitmap_set_t set2,
 	      }
 	    else
 	      {
-		newexpr->common.ann = NULL;
+		newexpr->base.ann = NULL;
 		vn_lookup_or_add_with_vuses (newexpr, newvuses);
 	      }
 	    expr = newexpr;
@@ -1272,7 +1272,7 @@ phi_translate (tree expr, bitmap_set_t set1, bitmap_set_t set2,
 	      }
 	    else
 	      {
-		newexpr->common.ann = NULL;
+		newexpr->base.ann = NULL;
 		vn_lookup_or_add (newexpr, NULL);
 	      }
 	    expr = newexpr;
@@ -1305,7 +1305,7 @@ phi_translate (tree expr, bitmap_set_t set1, bitmap_set_t set2,
 	      }
 	    else
 	      {
-		newexpr->common.ann = NULL;
+		newexpr->base.ann = NULL;
 		vn_lookup_or_add (newexpr, NULL);
 	      }
 	    expr = newexpr;
@@ -2490,7 +2490,7 @@ find_or_generate_expression (basic_block block, tree expr, tree stmts)
   return genop;
 }
 
-#define NECESSARY(stmt)		stmt->common.asm_written_flag
+#define NECESSARY(stmt)		stmt->base.asm_written_flag
 /* Create an expression in pieces, so that we can handle very complex
    expressions that may be ANTIC, but not necessary GIMPLE.
    BLOCK is the basic block the expression will be inserted into,
@@ -2608,8 +2608,8 @@ create_expression_by_pieces (basic_block block, tree expr, tree stmts)
       for (; !tsi_end_p (tsi); tsi_next (&tsi))
 	{
 	  tree stmt = tsi_stmt (tsi);
-	  tree forcedname = TREE_OPERAND (stmt, 0);
-	  tree forcedexpr = TREE_OPERAND (stmt, 1);
+	  tree forcedname = GIMPLE_STMT_OPERAND (stmt, 0);
+	  tree forcedexpr = GIMPLE_STMT_OPERAND (stmt, 1);
 	  tree val = vn_lookup_or_add (forcedexpr, NULL);
 
 	  VEC_safe_push (tree, heap, inserted_exprs, stmt);
@@ -2636,9 +2636,9 @@ create_expression_by_pieces (basic_block block, tree expr, tree stmts)
   if (TREE_CODE (TREE_TYPE (expr)) == COMPLEX_TYPE)
     DECL_COMPLEX_GIMPLE_REG_P (temp) = 1;
 
-  newexpr = build2 (MODIFY_EXPR, TREE_TYPE (expr), temp, newexpr);
+  newexpr = build2_gimple (GIMPLE_MODIFY_STMT, temp, newexpr);
   name = make_ssa_name (temp, newexpr);
-  TREE_OPERAND (newexpr, 0) = name;
+  GIMPLE_STMT_OPERAND (newexpr, 0) = name;
   NECESSARY (newexpr) = 0;
 
   tsi = tsi_last (stmts);
@@ -3375,7 +3375,7 @@ try_look_through_load (tree lhs, tree mem_ref, tree stmt, basic_block block)
 	 uses, we can stop right here.  Note that this means we do
 	 not look through PHI nodes, which is intentional.  */
       if (!def_stmt
-	  || TREE_CODE (def_stmt) != MODIFY_EXPR
+	  || TREE_CODE (def_stmt) != GIMPLE_MODIFY_STMT
 	  || !ZERO_SSA_OPERANDS (def_stmt, SSA_OP_VIRTUAL_USES))
 	return false;
 
@@ -3388,7 +3388,7 @@ try_look_through_load (tree lhs, tree mem_ref, tree stmt, basic_block block)
 	{
 	  /* Is this a store to the exact same location as the one we are
 	     loading from in STMT?  */
-	  if (!operand_equal_p (TREE_OPERAND (def_stmt, 0), mem_ref, 0))
+	  if (!operand_equal_p (GIMPLE_STMT_OPERAND (def_stmt, 0), mem_ref, 0))
 	    return false;
 
 	  /* Otherwise remember this statement and see if all other VUSEs
@@ -3400,7 +3400,7 @@ try_look_through_load (tree lhs, tree mem_ref, tree stmt, basic_block block)
   /* Alright then, we have visited all VUSEs of STMT and we've determined
      that all of them come from the same statement STORE_STMT.  See if there
      is a useful expression we can deduce from STORE_STMT.  */
-  rhs = TREE_OPERAND (store_stmt, 1);
+  rhs = GIMPLE_STMT_OPERAND (store_stmt, 1);
   if ((TREE_CODE (rhs) == SSA_NAME
        && !SSA_NAME_OCCURS_IN_ABNORMAL_PHI (rhs))
       || is_gimple_min_invariant (rhs)
@@ -3438,12 +3438,14 @@ poolify_tree (tree node)
 	return temp;
       }
       break;
-    case MODIFY_EXPR:
+    case GIMPLE_MODIFY_STMT:
       {
 	tree temp = (tree) pool_alloc (modify_expr_node_pool);
 	memcpy (temp, node, tree_size (node));
-	TREE_OPERAND (temp, 0) = poolify_tree (TREE_OPERAND (temp, 0));
-	TREE_OPERAND (temp, 1) = poolify_tree (TREE_OPERAND (temp, 1));
+	GIMPLE_STMT_OPERAND (temp, 0) =
+	  poolify_tree (GIMPLE_STMT_OPERAND (temp, 0));
+	GIMPLE_STMT_OPERAND (temp, 1) =
+	  poolify_tree (GIMPLE_STMT_OPERAND (temp, 1));
 	return temp;
       }
       break;
@@ -3462,17 +3464,16 @@ poolify_tree (tree node)
 
 static tree modify_expr_template;
 
-/* Allocate a MODIFY_EXPR with TYPE, and operands OP1, OP2 in the
+/* Allocate a GIMPLE_MODIFY_STMT with TYPE, and operands OP1, OP2 in the
    alloc pools and return it.  */
 static tree
-poolify_modify_expr (tree type, tree op1, tree op2)
+poolify_modify_stmt (tree op1, tree op2)
 {
   if (modify_expr_template == NULL)
-    modify_expr_template = build2 (MODIFY_EXPR, type, op1, op2);
+    modify_expr_template = build2_gimple (GIMPLE_MODIFY_STMT, op1, op2);
 
-  TREE_OPERAND (modify_expr_template, 0) = op1;
-  TREE_OPERAND (modify_expr_template, 1) = op2;
-  TREE_TYPE (modify_expr_template) = type;
+  GIMPLE_STMT_OPERAND (modify_expr_template, 0) = op1;
+  GIMPLE_STMT_OPERAND (modify_expr_template, 1) = op2;
 
   return poolify_tree (modify_expr_template);
 }
@@ -3506,15 +3507,16 @@ insert_fake_stores (void)
 	     or aggregate.  We also want to ignore things whose
 	     virtual uses occur in abnormal phis.  */
 
-	  if (TREE_CODE (stmt) == MODIFY_EXPR
-	      && TREE_CODE (TREE_OPERAND (stmt, 0)) == INDIRECT_REF
-	      && !AGGREGATE_TYPE_P (TREE_TYPE (TREE_OPERAND (stmt, 0)))
-	      && TREE_CODE (TREE_TYPE (TREE_OPERAND (stmt, 0))) != COMPLEX_TYPE)
+	  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+	      && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) == INDIRECT_REF
+	      && !AGGREGATE_TYPE_P (TREE_TYPE (GIMPLE_STMT_OPERAND (stmt, 0)))
+	      && TREE_CODE (TREE_TYPE (GIMPLE_STMT_OPERAND
+					(stmt, 0))) != COMPLEX_TYPE)
 	    {
 	      ssa_op_iter iter;
 	      def_operand_p defp;
-	      tree lhs = TREE_OPERAND (stmt, 0);
-	      tree rhs = TREE_OPERAND (stmt, 1);
+	      tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+	      tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 	      tree new;
 	      bool notokay = false;
 
@@ -3537,10 +3539,10 @@ insert_fake_stores (void)
 		  get_var_ann (storetemp);
 		}
 
-	      new = poolify_modify_expr (TREE_TYPE (stmt), storetemp, lhs);
+	      new = poolify_modify_stmt (storetemp, lhs);
 
 	      lhs = make_ssa_name (storetemp, new);
-	      TREE_OPERAND (new, 0) = lhs;
+	      GIMPLE_STMT_OPERAND (new, 0) = lhs;
 	      create_ssa_artficial_load_stmt (new, stmt);
 
 	      NECESSARY (new) = 0;
@@ -3570,7 +3572,7 @@ realify_fake_stores (void)
 	  tree newstmt;
 
 	  /* Mark the temp variable as referenced */
-	  add_referenced_var (SSA_NAME_VAR (TREE_OPERAND (stmt, 0)));
+	  add_referenced_var (SSA_NAME_VAR (GIMPLE_STMT_OPERAND (stmt, 0)));
 
 	  /* Put the new statement in GC memory, fix up the
 	     SSA_NAME_DEF_STMT on it, and then put it in place of
@@ -3578,10 +3580,10 @@ realify_fake_stores (void)
 	     as a plain ssa name copy.  */
 	  bsi = bsi_for_stmt (stmt);
 	  bsi_prev (&bsi);
-	  newstmt = build2 (MODIFY_EXPR, void_type_node,
-			    TREE_OPERAND (stmt, 0),
-			    TREE_OPERAND (bsi_stmt (bsi), 1));
-	  SSA_NAME_DEF_STMT (TREE_OPERAND (newstmt, 0)) = newstmt;
+	  newstmt = build2_gimple (GIMPLE_MODIFY_STMT,
+			           GIMPLE_STMT_OPERAND (stmt, 0),
+			    	   GIMPLE_STMT_OPERAND (bsi_stmt (bsi), 1));
+	  SSA_NAME_DEF_STMT (GIMPLE_STMT_OPERAND (newstmt, 0)) = newstmt;
 	  bsi_insert_before (&bsi, newstmt, BSI_SAME_STMT);
 	  bsi = bsi_for_stmt (stmt);
 	  bsi_remove (&bsi, true);
@@ -3752,10 +3754,10 @@ compute_avail (void)
 	      tree rhs;
 
 	      stmt = TREE_OPERAND (stmt, 0);
-	      if (stmt && TREE_CODE (stmt) == MODIFY_EXPR)
+	      if (stmt && TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
 		{
-		  lhs  = TREE_OPERAND (stmt, 0);
-		  rhs = TREE_OPERAND (stmt, 1);
+		  lhs  = GIMPLE_STMT_OPERAND (stmt, 0);
+		  rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 		  if (TREE_CODE (rhs) == SSA_NAME
 		      && !is_undefined_value (rhs))
 		    bitmap_value_insert_into_set (EXP_GEN (block), rhs);
@@ -3767,13 +3769,14 @@ compute_avail (void)
 	      continue;
 	    }
 
-	  else if (TREE_CODE (stmt) == MODIFY_EXPR
+	  else if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
 	      && !ann->has_volatile_ops
-	      && TREE_CODE (TREE_OPERAND (stmt, 0)) == SSA_NAME
-	      && !SSA_NAME_OCCURS_IN_ABNORMAL_PHI (TREE_OPERAND (stmt, 0)))
+	      && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) == SSA_NAME
+	      && !SSA_NAME_OCCURS_IN_ABNORMAL_PHI
+	           (GIMPLE_STMT_OPERAND (stmt, 0)))
 	    {
-	      tree lhs = TREE_OPERAND (stmt, 0);
-	      tree rhs = TREE_OPERAND (stmt, 1);
+	      tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+	      tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
 	      /* Try to look through loads.  */
 	      if (TREE_CODE (lhs) == SSA_NAME
@@ -3868,14 +3871,14 @@ eliminate (void)
 	  /* Lookup the RHS of the expression, see if we have an
 	     available computation for it.  If so, replace the RHS with
 	     the available computation.  */
-	  if (TREE_CODE (stmt) == MODIFY_EXPR
-	      && TREE_CODE (TREE_OPERAND (stmt, 0)) == SSA_NAME
-	      && TREE_CODE (TREE_OPERAND (stmt ,1)) != SSA_NAME
-	      && !is_gimple_min_invariant (TREE_OPERAND (stmt, 1))
+	  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+	      && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) == SSA_NAME
+	      && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) != SSA_NAME
+	      && !is_gimple_min_invariant (GIMPLE_STMT_OPERAND (stmt, 1))
 	      && !stmt_ann (stmt)->has_volatile_ops)
 	    {
-	      tree lhs = TREE_OPERAND (stmt, 0);
-	      tree *rhs_p = &TREE_OPERAND (stmt, 1);
+	      tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+	      tree *rhs_p = &GIMPLE_STMT_OPERAND (stmt, 1);
 	      tree sprime;
 
 	      sprime = bitmap_find_leader (AVAIL_OUT (b),
@@ -4097,8 +4100,8 @@ init_pre (bool do_fre)
 				      tree_code_size (TREE_LIST), 30);
   comparison_node_pool = create_alloc_pool ("Comparison tree nodes",
 					    tree_code_size (EQ_EXPR), 30);
-  modify_expr_node_pool = create_alloc_pool ("MODIFY_EXPR nodes",
-					     tree_code_size (MODIFY_EXPR),
+  modify_expr_node_pool = create_alloc_pool ("GIMPLE_MODIFY_STMT nodes",
+					     tree_code_size (GIMPLE_MODIFY_STMT),
 					     30);
   modify_expr_template = NULL;
 
diff --git a/gcc/tree-ssa-propagate.c b/gcc/tree-ssa-propagate.c
index a5114862dc8dbdc093315fa492f5cfdddd5d5406..b787aae70ba370de2ebffd87e1149045d26e4848 100644
--- a/gcc/tree-ssa-propagate.c
+++ b/gcc/tree-ssa-propagate.c
@@ -531,12 +531,12 @@ get_rhs (tree stmt)
     {
     case RETURN_EXPR:
       stmt = TREE_OPERAND (stmt, 0);
-      if (!stmt || TREE_CODE (stmt) != MODIFY_EXPR)
+      if (!stmt || TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
 	return stmt;
       /* FALLTHRU */
 
-    case MODIFY_EXPR:
-      stmt = TREE_OPERAND (stmt, 1);
+    case GIMPLE_MODIFY_STMT:
+      stmt = GENERIC_TREE_OPERAND (stmt, 1);
       if (TREE_CODE (stmt) == WITH_SIZE_EXPR)
 	return TREE_OPERAND (stmt, 0);
       else
@@ -641,7 +641,8 @@ set_rhs (tree *stmt_p, tree expr)
     }
 
   if (EXPR_HAS_LOCATION (stmt)
-      && EXPR_P (expr)
+      && (EXPR_P (expr)
+	  || GIMPLE_STMT_P (expr))
       && ! EXPR_HAS_LOCATION (expr)
       && TREE_SIDE_EFFECTS (expr)
       && TREE_CODE (expr) != LABEL_EXPR)
@@ -651,19 +652,23 @@ set_rhs (tree *stmt_p, tree expr)
     {
     case RETURN_EXPR:
       op = TREE_OPERAND (stmt, 0);
-      if (TREE_CODE (op) != MODIFY_EXPR)
+      if (TREE_CODE (op) != GIMPLE_MODIFY_STMT)
 	{
-	  TREE_OPERAND (stmt, 0) = expr;
+	  GIMPLE_STMT_OPERAND (stmt, 0) = expr;
 	  break;
 	}
       stmt = op;
       /* FALLTHRU */
 
-    case MODIFY_EXPR:
-      op = TREE_OPERAND (stmt, 1);
+    case GIMPLE_MODIFY_STMT:
+      op = GIMPLE_STMT_OPERAND (stmt, 1);
       if (TREE_CODE (op) == WITH_SIZE_EXPR)
-	stmt = op;
-      TREE_OPERAND (stmt, 1) = expr;
+	{
+	  stmt = op;
+          TREE_OPERAND (stmt, 1) = expr;
+	}
+      else
+        GIMPLE_STMT_OPERAND (stmt, 1) = expr;
       break;
 
     case COND_EXPR:
@@ -686,7 +691,7 @@ set_rhs (tree *stmt_p, tree expr)
 	 effects, then replace *STMT_P with an empty statement.  */
       ann = stmt_ann (stmt);
       *stmt_p = TREE_SIDE_EFFECTS (expr) ? expr : build_empty_stmt ();
-      (*stmt_p)->common.ann = (tree_ann_t) ann;
+      (*stmt_p)->base.ann = (tree_ann_t) ann;
 
       if (gimple_in_ssa_p (cfun)
 	  && TREE_SIDE_EFFECTS (expr))
@@ -770,13 +775,13 @@ stmt_makes_single_load (tree stmt)
 {
   tree rhs;
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
 
   if (ZERO_SSA_OPERANDS (stmt, SSA_OP_VMAYDEF|SSA_OP_VUSE))
     return false;
 
-  rhs = TREE_OPERAND (stmt, 1);
+  rhs = GIMPLE_STMT_OPERAND (stmt, 1);
   STRIP_NOPS (rhs);
 
   return (!TREE_THIS_VOLATILE (rhs)
@@ -795,13 +800,13 @@ stmt_makes_single_store (tree stmt)
 {
   tree lhs;
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
 
   if (ZERO_SSA_OPERANDS (stmt, SSA_OP_VMAYDEF|SSA_OP_VMUSTDEF))
     return false;
 
-  lhs = TREE_OPERAND (stmt, 0);
+  lhs = GIMPLE_STMT_OPERAND (stmt, 0);
   STRIP_NOPS (lhs);
 
   return (!TREE_THIS_VOLATILE (lhs)
@@ -963,7 +968,7 @@ replace_vuses_in (tree stmt, bool *replaced_addresses_p,
 	 see if we are trying to propagate a constant or a GIMPLE
 	 register (case #1 above).  */
       prop_value_t *val = get_value_loaded_by (stmt, prop_value);
-      tree rhs = TREE_OPERAND (stmt, 1);
+      tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
       if (val
 	  && val->value
@@ -975,7 +980,7 @@ replace_vuses_in (tree stmt, bool *replaced_addresses_p,
 	  /* If we are replacing a constant address, inform our
 	     caller.  */
 	  if (TREE_CODE (val->value) != SSA_NAME
-	      && POINTER_TYPE_P (TREE_TYPE (TREE_OPERAND (stmt, 1)))
+	      && POINTER_TYPE_P (TREE_TYPE (GIMPLE_STMT_OPERAND (stmt, 1)))
 	      && replaced_addresses_p)
 	    *replaced_addresses_p = true;
 
@@ -985,7 +990,7 @@ replace_vuses_in (tree stmt, bool *replaced_addresses_p,
 	     stores between DEF_STMT and STMT, we only need to check
 	     that the RHS of STMT is the same as the memory reference
 	     propagated together with the value.  */
-	  TREE_OPERAND (stmt, 1) = val->value;
+	  GIMPLE_STMT_OPERAND (stmt, 1) = val->value;
 
 	  if (TREE_CODE (val->value) != SSA_NAME)
 	    prop_stats.num_const_prop++;
@@ -1084,14 +1089,14 @@ static bool
 fold_predicate_in (tree stmt)
 {
   tree *pred_p = NULL;
-  bool modify_expr_p = false;
+  bool modify_stmt_p = false;
   tree val;
 
-  if (TREE_CODE (stmt) == MODIFY_EXPR
-      && COMPARISON_CLASS_P (TREE_OPERAND (stmt, 1)))
+  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+      && COMPARISON_CLASS_P (GIMPLE_STMT_OPERAND (stmt, 1)))
     {
-      modify_expr_p = true;
-      pred_p = &TREE_OPERAND (stmt, 1);
+      modify_stmt_p = true;
+      pred_p = &GIMPLE_STMT_OPERAND (stmt, 1);
     }
   else if (TREE_CODE (stmt) == COND_EXPR)
     pred_p = &COND_EXPR_COND (stmt);
@@ -1101,7 +1106,7 @@ fold_predicate_in (tree stmt)
   val = vrp_evaluate_conditional (*pred_p, true);
   if (val)
     {
-      if (modify_expr_p)
+      if (modify_stmt_p)
         val = fold_convert (TREE_TYPE (*pred_p), val);
       
       if (dump_file)
@@ -1167,8 +1172,8 @@ substitute_and_fold (prop_value_t *prop_value, bool use_ranges_p)
 	  /* Ignore ASSERT_EXPRs.  They are used by VRP to generate
 	     range information for names and they are discarded
 	     afterwards.  */
-	  if (TREE_CODE (stmt) == MODIFY_EXPR
-	      && TREE_CODE (TREE_OPERAND (stmt, 1)) == ASSERT_EXPR)
+	  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+	      && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == ASSERT_EXPR)
 	    continue;
 
 	  /* Replace the statement with its folded version and mark it
diff --git a/gcc/tree-ssa-reassoc.c b/gcc/tree-ssa-reassoc.c
index 8b5d34a0f309194cb8fc5e23af9a2f28588b6001..17c4c6f4a5292883128ccb38316560a93a558302 100644
--- a/gcc/tree-ssa-reassoc.c
+++ b/gcc/tree-ssa-reassoc.c
@@ -271,7 +271,7 @@ get_rank (tree e)
       if (bb_for_stmt (stmt) == NULL)
 	return 0;
 
-      if (TREE_CODE (stmt) != MODIFY_EXPR
+      if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT
 	  || !ZERO_SSA_OPERANDS (stmt, SSA_OP_VIRTUAL_DEFS))
 	return bb_rank[bb_for_stmt (stmt)->index];
 
@@ -284,7 +284,7 @@ get_rank (tree e)
 	 rank, whichever is less.   */
       rank = 0;
       maxrank = bb_rank[bb_for_stmt(stmt)->index];
-      rhs = TREE_OPERAND (stmt, 1);
+      rhs = GIMPLE_STMT_OPERAND (stmt, 1);
       if (TREE_CODE_LENGTH (TREE_CODE (rhs)) == 0)
 	rank = MAX (rank, get_rank (rhs));
       else
@@ -378,9 +378,9 @@ static bool
 is_reassociable_op (tree stmt, enum tree_code code)
 {
   if (!IS_EMPTY_STMT (stmt)
-      && TREE_CODE (stmt) == MODIFY_EXPR
-      && TREE_CODE (TREE_OPERAND (stmt, 1)) == code
-      && has_single_use (TREE_OPERAND (stmt, 0)))
+      && TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+      && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == code
+      && has_single_use (GIMPLE_STMT_OPERAND (stmt, 0)))
     return true;
   return false;
 }
@@ -395,10 +395,10 @@ get_unary_op (tree name, enum tree_code opcode)
   tree stmt = SSA_NAME_DEF_STMT (name);
   tree rhs;
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return NULL_TREE;
 
-  rhs = TREE_OPERAND (stmt, 1);
+  rhs = GIMPLE_STMT_OPERAND (stmt, 1);
   if (TREE_CODE (rhs) == opcode)
     return TREE_OPERAND (rhs, 0);
   return NULL_TREE;
@@ -814,7 +814,7 @@ static bool
 is_phi_for_stmt (tree stmt, tree operand)
 {
   tree def_stmt;
-  tree lhs = TREE_OPERAND (stmt, 0);
+  tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
   use_operand_p arg_p;
   ssa_op_iter i;
 
@@ -839,7 +839,7 @@ static void
 rewrite_expr_tree (tree stmt, unsigned int opindex,
 		   VEC(operand_entry_t, heap) * ops)
 {
-  tree rhs = TREE_OPERAND (stmt, 1);
+  tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
   operand_entry_t oe;
 
   /* If we have three operands left, then we want to make sure the one
@@ -952,7 +952,7 @@ static void
 linearize_expr (tree stmt)
 {
   block_stmt_iterator bsinow, bsirhs;
-  tree rhs = TREE_OPERAND (stmt, 1);
+  tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
   enum tree_code rhscode = TREE_CODE (rhs);
   tree binrhs = SSA_NAME_DEF_STMT (TREE_OPERAND (rhs, 1));
   tree binlhs = SSA_NAME_DEF_STMT (TREE_OPERAND (rhs, 0));
@@ -965,11 +965,12 @@ linearize_expr (tree stmt)
   bsirhs = bsi_for_stmt (binrhs);
   bsi_move_before (&bsirhs, &bsinow);
 
-  TREE_OPERAND (rhs, 1) = TREE_OPERAND (TREE_OPERAND (binrhs, 1), 0);
+  TREE_OPERAND (rhs, 1) = TREE_OPERAND (GIMPLE_STMT_OPERAND (binrhs, 1), 0);
   if (TREE_CODE (TREE_OPERAND (rhs, 1)) == SSA_NAME)
     newbinrhs = SSA_NAME_DEF_STMT (TREE_OPERAND (rhs, 1));
-  TREE_OPERAND (TREE_OPERAND (binrhs, 1), 0) = TREE_OPERAND (binlhs, 0);
-  TREE_OPERAND (rhs, 0) = TREE_OPERAND (binrhs, 0);
+  TREE_OPERAND (GIMPLE_STMT_OPERAND (binrhs, 1), 0)
+    = GIMPLE_STMT_OPERAND (binlhs, 0);
+  TREE_OPERAND (rhs, 0) = GIMPLE_STMT_OPERAND (binrhs, 0);
 
   if (dump_file && (dump_flags & TDF_DETAILS))
     {
@@ -991,7 +992,7 @@ linearize_expr (tree stmt)
 
 }
 
-/* If LHS has a single immediate use that is a MODIFY_EXPR, return
+/* If LHS has a single immediate use that is a GIMPLE_MODIFY_STMT, return
    it.  Otherwise, return NULL.  */
 
 static tree
@@ -1005,7 +1006,7 @@ get_single_immediate_use (tree lhs)
     {
       if (TREE_CODE (immusestmt) == RETURN_EXPR)
 	immusestmt = TREE_OPERAND (immusestmt, 0);
-      if (TREE_CODE (immusestmt) == MODIFY_EXPR)
+      if (TREE_CODE (immusestmt) == GIMPLE_MODIFY_STMT)
 	return immusestmt;
     }
   return NULL_TREE;
@@ -1032,13 +1033,13 @@ negate_value (tree tonegate, block_stmt_iterator *bsi)
   /* If we are trying to negate a name, defined by an add, negate the
      add operands instead.  */
   if (TREE_CODE (tonegate) == SSA_NAME
-      && TREE_CODE (negatedef) == MODIFY_EXPR
-      && TREE_CODE (TREE_OPERAND (negatedef, 0)) == SSA_NAME
-      && has_single_use (TREE_OPERAND (negatedef, 0))
-      && TREE_CODE (TREE_OPERAND (negatedef, 1)) == PLUS_EXPR)
+      && TREE_CODE (negatedef) == GIMPLE_MODIFY_STMT
+      && TREE_CODE (GIMPLE_STMT_OPERAND (negatedef, 0)) == SSA_NAME
+      && has_single_use (GIMPLE_STMT_OPERAND (negatedef, 0))
+      && TREE_CODE (GIMPLE_STMT_OPERAND (negatedef, 1)) == PLUS_EXPR)
     {
       block_stmt_iterator bsi;
-      tree binop = TREE_OPERAND (negatedef, 1);
+      tree binop = GIMPLE_STMT_OPERAND (negatedef, 1);
 
       bsi = bsi_for_stmt (negatedef);
       TREE_OPERAND (binop, 0) = negate_value (TREE_OPERAND (binop, 0),
@@ -1047,7 +1048,7 @@ negate_value (tree tonegate, block_stmt_iterator *bsi)
       TREE_OPERAND (binop, 1) = negate_value (TREE_OPERAND (binop, 1),
 					      &bsi);
       update_stmt (negatedef);
-      return TREE_OPERAND (negatedef, 0);
+      return GIMPLE_STMT_OPERAND (negatedef, 0);
     }
 
   tonegate = fold_build1 (NEGATE_EXPR, TREE_TYPE (tonegate), tonegate);
@@ -1068,8 +1069,8 @@ static bool
 should_break_up_subtract (tree stmt)
 {
 
-  tree lhs = TREE_OPERAND (stmt, 0);
-  tree rhs = TREE_OPERAND (stmt, 1);
+  tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+  tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
   tree binlhs = TREE_OPERAND (rhs, 0);
   tree binrhs = TREE_OPERAND (rhs, 1);
   tree immusestmt;
@@ -1084,7 +1085,7 @@ should_break_up_subtract (tree stmt)
 
   if (TREE_CODE (lhs) == SSA_NAME
       && (immusestmt = get_single_immediate_use (lhs))
-      && TREE_CODE (TREE_OPERAND (immusestmt, 1)) == PLUS_EXPR)
+      && TREE_CODE (GIMPLE_STMT_OPERAND (immusestmt, 1)) == PLUS_EXPR)
     return true;
   return false;
 
@@ -1095,7 +1096,7 @@ should_break_up_subtract (tree stmt)
 static void
 break_up_subtract (tree stmt, block_stmt_iterator *bsi)
 {
-  tree rhs = TREE_OPERAND (stmt, 1);
+  tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
   if (dump_file && (dump_flags & TDF_DETAILS))
     {
@@ -1103,7 +1104,7 @@ break_up_subtract (tree stmt, block_stmt_iterator *bsi)
       print_generic_stmt (dump_file, stmt, 0);
     }
 
-  TREE_SET_CODE (TREE_OPERAND (stmt, 1), PLUS_EXPR);
+  TREE_SET_CODE (GIMPLE_STMT_OPERAND (stmt, 1), PLUS_EXPR);
   TREE_OPERAND (rhs, 1) = negate_value (TREE_OPERAND (rhs, 1), bsi);
 
   update_stmt (stmt);
@@ -1116,7 +1117,7 @@ static void
 linearize_expr_tree (VEC(operand_entry_t, heap) **ops, tree stmt)
 {
   block_stmt_iterator bsinow, bsilhs;
-  tree rhs = TREE_OPERAND (stmt, 1);
+  tree rhs = GENERIC_TREE_OPERAND (stmt, 1);
   tree binrhs = TREE_OPERAND (rhs, 1);
   tree binlhs = TREE_OPERAND (rhs, 0);
   tree binlhsdef, binrhsdef;
@@ -1180,7 +1181,7 @@ linearize_expr_tree (VEC(operand_entry_t, heap) **ops, tree stmt)
   else if (binrhsisreassoc)
     {
       linearize_expr (stmt);
-      gcc_assert (rhs == TREE_OPERAND (stmt, 1));
+      gcc_assert (rhs == GIMPLE_STMT_OPERAND (stmt, 1));
       binlhs = TREE_OPERAND (rhs, 0);
       binrhs = TREE_OPERAND (rhs, 1);
     }
@@ -1213,15 +1214,15 @@ repropagate_negates (void)
 	 Force the negate operand to the RHS of the PLUS_EXPR, then
 	 transform the PLUS_EXPR into a MINUS_EXPR.  */
       if (user
-	  && TREE_CODE (user) == MODIFY_EXPR
-	  && TREE_CODE (TREE_OPERAND (user, 1)) == PLUS_EXPR)
+	  && TREE_CODE (user) == GIMPLE_MODIFY_STMT
+	  && TREE_CODE (GIMPLE_STMT_OPERAND (user, 1)) == PLUS_EXPR)
 	{
-	  tree rhs = TREE_OPERAND (user, 1);
+	  tree rhs = GIMPLE_STMT_OPERAND (user, 1);
 
 	  /* If the negated operand appears on the LHS of the
 	     PLUS_EXPR, exchange the operands of the PLUS_EXPR
 	     to force the negated operand to the RHS of the PLUS_EXPR.  */
-	  if (TREE_OPERAND (TREE_OPERAND (user, 1), 0) == negate)
+	  if (TREE_OPERAND (GIMPLE_STMT_OPERAND (user, 1), 0) == negate)
 	    {
 	      tree temp = TREE_OPERAND (rhs, 0);
 	      TREE_OPERAND (rhs, 0) = TREE_OPERAND (rhs, 1);
@@ -1230,7 +1231,7 @@ repropagate_negates (void)
 
 	  /* Now transform the PLUS_EXPR into a MINUS_EXPR and replace
 	     the RHS of the PLUS_EXPR with the operand of the NEGATE_EXPR.  */
-	  if (TREE_OPERAND (TREE_OPERAND (user, 1), 1) == negate)
+	  if (TREE_OPERAND (GIMPLE_STMT_OPERAND (user, 1), 1) == negate)
 	    {
 	      TREE_SET_CODE (rhs, MINUS_EXPR);
 	      TREE_OPERAND (rhs, 1) = get_unary_op (negate, NEGATE_EXPR);
@@ -1265,10 +1266,10 @@ break_up_subtract_bb (basic_block bb)
     {
       tree stmt = bsi_stmt (bsi);
 
-      if (TREE_CODE (stmt) == MODIFY_EXPR)
+      if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
 	{
-	  tree lhs = TREE_OPERAND (stmt, 0);
-	  tree rhs = TREE_OPERAND (stmt, 1);
+	  tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+	  tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
 	  TREE_VISITED (stmt) = 0;
 	  /* If unsafe math optimizations we can do reassociation for
@@ -1308,10 +1309,10 @@ reassociate_bb (basic_block bb)
     {
       tree stmt = bsi_stmt (bsi);
 
-      if (TREE_CODE (stmt) == MODIFY_EXPR)
+      if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
 	{
-	  tree lhs = TREE_OPERAND (stmt, 0);
-	  tree rhs = TREE_OPERAND (stmt, 1);
+	  tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+	  tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
 	  /* If this was part of an already processed tree, we don't
 	     need to touch it again. */
@@ -1351,14 +1352,15 @@ reassociate_bb (basic_block bb)
 		      fprintf (dump_file, "Transforming ");
 		      print_generic_expr (dump_file, rhs, 0);
 		    }
-		  TREE_OPERAND (stmt, 1) = VEC_last (operand_entry_t, ops)->op;
+		  GIMPLE_STMT_OPERAND (stmt, 1) 
+		    = VEC_last (operand_entry_t, ops)->op;
 		  update_stmt (stmt);
 
 		  if (dump_file && (dump_flags & TDF_DETAILS))
 		    {
 		      fprintf (dump_file, " into ");
 		      print_generic_stmt (dump_file,
-					  TREE_OPERAND (stmt, 1), 0);
+					  GIMPLE_STMT_OPERAND (stmt, 1), 0);
 		    }
 		}
 	      else
diff --git a/gcc/tree-ssa-sink.c b/gcc/tree-ssa-sink.c
index fa711b386430b2f921ddd775cfd99d3fde4ad9c2..7bb37187e2023ad7f319aa02fb806903fa731486 100644
--- a/gcc/tree-ssa-sink.c
+++ b/gcc/tree-ssa-sink.c
@@ -144,7 +144,7 @@ is_hidden_global_store (tree stmt)
     {
       tree lhs;
 
-      gcc_assert (TREE_CODE (stmt) == MODIFY_EXPR);
+      gcc_assert (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT);
 
       /* Note that we must not check the individual virtual operands
 	 here.  In particular, if this is an aliased store, we could
@@ -171,7 +171,7 @@ is_hidden_global_store (tree stmt)
 	 address is a pointer, we check if its name tag or symbol tag is
 	 a global variable.  Otherwise, we check if the base variable
 	 is a global.  */
-      lhs = TREE_OPERAND (stmt, 0);
+      lhs = GIMPLE_STMT_OPERAND (stmt, 0);
       if (REFERENCE_CLASS_P (lhs))
 	lhs = get_base_address (lhs);
 
@@ -292,9 +292,9 @@ statement_sink_location (tree stmt, basic_block frombb)
   if (one_use == NULL_USE_OPERAND_P)
     return NULL;
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return NULL;
-  rhs = TREE_OPERAND (stmt, 1);
+  rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
   /* There are a few classes of things we can't or don't move, some because we
      don't have code to handle it, some because it's not profitable and some
diff --git a/gcc/tree-ssa-structalias.c b/gcc/tree-ssa-structalias.c
index 7fda8b55cc36b0d939266e1702746cd18d6a8215..99deb41b555599f45aa0f851730437c062398086 100644
--- a/gcc/tree-ssa-structalias.c
+++ b/gcc/tree-ssa-structalias.c
@@ -2763,13 +2763,13 @@ update_alias_info (tree stmt, struct alias_info *ai)
 	 of an assignment and their base address is always an
 	 INDIRECT_REF expression.  */
       is_potential_deref = false;
-      if (TREE_CODE (stmt) == MODIFY_EXPR
-	  && TREE_CODE (TREE_OPERAND (stmt, 1)) == ADDR_EXPR
-	  && !is_gimple_val (TREE_OPERAND (stmt, 1)))
+      if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+	  && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == ADDR_EXPR
+	  && !is_gimple_val (GIMPLE_STMT_OPERAND (stmt, 1)))
 	{
 	  /* If the RHS if of the form &PTR->FLD and PTR == OP, then
 	     this represents a potential dereference of PTR.  */
-	  tree rhs = TREE_OPERAND (stmt, 1);
+	  tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 	  tree base = get_base_address (TREE_OPERAND (rhs, 0));
 	  if (TREE_CODE (base) == INDIRECT_REF
 	      && TREE_OPERAND (base, 0) == op)
@@ -2971,9 +2971,9 @@ find_func_aliases (tree origt)
      modify_expr when we are returning a value, or just a plain
      call_expr when we are not.   */
   else if (in_ipa_mode
-	   && ((TREE_CODE (t) == MODIFY_EXPR
-		&& TREE_CODE (TREE_OPERAND (t, 1)) == CALL_EXPR
-	       && !(call_expr_flags (TREE_OPERAND (t, 1))
+	   && ((TREE_CODE (t) == GIMPLE_MODIFY_STMT
+		&& TREE_CODE (GIMPLE_STMT_OPERAND (t, 1)) == CALL_EXPR
+	       && !(call_expr_flags (GIMPLE_STMT_OPERAND (t, 1))
 		    & (ECF_MALLOC | ECF_MAY_BE_ALLOCA)))
 	       || (TREE_CODE (t) == CALL_EXPR
 		   && !(call_expr_flags (t)
@@ -2986,10 +2986,10 @@ find_func_aliases (tree origt)
       varinfo_t fi;
       int i = 1;
       tree decl;
-      if (TREE_CODE (t) == MODIFY_EXPR)
+      if (TREE_CODE (t) == GIMPLE_MODIFY_STMT)
 	{
-	  lhsop = TREE_OPERAND (t, 0);
-	  rhsop = TREE_OPERAND (t, 1);
+	  lhsop = GIMPLE_STMT_OPERAND (t, 0);
+	  rhsop = GIMPLE_STMT_OPERAND (t, 1);
 	}
       else
 	{
@@ -3068,10 +3068,10 @@ find_func_aliases (tree origt)
 	}
     }
   /* Otherwise, just a regular assignment statement.  */
-  else if (TREE_CODE (t) == MODIFY_EXPR)
+  else if (TREE_CODE (t) == GIMPLE_MODIFY_STMT)
     {
-      tree lhsop = TREE_OPERAND (t, 0);
-      tree rhsop = TREE_OPERAND (t, 1);
+      tree lhsop = GIMPLE_STMT_OPERAND (t, 0);
+      tree rhsop = GIMPLE_STMT_OPERAND (t, 1);
       int i;
 
       if ((AGGREGATE_TYPE_P (TREE_TYPE (lhsop))
diff --git a/gcc/tree-ssa-threadedge.c b/gcc/tree-ssa-threadedge.c
index 6ae5d3e5468df2f1b4f3b88a4dbb4b2fe5fe8e18..e48cd650d17f37ecb6a9bda125e58b718e2d10b0 100644
--- a/gcc/tree-ssa-threadedge.c
+++ b/gcc/tree-ssa-threadedge.c
@@ -91,12 +91,12 @@ lhs_of_dominating_assert (tree op, basic_block bb, tree stmt)
     {
       use_stmt = USE_STMT (use_p);
       if (use_stmt != stmt
-          && TREE_CODE (use_stmt) == MODIFY_EXPR
-          && TREE_CODE (TREE_OPERAND (use_stmt, 1)) == ASSERT_EXPR
-          && TREE_OPERAND (TREE_OPERAND (use_stmt, 1), 0) == op
+          && TREE_CODE (use_stmt) == GIMPLE_MODIFY_STMT
+          && TREE_CODE (GIMPLE_STMT_OPERAND (use_stmt, 1)) == ASSERT_EXPR
+          && TREE_OPERAND (GIMPLE_STMT_OPERAND (use_stmt, 1), 0) == op
 	  && dominated_by_p (CDI_DOMINATORS, bb, bb_for_stmt (use_stmt)))
 	{
-	  return TREE_OPERAND (use_stmt, 0);
+	  return GIMPLE_STMT_OPERAND (use_stmt, 0);
 	}
     }
   return op;
@@ -245,11 +245,11 @@ record_temporary_equivalences_from_stmts_at_dest (edge e,
       if (stmt_count > max_stmt_count)
 	return NULL;
 
-      /* If this is not a MODIFY_EXPR which sets an SSA_NAME to a new
+      /* If this is not a GIMPLE_MODIFY_STMT which sets an SSA_NAME to a new
 	 value, then do not try to simplify this statement as it will
 	 not simplify in any way that is helpful for jump threading.  */
-      if (TREE_CODE (stmt) != MODIFY_EXPR
-	  || TREE_CODE (TREE_OPERAND (stmt, 0)) != SSA_NAME)
+      if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT
+	  || TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) != SSA_NAME)
 	continue;
 
       /* At this point we have a statement which assigns an RHS to an
@@ -259,10 +259,10 @@ record_temporary_equivalences_from_stmts_at_dest (edge e,
 
 	 Handle simple copy operations as well as implied copies from
 	 ASSERT_EXPRs.  */
-      if (TREE_CODE (TREE_OPERAND (stmt, 1)) == SSA_NAME)
-	cached_lhs = TREE_OPERAND (stmt, 1);
-      else if (TREE_CODE (TREE_OPERAND (stmt, 1)) == ASSERT_EXPR)
-	cached_lhs = TREE_OPERAND (TREE_OPERAND (stmt, 1), 0);
+      if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == SSA_NAME)
+	cached_lhs = GIMPLE_STMT_OPERAND (stmt, 1);
+      else if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == ASSERT_EXPR)
+	cached_lhs = TREE_OPERAND (GIMPLE_STMT_OPERAND (stmt, 1), 0);
       else
 	{
 	  /* A statement that is not a trivial copy or ASSERT_EXPR.
@@ -296,19 +296,19 @@ record_temporary_equivalences_from_stmts_at_dest (edge e,
 	     here, because fold expects all the operands of an expression
 	     to be folded before the expression itself is folded, but we
 	     can't just substitute the folded condition here.  */
-	  if (TREE_CODE (TREE_OPERAND (stmt, 1)) == COND_EXPR)
+	  if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == COND_EXPR)
 	    {
-	      tree cond = COND_EXPR_COND (TREE_OPERAND (stmt, 1));
+	      tree cond = COND_EXPR_COND (GIMPLE_STMT_OPERAND (stmt, 1));
 	      cond = fold (cond);
 	      if (cond == boolean_true_node)
-		pre_fold_expr = COND_EXPR_THEN (TREE_OPERAND (stmt, 1));
+		pre_fold_expr = COND_EXPR_THEN (GIMPLE_STMT_OPERAND (stmt, 1));
 	      else if (cond == boolean_false_node)
-		pre_fold_expr = COND_EXPR_ELSE (TREE_OPERAND (stmt, 1));
+		pre_fold_expr = COND_EXPR_ELSE (GIMPLE_STMT_OPERAND (stmt, 1));
 	      else
-		pre_fold_expr = TREE_OPERAND (stmt, 1);
+		pre_fold_expr = GIMPLE_STMT_OPERAND (stmt, 1);
 	    }
 	  else
-	    pre_fold_expr = TREE_OPERAND (stmt, 1);
+	    pre_fold_expr = GIMPLE_STMT_OPERAND (stmt, 1);
 
 	  if (pre_fold_expr)
 	    {
@@ -331,7 +331,7 @@ record_temporary_equivalences_from_stmts_at_dest (edge e,
       if (cached_lhs
 	  && (TREE_CODE (cached_lhs) == SSA_NAME
 	      || is_gimple_min_invariant (cached_lhs)))
-	record_temporary_equivalence (TREE_OPERAND (stmt, 0),
+	record_temporary_equivalence (GIMPLE_STMT_OPERAND (stmt, 0),
 				      cached_lhs,
 				      stack);
     }
diff --git a/gcc/tree-ssa.c b/gcc/tree-ssa.c
index 470427180696f7504cbbb37777533855144e0c57..ce46fa27902a3852c65a4787e52262db23d7e0c5 100644
--- a/gcc/tree-ssa.c
+++ b/gcc/tree-ssa.c
@@ -624,12 +624,12 @@ verify_ssa (bool check_modified_stmt)
 	      goto err;
 	    }
 
-	  if (TREE_CODE (stmt) == MODIFY_EXPR
-	      && TREE_CODE (TREE_OPERAND (stmt, 0)) != SSA_NAME)
+	  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+	      && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) != SSA_NAME)
 	    {
 	      tree lhs, base_address;
 
-	      lhs = TREE_OPERAND (stmt, 0);
+	      lhs = GIMPLE_STMT_OPERAND (stmt, 0);
 	      base_address = get_base_address (lhs);
 
 	      if (base_address
@@ -758,8 +758,8 @@ delete_tree_ssa (void)
   /* Remove annotations from every referenced variable.  */
   FOR_EACH_REFERENCED_VAR (var, rvi)
     {
-      ggc_free (var->common.ann);
-      var->common.ann = NULL;
+      ggc_free (var->base.ann);
+      var->base.ann = NULL;
     }
   htab_delete (gimple_referenced_vars (cfun));
   cfun->gimple_df->referenced_vars = NULL;
diff --git a/gcc/tree-ssanames.c b/gcc/tree-ssanames.c
index 21d5761d03b133768080d6c7e7efdb75d5979606..a8716dad8d16c3f59ba0474a1aefaad16453023c 100644
--- a/gcc/tree-ssanames.c
+++ b/gcc/tree-ssanames.c
@@ -119,7 +119,9 @@ make_ssa_name (tree var, tree stmt)
   gcc_assert (DECL_P (var)
 	      || TREE_CODE (var) == INDIRECT_REF);
 
-  gcc_assert (!stmt || EXPR_P (stmt) || TREE_CODE (stmt) == PHI_NODE);
+  gcc_assert (!stmt
+	      || EXPR_P (stmt) || GIMPLE_STMT_P (stmt)
+	      || TREE_CODE (stmt) == PHI_NODE);
 
   /* If our free list has an element, then use it.  */
   if (FREE_SSANAMES (cfun))
diff --git a/gcc/tree-stdarg.c b/gcc/tree-stdarg.c
index 4a67bc850f6944abda255c0c18ed28320e307de7..bc72c17baeacab222c79e2e80b5dc0bad77ae277 100644
--- a/gcc/tree-stdarg.c
+++ b/gcc/tree-stdarg.c
@@ -149,11 +149,11 @@ va_list_counter_bump (struct stdarg_info *si, tree counter, tree rhs,
 
       stmt = SSA_NAME_DEF_STMT (lhs);
 
-      if (TREE_CODE (stmt) != MODIFY_EXPR
-	  || TREE_OPERAND (stmt, 0) != lhs)
+      if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT
+	  || GIMPLE_STMT_OPERAND (stmt, 0) != lhs)
 	return (unsigned HOST_WIDE_INT) -1;
 
-      rhs = TREE_OPERAND (stmt, 1);
+      rhs = GIMPLE_STMT_OPERAND (stmt, 1);
       if (TREE_CODE (rhs) == WITH_SIZE_EXPR)
 	rhs = TREE_OPERAND (rhs, 0);
 
@@ -211,7 +211,7 @@ va_list_counter_bump (struct stdarg_info *si, tree counter, tree rhs,
 
       stmt = SSA_NAME_DEF_STMT (lhs);
 
-      rhs = TREE_OPERAND (stmt, 1);
+      rhs = GIMPLE_STMT_OPERAND (stmt, 1);
       if (TREE_CODE (rhs) == WITH_SIZE_EXPR)
 	rhs = TREE_OPERAND (rhs, 0);
 
@@ -522,10 +522,10 @@ check_all_va_list_escapes (struct stdarg_info *si)
 				  DECL_UID (SSA_NAME_VAR (use))))
 		continue;
 
-	      if (TREE_CODE (stmt) == MODIFY_EXPR)
+	      if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
 		{
-		  tree lhs = TREE_OPERAND (stmt, 0);
-		  tree rhs = TREE_OPERAND (stmt, 1);
+		  tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+		  tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
 		  if (TREE_CODE (rhs) == WITH_SIZE_EXPR)
 		    rhs = TREE_OPERAND (rhs, 0);
@@ -807,10 +807,10 @@ execute_optimize_stdarg (void)
 		continue;
 	    }
 
-	  if (TREE_CODE (stmt) == MODIFY_EXPR)
+	  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
 	    {
-	      tree lhs = TREE_OPERAND (stmt, 0);
-	      tree rhs = TREE_OPERAND (stmt, 1);
+	      tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+	      tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
 	      if (TREE_CODE (rhs) == WITH_SIZE_EXPR)
 		rhs = TREE_OPERAND (rhs, 0);
diff --git a/gcc/tree-tailcall.c b/gcc/tree-tailcall.c
index 616a550d55cb4ce89059bceedbdec0dfe73ba3f5..05c2778ae120bafd814b7e7961db6a0703f68923 100644
--- a/gcc/tree-tailcall.c
+++ b/gcc/tree-tailcall.c
@@ -272,8 +272,8 @@ process_assignment (tree ass, tree stmt, block_stmt_iterator call, tree *m,
 		    tree *a, tree *ass_var)
 {
   tree op0, op1, non_ass_var;
-  tree dest = TREE_OPERAND (ass, 0);
-  tree src = TREE_OPERAND (ass, 1);
+  tree dest = GIMPLE_STMT_OPERAND (ass, 0);
+  tree src = GIMPLE_STMT_OPERAND (ass, 1);
   enum tree_code code = TREE_CODE (src);
   tree src_var = src;
 
@@ -395,10 +395,10 @@ find_tail_calls (basic_block bb, struct tailcall **ret)
 	continue;
 
       /* Check for a call.  */
-      if (TREE_CODE (stmt) == MODIFY_EXPR)
+      if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
 	{
-	  ass_var = TREE_OPERAND (stmt, 0);
-	  call = TREE_OPERAND (stmt, 1);
+	  ass_var = GIMPLE_STMT_OPERAND (stmt, 0);
+	  call = GIMPLE_STMT_OPERAND (stmt, 1);
 	  if (TREE_CODE (call) == WITH_SIZE_EXPR)
 	    call = TREE_OPERAND (call, 0);
 	}
@@ -454,7 +454,7 @@ find_tail_calls (basic_block bb, struct tailcall **ret)
 		 of copying the value.  This test implies is_gimple_reg_type
 		 from the previous condition, however this one could be
 		 relaxed by being more careful with copying the new value
-		 of the parameter (emitting appropriate MODIFY_EXPR and
+		 of the parameter (emitting appropriate GIMPLE_MODIFY_STMT and
 		 updating the virtual operands).  */
 	      if (!is_gimple_reg (param))
 		break;
@@ -492,7 +492,7 @@ find_tail_calls (basic_block bb, struct tailcall **ret)
       if (TREE_CODE (stmt) == RETURN_EXPR)
 	break;
 
-      if (TREE_CODE (stmt) != MODIFY_EXPR)
+      if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
 	return;
 
       if (!process_assignment (stmt, stmt, bsi, &m, &a, &ass_var))
@@ -502,9 +502,9 @@ find_tail_calls (basic_block bb, struct tailcall **ret)
   /* See if this is a tail call we can handle.  */
   ret_var = TREE_OPERAND (stmt, 0);
   if (ret_var
-      && TREE_CODE (ret_var) == MODIFY_EXPR)
+      && TREE_CODE (ret_var) == GIMPLE_MODIFY_STMT)
     {
-      tree ret_op = TREE_OPERAND (ret_var, 1);
+      tree ret_op = GIMPLE_STMT_OPERAND (ret_var, 1);
       STRIP_NOPS (ret_op);
       if (!tail_recursion
 	  && TREE_CODE (ret_op) != SSA_NAME)
@@ -512,7 +512,7 @@ find_tail_calls (basic_block bb, struct tailcall **ret)
 
       if (!process_assignment (ret_var, stmt, bsi, &m, &a, &ass_var))
 	return;
-      ret_var = TREE_OPERAND (ret_var, 0);
+      ret_var = GIMPLE_STMT_OPERAND (ret_var, 0);
     }
 
   /* We may proceed if there either is no return value, or the return value
@@ -558,34 +558,34 @@ adjust_accumulator_values (block_stmt_iterator bsi, tree m, tree a, edge back)
 	    var = m_acc;
 	  else
 	    {
-	      stmt = build2 (MODIFY_EXPR, ret_type, NULL_TREE,
+	      stmt = build2 (GIMPLE_MODIFY_STMT, ret_type, NULL_TREE,
 			     build2 (MULT_EXPR, ret_type, m_acc, a));
 
 	      tmp = create_tmp_var (ret_type, "acc_tmp");
 	      add_referenced_var (tmp);
 
 	      var = make_ssa_name (tmp, stmt);
-	      TREE_OPERAND (stmt, 0) = var;
+	      GIMPLE_STMT_OPERAND (stmt, 0) = var;
 	      bsi_insert_after (&bsi, stmt, BSI_NEW_STMT);
 	    }
 	}
       else
 	var = a;
 
-      stmt = build2 (MODIFY_EXPR, ret_type, NULL_TREE,
+      stmt = build2 (GIMPLE_MODIFY_STMT, ret_type, NULL_TREE,
 		     build2 (PLUS_EXPR, ret_type, a_acc, var));
       var = make_ssa_name (SSA_NAME_VAR (a_acc), stmt);
-      TREE_OPERAND (stmt, 0) = var;
+      GIMPLE_STMT_OPERAND (stmt, 0) = var;
       bsi_insert_after (&bsi, stmt, BSI_NEW_STMT);
       a_acc_arg = var;
     }
 
   if (m)
     {
-      stmt = build2 (MODIFY_EXPR, ret_type, NULL_TREE,
+      stmt = build2 (GIMPLE_MODIFY_STMT, ret_type, NULL_TREE,
 		     build2 (MULT_EXPR, ret_type, m_acc, m));
       var = make_ssa_name (SSA_NAME_VAR (m_acc), stmt);
-      TREE_OPERAND (stmt, 0) = var;
+      GIMPLE_STMT_OPERAND (stmt, 0) = var;
       bsi_insert_after (&bsi, stmt, BSI_NEW_STMT);
       m_acc_arg = var;
     }
@@ -625,26 +625,26 @@ adjust_return_value (basic_block bb, tree m, tree a)
   if (!ret_var)
     return;
 
-  if (TREE_CODE (ret_var) == MODIFY_EXPR)
+  if (TREE_CODE (ret_var) == GIMPLE_MODIFY_STMT)
     {
-      ret_var->common.ann = (tree_ann_t) stmt_ann (ret_stmt);
+      ret_var->base.ann = (tree_ann_t) stmt_ann (ret_stmt);
       bsi_replace (&bsi, ret_var, true);
-      SSA_NAME_DEF_STMT (TREE_OPERAND (ret_var, 0)) = ret_var;
-      ret_var = TREE_OPERAND (ret_var, 0);
+      SSA_NAME_DEF_STMT (GIMPLE_STMT_OPERAND (ret_var, 0)) = ret_var;
+      ret_var = GIMPLE_STMT_OPERAND (ret_var, 0);
       ret_stmt = build1 (RETURN_EXPR, TREE_TYPE (ret_stmt), ret_var);
       bsi_insert_after (&bsi, ret_stmt, BSI_NEW_STMT);
     }
 
   if (m)
     {
-      stmt = build2 (MODIFY_EXPR, ret_type, NULL_TREE,
+      stmt = build2 (GIMPLE_MODIFY_STMT, ret_type, NULL_TREE,
 		     build2 (MULT_EXPR, ret_type, m_acc, ret_var));
 
       tmp = create_tmp_var (ret_type, "acc_tmp");
       add_referenced_var (tmp);
 
       var = make_ssa_name (tmp, stmt);
-      TREE_OPERAND (stmt, 0) = var;
+      GIMPLE_STMT_OPERAND (stmt, 0) = var;
       bsi_insert_before (&bsi, stmt, BSI_SAME_STMT);
     }
   else
@@ -652,14 +652,14 @@ adjust_return_value (basic_block bb, tree m, tree a)
 
   if (a)
     {
-      stmt = build2 (MODIFY_EXPR, ret_type, NULL_TREE,
+      stmt = build2 (GIMPLE_MODIFY_STMT, ret_type, NULL_TREE,
 		     build2 (PLUS_EXPR, ret_type, a_acc, var));
 
       tmp = create_tmp_var (ret_type, "acc_tmp");
       add_referenced_var (tmp);
 
       var = make_ssa_name (tmp, stmt);
-      TREE_OPERAND (stmt, 0) = var;
+      GIMPLE_STMT_OPERAND (stmt, 0) = var;
       bsi_insert_before (&bsi, stmt, BSI_SAME_STMT);
     }
 
@@ -733,8 +733,8 @@ eliminate_tail_call (struct tailcall *t)
       fprintf (dump_file, "\n");
     }
 
-  if (TREE_CODE (stmt) == MODIFY_EXPR)
-    stmt = TREE_OPERAND (stmt, 1);
+  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
+    stmt = GIMPLE_STMT_OPERAND (stmt, 1);
 
   first = single_succ (ENTRY_BLOCK_PTR);
 
@@ -788,9 +788,9 @@ eliminate_tail_call (struct tailcall *t)
   adjust_accumulator_values (t->call_bsi, t->mult, t->add, e);
 
   call = bsi_stmt (t->call_bsi);
-  if (TREE_CODE (call) == MODIFY_EXPR)
+  if (TREE_CODE (call) == GIMPLE_MODIFY_STMT)
     {
-      rslt = TREE_OPERAND (call, 0);
+      rslt = GIMPLE_STMT_OPERAND (call, 0);
 
       /* Result of the call will no longer be defined.  So adjust the
 	 SSA_NAME_DEF_STMT accordingly.  */
diff --git a/gcc/tree-vect-analyze.c b/gcc/tree-vect-analyze.c
index 89555151387cbcf818d3abe188d24855aa334837..31895733534266077f7b6ccbf4e57216f577300d 100644
--- a/gcc/tree-vect-analyze.c
+++ b/gcc/tree-vect-analyze.c
@@ -130,7 +130,8 @@ vect_determine_vectorization_factor (loop_vec_info loop_vinfo)
               continue;
             }
 
-          if (VECTOR_MODE_P (TYPE_MODE (TREE_TYPE (stmt))))
+          if (!GIMPLE_STMT_P (stmt)
+	      && VECTOR_MODE_P (TYPE_MODE (TREE_TYPE (stmt))))
             {
               if (vect_print_dump_info (REPORT_UNVECTORIZED_LOOPS))
                 {
@@ -150,8 +151,8 @@ vect_determine_vectorization_factor (loop_vec_info loop_vinfo)
 	      if (STMT_VINFO_DATA_REF (stmt_info))
 		scalar_type = 
 			TREE_TYPE (DR_REF (STMT_VINFO_DATA_REF (stmt_info)));
-	      else if (TREE_CODE (stmt) == MODIFY_EXPR)
-		scalar_type = TREE_TYPE (TREE_OPERAND (stmt, 0));
+	      else if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
+		scalar_type = TREE_TYPE (GIMPLE_STMT_OPERAND (stmt, 0));
 	      else
 		scalar_type = TREE_TYPE (stmt);
 
@@ -293,7 +294,8 @@ vect_analyze_operations (loop_vec_info loop_vinfo)
 
           if (STMT_VINFO_RELEVANT_P (stmt_info))
             {
-              gcc_assert (!VECTOR_MODE_P (TYPE_MODE (TREE_TYPE (stmt))));
+              gcc_assert (GIMPLE_STMT_P (stmt)
+		  	  || !VECTOR_MODE_P (TYPE_MODE (TREE_TYPE (stmt))));
               gcc_assert (STMT_VINFO_VECTYPE (stmt_info));
 
 	      ok = (vectorizable_type_promotion (stmt, NULL, NULL)
@@ -429,10 +431,10 @@ exist_non_indexing_operands_for_use_p (tree use, tree stmt)
      Therefore, all we need to check is if STMT falls into the
      first case, and whether var corresponds to USE.  */
  
-  if (TREE_CODE (TREE_OPERAND (stmt, 0)) == SSA_NAME)
+  if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) == SSA_NAME)
     return false;
 
-  operand = TREE_OPERAND (stmt, 1);
+  operand = GIMPLE_STMT_OPERAND (stmt, 1);
 
   if (TREE_CODE (operand) != SSA_NAME)
     return false;
diff --git a/gcc/tree-vect-generic.c b/gcc/tree-vect-generic.c
index 840c4abd33c6ac5fb1ec55686424041051f5340c..fb310f23ed63f705c72c322fcf17bf6808314818 100644
--- a/gcc/tree-vect-generic.c
+++ b/gcc/tree-vect-generic.c
@@ -380,14 +380,14 @@ expand_vector_operations_1 (block_stmt_iterator *bsi)
     {
     case RETURN_EXPR:
       stmt = TREE_OPERAND (stmt, 0);
-      if (!stmt || TREE_CODE (stmt) != MODIFY_EXPR)
+      if (!stmt || TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
 	return;
 
       /* FALLTHRU */
 
-    case MODIFY_EXPR:
-      p_lhs = &TREE_OPERAND (stmt, 0);
-      p_rhs = &TREE_OPERAND (stmt, 1);
+    case GIMPLE_MODIFY_STMT:
+      p_lhs = &GIMPLE_STMT_OPERAND (stmt, 0);
+      p_rhs = &GIMPLE_STMT_OPERAND (stmt, 1);
       lhs = *p_lhs;
       rhs = *p_rhs;
       break;
diff --git a/gcc/tree-vect-patterns.c b/gcc/tree-vect-patterns.c
index 6d5d3dcf35c40426fdc56d224e02b5431b61b1af..cb5d4e72d2a5732a99597ea63412f09cea7c2ed8 100644
--- a/gcc/tree-vect-patterns.c
+++ b/gcc/tree-vect-patterns.c
@@ -91,10 +91,10 @@ widened_name_p (tree name, tree use_stmt, tree *half_type, tree *def_stmt)
   if (! *def_stmt)
     return false;
 
-  if (TREE_CODE (*def_stmt) != MODIFY_EXPR)
+  if (TREE_CODE (*def_stmt) != GIMPLE_MODIFY_STMT)
     return false;
 
-  expr = TREE_OPERAND (*def_stmt, 1);
+  expr = GIMPLE_STMT_OPERAND (*def_stmt, 1);
   if (TREE_CODE (expr) != NOP_EXPR)
     return false;
 
@@ -166,10 +166,10 @@ vect_recog_dot_prod_pattern (tree last_stmt, tree *type_in, tree *type_out)
   tree pattern_expr;
   tree prod_type;
 
-  if (TREE_CODE (last_stmt) != MODIFY_EXPR)
+  if (TREE_CODE (last_stmt) != GIMPLE_MODIFY_STMT)
     return NULL;
 
-  expr = TREE_OPERAND (last_stmt, 1);
+  expr = GIMPLE_STMT_OPERAND (last_stmt, 1);
   type = TREE_TYPE (expr);
 
   /* Look for the following pattern 
@@ -228,7 +228,7 @@ vect_recog_dot_prod_pattern (tree last_stmt, tree *type_in, tree *type_out)
       if (widened_name_p (oprnd0, stmt, &half_type, &def_stmt))
         {
           stmt = def_stmt;
-          expr = TREE_OPERAND (stmt, 1);
+          expr = GIMPLE_STMT_OPERAND (stmt, 1);
           oprnd0 = TREE_OPERAND (expr, 0);
         }
       else
@@ -247,7 +247,7 @@ vect_recog_dot_prod_pattern (tree last_stmt, tree *type_in, tree *type_out)
   gcc_assert (stmt_vinfo);
   if (STMT_VINFO_DEF_TYPE (stmt_vinfo) != vect_loop_def)
     return NULL;
-  expr = TREE_OPERAND (stmt, 1);
+  expr = GIMPLE_STMT_OPERAND (stmt, 1);
   if (TREE_CODE (expr) != MULT_EXPR)
     return NULL;
   if (STMT_VINFO_IN_PATTERN_P (stmt_vinfo))
@@ -255,7 +255,7 @@ vect_recog_dot_prod_pattern (tree last_stmt, tree *type_in, tree *type_out)
       /* Has been detected as a widening multiplication?  */
 
       stmt = STMT_VINFO_RELATED_STMT (stmt_vinfo);
-      expr = TREE_OPERAND (stmt, 1);
+      expr = GIMPLE_STMT_OPERAND (stmt, 1);
       if (TREE_CODE (expr) != WIDEN_MULT_EXPR)
         return NULL;
       stmt_vinfo = vinfo_for_stmt (stmt);
@@ -279,10 +279,10 @@ vect_recog_dot_prod_pattern (tree last_stmt, tree *type_in, tree *type_out)
         return NULL;
       if (!widened_name_p (oprnd0, stmt, &half_type0, &def_stmt))
         return NULL;
-      oprnd00 = TREE_OPERAND (TREE_OPERAND (def_stmt, 1), 0);
+      oprnd00 = TREE_OPERAND (GIMPLE_STMT_OPERAND (def_stmt, 1), 0);
       if (!widened_name_p (oprnd1, stmt, &half_type1, &def_stmt))
         return NULL;
-      oprnd01 = TREE_OPERAND (TREE_OPERAND (def_stmt, 1), 0);
+      oprnd01 = TREE_OPERAND (GIMPLE_STMT_OPERAND (def_stmt, 1), 0);
       if (TYPE_MAIN_VARIANT (half_type0) != TYPE_MAIN_VARIANT (half_type1))
         return NULL;
       if (TYPE_PRECISION (prod_type) != TYPE_PRECISION (half_type0) * 2)
@@ -349,10 +349,10 @@ vect_recog_widen_mult_pattern (tree last_stmt,
   tree dummy;
   enum tree_code dummy_code;
 
-  if (TREE_CODE (last_stmt) != MODIFY_EXPR)
+  if (TREE_CODE (last_stmt) != GIMPLE_MODIFY_STMT)
     return NULL;
 
-  expr = TREE_OPERAND (last_stmt, 1);
+  expr = GIMPLE_STMT_OPERAND (last_stmt, 1);
   type = TREE_TYPE (expr);
 
   /* Starting from LAST_STMT, follow the defs of its uses in search
@@ -370,12 +370,12 @@ vect_recog_widen_mult_pattern (tree last_stmt,
   /* Check argument 0 */
   if (!widened_name_p (oprnd0, last_stmt, &half_type0, &def_stmt0))
     return NULL;
-  oprnd0 = TREE_OPERAND (TREE_OPERAND (def_stmt0, 1), 0);
+  oprnd0 = TREE_OPERAND (GIMPLE_STMT_OPERAND (def_stmt0, 1), 0);
 
   /* Check argument 1 */
   if (!widened_name_p (oprnd1, last_stmt, &half_type1, &def_stmt1))
     return NULL;
-  oprnd1 = TREE_OPERAND (TREE_OPERAND (def_stmt1, 1), 0);
+  oprnd1 = TREE_OPERAND (GIMPLE_STMT_OPERAND (def_stmt1, 1), 0);
 
   if (TYPE_MAIN_VARIANT (half_type0) != TYPE_MAIN_VARIANT (half_type1))
     return NULL;
@@ -435,10 +435,10 @@ vect_recog_pow_pattern (tree last_stmt, tree *type_in, tree *type_out)
   tree type;
   tree fn, arglist, base, exp;
 
-  if (TREE_CODE (last_stmt) != MODIFY_EXPR)
+  if (TREE_CODE (last_stmt) != GIMPLE_MODIFY_STMT)
     return NULL;
 
-  expr = TREE_OPERAND (last_stmt, 1);
+  expr = GIMPLE_STMT_OPERAND (last_stmt, 1);
   type = TREE_TYPE (expr);
 
   if (TREE_CODE (expr) != CALL_EXPR)
@@ -538,10 +538,10 @@ vect_recog_widen_sum_pattern (tree last_stmt, tree *type_in, tree *type_out)
   tree type, half_type;
   tree pattern_expr;
 
-  if (TREE_CODE (last_stmt) != MODIFY_EXPR)
+  if (TREE_CODE (last_stmt) != GIMPLE_MODIFY_STMT)
     return NULL;
 
-  expr = TREE_OPERAND (last_stmt, 1);
+  expr = GIMPLE_STMT_OPERAND (last_stmt, 1);
   type = TREE_TYPE (expr);
 
   /* Look for the following pattern
@@ -575,7 +575,7 @@ vect_recog_widen_sum_pattern (tree last_stmt, tree *type_in, tree *type_out)
   if (!widened_name_p (oprnd0, last_stmt, &half_type, &stmt))
     return NULL;
 
-  oprnd0 = TREE_OPERAND (TREE_OPERAND (stmt, 1), 0);
+  oprnd0 = TREE_OPERAND (GIMPLE_STMT_OPERAND (stmt, 1), 0);
   *type_in = half_type;
   *type_out = type;
 
@@ -672,7 +672,8 @@ vect_pattern_recog_1 (
   var = create_tmp_var (pattern_type, "patt");
   add_referenced_var (var);
   var_name = make_ssa_name (var, NULL_TREE);
-  pattern_expr = build2 (MODIFY_EXPR, void_type_node, var_name, pattern_expr);
+  pattern_expr = build2 (GIMPLE_MODIFY_STMT, void_type_node, var_name,
+      			 pattern_expr);
   SSA_NAME_DEF_STMT (var_name) = pattern_expr;
   bsi_insert_before (&si, pattern_expr, BSI_SAME_STMT);
   ann = stmt_ann (pattern_expr);
diff --git a/gcc/tree-vect-transform.c b/gcc/tree-vect-transform.c
index 896e723d0589e42c6c588394bfa96f976bcefbe1..213ced9ddc9a514dd9555b843e2a0a63e72283e5 100644
--- a/gcc/tree-vect-transform.c
+++ b/gcc/tree-vect-transform.c
@@ -210,7 +210,8 @@ vect_create_addr_base_for_vector_ref (tree stmt,
 
    Input:
    1. STMT: a stmt that references memory. Expected to be of the form
-         MODIFY_EXPR <name, data-ref> or MODIFY_EXPR <data-ref, name>.
+         GIMPLE_MODIFY_STMT <name, data-ref> or
+	 GIMPLE_MODIFY_STMT <data-ref, name>.
    2. BSI: block_stmt_iterator where new stmts can be added.
    3. OFFSET (optional): an offset to be added to the initial address accessed
         by the data-ref in STMT.
@@ -317,9 +318,9 @@ vect_create_data_ref_ptr (tree stmt,
 
   /* Create: p = (vectype *) initial_base  */
   vec_stmt = fold_convert (vect_ptr_type, new_temp);
-  vec_stmt = build2 (MODIFY_EXPR, void_type_node, vect_ptr, vec_stmt);
+  vec_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, vect_ptr, vec_stmt);
   vect_ptr_init = make_ssa_name (vect_ptr, vec_stmt);
-  TREE_OPERAND (vec_stmt, 0) = vect_ptr_init;
+  GIMPLE_STMT_OPERAND (vec_stmt, 0) = vect_ptr_init;
   new_bb = bsi_insert_on_edge_immediate (pe, vec_stmt);
   gcc_assert (!new_bb);
 
@@ -410,10 +411,10 @@ bump_vector_ptr (tree dataref_ptr, tree ptr_incr, block_stmt_iterator *bsi,
   use_operand_p use_p;
   tree new_dataref_ptr;
 
-  incr_stmt = build2 (MODIFY_EXPR, void_type_node, ptr_var,
+  incr_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, ptr_var,
                 build2 (PLUS_EXPR, vptr_type, dataref_ptr, update));
   new_dataref_ptr = make_ssa_name (ptr_var, incr_stmt);
-  TREE_OPERAND (incr_stmt, 0) = new_dataref_ptr;
+  GIMPLE_STMT_OPERAND (incr_stmt, 0) = new_dataref_ptr;
   vect_finish_stmt_generation (stmt, incr_stmt, bsi);
 
   /* Update the vector-pointer's cross-iteration increment.  */
@@ -485,9 +486,9 @@ vect_init_vector (tree stmt, tree vector_var, tree vector_type)
   new_var = vect_get_new_vect_var (vector_type, vect_simple_var, "cst_");
   add_referenced_var (new_var); 
  
-  init_stmt = build2 (MODIFY_EXPR, void_type_node, new_var, vector_var);
+  init_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, new_var, vector_var);
   new_temp = make_ssa_name (new_var, init_stmt);
-  TREE_OPERAND (init_stmt, 0) = new_temp;
+  GIMPLE_STMT_OPERAND (init_stmt, 0) = new_temp;
 
   pe = loop_preheader_edge (loop);
   new_bb = bsi_insert_on_edge_immediate (pe, init_stmt);
@@ -499,7 +500,7 @@ vect_init_vector (tree stmt, tree vector_var, tree vector_type)
       print_generic_expr (vect_dump, init_stmt, TDF_SLIM);
     }
 
-  vec_oprnd = TREE_OPERAND (init_stmt, 0);
+  vec_oprnd = GIMPLE_STMT_OPERAND (init_stmt, 0);
   return vec_oprnd;
 }
 
@@ -611,7 +612,7 @@ vect_get_vec_def_for_operand (tree op, tree stmt, tree *scalar_def)
         def_stmt_info = vinfo_for_stmt (def_stmt);
         vec_stmt = STMT_VINFO_VEC_STMT (def_stmt_info);
         gcc_assert (vec_stmt);
-        vec_oprnd = TREE_OPERAND (vec_stmt, 0);
+        vec_oprnd = GIMPLE_STMT_OPERAND (vec_stmt, 0);
         return vec_oprnd;
       }
 
@@ -712,7 +713,7 @@ vect_get_vec_def_for_stmt_copy (enum vect_def_type dt, tree vec_oprnd)
   gcc_assert (def_stmt_info);
   vec_stmt_for_operand = STMT_VINFO_RELATED_STMT (def_stmt_info);
   gcc_assert (vec_stmt_for_operand);
-  vec_oprnd = TREE_OPERAND (vec_stmt_for_operand, 0);
+  vec_oprnd = GIMPLE_STMT_OPERAND (vec_stmt_for_operand, 0);
 
   return vec_oprnd;
 }
@@ -802,7 +803,7 @@ get_initial_def_for_reduction (tree stmt, tree init_val, tree *scalar_def)
   tree vectype = STMT_VINFO_VECTYPE (stmt_vinfo);
   int nunits = GET_MODE_NUNITS (TYPE_MODE (vectype));
   int nelements;
-  enum tree_code code = TREE_CODE (TREE_OPERAND (stmt, 1));
+  enum tree_code code = TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1));
   tree type = TREE_TYPE (init_val);
   tree def;
   tree vec, t = NULL_TREE;
@@ -940,7 +941,7 @@ vect_create_epilog_for_reduction (tree vect_def, tree stmt,
   tree epilog_stmt;
   tree new_scalar_dest, exit_phi;
   tree bitsize, bitpos, bytesize; 
-  enum tree_code code = TREE_CODE (TREE_OPERAND (stmt, 1));
+  enum tree_code code = TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1));
   tree scalar_initial_def;
   tree vec_initial_def;
   tree orig_name;
@@ -950,7 +951,7 @@ vect_create_epilog_for_reduction (tree vect_def, tree stmt,
   tree reduction_op;
   tree orig_stmt;
   tree use_stmt;
-  tree operation = TREE_OPERAND (stmt, 1);
+  tree operation = GIMPLE_STMT_OPERAND (stmt, 1);
   int op_type;
   
   op_type = TREE_CODE_LENGTH (TREE_CODE (operation));
@@ -1037,8 +1038,8 @@ vect_create_epilog_for_reduction (tree vect_def, tree stmt,
       gcc_assert (STMT_VINFO_IN_PATTERN_P (stmt_vinfo));
       gcc_assert (STMT_VINFO_RELATED_STMT (stmt_vinfo) == stmt);
     }
-  code = TREE_CODE (TREE_OPERAND (orig_stmt, 1));
-  scalar_dest = TREE_OPERAND (orig_stmt, 0);
+  code = TREE_CODE (GIMPLE_STMT_OPERAND (orig_stmt, 1));
+  scalar_dest = GIMPLE_STMT_OPERAND (orig_stmt, 0);
   scalar_type = TREE_TYPE (scalar_dest);
   new_scalar_dest = vect_create_destination_var (scalar_dest, NULL);
   bitsize = TYPE_SIZE (scalar_type);
@@ -1056,10 +1057,10 @@ vect_create_epilog_for_reduction (tree vect_def, tree stmt,
 	fprintf (vect_dump, "Reduce using direct vector reduction.");
 
       vec_dest = vect_create_destination_var (scalar_dest, vectype);
-      epilog_stmt = build2 (MODIFY_EXPR, void_type_node, vec_dest,
+      epilog_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, vec_dest,
 			build1 (reduc_code, vectype,  PHI_RESULT (new_phi)));
       new_temp = make_ssa_name (vec_dest, epilog_stmt);
-      TREE_OPERAND (epilog_stmt, 0) = new_temp;
+      GIMPLE_STMT_OPERAND (epilog_stmt, 0) = new_temp;
       bsi_insert_after (&exit_bsi, epilog_stmt, BSI_NEW_STMT);
 
       extract_scalar_result = true;
@@ -1114,18 +1115,20 @@ vect_create_epilog_for_reduction (tree vect_def, tree stmt,
 	    {
 	      tree bitpos = size_int (bit_offset);
 
-	      epilog_stmt = build2 (MODIFY_EXPR, void_type_node, vec_dest,
+	      epilog_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node,
+		  		    vec_dest,
 				    build2 (shift_code, vectype,
 					    new_temp, bitpos));
 	      new_name = make_ssa_name (vec_dest, epilog_stmt);
-	      TREE_OPERAND (epilog_stmt, 0) = new_name;
+	      GIMPLE_STMT_OPERAND (epilog_stmt, 0) = new_name;
 	      bsi_insert_after (&exit_bsi, epilog_stmt, BSI_NEW_STMT);
 
-	      epilog_stmt = build2 (MODIFY_EXPR, void_type_node, vec_dest,
+	      epilog_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node,
+		  		    vec_dest,
 				    build2 (code, vectype,
 					    new_name, new_temp));
 	      new_temp = make_ssa_name (vec_dest, epilog_stmt);
-	      TREE_OPERAND (epilog_stmt, 0) = new_temp;
+	      GIMPLE_STMT_OPERAND (epilog_stmt, 0) = new_temp;
 	      bsi_insert_after (&exit_bsi, epilog_stmt, BSI_NEW_STMT);
 	    }
 
@@ -1153,9 +1156,10 @@ vect_create_epilog_for_reduction (tree vect_def, tree stmt,
 	  rhs = build3 (BIT_FIELD_REF, scalar_type, vec_temp, bitsize,
 			 bitsize_zero_node);
 	  BIT_FIELD_REF_UNSIGNED (rhs) = TYPE_UNSIGNED (scalar_type);
-	  epilog_stmt = build2 (MODIFY_EXPR, void_type_node, new_scalar_dest, rhs);
+	  epilog_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node,
+	      			new_scalar_dest, rhs);
 	  new_temp = make_ssa_name (new_scalar_dest, epilog_stmt);
-	  TREE_OPERAND (epilog_stmt, 0) = new_temp;
+	  GIMPLE_STMT_OPERAND (epilog_stmt, 0) = new_temp;
 	  bsi_insert_after (&exit_bsi, epilog_stmt, BSI_NEW_STMT);
 	      
 	  for (bit_offset = element_bitsize;
@@ -1167,16 +1171,17 @@ vect_create_epilog_for_reduction (tree vect_def, tree stmt,
 				 bitpos);
 		
 	      BIT_FIELD_REF_UNSIGNED (rhs) = TYPE_UNSIGNED (scalar_type);
-	      epilog_stmt = build2 (MODIFY_EXPR, void_type_node, new_scalar_dest,
-				    rhs);	
+	      epilog_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node,
+		  		    new_scalar_dest, rhs);	
 	      new_name = make_ssa_name (new_scalar_dest, epilog_stmt);
-	      TREE_OPERAND (epilog_stmt, 0) = new_name;
+	      GIMPLE_STMT_OPERAND (epilog_stmt, 0) = new_name;
 	      bsi_insert_after (&exit_bsi, epilog_stmt, BSI_NEW_STMT);
 
-	      epilog_stmt = build2 (MODIFY_EXPR, void_type_node, new_scalar_dest,
+	      epilog_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node,
+		  		new_scalar_dest,
 				build2 (code, scalar_type, new_name, new_temp));
 	      new_temp = make_ssa_name (new_scalar_dest, epilog_stmt);
-	      TREE_OPERAND (epilog_stmt, 0) = new_temp;
+	      GIMPLE_STMT_OPERAND (epilog_stmt, 0) = new_temp;
 	      bsi_insert_after (&exit_bsi, epilog_stmt, BSI_NEW_STMT);
 	    }
 
@@ -1203,9 +1208,10 @@ vect_create_epilog_for_reduction (tree vect_def, tree stmt,
 
       rhs = build3 (BIT_FIELD_REF, scalar_type, new_temp, bitsize, bitpos);
       BIT_FIELD_REF_UNSIGNED (rhs) = TYPE_UNSIGNED (scalar_type);
-      epilog_stmt = build2 (MODIFY_EXPR, void_type_node, new_scalar_dest, rhs);
+      epilog_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node,
+	  		    new_scalar_dest, rhs);
       new_temp = make_ssa_name (new_scalar_dest, epilog_stmt);
-      TREE_OPERAND (epilog_stmt, 0) = new_temp; 
+      GIMPLE_STMT_OPERAND (epilog_stmt, 0) = new_temp; 
       bsi_insert_after (&exit_bsi, epilog_stmt, BSI_NEW_STMT);
     }
 
@@ -1218,10 +1224,11 @@ vect_create_epilog_for_reduction (tree vect_def, tree stmt,
   
   if (scalar_initial_def)
     {
-      epilog_stmt = build2 (MODIFY_EXPR, void_type_node, new_scalar_dest,
+      epilog_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node,
+	  	      new_scalar_dest,
                       build2 (code, scalar_type, new_temp, scalar_initial_def));
       new_temp = make_ssa_name (new_scalar_dest, epilog_stmt);
-      TREE_OPERAND (epilog_stmt, 0) = new_temp;
+      GIMPLE_STMT_OPERAND (epilog_stmt, 0) = new_temp;
       bsi_insert_after (&exit_bsi, epilog_stmt, BSI_NEW_STMT);
     }
 
@@ -1357,14 +1364,14 @@ vectorizable_reduction (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
         inside the loop body. The last operand is the reduction variable,
         which is defined by the loop-header-phi.  */
 
-  gcc_assert (TREE_CODE (stmt) == MODIFY_EXPR);
+  gcc_assert (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT);
 
-  operation = TREE_OPERAND (stmt, 1);
+  operation = GIMPLE_STMT_OPERAND (stmt, 1);
   code = TREE_CODE (operation);
   op_type = TREE_CODE_LENGTH (code);
   if (op_type != binary_op && op_type != ternary_op)
     return false;
-  scalar_dest = TREE_OPERAND (stmt, 0);
+  scalar_dest = GIMPLE_STMT_OPERAND (stmt, 0);
   scalar_type = TREE_TYPE (scalar_dest);
 
   /* All uses but the last are expected to be defined in the loop.
@@ -1462,7 +1469,7 @@ vectorizable_reduction (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
     {
       /* This is a reduction pattern: get the vectype from the type of the
          reduction variable, and get the tree-code from orig_stmt.  */
-      orig_code = TREE_CODE (TREE_OPERAND (orig_stmt, 1));
+      orig_code = TREE_CODE (GIMPLE_STMT_OPERAND (orig_stmt, 1));
       vectype = get_vectype_for_scalar_type (TREE_TYPE (def));
       vec_mode = TYPE_MODE (vectype);
     }
@@ -1538,7 +1545,7 @@ vectorizable_reduction (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
                                                                                 
           /* Get the vector def for the reduction variable from the vectorized
              reduction operation generated in the previous iteration (j-1)  */
-          reduc_def = TREE_OPERAND (new_stmt ,0);
+          reduc_def = GIMPLE_STMT_OPERAND (new_stmt ,0);
         }
                                                                                 
       /* Arguments are ready. create the new vector stmt.  */
@@ -1548,9 +1555,9 @@ vectorizable_reduction (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
       else
         expr = build3 (code, vectype, loop_vec_def0, loop_vec_def1, 
 								reduc_def);
-      new_stmt = build2 (MODIFY_EXPR, void_type_node, vec_dest, expr);
+      new_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, vec_dest, expr);
       new_temp = make_ssa_name (vec_dest, new_stmt);
-      TREE_OPERAND (new_stmt, 0) = new_temp;
+      GIMPLE_STMT_OPERAND (new_stmt, 0) = new_temp;
       vect_finish_stmt_generation (stmt, new_stmt, bsi);
                                                                                 
       if (j == 0)
@@ -1632,13 +1639,13 @@ vectorizable_call (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
   enum vect_def_type dt;
 
   /* Is STMT a vectorizable call?   */
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
 
-  if (TREE_CODE (TREE_OPERAND (stmt, 0)) != SSA_NAME)
+  if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) != SSA_NAME)
     return false;
 
-  operation = TREE_OPERAND (stmt, 1);
+  operation = GIMPLE_STMT_OPERAND (stmt, 1);
   if (TREE_CODE (operation) != CALL_EXPR)
     return false;
    
@@ -1679,7 +1686,7 @@ vectorizable_call (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
     fprintf (vect_dump, "transform operation.");
 
   /* Handle def.  */
-  scalar_dest = TREE_OPERAND (stmt, 0);
+  scalar_dest = GIMPLE_STMT_OPERAND (stmt, 0);
   vec_dest = vect_create_destination_var (scalar_dest, vectype);
 
   /* Handle uses.  */
@@ -1696,9 +1703,9 @@ vectorizable_call (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
 
   fndecl = get_callee_fndecl (operation);
   rhs = build_vectorized_function_call (fndecl, vectype, vargs);
-  *vec_stmt = build2 (MODIFY_EXPR, vectype, vec_dest, rhs);
+  *vec_stmt = build2 (GIMPLE_MODIFY_STMT, vectype, vec_dest, rhs);
   new_temp = make_ssa_name (vec_dest, *vec_stmt);
-  TREE_OPERAND (*vec_stmt, 0) = new_temp;
+  GIMPLE_STMT_OPERAND (*vec_stmt, 0) = new_temp;
 
   vect_finish_stmt_generation (stmt, *vec_stmt, bsi);
 
@@ -1746,14 +1753,14 @@ vectorizable_assignment (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
 
   gcc_assert (STMT_VINFO_DEF_TYPE (stmt_info) == vect_loop_def);
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
 
-  scalar_dest = TREE_OPERAND (stmt, 0);
+  scalar_dest = GIMPLE_STMT_OPERAND (stmt, 0);
   if (TREE_CODE (scalar_dest) != SSA_NAME)
     return false;
 
-  op = TREE_OPERAND (stmt, 1);
+  op = GIMPLE_STMT_OPERAND (stmt, 1);
   if (!vect_is_simple_use (op, loop_vinfo, &def_stmt, &def, &dt))
     {
       if (vect_print_dump_info (REPORT_DETAILS))
@@ -1775,13 +1782,13 @@ vectorizable_assignment (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
   vec_dest = vect_create_destination_var (scalar_dest, vectype);
 
   /* Handle use.  */
-  op = TREE_OPERAND (stmt, 1);
+  op = GIMPLE_STMT_OPERAND (stmt, 1);
   vec_oprnd = vect_get_vec_def_for_operand (op, stmt, NULL);
 
   /* Arguments are ready. create the new vector stmt.  */
-  *vec_stmt = build2 (MODIFY_EXPR, void_type_node, vec_dest, vec_oprnd);
+  *vec_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, vec_dest, vec_oprnd);
   new_temp = make_ssa_name (vec_dest, *vec_stmt);
-  TREE_OPERAND (*vec_stmt, 0) = new_temp;
+  GIMPLE_STMT_OPERAND (*vec_stmt, 0) = new_temp;
   vect_finish_stmt_generation (stmt, *vec_stmt, bsi);
   
   return true;
@@ -1866,19 +1873,19 @@ vectorizable_operation (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
       return false;
     }
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
 
-  if (TREE_CODE (TREE_OPERAND (stmt, 0)) != SSA_NAME)
+  if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) != SSA_NAME)
     return false;
 
-  scalar_dest = TREE_OPERAND (stmt, 0);
+  scalar_dest = GIMPLE_STMT_OPERAND (stmt, 0);
   vectype_out = get_vectype_for_scalar_type (TREE_TYPE (scalar_dest));
   nunits_out = TYPE_VECTOR_SUBPARTS (vectype_out);
   if (nunits_out != nunits_in)
     return false;
 
-  operation = TREE_OPERAND (stmt, 1);
+  operation = GIMPLE_STMT_OPERAND (stmt, 1);
   code = TREE_CODE (operation);
   optab = optab_for_tree_code (code, vectype);
 
@@ -2064,13 +2071,13 @@ vectorizable_operation (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
       /* Arguments are ready. create the new vector stmt.  */
                                                                                 
       if (op_type == binary_op)
-        new_stmt = build2 (MODIFY_EXPR, void_type_node, vec_dest,
+        new_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, vec_dest,
                     build2 (code, vectype, vec_oprnd0, vec_oprnd1));
       else
-        new_stmt = build2 (MODIFY_EXPR, void_type_node, vec_dest,
+        new_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, vec_dest,
                     build1 (code, vectype, vec_oprnd0));
       new_temp = make_ssa_name (vec_dest, new_stmt);
-      TREE_OPERAND (new_stmt, 0) = new_temp;
+      GIMPLE_STMT_OPERAND (new_stmt, 0) = new_temp;
       vect_finish_stmt_generation (stmt, new_stmt, bsi);
                                                                                 
       if (j == 0)
@@ -2135,13 +2142,13 @@ vectorizable_type_demotion (tree stmt, block_stmt_iterator *bsi,
       return false;
     }
                                                                                 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
                                                                                 
-  if (TREE_CODE (TREE_OPERAND (stmt, 0)) != SSA_NAME)
+  if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) != SSA_NAME)
     return false;
                                                                                 
-  operation = TREE_OPERAND (stmt, 1);
+  operation = GIMPLE_STMT_OPERAND (stmt, 1);
   code = TREE_CODE (operation);
   if (code != NOP_EXPR && code != CONVERT_EXPR)
     return false;
@@ -2150,7 +2157,7 @@ vectorizable_type_demotion (tree stmt, block_stmt_iterator *bsi,
   vectype_in = get_vectype_for_scalar_type (TREE_TYPE (op0));
   nunits_in = TYPE_VECTOR_SUBPARTS (vectype_in);
                                                                                 
-  scalar_dest = TREE_OPERAND (stmt, 0);
+  scalar_dest = GIMPLE_STMT_OPERAND (stmt, 0);
   scalar_type = TREE_TYPE (scalar_dest);
   vectype_out = get_vectype_for_scalar_type (scalar_type);
   nunits_out = TYPE_VECTOR_SUBPARTS (vectype_out);
@@ -2217,9 +2224,9 @@ vectorizable_type_demotion (tree stmt, block_stmt_iterator *bsi,
                                                                                 
       /* Arguments are ready. Create the new vector stmt.  */
       expr = build2 (code, vectype_out, vec_oprnd0, vec_oprnd1);
-      new_stmt = build2 (MODIFY_EXPR, void_type_node, vec_dest, expr);
+      new_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, vec_dest, expr);
       new_temp = make_ssa_name (vec_dest, new_stmt);
-      TREE_OPERAND (new_stmt, 0) = new_temp;
+      GIMPLE_STMT_OPERAND (new_stmt, 0) = new_temp;
       vect_finish_stmt_generation (stmt, new_stmt, bsi);
                                                                                 
       if (j == 0)
@@ -2275,9 +2282,9 @@ vect_gen_widened_results_half (enum tree_code code, tree vectype, tree decl,
       else  
         expr = build1 (code, vectype, vec_oprnd0); 
     } 
-  new_stmt = build2 (MODIFY_EXPR, void_type_node, vec_dest, expr);
+  new_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, vec_dest, expr);
   new_temp = make_ssa_name (vec_dest, new_stmt); 
-  TREE_OPERAND (new_stmt, 0) = new_temp; 
+  GIMPLE_STMT_OPERAND (new_stmt, 0) = new_temp; 
   vect_finish_stmt_generation (stmt, new_stmt, bsi); 
 
   if (code == CALL_EXPR)
@@ -2342,13 +2349,13 @@ vectorizable_type_promotion (tree stmt, block_stmt_iterator *bsi,
       return false;
     }
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
 
-  if (TREE_CODE (TREE_OPERAND (stmt, 0)) != SSA_NAME)
+  if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) != SSA_NAME)
     return false;
 
-  operation = TREE_OPERAND (stmt, 1);
+  operation = GIMPLE_STMT_OPERAND (stmt, 1);
   code = TREE_CODE (operation);
   if (code != NOP_EXPR && code != WIDEN_MULT_EXPR)
     return false;
@@ -2359,7 +2366,7 @@ vectorizable_type_promotion (tree stmt, block_stmt_iterator *bsi,
   ncopies = LOOP_VINFO_VECT_FACTOR (loop_vinfo) / nunits_in;
   gcc_assert (ncopies >= 1);
 
-  scalar_dest = TREE_OPERAND (stmt, 0);
+  scalar_dest = GIMPLE_STMT_OPERAND (stmt, 0);
   vectype_out = get_vectype_for_scalar_type (TREE_TYPE (scalar_dest));
   nunits_out = TYPE_VECTOR_SUBPARTS (vectype_out);
   if (nunits_out != nunits_in / 2) /* FORNOW */
@@ -2588,22 +2595,22 @@ vect_permute_store_chain (VEC(tree,heap) *dr_chain,
 	  /* high = interleave_high (vect1, vect2);  */
 	  perm_dest = create_tmp_var (vectype, "vect_inter_high");
 	  add_referenced_var (perm_dest);
-	  perm_stmt = build2 (MODIFY_EXPR, void_type_node, perm_dest,
+	  perm_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, perm_dest,
 			      build2 (VEC_INTERLEAVE_HIGH_EXPR, vectype, vect1, 
 				      vect2));
 	  high = make_ssa_name (perm_dest, perm_stmt);
-	  TREE_OPERAND (perm_stmt, 0) = high;
+	  GIMPLE_STMT_OPERAND (perm_stmt, 0) = high;
 	  vect_finish_stmt_generation (stmt, perm_stmt, bsi);
 	  VEC_replace (tree, *result_chain, 2*j, high);
 
 	  /* low = interleave_low (vect1, vect2);  */
 	  perm_dest = create_tmp_var (vectype, "vect_inter_low");
 	  add_referenced_var (perm_dest);
-	  perm_stmt = build2 (MODIFY_EXPR, void_type_node, perm_dest,
+	  perm_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, perm_dest,
 			      build2 (VEC_INTERLEAVE_LOW_EXPR, vectype, vect1, 
 				      vect2));
 	  low = make_ssa_name (perm_dest, perm_stmt);
-	  TREE_OPERAND (perm_stmt, 0) = low;
+	  GIMPLE_STMT_OPERAND (perm_stmt, 0) = low;
 	  vect_finish_stmt_generation (stmt, perm_stmt, bsi);
 	  VEC_replace (tree, *result_chain, 2*j+1, low);
 	}
@@ -2652,16 +2659,16 @@ vectorizable_store (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
 
   /* Is vectorizable store? */
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
 
-  scalar_dest = TREE_OPERAND (stmt, 0);
+  scalar_dest = GIMPLE_STMT_OPERAND (stmt, 0);
   if (TREE_CODE (scalar_dest) != ARRAY_REF
       && TREE_CODE (scalar_dest) != INDIRECT_REF
       && !DR_GROUP_FIRST_DR (stmt_info))
     return false;
 
-  op = TREE_OPERAND (stmt, 1);
+  op = GIMPLE_STMT_OPERAND (stmt, 1);
   if (!vect_is_simple_use (op, loop_vinfo, &def_stmt, &def, &dt))
     {
       if (vect_print_dump_info (REPORT_DETAILS))
@@ -2791,7 +2798,7 @@ vectorizable_store (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
 		 executed.
 	      */
 	      gcc_assert (next_stmt);
-	      op = TREE_OPERAND (next_stmt, 1);
+	      op = GIMPLE_STMT_OPERAND (next_stmt, 1);
 	      vec_oprnd = vect_get_vec_def_for_operand (op, next_stmt, NULL);
 	      VEC_quick_push(tree, dr_chain, vec_oprnd); 
 	      VEC_quick_push(tree, oprnds, vec_oprnd); 
@@ -2840,7 +2847,7 @@ vectorizable_store (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
 
 	  data_ref = build_fold_indirect_ref (dataref_ptr);
 	  /* Arguments are ready. Create the new vector stmt.  */
-	  new_stmt = build2 (MODIFY_EXPR, void_type_node, data_ref, 
+	  new_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, data_ref, 
 			     vec_oprnd);
 	  vect_finish_stmt_generation (stmt, new_stmt, bsi);
 
@@ -2952,12 +2959,12 @@ vect_setup_realignment (tree stmt, block_stmt_iterator *bsi,
   ptr = vect_create_data_ref_ptr (stmt, bsi, NULL_TREE, &init_addr, &inc, true,
 				  NULL_TREE);
   data_ref = build1 (ALIGN_INDIRECT_REF, vectype, ptr);
-  new_stmt = build2 (MODIFY_EXPR, void_type_node, vec_dest, data_ref);
+  new_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, vec_dest, data_ref);
   new_temp = make_ssa_name (vec_dest, new_stmt);
-  TREE_OPERAND (new_stmt, 0) = new_temp;
+  GIMPLE_STMT_OPERAND (new_stmt, 0) = new_temp;
   new_bb = bsi_insert_on_edge_immediate (pe, new_stmt);
   gcc_assert (!new_bb);
-  msq_init = TREE_OPERAND (new_stmt, 0);
+  msq_init = GIMPLE_STMT_OPERAND (new_stmt, 0);
   copy_virtual_operands (new_stmt, stmt);
   update_vuses_to_preheader (new_stmt, loop);
 
@@ -2971,12 +2978,13 @@ vect_setup_realignment (tree stmt, block_stmt_iterator *bsi,
       new_stmt = build_function_call_expr (builtin_decl, params);
       vec_dest = vect_create_destination_var (scalar_dest, 
 					      TREE_TYPE (new_stmt));
-      new_stmt = build2 (MODIFY_EXPR, void_type_node, vec_dest, new_stmt);
+      new_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, vec_dest,
+	  		 new_stmt);
       new_temp = make_ssa_name (vec_dest, new_stmt);
-      TREE_OPERAND (new_stmt, 0) = new_temp;
+      GIMPLE_STMT_OPERAND (new_stmt, 0) = new_temp;
       new_bb = bsi_insert_on_edge_immediate (pe, new_stmt);
       gcc_assert (!new_bb);
-      *realignment_token = TREE_OPERAND (new_stmt, 0);
+      *realignment_token = GIMPLE_STMT_OPERAND (new_stmt, 0);
 
       /* The result of the CALL_EXPR to this builtin is determined from
          the value of the parameter and no global variables are touched
@@ -3147,12 +3155,12 @@ vect_permute_load_chain (VEC(tree,heap) *dr_chain,
 	  perm_dest = create_tmp_var (vectype, "vect_perm_even");
 	  add_referenced_var (perm_dest);
 	 
-	  perm_stmt = build2 (MODIFY_EXPR, void_type_node, perm_dest,
+	  perm_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, perm_dest,
 			      build2 (VEC_EXTRACT_EVEN_EXPR, vectype, 
 				      first_vect, second_vect));
 
 	  data_ref = make_ssa_name (perm_dest, perm_stmt);
-	  TREE_OPERAND (perm_stmt, 0) = data_ref;
+	  GIMPLE_STMT_OPERAND (perm_stmt, 0) = data_ref;
 	  vect_finish_stmt_generation (stmt, perm_stmt, bsi);
 	  mark_new_vars_to_rename (perm_stmt);
 
@@ -3162,11 +3170,11 @@ vect_permute_load_chain (VEC(tree,heap) *dr_chain,
 	  perm_dest = create_tmp_var (vectype, "vect_perm_odd");
 	  add_referenced_var (perm_dest);
 
-	  perm_stmt = build2 (MODIFY_EXPR, void_type_node, perm_dest,
+	  perm_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, perm_dest,
 			      build2 (VEC_EXTRACT_ODD_EXPR, vectype, 
 				      first_vect, second_vect));
 	  data_ref = make_ssa_name (perm_dest, perm_stmt);
-	  TREE_OPERAND (perm_stmt, 0) = data_ref;
+	  GIMPLE_STMT_OPERAND (perm_stmt, 0) = data_ref;
 	  vect_finish_stmt_generation (stmt, perm_stmt, bsi);
 	  mark_new_vars_to_rename (perm_stmt);
 
@@ -3312,14 +3320,14 @@ vectorizable_load (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
       return false;
     }
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
 
-  scalar_dest = TREE_OPERAND (stmt, 0);
+  scalar_dest = GIMPLE_STMT_OPERAND (stmt, 0);
   if (TREE_CODE (scalar_dest) != SSA_NAME)
     return false;
 
-  op = TREE_OPERAND (stmt, 1);
+  op = GIMPLE_STMT_OPERAND (stmt, 1);
   if (TREE_CODE (op) != ARRAY_REF 
       && TREE_CODE (op) != INDIRECT_REF
       && !DR_GROUP_FIRST_DR (stmt_info))
@@ -3526,9 +3534,10 @@ vectorizable_load (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
 	      gcc_unreachable ();
 	    }
 	  vec_dest = vect_create_destination_var (scalar_dest, vectype);
-	  new_stmt = build2 (MODIFY_EXPR, void_type_node, vec_dest, data_ref);
+	  new_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, vec_dest,
+	      		     data_ref);
 	  new_temp = make_ssa_name (vec_dest, new_stmt);
-	  TREE_OPERAND (new_stmt, 0) = new_temp;
+	  GIMPLE_STMT_OPERAND (new_stmt, 0) = new_temp;
 	  vect_finish_stmt_generation (stmt, new_stmt, bsi);
 	  copy_virtual_operands (new_stmt, stmt);
 	  mark_new_vars_to_rename (new_stmt);
@@ -3538,15 +3547,16 @@ vectorizable_load (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
 	    {
 	      /* Create in loop: 
 		 <vec_dest = realign_load (msq, lsq, realignment_token)>  */
-	      lsq = TREE_OPERAND (new_stmt, 0);
+	      lsq = GIMPLE_STMT_OPERAND (new_stmt, 0);
 	      if (!realignment_token)
 		realignment_token = dataref_ptr;
 	      vec_dest = vect_create_destination_var (scalar_dest, vectype);
 	      new_stmt =
 		build3 (REALIGN_LOAD_EXPR, vectype, msq, lsq, realignment_token);
-	      new_stmt = build2 (MODIFY_EXPR, void_type_node, vec_dest, new_stmt);
+	      new_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, vec_dest,
+		  		 new_stmt);
 	      new_temp = make_ssa_name (vec_dest, new_stmt);
-	      TREE_OPERAND (new_stmt, 0) = new_temp;
+	      GIMPLE_STMT_OPERAND (new_stmt, 0) = new_temp;
 	      vect_finish_stmt_generation (stmt, new_stmt, bsi);
 	      if (i == group_size - 1 && j == ncopies - 1)
 		add_phi_arg (phi_stmt, lsq, loop_latch_edge (loop));
@@ -3602,13 +3612,13 @@ vectorizable_live_operation (tree stmt,
   if (!STMT_VINFO_LIVE_P (stmt_info))
     return false;
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
 
-  if (TREE_CODE (TREE_OPERAND (stmt, 0)) != SSA_NAME)
+  if (TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 0)) != SSA_NAME)
     return false;
 
-  operation = TREE_OPERAND (stmt, 1);
+  operation = GIMPLE_STMT_OPERAND (stmt, 1);
   code = TREE_CODE (operation);
 
   op_type = TREE_CODE_LENGTH (code);
@@ -3724,10 +3734,10 @@ vectorizable_condition (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
       return false;
     }
 
-  if (TREE_CODE (stmt) != MODIFY_EXPR)
+  if (TREE_CODE (stmt) != GIMPLE_MODIFY_STMT)
     return false;
 
-  op = TREE_OPERAND (stmt, 1);
+  op = GIMPLE_STMT_OPERAND (stmt, 1);
 
   if (TREE_CODE (op) != COND_EXPR)
     return false;
@@ -3778,7 +3788,7 @@ vectorizable_condition (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
   /* Transform */
 
   /* Handle def.  */
-  scalar_dest = TREE_OPERAND (stmt, 0);
+  scalar_dest = GIMPLE_STMT_OPERAND (stmt, 0);
   vec_dest = vect_create_destination_var (scalar_dest, vectype);
 
   /* Handle cond expr.  */
@@ -3795,9 +3805,10 @@ vectorizable_condition (tree stmt, block_stmt_iterator *bsi, tree *vec_stmt)
   vec_cond_expr = build3 (VEC_COND_EXPR, vectype, 
 			  vec_compare, vec_then_clause, vec_else_clause);
 
-  *vec_stmt = build2 (MODIFY_EXPR, void_type_node, vec_dest, vec_cond_expr);
+  *vec_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node, vec_dest,
+      		      vec_cond_expr);
   new_temp = make_ssa_name (vec_dest, *vec_stmt);
-  TREE_OPERAND (*vec_stmt, 0) = new_temp;
+  GIMPLE_STMT_OPERAND (*vec_stmt, 0) = new_temp;
   vect_finish_stmt_generation (stmt, *vec_stmt, bsi);
   
   return true;
@@ -4574,7 +4585,7 @@ vect_create_cond_for_align_checks (loop_vec_info loop_vinfo,
       add_referenced_var (addr_tmp);
       addr_tmp_name = make_ssa_name (addr_tmp, NULL_TREE);
       addr_stmt = fold_convert (int_ptrsize_type, addr_base);
-      addr_stmt = build2 (MODIFY_EXPR, void_type_node,
+      addr_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node,
                           addr_tmp_name, addr_stmt);
       SSA_NAME_DEF_STMT (addr_tmp_name) = addr_stmt;
       append_to_statement_list_force (addr_stmt, cond_expr_stmt_list);
@@ -4588,7 +4599,8 @@ vect_create_cond_for_align_checks (loop_vec_info loop_vinfo,
           or_tmp = create_tmp_var (int_ptrsize_type, tmp_name);
           add_referenced_var (or_tmp);
           new_or_tmp_name = make_ssa_name (or_tmp, NULL_TREE);
-          or_stmt = build2 (MODIFY_EXPR, void_type_node, new_or_tmp_name,
+          or_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node,
+	      		    new_or_tmp_name,
                             build2 (BIT_IOR_EXPR, int_ptrsize_type,
 	                            or_tmp_name,
                                     addr_tmp_name));
@@ -4608,7 +4620,7 @@ vect_create_cond_for_align_checks (loop_vec_info loop_vinfo,
   add_referenced_var (and_tmp);
   and_tmp_name = make_ssa_name (and_tmp, NULL_TREE);
 
-  and_stmt = build2 (MODIFY_EXPR, void_type_node,
+  and_stmt = build2 (GIMPLE_MODIFY_STMT, void_type_node,
                      and_tmp_name,
                      build2 (BIT_AND_EXPR, int_ptrsize_type,
                              or_tmp_name, mask_cst));
diff --git a/gcc/tree-vectorizer.c b/gcc/tree-vectorizer.c
index 3e186a3c370f2a4d3b66d23453b5f3b178022730..9974343dce7fd235304129b50f6e7dbeda3ac222 100644
--- a/gcc/tree-vectorizer.c
+++ b/gcc/tree-vectorizer.c
@@ -1233,7 +1233,7 @@ find_loop_location (struct loop *loop)
 
   node = get_loop_exit_condition (loop);
 
-  if (node && EXPR_P (node) && EXPR_HAS_LOCATION (node)
+  if (node && CAN_HAVE_LOCATION_P (node) && EXPR_HAS_LOCATION (node)
       && EXPR_FILENAME (node) && EXPR_LINENO (node))
     return EXPR_LOC (node);
 
@@ -1248,7 +1248,7 @@ find_loop_location (struct loop *loop)
   for (si = bsi_start (bb); !bsi_end_p (si); bsi_next (&si))
     {
       node = bsi_stmt (si);
-      if (node && EXPR_P (node) && EXPR_HAS_LOCATION (node))
+      if (node && CAN_HAVE_LOCATION_P (node) && EXPR_HAS_LOCATION (node))
         return EXPR_LOC (node);
     }
 
@@ -1681,7 +1681,7 @@ vect_is_simple_use (tree operand, loop_vec_info loop_vinfo, tree *def_stmt,
     }
 
   /* empty stmt is expected only in case of a function argument.
-     (Otherwise - we expect a phi_node or a modify_expr).  */
+     (Otherwise - we expect a phi_node or a GIMPLE_MODIFY_STMT).  */
   if (IS_EMPTY_STMT (*def_stmt))
     {
       tree arg = TREE_OPERAND (*def_stmt, 0);
@@ -1733,8 +1733,8 @@ vect_is_simple_use (tree operand, loop_vec_info loop_vinfo, tree *def_stmt,
                   || *dt == vect_invariant_def);
       break;
 
-    case MODIFY_EXPR:
-      *def = TREE_OPERAND (*def_stmt, 0);
+    case GIMPLE_MODIFY_STMT:
+      *def = GIMPLE_STMT_OPERAND (*def_stmt, 0);
       gcc_assert (*dt == vect_loop_def || *dt == vect_invariant_def);
       break;
 
@@ -1783,7 +1783,7 @@ supportable_widening_operation (enum tree_code code, tree stmt, tree vectype,
   enum machine_mode vec_mode;
   enum insn_code icode1, icode2;
   optab optab1, optab2;
-  tree expr = TREE_OPERAND (stmt, 1);
+  tree expr = GIMPLE_STMT_OPERAND (stmt, 1);
   tree type = TREE_TYPE (expr);
   tree wide_vectype = get_vectype_for_scalar_type (type);
   enum tree_code c1, c2;
@@ -1960,7 +1960,7 @@ vect_is_simple_reduction (struct loop *loop, tree phi)
       return NULL_TREE;
     }
 
-  if (TREE_CODE (def_stmt) != MODIFY_EXPR)
+  if (TREE_CODE (def_stmt) != GIMPLE_MODIFY_STMT)
     {
       if (vect_print_dump_info (REPORT_DETAILS))
         {
@@ -1969,7 +1969,7 @@ vect_is_simple_reduction (struct loop *loop, tree phi)
       return NULL_TREE;
     }
 
-  operation = TREE_OPERAND (def_stmt, 1);
+  operation = GIMPLE_STMT_OPERAND (def_stmt, 1);
   code = TREE_CODE (operation);
   if (!commutative_tree_code (code) || !associative_tree_code (code))
     {
@@ -2059,7 +2059,7 @@ vect_is_simple_reduction (struct loop *loop, tree phi)
       return NULL_TREE;
     }
 
-  if (TREE_CODE (def1) == MODIFY_EXPR
+  if (TREE_CODE (def1) == GIMPLE_MODIFY_STMT
       && flow_bb_inside_loop_p (loop, bb_for_stmt (def1))
       && def2 == phi)
     {
@@ -2070,7 +2070,7 @@ vect_is_simple_reduction (struct loop *loop, tree phi)
         }
       return def_stmt;
     }
-  else if (TREE_CODE (def2) == MODIFY_EXPR
+  else if (TREE_CODE (def2) == GIMPLE_MODIFY_STMT
       && flow_bb_inside_loop_p (loop, bb_for_stmt (def2))
       && def1 == phi)
     {
diff --git a/gcc/tree-vn.c b/gcc/tree-vn.c
index bf47acfd37098f1e04518fd9359c95333e086a32..aceacc5ebcb987fec507bbac5965c2ca6e30ef4c 100644
--- a/gcc/tree-vn.c
+++ b/gcc/tree-vn.c
@@ -85,8 +85,8 @@ vn_compute (tree expr, hashval_t val)
   /* EXPR must not be a statement.  We are only interested in value
      numbering expressions on the RHS of assignments.  */
   gcc_assert (expr);
-  gcc_assert (!expr->common.ann
-	      || expr->common.ann->common.type != STMT_ANN);
+  gcc_assert (!expr->base.ann
+	      || expr->base.ann->common.type != STMT_ANN);
 
   val = iterative_hash_expr (expr, val);
   return val;
@@ -181,6 +181,7 @@ set_value_handle (tree e, tree v)
   if (TREE_CODE (e) == SSA_NAME)
     SSA_NAME_VALUE (e) = v;
   else if (EXPR_P (e) || DECL_P (e) || TREE_CODE (e) == TREE_LIST
+	   || GIMPLE_STMT_P (e)
 	   || TREE_CODE (e) == CONSTRUCTOR)
     get_tree_common_ann (e)->value_handle = v;
   else
diff --git a/gcc/tree-vrp.c b/gcc/tree-vrp.c
index adcbbdc616e445477cadbdf4d9f1029fbe3bc28f..759bf7518e08285d4ed3755c6b06a4773830f499 100644
--- a/gcc/tree-vrp.c
+++ b/gcc/tree-vrp.c
@@ -2399,20 +2399,22 @@ build_assert_expr_for (tree cond, tree v)
   if (COMPARISON_CLASS_P (cond))
     {
       tree a = build2 (ASSERT_EXPR, TREE_TYPE (v), v, cond); 
-      assertion = build2 (MODIFY_EXPR, TREE_TYPE (v), n, a);
+      assertion = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (v), n, a);
     }
   else if (TREE_CODE (cond) == TRUTH_NOT_EXPR)
     {
       /* Given !V, build the assignment N = false.  */
       tree op0 = TREE_OPERAND (cond, 0);
       gcc_assert (op0 == v);
-      assertion = build2 (MODIFY_EXPR, TREE_TYPE (v), n, boolean_false_node);
+      assertion = build2 (GIMPLE_MODIFY_STMT, TREE_TYPE (v), n,
+			  boolean_false_node);
     }
   else if (TREE_CODE (cond) == SSA_NAME)
     {
       /* Given V, build the assignment N = true.  */
       gcc_assert (v == cond);
-      assertion = build2 (MODIFY_EXPR, TREE_TYPE (v), n, boolean_true_node);
+      assertion = build2 (GIMPLE_MODIFY_STMT,
+	  		  TREE_TYPE (v), n, boolean_true_node);
     }
   else
     gcc_unreachable ();
@@ -2797,10 +2799,10 @@ register_edge_assert_for_1 (tree op, enum tree_code code,
      a truth operation or some bit operations, then we may be able
      to register information about the operands of that assignment.  */
   op_def = SSA_NAME_DEF_STMT (op);
-  if (TREE_CODE (op_def) != MODIFY_EXPR)
+  if (TREE_CODE (op_def) != GIMPLE_MODIFY_STMT)
     return retval;
 
-  rhs = TREE_OPERAND (op_def, 1);
+  rhs = GIMPLE_STMT_OPERAND (op_def, 1);
 
   if (COMPARISON_CLASS_P (rhs))
     {
@@ -2908,12 +2910,12 @@ register_edge_assert_for (tree name, edge e, block_stmt_iterator si, tree cond)
     {
       tree def_stmt = SSA_NAME_DEF_STMT (name);
 
-      if (TREE_CODE (def_stmt) == MODIFY_EXPR
-	  && (TREE_CODE (TREE_OPERAND (def_stmt, 1)) == TRUTH_AND_EXPR
-	      || TREE_CODE (TREE_OPERAND (def_stmt, 1)) == BIT_AND_EXPR))
+      if (TREE_CODE (def_stmt) == GIMPLE_MODIFY_STMT
+	  && (TREE_CODE (GIMPLE_STMT_OPERAND (def_stmt, 1)) == TRUTH_AND_EXPR
+	      || TREE_CODE (GIMPLE_STMT_OPERAND (def_stmt, 1)) == BIT_AND_EXPR))
 	{
-	  tree op0 = TREE_OPERAND (TREE_OPERAND (def_stmt, 1), 0);
-	  tree op1 = TREE_OPERAND (TREE_OPERAND (def_stmt, 1), 1);
+	  tree op0 = TREE_OPERAND (GIMPLE_STMT_OPERAND (def_stmt, 1), 0);
+	  tree op1 = TREE_OPERAND (GIMPLE_STMT_OPERAND (def_stmt, 1), 1);
 	  retval |= register_edge_assert_for_1 (op0, NE_EXPR, e, si);
 	  retval |= register_edge_assert_for_1 (op1, NE_EXPR, e, si);
 	}
@@ -2927,12 +2929,12 @@ register_edge_assert_for (tree name, edge e, block_stmt_iterator si, tree cond)
     {
       tree def_stmt = SSA_NAME_DEF_STMT (name);
 
-      if (TREE_CODE (def_stmt) == MODIFY_EXPR
-	  && (TREE_CODE (TREE_OPERAND (def_stmt, 1)) == TRUTH_OR_EXPR
-	      || TREE_CODE (TREE_OPERAND (def_stmt, 1)) == BIT_IOR_EXPR))
+      if (TREE_CODE (def_stmt) == GIMPLE_MODIFY_STMT
+	  && (TREE_CODE (GIMPLE_STMT_OPERAND (def_stmt, 1)) == TRUTH_OR_EXPR
+	      || TREE_CODE (GIMPLE_STMT_OPERAND (def_stmt, 1)) == BIT_IOR_EXPR))
 	{
-	  tree op0 = TREE_OPERAND (TREE_OPERAND (def_stmt, 1), 0);
-	  tree op1 = TREE_OPERAND (TREE_OPERAND (def_stmt, 1), 1);
+	  tree op0 = TREE_OPERAND (GIMPLE_STMT_OPERAND (def_stmt, 1), 0);
+	  tree op1 = TREE_OPERAND (GIMPLE_STMT_OPERAND (def_stmt, 1), 1);
 	  retval |= register_edge_assert_for_1 (op0, EQ_EXPR, e, si);
 	  retval |= register_edge_assert_for_1 (op1, EQ_EXPR, e, si);
 	}
@@ -3156,12 +3158,18 @@ find_assert_locations (basic_block bb)
 		  tree t = op;
 		  tree def_stmt = SSA_NAME_DEF_STMT (t);
 	
-		  while (TREE_CODE (def_stmt) == MODIFY_EXPR
-			 && TREE_CODE (TREE_OPERAND (def_stmt, 1)) == NOP_EXPR
-			 && TREE_CODE (TREE_OPERAND (TREE_OPERAND (def_stmt, 1), 0)) == SSA_NAME
-			 && POINTER_TYPE_P (TREE_TYPE (TREE_OPERAND (TREE_OPERAND (def_stmt, 1), 0))))
+		  while (TREE_CODE (def_stmt) == GIMPLE_MODIFY_STMT
+			 && TREE_CODE
+			     (GIMPLE_STMT_OPERAND (def_stmt, 1)) == NOP_EXPR
+			 && TREE_CODE
+			     (TREE_OPERAND (GIMPLE_STMT_OPERAND (def_stmt, 1),
+					    0)) == SSA_NAME
+			 && POINTER_TYPE_P
+			     (TREE_TYPE (TREE_OPERAND
+					  (GIMPLE_STMT_OPERAND (def_stmt,
+								1), 0))))
 		    {
-		      t = TREE_OPERAND (TREE_OPERAND (def_stmt, 1), 0);
+		      t = TREE_OPERAND (GIMPLE_STMT_OPERAND (def_stmt, 1), 0);
 		      def_stmt = SSA_NAME_DEF_STMT (t);
 
 		      /* Note we want to register the assert for the
@@ -3412,10 +3420,10 @@ remove_range_assertions (void)
 	tree stmt = bsi_stmt (si);
 	tree use_stmt;
 
-	if (TREE_CODE (stmt) == MODIFY_EXPR
-	    && TREE_CODE (TREE_OPERAND (stmt, 1)) == ASSERT_EXPR)
+	if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT
+	    && TREE_CODE (GIMPLE_STMT_OPERAND (stmt, 1)) == ASSERT_EXPR)
 	  {
-	    tree rhs = TREE_OPERAND (stmt, 1), var;
+	    tree rhs = GIMPLE_STMT_OPERAND (stmt, 1), var;
 	    tree cond = fold (ASSERT_EXPR_COND (rhs));
 	    use_operand_p use_p;
 	    imm_use_iterator iter;
@@ -3424,7 +3432,8 @@ remove_range_assertions (void)
 
 	    /* Propagate the RHS into every use of the LHS.  */
 	    var = ASSERT_EXPR_VAR (rhs);
-	    FOR_EACH_IMM_USE_STMT (use_stmt, iter, TREE_OPERAND (stmt, 0))
+	    FOR_EACH_IMM_USE_STMT (use_stmt, iter,
+				   GIMPLE_STMT_OPERAND (stmt, 0))
 	      FOR_EACH_IMM_USE_ON_STMT (use_p, iter)
 		{
 		  SET_USE (use_p, var);
@@ -3452,10 +3461,10 @@ stmt_interesting_for_vrp (tree stmt)
       && (INTEGRAL_TYPE_P (TREE_TYPE (PHI_RESULT (stmt)))
 	  || POINTER_TYPE_P (TREE_TYPE (PHI_RESULT (stmt)))))
     return true;
-  else if (TREE_CODE (stmt) == MODIFY_EXPR)
+  else if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
     {
-      tree lhs = TREE_OPERAND (stmt, 0);
-      tree rhs = TREE_OPERAND (stmt, 1);
+      tree lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+      tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
       /* In general, assignments with virtual operands are not useful
 	 for deriving ranges, with the obvious exception of calls to
@@ -3533,8 +3542,8 @@ vrp_visit_assignment (tree stmt, tree *output_p)
   tree lhs, rhs, def;
   ssa_op_iter iter;
 
-  lhs = TREE_OPERAND (stmt, 0);
-  rhs = TREE_OPERAND (stmt, 1);
+  lhs = GIMPLE_STMT_OPERAND (stmt, 0);
+  rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
   /* We only keep track of ranges in integral and pointer types.  */
   if (TREE_CODE (lhs) == SSA_NAME
@@ -3951,9 +3960,9 @@ vrp_visit_stmt (tree stmt, edge *taken_edge_p, tree *output_p)
     }
 
   ann = stmt_ann (stmt);
-  if (TREE_CODE (stmt) == MODIFY_EXPR)
+  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
     {
-      tree rhs = TREE_OPERAND (stmt, 1);
+      tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
 
       /* In general, assignments with virtual operands are not useful
 	 for deriving ranges, with the obvious exception of calls to
@@ -4267,7 +4276,7 @@ simplify_div_or_mod_using_ranges (tree stmt, tree rhs, enum tree_code rhs_code)
 	  t = build2 (BIT_AND_EXPR, TREE_TYPE (op0), op0, t);
 	}
 
-      TREE_OPERAND (stmt, 1) = t;
+      GIMPLE_STMT_OPERAND (stmt, 1) = t;
       update_stmt (stmt);
     }
 }
@@ -4314,7 +4323,7 @@ simplify_abs_using_ranges (tree stmt, tree rhs)
 	  else
 	    t = op;
 
-	  TREE_OPERAND (stmt, 1) = t;
+	  GIMPLE_STMT_OPERAND (stmt, 1) = t;
 	  update_stmt (stmt);
 	}
     }
@@ -4464,9 +4473,9 @@ simplify_cond_using_ranges (tree stmt)
 void
 simplify_stmt_using_ranges (tree stmt)
 {
-  if (TREE_CODE (stmt) == MODIFY_EXPR)
+  if (TREE_CODE (stmt) == GIMPLE_MODIFY_STMT)
     {
-      tree rhs = TREE_OPERAND (stmt, 1);
+      tree rhs = GIMPLE_STMT_OPERAND (stmt, 1);
       enum tree_code rhs_code = TREE_CODE (rhs);
 
       /* Transform TRUNC_DIV_EXPR and TRUNC_MOD_EXPR into RSHIFT_EXPR
diff --git a/gcc/tree.c b/gcc/tree.c
index 2d2ef08e5f7091e0f7651ebbbdd91c5ecf8c4959..68aa58f9619e4533eb7468093feac4c8c51faf3c 100644
--- a/gcc/tree.c
+++ b/gcc/tree.c
@@ -98,7 +98,8 @@ static const char * const tree_node_kind_names[] = {
   "random kinds",
   "lang_decl kinds",
   "lang_type kinds",
-  "omp clauses"
+  "omp clauses",
+  "gimple statements"
 };
 #endif /* GATHER_STATISTICS */
 
@@ -356,6 +357,10 @@ tree_code_size (enum tree_code code)
       return (sizeof (struct tree_exp)
 	      + (TREE_CODE_LENGTH (code) - 1) * sizeof (char *));
 
+    case tcc_gimple_stmt:
+      return (sizeof (struct gimple_stmt)
+	      + (TREE_CODE_LENGTH (code) - 1) * sizeof (char *));
+
     case tcc_constant:  /* a constant */
       switch (code)
 	{
@@ -476,6 +481,10 @@ make_node_stat (enum tree_code code MEM_STAT_DECL)
       kind = c_kind;
       break;
 
+    case tcc_gimple_stmt:
+      kind = gimple_stmt_kind;
+      break;
+
     case tcc_exceptional:  /* something random, like an identifier.  */
       switch (code)
 	{
@@ -591,6 +600,17 @@ make_node_stat (enum tree_code code MEM_STAT_DECL)
 	}
       break;
 
+    case tcc_gimple_stmt:
+      switch (code)
+	{
+      case GIMPLE_MODIFY_STMT:
+	TREE_SIDE_EFFECTS (t) = 1;
+	break;
+
+      default:
+	break;
+	}
+
     default:
       /* Other classes need no special treatment.  */
       break;
@@ -615,10 +635,11 @@ copy_node_stat (tree node MEM_STAT_DECL)
   t = ggc_alloc_zone_pass_stat (length, &tree_zone);
   memcpy (t, node, length);
 
-  TREE_CHAIN (t) = 0;
+  if (!GIMPLE_TUPLE_P (node))
+    TREE_CHAIN (t) = 0;
   TREE_ASM_WRITTEN (t) = 0;
   TREE_VISITED (t) = 0;
-  t->common.ann = 0;
+  t->base.ann = 0;
 
   if (TREE_CODE_CLASS (code) == tcc_declaration)
     {
@@ -1872,7 +1893,14 @@ expr_align (tree t)
       align1 = TYPE_ALIGN (TREE_TYPE (t));
       return MAX (align0, align1);
 
-    case SAVE_EXPR:         case COMPOUND_EXPR:       case MODIFY_EXPR:
+    case MODIFY_EXPR:
+      /* FIXME tuples: It is unclear to me if this function, which
+         is only called from ADA, is called on gimple or non gimple
+         trees.  Let's assume it's from gimple trees unless we hit
+         this abort.  */
+      gcc_unreachable ();
+
+    case SAVE_EXPR:         case COMPOUND_EXPR:       case GIMPLE_MODIFY_STMT:
     case INIT_EXPR:         case TARGET_EXPR:         case WITH_CLEANUP_EXPR:
     case CLEANUP_POINT_EXPR:
       /* These don't change the alignment of an object.  */
@@ -2141,6 +2169,8 @@ tree_node_structure (tree t)
     case tcc_expression:
     case tcc_statement:
       return TS_EXP;
+    case tcc_gimple_stmt:
+      return TS_GIMPLE_STATEMENT;
     default:  /* tcc_constant and tcc_exceptional */
       break;
     }
@@ -2153,6 +2183,8 @@ tree_node_structure (tree t)
     case VECTOR_CST:		return TS_VECTOR;
     case STRING_CST:		return TS_STRING;
       /* tcc_exceptional cases.  */
+    /* FIXME tuples: eventually this should be TS_BASE.  For now, nothing
+       returns TS_BASE.  */
     case ERROR_MARK:		return TS_COMMON;
     case IDENTIFIER_NODE:	return TS_IDENTIFIER;
     case TREE_LIST:		return TS_LIST;
@@ -2967,6 +2999,17 @@ build2_stat (enum tree_code code, tree tt, tree arg0, tree arg1 MEM_STAT_DECL)
 
   gcc_assert (TREE_CODE_LENGTH (code) == 2);
 
+  if (code == MODIFY_EXPR && cfun && cfun->gimplified)
+    {
+      /* We should be talking GIMPLE_MODIFY_STMT by now.  */
+      gcc_unreachable ();
+    }
+
+  /* FIXME tuples: For now let's be lazy; later we must rewrite all
+     build2 calls to build2_gimple calls.  */
+  if (TREE_CODE_CLASS (code) == tcc_gimple_stmt)
+    return build2_gimple (code, arg0, arg1);
+
   t = make_node_stat (code PASS_MEM_STAT);
   TREE_TYPE (t) = tt;
 
@@ -2997,6 +3040,35 @@ build2_stat (enum tree_code code, tree tt, tree arg0, tree arg1 MEM_STAT_DECL)
   return t;
 }
 
+
+/* Similar as build2_stat, but for GIMPLE tuples.  For convenience's sake,
+   arguments and return type are trees.  */
+
+tree
+build2_gimple_stat (enum tree_code code, tree arg0, tree arg1 MEM_STAT_DECL)
+{
+  bool side_effects;
+  tree t;
+
+  gcc_assert (TREE_CODE_LENGTH (code) == 2);
+
+  t = make_node_stat (code PASS_MEM_STAT);
+
+  side_effects = TREE_SIDE_EFFECTS (t);
+
+  /* ?? We don't care about setting flags for tuples...  */
+  GIMPLE_STMT_OPERAND (t, 0) = arg0;
+  GIMPLE_STMT_OPERAND (t, 1) = arg1;
+
+  /* ...except perhaps side_effects and volatility.  ?? */
+  TREE_SIDE_EFFECTS (t) = side_effects;
+  TREE_THIS_VOLATILE (t) = (TREE_CODE_CLASS (code) == tcc_reference
+	             	    && arg0 && TREE_THIS_VOLATILE (arg0));
+
+
+  return t;
+}
+
 tree
 build3_stat (enum tree_code code, tree tt, tree arg0, tree arg1,
 	     tree arg2 MEM_STAT_DECL)
@@ -3286,6 +3358,130 @@ annotate_with_locus (tree node, location_t locus)
 }
 #endif
 
+/* Source location accessor functions.  */
+
+
+/* The source location of this expression.  Non-tree_exp nodes such as
+   decls and constants can be shared among multiple locations, so
+   return nothing.  */
+location_t
+expr_location (tree node)
+{
+#ifdef USE_MAPPED_LOCATION
+  if (GIMPLE_STMT_P (node))
+    return GIMPLE_STMT_LOCUS (node);
+  return EXPR_P (node) ? node->exp.locus : UNKNOWN_LOCATION;
+#else
+  if (GIMPLE_STMT_P (node))
+    return EXPR_HAS_LOCATION (node)
+      ? *GIMPLE_STMT_LOCUS (node) : UNKNOWN_LOCATION;
+  return EXPR_HAS_LOCATION (node) ? *node->exp.locus : UNKNOWN_LOCATION;
+#endif
+}
+
+void
+set_expr_location (tree node, location_t locus)
+{
+#ifdef USE_MAPPED_LOCATION
+  if (GIMPLE_STMT_P (node))
+    GIMPLE_STMT_LOCUS (node) = locus;
+  else
+    EXPR_CHECK (node)->exp.locus = locus;
+#else
+      annotate_with_locus (node, locus);
+#endif
+}
+
+bool
+expr_has_location (tree node)
+{
+#ifdef USE_MAPPED_LOCATION
+  return expr_location (node) != UNKNOWN_LOCATION;
+#else
+  return expr_locus (node) != NULL;
+#endif
+}
+
+#ifdef USE_MAPPED_LOCATION
+source_location *
+#else
+source_locus
+#endif
+expr_locus (tree node)
+{
+#ifdef USE_MAPPED_LOCATION
+  if (GIMPLE_STMT_P (node))
+    return &GIMPLE_STMT_LOCUS (node);
+  return EXPR_P (node) ? &node->exp.locus : (location_t *) NULL;
+#else
+  if (GIMPLE_STMT_P (node))
+    return GIMPLE_STMT_LOCUS (node);
+  /* ?? The cast below was originally "(location_t *)" in the macro,
+     but that makes no sense.  ?? */
+  return EXPR_P (node) ? node->exp.locus : (source_locus) NULL;
+#endif
+}
+
+void
+set_expr_locus (tree node,
+#ifdef USE_MAPPED_LOCATION
+		source_location *loc
+#else
+		source_locus loc
+#endif
+		)
+{
+#ifdef USE_MAPPED_LOCATION
+  if (loc == NULL)
+    {
+      if (GIMPLE_STMT_P (node))
+	GIMPLE_STMT_LOCUS (node) = UNKNOWN_LOCATION;
+      else
+	EXPR_CHECK (node)->exp.locus = UNKNOWN_LOCATION;
+    }
+  else
+    {
+      if (GIMPLE_STMT_P (node))
+	GIMPLE_STMT_LOCUS (node) = *loc;
+      else
+	EXPR_CHECK (node)->exp.locus = *loc;
+    }
+#else
+  if (GIMPLE_STMT_P (node))
+    GIMPLE_STMT_LOCUS (node) = loc;
+  else
+    EXPR_CHECK (node)->exp.locus = loc;
+#endif
+}
+
+const char **
+expr_filename (tree node)
+{
+#ifdef USE_MAPPED_LOCATION
+  if (GIMPLE_STMT_P (node))
+    return &LOCATION_FILE (GIMPLE_STMT_LOCUS (node));
+  return &LOCATION_FILE (EXPR_CHECK (node)->exp.locus);
+#else
+  if (GIMPLE_STMT_P (node))
+    return &GIMPLE_STMT_LOCUS (node)->file;
+  return &(EXPR_CHECK (node)->exp.locus->file);
+#endif
+}
+
+int *
+expr_lineno (tree node)
+{
+#ifdef USE_MAPPED_LOCATION
+  if (GIMPLE_STMT_P (node))
+    return &LOCATION_LINE (GIMPLE_STMT_LOCUS (node));
+  return &LOCATION_LINE (EXPR_CHECK (node)->exp.locus);
+#else
+  if (GIMPLE_STMT_P (node))
+    return &GIMPLE_STMT_LOCUS (node)->line;
+  return &EXPR_CHECK (node)->exp.locus->line;
+#endif
+}
+
 /* Return a declaration like DDECL except that its DECL_ATTRIBUTES
    is ATTRIBUTE.  */
 
@@ -7709,7 +7905,8 @@ walk_tree (tree *tp, walk_tree_fn func, void *data, struct pointer_set_t *pset)
       /* FALLTHRU */
 
     default:
-      if (IS_EXPR_CODE_CLASS (TREE_CODE_CLASS (code)))
+      if (IS_EXPR_CODE_CLASS (TREE_CODE_CLASS (code))
+	  || IS_GIMPLE_STMT_CODE_CLASS (TREE_CODE_CLASS (code)))
 	{
 	  int i, len;
 
@@ -7721,11 +7918,10 @@ walk_tree (tree *tp, walk_tree_fn func, void *data, struct pointer_set_t *pset)
 	  if (len)
 	    {
 	      for (i = 0; i < len - 1; ++i)
-		WALK_SUBTREE (TREE_OPERAND (*tp, i));
-	      WALK_SUBTREE_TAIL (TREE_OPERAND (*tp, len - 1));
+		WALK_SUBTREE (GENERIC_TREE_OPERAND (*tp, i));
+	      WALK_SUBTREE_TAIL (GENERIC_TREE_OPERAND (*tp, len - 1));
 	    }
 	}
-
       /* If this is a type, walk the needed fields in the type.  */
       else if (TYPE_P (*tp))
 	return walk_type_fields (*tp, func, data, pset);
@@ -7779,4 +7975,33 @@ empty_body_p (tree stmt)
   return true;
 }
 
+tree *
+tree_block (tree t)
+{
+  char const c = TREE_CODE_CLASS (TREE_CODE (t));
+
+  if (IS_EXPR_CODE_CLASS (c))
+    return &t->exp.block;
+  else if (IS_GIMPLE_STMT_CODE_CLASS (c))
+    return &GIMPLE_STMT_BLOCK (t);
+  gcc_unreachable ();
+  return NULL;
+}
+
+tree *
+generic_tree_operand (tree node, int i)
+{
+  if (GIMPLE_STMT_P (node))
+    return &GIMPLE_STMT_OPERAND (node, i);
+  return &TREE_OPERAND (node, i);
+}
+
+tree *
+generic_tree_type (tree node)
+{
+  if (GIMPLE_STMT_P (node))
+    return &void_type_node;
+  return &TREE_TYPE (node);
+}
+
 #include "gt-tree.h"
diff --git a/gcc/tree.def b/gcc/tree.def
index d5df9f26125bf0ae4b93cfa5ce9452953eda3ac0..c53d9be5a892870614428552b971280663583710 100644
--- a/gcc/tree.def
+++ b/gcc/tree.def
@@ -1065,6 +1065,11 @@ DEFTREECODE (WIDEN_MULT_EXPR, "widen_mult_expr", tcc_binary, 2)
    Operand 1 is an integer shift amount in bits.  */
 DEFTREECODE (VEC_LSHIFT_EXPR, "vec_lshift_expr", tcc_binary, 2)
 DEFTREECODE (VEC_RSHIFT_EXPR, "vec_rshift_expr", tcc_binary, 2)
+
+/* GIMPLE tree codes.  */
+
+/* Assignment expression.  Operand 0 is the what to set; 1, the new value.  */
+DEFTREECODE (GIMPLE_MODIFY_STMT, "gimple_modify_stmt", tcc_gimple_stmt, 2)
 
 /* Widening vector multiplication.
    The two operands are vectors with N elements of size S. Multiplying the
diff --git a/gcc/tree.h b/gcc/tree.h
index 52a04c40eedac261ead662fd0bf5a29f7f3c1f7f..50a7762bc5b93527c2c60ff1455c173e32591ffc 100644
--- a/gcc/tree.h
+++ b/gcc/tree.h
@@ -64,7 +64,8 @@ enum tree_code_class {
   tcc_binary,      /* A binary arithmetic expression.  */
   tcc_statement,   /* A statement expression, which have side effects
 		      but usually no interesting value.  */
-  tcc_expression   /* Any other expression.  */
+  tcc_expression,  /* Any other expression.  */
+  tcc_gimple_stmt  /* A GIMPLE statement.  */
 };
 
 /* Each tree code class has an associated string representation.
@@ -163,6 +164,10 @@ extern const enum tree_code_class tree_code_type[];
 #define IS_EXPR_CODE_CLASS(CLASS)\
 	((CLASS) >= tcc_reference && (CLASS) <= tcc_expression)
 
+/* Returns nonzer iff CLASS is a GIMPLE statement.  */
+
+#define IS_GIMPLE_STMT_CODE_CLASS(CLASS) ((CLASS) == tcc_gimple_stmt)
+
 /* Returns nonzero iff NODE is an expression of some kind.  */
 
 #define EXPR_P(NODE) IS_EXPR_CODE_CLASS (TREE_CODE_CLASS (TREE_CODE (NODE)))
@@ -347,12 +352,8 @@ enum omp_clause_code
    fields.  */
 union tree_ann_d;
 
-struct tree_common GTY(())
+struct tree_base GTY(())
 {
-  tree chain;
-  tree type;
-  union tree_ann_d *ann;
-
   ENUM_BITFIELD(tree_code) code : 8;
 
   unsigned side_effects_flag : 1;
@@ -381,6 +382,27 @@ struct tree_common GTY(())
   unsigned lang_flag_5 : 1;
   unsigned lang_flag_6 : 1;
   unsigned visited : 1;
+
+  /* FIXME tuples: Eventually, we need to move this somewhere external to
+     the trees.  */
+  union tree_ann_d *ann;
+};
+
+struct tree_common GTY(())
+{
+  struct tree_base base;
+  tree chain;
+  tree type;
+};
+
+/* GIMPLE_MODIFY_STMT */
+struct gimple_stmt GTY(())
+{
+  struct tree_base base;
+  source_locus locus;
+  tree block;
+  /* FIXME tuples: Eventually this should be of type ``struct gimple_expr''.  */
+  tree GTY ((length ("TREE_CODE_LENGTH (TREE_CODE (&%h))"))) operands[1];
 };
 
 /* The following table lists the uses of each of the above flags and
@@ -555,8 +577,8 @@ enum tree_node_structure_enum {
 
 /* The tree-code says what kind of node it is.
    Codes are defined in tree.def.  */
-#define TREE_CODE(NODE) ((enum tree_code) (NODE)->common.code)
-#define TREE_SET_CODE(NODE, VALUE) ((NODE)->common.code = (VALUE))
+#define TREE_CODE(NODE) ((enum tree_code) (NODE)->base.code)
+#define TREE_SET_CODE(NODE, VALUE) ((NODE)->base.code = (VALUE))
 
 /* When checking is enabled, errors will be generated if a tree node
    is accessed incorrectly. The macros die with a fatal error.  */
@@ -703,6 +725,14 @@ enum tree_node_structure_enum {
 			       __FUNCTION__);				\
     __t; })
 
+#define GIMPLE_STMT_CHECK(T) __extension__				\
+({  const tree __t = (T);						\
+    char const __c = TREE_CODE_CLASS (TREE_CODE (__t));			\
+    if (!IS_GIMPLE_STMT_CODE_CLASS (__c))				\
+      tree_class_check_failed (__t, tcc_gimple_stmt, __FILE__, __LINE__,\
+			       __FUNCTION__);				\
+    __t; })
+
 /* These checks have to be special cased.  */
 #define NON_TYPE_CHECK(T) __extension__					\
 ({  const tree __t = (T);						\
@@ -748,6 +778,8 @@ enum tree_node_structure_enum {
 #define TREE_OPERAND_CHECK(T, I) __extension__				\
 (*({const tree __t = EXPR_CHECK (T);					\
     const int __i = (I);						\
+    if (GIMPLE_TUPLE_P (__t))						\
+      gcc_unreachable ();						\
     if (__i < 0 || __i >= TREE_CODE_LENGTH (TREE_CODE (__t)))		\
       tree_operand_check_failed (__i, TREE_CODE (__t),			\
 				 __FILE__, __LINE__, __FUNCTION__);	\
@@ -763,6 +795,15 @@ enum tree_node_structure_enum {
 				 __FILE__, __LINE__, __FUNCTION__);	\
     &__t->exp.operands[__i]; }))
 
+/* Special checks for GIMPLE_STMT_OPERANDs.  */
+#define GIMPLE_STMT_OPERAND_CHECK(T, I) __extension__			\
+(*({const tree __t = GIMPLE_STMT_CHECK (T);				\
+    const int __i = (I);						\
+    if (__i < 0 || __i >= TREE_CODE_LENGTH (TREE_CODE (__t)))		\
+      tree_operand_check_failed (__i, TREE_CODE (__t),			\
+				 __FILE__, __LINE__, __FUNCTION__);	\
+    &__t->gstmt.operands[__i]; }))
+
 #define TREE_RTL_OPERAND_CHECK(T, CODE, I) __extension__		\
 (*(rtx *)								\
  ({const tree __t = (T);						\
@@ -774,6 +815,31 @@ enum tree_node_structure_enum {
 				 __FILE__, __LINE__, __FUNCTION__);	\
     &__t->exp.operands[__i]; }))
 
+/* Nodes are chained together for many purposes.
+   Types are chained together to record them for being output to the debugger
+   (see the function `chain_type').
+   Decls in the same scope are chained together to record the contents
+   of the scope.
+   Statement nodes for successive statements used to be chained together.
+   Often lists of things are represented by TREE_LIST nodes that
+   are chained together.  */
+
+#define TREE_CHAIN(NODE) __extension__ \
+(*({const tree __t = (NODE);					\
+    if (GIMPLE_TUPLE_P (__t))					\
+      gcc_unreachable ();					\
+    &__t->common.chain; }))
+
+/* In all nodes that are expressions, this is the data type of the expression.
+   In POINTER_TYPE nodes, this is the type that the pointer points to.
+   In ARRAY_TYPE nodes, this is the type of the elements.
+   In VECTOR_TYPE nodes, this is the type of the elements.  */
+#define TREE_TYPE(NODE) __extension__ \
+(*({const tree __t = (NODE);					\
+    if (GIMPLE_TUPLE_P (__t))					\
+      gcc_unreachable ();					\
+    &__t->common.type; }))
+
 extern void tree_contains_struct_check_failed (const tree,
 					       const enum tree_node_structure_enum,
 					       const char *, int, const char *)
@@ -829,19 +895,24 @@ extern void omp_clause_range_check_failed (const tree, const char *, int,
 #define TREE_CLASS_CHECK(T, CODE)		(T)
 #define TREE_RANGE_CHECK(T, CODE1, CODE2)	(T)
 #define EXPR_CHECK(T)				(T)
+#define GIMPLE_STMT_CHECK(T)			(T)
 #define NON_TYPE_CHECK(T)			(T)
 #define TREE_VEC_ELT_CHECK(T, I)		((T)->vec.a[I])
 #define TREE_OPERAND_CHECK(T, I)		((T)->exp.operands[I])
 #define TREE_OPERAND_CHECK_CODE(T, CODE, I)	((T)->exp.operands[I])
+#define GIMPLE_STMT_OPERAND_CHECK(T, I)		((T)->gstmt.operands[I])
 #define TREE_RTL_OPERAND_CHECK(T, CODE, I)  (*(rtx *) &((T)->exp.operands[I]))
 #define PHI_NODE_ELT_CHECK(T, i)	((T)->phi.a[i])
 #define OMP_CLAUSE_ELT_CHECK(T, i)	        ((T)->omp_clause.ops[i])
 #define OMP_CLAUSE_RANGE_CHECK(T, CODE1, CODE2)	(T)
 #define OMP_CLAUSE_SUBCODE_CHECK(T, CODE)	(T)
 
+#define TREE_CHAIN(NODE) ((NODE)->common.chain)
+#define TREE_TYPE(NODE) ((NODE)->common.type)
+
 #endif
 
-#define TREE_BLOCK(NODE)		(EXPR_CHECK (NODE)->exp.block)
+#define TREE_BLOCK(NODE)		*(tree_block (NODE))
 
 #include "tree-check.h"
 
@@ -865,11 +936,26 @@ extern void omp_clause_range_check_failed (const tree, const char *, int,
 #define NUMERICAL_TYPE_CHECK(T)					\
   TREE_CHECK4 (T, INTEGER_TYPE, ENUMERAL_TYPE, BOOLEAN_TYPE, REAL_TYPE)
 
-/* In all nodes that are expressions, this is the data type of the expression.
-   In POINTER_TYPE nodes, this is the type that the pointer points to.
-   In ARRAY_TYPE nodes, this is the type of the elements.
-   In VECTOR_TYPE nodes, this is the type of the elements.  */
-#define TREE_TYPE(NODE) ((NODE)->common.type)
+/* Nonzero if NODE is a GIMPLE statement.  */
+#define GIMPLE_STMT_P(NODE) \
+  (TREE_CODE_CLASS (TREE_CODE ((NODE))) == tcc_gimple_stmt)
+
+/* Nonzero if NODE is a GIMPLE tuple.  */
+#define GIMPLE_TUPLE_P(NODE) (GIMPLE_STMT_P (NODE))
+
+/* A GIMPLE tuple that has a ``locus'' field.  */
+#define GIMPLE_TUPLE_HAS_LOCUS_P(NODE) GIMPLE_STMT_P ((NODE))
+
+/* Like TREE_OPERAND but works with GIMPLE stmt tuples as well.
+
+   If you know the NODE is a GIMPLE statement, use GIMPLE_STMT_OPERAND.  If the
+   NODE code is unknown at compile time, use this macro.  */
+#define GENERIC_TREE_OPERAND(NODE, I) *(generic_tree_operand ((NODE), (I)))
+
+/* Like TREE_TYPE but returns void_type_node for gimple tuples that have
+   no type.  */
+
+#define GENERIC_TREE_TYPE(NODE) *(generic_tree_type ((NODE)))
 
 /* Here is how primitive or already-canonicalized types' hash codes
    are made.  */
@@ -879,17 +965,6 @@ extern void omp_clause_range_check_failed (const tree, const char *, int,
    used in hash tables which are saved to a PCH.  */
 #define TREE_HASH(NODE) ((size_t) (NODE) & 0777777)
 
-/* Nodes are chained together for many purposes.
-   Types are chained together to record them for being output to the debugger
-   (see the function `chain_type').
-   Decls in the same scope are chained together to record the contents
-   of the scope.
-   Statement nodes for successive statements used to be chained together.
-   Often lists of things are represented by TREE_LIST nodes that
-   are chained together.  */
-
-#define TREE_CHAIN(NODE) ((NODE)->common.chain)
-
 /* Given an expression as a tree, strip any NON_LVALUE_EXPRs and NOP_EXPRs
    that don't change the machine mode.  */
 
@@ -899,7 +974,7 @@ extern void omp_clause_range_check_failed (const tree, const char *, int,
 	  || TREE_CODE (EXP) == NON_LVALUE_EXPR)		\
 	 && TREE_OPERAND (EXP, 0) != error_mark_node		\
 	 && (TYPE_MODE (TREE_TYPE (EXP))			\
-	     == TYPE_MODE (TREE_TYPE (TREE_OPERAND (EXP, 0)))))	\
+	     == TYPE_MODE (GENERIC_TREE_TYPE (TREE_OPERAND (EXP, 0))))) \
     (EXP) = TREE_OPERAND (EXP, 0)
 
 /* Like STRIP_NOPS, but don't let the signedness change either.  */
@@ -1019,17 +1094,18 @@ extern void omp_clause_range_check_failed (const tree, const char *, int,
    object cannot go into register parameters, for example.
    In IDENTIFIER_NODEs, this means that some extern decl for this name
    had its address taken.  That matters for inline functions.  */
-#define TREE_ADDRESSABLE(NODE) ((NODE)->common.addressable_flag)
+#define TREE_ADDRESSABLE(NODE) ((NODE)->base.addressable_flag)
 
 /* Set on a CALL_EXPR if the call is in a tail position, ie. just before the
    exit of a function.  Calls for which this is true are candidates for tail
    call optimizations.  */
-#define CALL_EXPR_TAILCALL(NODE) (CALL_EXPR_CHECK(NODE)->common.addressable_flag)
+#define CALL_EXPR_TAILCALL(NODE) \
+  (CALL_EXPR_CHECK(NODE)->base.addressable_flag)
 
 /* Used as a temporary field on a CASE_LABEL_EXPR to indicate that the
    CASE_LOW operand has been processed.  */
 #define CASE_LOW_SEEN(NODE) \
-  (CASE_LABEL_EXPR_CHECK (NODE)->common.addressable_flag)
+  (CASE_LABEL_EXPR_CHECK (NODE)->base.addressable_flag)
 
 /* In a VAR_DECL, nonzero means allocate static storage.
    In a FUNCTION_DECL, nonzero if function has been defined.
@@ -1037,63 +1113,63 @@ extern void omp_clause_range_check_failed (const tree, const char *, int,
 
    ??? This is also used in lots of other nodes in unclear ways which
    should be cleaned up some day.  */
-#define TREE_STATIC(NODE) ((NODE)->common.static_flag)
+#define TREE_STATIC(NODE) ((NODE)->base.static_flag)
 
 /* In a TARGET_EXPR, WITH_CLEANUP_EXPR, means that the pertinent cleanup
    should only be executed if an exception is thrown, not on normal exit
    of its scope.  */
-#define CLEANUP_EH_ONLY(NODE) ((NODE)->common.static_flag)
+#define CLEANUP_EH_ONLY(NODE) ((NODE)->base.static_flag)
 
 /* Used as a temporary field on a CASE_LABEL_EXPR to indicate that the
    CASE_HIGH operand has been processed.  */
 #define CASE_HIGH_SEEN(NODE) \
-  (CASE_LABEL_EXPR_CHECK (NODE)->common.static_flag)
+  (CASE_LABEL_EXPR_CHECK (NODE)->base.static_flag)
 
 /* In an expr node (usually a conversion) this means the node was made
    implicitly and should not lead to any sort of warning.  In a decl node,
    warnings concerning the decl should be suppressed.  This is used at
    least for used-before-set warnings, and it set after one warning is
    emitted.  */
-#define TREE_NO_WARNING(NODE) ((NODE)->common.nowarning_flag)
+#define TREE_NO_WARNING(NODE) ((NODE)->base.nowarning_flag)
 
 /* In an INTEGER_CST, REAL_CST, COMPLEX_CST, or VECTOR_CST this means
    there was an overflow in folding.  This is distinct from
    TREE_OVERFLOW because ANSI C requires a diagnostic when overflows
    occur in constant expressions.  */
-#define TREE_CONSTANT_OVERFLOW(NODE) (CST_CHECK (NODE)->common.static_flag)
+#define TREE_CONSTANT_OVERFLOW(NODE) (CST_CHECK (NODE)->base.static_flag)
 
 /* In an IDENTIFIER_NODE, this means that assemble_name was called with
    this string as an argument.  */
 #define TREE_SYMBOL_REFERENCED(NODE) \
-  (IDENTIFIER_NODE_CHECK (NODE)->common.static_flag)
+  (IDENTIFIER_NODE_CHECK (NODE)->base.static_flag)
 
 /* Nonzero in a pointer or reference type means the data pointed to
    by this type can alias anything.  */
 #define TYPE_REF_CAN_ALIAS_ALL(NODE) \
-  (PTR_OR_REF_CHECK (NODE)->common.static_flag)
+  (PTR_OR_REF_CHECK (NODE)->base.static_flag)
 
 /* In an INTEGER_CST, REAL_CST, COMPLEX_CST, or VECTOR_CST, this means
    there was an overflow in folding, and no warning has been issued
    for this subexpression.  TREE_OVERFLOW implies TREE_CONSTANT_OVERFLOW,
    but not vice versa.  */
 
-#define TREE_OVERFLOW(NODE) (CST_CHECK (NODE)->common.public_flag)
+#define TREE_OVERFLOW(NODE) (CST_CHECK (NODE)->base.public_flag)
 
 /* In a VAR_DECL, FUNCTION_DECL, NAMESPACE_DECL or TYPE_DECL,
    nonzero means name is to be accessible from outside this module.
    In an IDENTIFIER_NODE, nonzero means an external declaration
    accessible from outside this module was previously seen
    for this name in an inner scope.  */
-#define TREE_PUBLIC(NODE) ((NODE)->common.public_flag)
+#define TREE_PUBLIC(NODE) ((NODE)->base.public_flag)
 
 /* In a _TYPE, indicates whether TYPE_CACHED_VALUES contains a vector
    of cached values, or is something else.  */
-#define TYPE_CACHED_VALUES_P(NODE) (TYPE_CHECK(NODE)->common.public_flag)
+#define TYPE_CACHED_VALUES_P(NODE) (TYPE_CHECK(NODE)->base.public_flag)
 
 /* In a SAVE_EXPR, indicates that the original expression has already
    been substituted with a VAR_DECL that contains the value.  */
 #define SAVE_EXPR_RESOLVED_P(NODE) \
-  (TREE_CHECK (NODE, SAVE_EXPR)->common.public_flag)
+  (TREE_CHECK (NODE, SAVE_EXPR)->base.public_flag)
 
 /* In any expression, decl, or constant, nonzero means it has side effects or
    reevaluation of the whole expression could produce a different value.
@@ -1101,12 +1177,12 @@ extern void omp_clause_range_check_failed (const tree, const char *, int,
    reference to a volatile variable.  In a ..._DECL, this is set only if the
    declaration said `volatile'.  This will never be set for a constant.  */
 #define TREE_SIDE_EFFECTS(NODE) \
-  (NON_TYPE_CHECK (NODE)->common.side_effects_flag)
+  (NON_TYPE_CHECK (NODE)->base.side_effects_flag)
 
 /* In a LABEL_DECL, nonzero means this label had its address taken
    and therefore can never be deleted and is a jump target for
    computed gotos.  */
-#define FORCED_LABEL(NODE) ((NODE)->common.side_effects_flag)
+#define FORCED_LABEL(NODE) ((NODE)->base.side_effects_flag)
 
 /* Nonzero means this expression is volatile in the C sense:
    its address should be of type `volatile WHATEVER *'.
@@ -1121,7 +1197,7 @@ extern void omp_clause_range_check_failed (const tree, const char *, int,
    because eventually we may make that a different bit.
 
    If this bit is set in an expression, so is TREE_SIDE_EFFECTS.  */
-#define TREE_THIS_VOLATILE(NODE) ((NODE)->common.volatile_flag)
+#define TREE_THIS_VOLATILE(NODE) ((NODE)->base.volatile_flag)
 
 /* Nonzero means this node will not trap.  In an INDIRECT_REF, means
    accessing the memory pointed to won't generate a trap.  However,
@@ -1133,11 +1209,11 @@ extern void omp_clause_range_check_failed (const tree, const char *, int,
    (or slice of the array) always belongs to the range of the array.
    I.e. that the access will not trap, provided that the access to
    the base to the array will not trap.  */
-#define TREE_THIS_NOTRAP(NODE) ((NODE)->common.nothrow_flag)
+#define TREE_THIS_NOTRAP(NODE) ((NODE)->base.nothrow_flag)
 
 /* In a VAR_DECL, PARM_DECL or FIELD_DECL, or any kind of ..._REF node,
    nonzero means it may not be the lhs of an assignment.  */
-#define TREE_READONLY(NODE) (NON_TYPE_CHECK (NODE)->common.readonly_flag)
+#define TREE_READONLY(NODE) (NON_TYPE_CHECK (NODE)->base.readonly_flag)
 
 /* Nonzero if NODE is a _DECL with TREE_READONLY set.  */
 #define TREE_READONLY_DECL_P(NODE)\
@@ -1145,20 +1221,22 @@ extern void omp_clause_range_check_failed (const tree, const char *, int,
 
 /* Value of expression is constant.  Always on in all ..._CST nodes.  May
    also appear in an expression or decl where the value is constant.  */
-#define TREE_CONSTANT(NODE) (NON_TYPE_CHECK (NODE)->common.constant_flag)
+#define TREE_CONSTANT(NODE) (NON_TYPE_CHECK (NODE)->base.constant_flag)
 
 /* Nonzero if NODE, a type, has had its sizes gimplified.  */
-#define TYPE_SIZES_GIMPLIFIED(NODE) (TYPE_CHECK (NODE)->common.constant_flag)
+#define TYPE_SIZES_GIMPLIFIED(NODE) \
+  (TYPE_CHECK (NODE)->base.constant_flag)
 
 /* In a decl (most significantly a FIELD_DECL), means an unsigned field.  */
-#define DECL_UNSIGNED(NODE) (DECL_COMMON_CHECK (NODE)->common.unsigned_flag)
+#define DECL_UNSIGNED(NODE) \
+  (DECL_COMMON_CHECK (NODE)->base.unsigned_flag)
 
 /* In a BIT_FIELD_REF, means the bitfield is to be interpreted as unsigned.  */
 #define BIT_FIELD_REF_UNSIGNED(NODE) \
-  (BIT_FIELD_REF_CHECK (NODE)->common.unsigned_flag)
+  (BIT_FIELD_REF_CHECK (NODE)->base.unsigned_flag)
 
 /* In integral and pointer types, means an unsigned type.  */
-#define TYPE_UNSIGNED(NODE) (TYPE_CHECK (NODE)->common.unsigned_flag)
+#define TYPE_UNSIGNED(NODE) (TYPE_CHECK (NODE)->base.unsigned_flag)
 
 #define TYPE_TRAP_SIGNED(NODE) \
   (flag_trapv && ! TYPE_UNSIGNED (NODE))
@@ -1172,30 +1250,32 @@ extern void omp_clause_range_check_failed (const tree, const char *, int,
    In a BLOCK node, nonzero if reorder_blocks has already seen this block.
    In an SSA_NAME node, nonzero if the SSA_NAME occurs in an abnormal
    PHI node.  */
-#define TREE_ASM_WRITTEN(NODE) ((NODE)->common.asm_written_flag)
+#define TREE_ASM_WRITTEN(NODE) ((NODE)->base.asm_written_flag)
 
 /* Nonzero in a _DECL if the name is used in its scope.
    Nonzero in an expr node means inhibit warning if value is unused.
    In IDENTIFIER_NODEs, this means that some extern decl for this name
    was used.
    In a BLOCK, this means that the block contains variables that are used.  */
-#define TREE_USED(NODE) ((NODE)->common.used_flag)
+#define TREE_USED(NODE) ((NODE)->base.used_flag)
 
 /* In a FUNCTION_DECL, nonzero means a call to the function cannot throw
    an exception.  In a CALL_EXPR, nonzero means the call cannot throw.  */
-#define TREE_NOTHROW(NODE) ((NODE)->common.nothrow_flag)
+#define TREE_NOTHROW(NODE) ((NODE)->base.nothrow_flag)
 
 /* In a CALL_EXPR, means that it's safe to use the target of the call
    expansion as the return slot for a call that returns in memory.  */
-#define CALL_EXPR_RETURN_SLOT_OPT(NODE) ((NODE)->common.private_flag)
+#define CALL_EXPR_RETURN_SLOT_OPT(NODE) ((NODE)->base.private_flag)
 
 /* In a RESULT_DECL or PARM_DECL, means that it is passed by invisible
    reference (and the TREE_TYPE is a pointer to the true type).  */
-#define DECL_BY_REFERENCE(NODE) (DECL_COMMON_CHECK (NODE)->common.private_flag)
+#define DECL_BY_REFERENCE(NODE) \
+  (DECL_COMMON_CHECK (NODE)->base.private_flag)
 
 /* In a CALL_EXPR, means that the call is the jump from a thunk to the
    thunked-to function.  */
-#define CALL_FROM_THUNK_P(NODE) (CALL_EXPR_CHECK (NODE)->common.protected_flag)
+#define CALL_FROM_THUNK_P(NODE) \
+  (CALL_EXPR_CHECK (NODE)->base.protected_flag)
 
 /* In a type, nonzero means that all objects of the type are guaranteed by the
    language or front-end to be properly aligned, so we can indicate that a MEM
@@ -1206,38 +1286,38 @@ extern void omp_clause_range_check_failed (const tree, const char *, int,
 
    In an SSA_NAME node, nonzero if the SSA_NAME node is on the SSA_NAME
    freelist.  */
-#define TYPE_ALIGN_OK(NODE) (TYPE_CHECK (NODE)->common.nothrow_flag)
+#define TYPE_ALIGN_OK(NODE) (TYPE_CHECK (NODE)->base.nothrow_flag)
 
 /* Used in classes in C++.  */
-#define TREE_PRIVATE(NODE) ((NODE)->common.private_flag)
+#define TREE_PRIVATE(NODE) ((NODE)->base.private_flag)
 /* Used in classes in C++.
    In a BLOCK node, this is BLOCK_HANDLER_BLOCK.  */
-#define TREE_PROTECTED(NODE) ((NODE)->common.protected_flag)
+#define TREE_PROTECTED(NODE) ((NODE)->base.protected_flag)
 
 /* Nonzero in a _DECL if the use of the name is defined as a
    deprecated feature by __attribute__((deprecated)).  */
 #define TREE_DEPRECATED(NODE) \
-  ((NODE)->common.deprecated_flag)
+  ((NODE)->base.deprecated_flag)
 
 /* Nonzero in an IDENTIFIER_NODE if the name is a local alias, whose
    uses are to be substituted for uses of the TREE_CHAINed identifier.  */
 #define IDENTIFIER_TRANSPARENT_ALIAS(NODE) \
-  (IDENTIFIER_NODE_CHECK (NODE)->common.deprecated_flag)
+  (IDENTIFIER_NODE_CHECK (NODE)->base.deprecated_flag)
 
 /* Value of expression is function invariant.  A strict subset of
    TREE_CONSTANT, such an expression is constant over any one function
    invocation, though not across different invocations.  May appear in
    any expression node.  */
-#define TREE_INVARIANT(NODE) ((NODE)->common.invariant_flag)
+#define TREE_INVARIANT(NODE) ((NODE)->base.invariant_flag)
 
 /* These flags are available for each language front end to use internally.  */
-#define TREE_LANG_FLAG_0(NODE) ((NODE)->common.lang_flag_0)
-#define TREE_LANG_FLAG_1(NODE) ((NODE)->common.lang_flag_1)
-#define TREE_LANG_FLAG_2(NODE) ((NODE)->common.lang_flag_2)
-#define TREE_LANG_FLAG_3(NODE) ((NODE)->common.lang_flag_3)
-#define TREE_LANG_FLAG_4(NODE) ((NODE)->common.lang_flag_4)
-#define TREE_LANG_FLAG_5(NODE) ((NODE)->common.lang_flag_5)
-#define TREE_LANG_FLAG_6(NODE) ((NODE)->common.lang_flag_6)
+#define TREE_LANG_FLAG_0(NODE) ((NODE)->base.lang_flag_0)
+#define TREE_LANG_FLAG_1(NODE) ((NODE)->base.lang_flag_1)
+#define TREE_LANG_FLAG_2(NODE) ((NODE)->base.lang_flag_2)
+#define TREE_LANG_FLAG_3(NODE) ((NODE)->base.lang_flag_3)
+#define TREE_LANG_FLAG_4(NODE) ((NODE)->base.lang_flag_4)
+#define TREE_LANG_FLAG_5(NODE) ((NODE)->base.lang_flag_5)
+#define TREE_LANG_FLAG_6(NODE) ((NODE)->base.lang_flag_6)
 
 /* Define additional fields and accessors for nodes representing constants.  */
 
@@ -1424,46 +1504,28 @@ struct tree_constructor GTY(())
 #define TREE_OPERAND(NODE, I) TREE_OPERAND_CHECK (NODE, I)
 #define TREE_COMPLEXITY(NODE) (EXPR_CHECK (NODE)->exp.complexity)
 
+/* In gimple statements.  */
+#define GIMPLE_STMT_OPERAND(NODE, I) GIMPLE_STMT_OPERAND_CHECK (NODE, I)
+#define GIMPLE_STMT_LOCUS(NODE) (GIMPLE_STMT_CHECK (NODE)->gstmt.locus)
+#define GIMPLE_STMT_BLOCK(NODE) (GIMPLE_STMT_CHECK (NODE)->gstmt.block)
+
 /* In a LOOP_EXPR node.  */
 #define LOOP_EXPR_BODY(NODE) TREE_OPERAND_CHECK_CODE (NODE, LOOP_EXPR, 0)
 
-#ifdef USE_MAPPED_LOCATION
 /* The source location of this expression.  Non-tree_exp nodes such as
    decls and constants can be shared among multiple locations, so
    return nothing.  */
-#define EXPR_LOCATION(NODE)					\
-  (EXPR_P (NODE) ? (NODE)->exp.locus : UNKNOWN_LOCATION)
-#define SET_EXPR_LOCATION(NODE, FROM) \
-  (EXPR_CHECK (NODE)->exp.locus = (FROM))
-#define EXPR_HAS_LOCATION(NODE) (EXPR_LOCATION (NODE) != UNKNOWN_LOCATION)
-/* EXPR_LOCUS and SET_EXPR_LOCUS are deprecated.  */
-#define EXPR_LOCUS(NODE)					\
-  (EXPR_P (NODE) ? &(NODE)->exp.locus : (location_t *)NULL)
-#define SET_EXPR_LOCUS(NODE, FROM) \
-  do { source_location *loc_tmp = FROM; \
-       EXPR_CHECK (NODE)->exp.locus \
-       = loc_tmp == NULL ? UNKNOWN_LOCATION : *loc_tmp; } while (0)
-#define EXPR_FILENAME(NODE) \
-  LOCATION_FILE (EXPR_CHECK (NODE)->exp.locus)
-#define EXPR_LINENO(NODE) \
-  LOCATION_LINE (EXPR_CHECK (NODE)->exp.locus)
-#else
-/* The source location of this expression.  Non-tree_exp nodes such as
-   decls and constants can be shared among multiple locations, so
-   return nothing.  */
-#define EXPR_LOCUS(NODE)					\
-  (EXPR_P (NODE) ? (NODE)->exp.locus : (location_t *)NULL)
-#define SET_EXPR_LOCUS(NODE, FROM) \
-  (EXPR_CHECK (NODE)->exp.locus = (FROM))
-#define SET_EXPR_LOCATION(NODE, FROM) annotate_with_locus (NODE, FROM)
-#define EXPR_FILENAME(NODE) \
-  (EXPR_CHECK (NODE)->exp.locus->file)
-#define EXPR_LINENO(NODE) \
-  (EXPR_CHECK (NODE)->exp.locus->line)
-#define EXPR_HAS_LOCATION(NODE) (EXPR_LOCUS (NODE) != NULL)
-#define EXPR_LOCATION(NODE) \
-  (EXPR_HAS_LOCATION(NODE) ? *(NODE)->exp.locus : UNKNOWN_LOCATION)
-#endif
+#define EXPR_LOCATION(NODE) expr_location ((NODE))
+#define SET_EXPR_LOCATION(NODE, FROM) set_expr_location ((NODE), (FROM))
+#define EXPR_HAS_LOCATION(NODE) expr_has_location ((NODE))
+#define EXPR_LOCUS(NODE) expr_locus ((NODE))
+#define SET_EXPR_LOCUS(NODE, FROM) set_expr_locus ((NODE), (FROM))
+#define EXPR_FILENAME(NODE) *(expr_filename ((NODE)))
+#define EXPR_LINENO(NODE) *(expr_lineno ((NODE)))
+
+/* True if a tree is an expression or statement that can have a
+   location.  */
+#define CAN_HAVE_LOCATION_P(NODE) (EXPR_P (NODE) || GIMPLE_STMT_P (NODE))
 
 /* In a TARGET_EXPR node.  */
 #define TARGET_EXPR_SLOT(NODE) TREE_OPERAND_CHECK_CODE (NODE, TARGET_EXPR, 0)
@@ -1686,13 +1748,13 @@ struct tree_exp GTY(())
    never output, so we can safely use the ASM_WRITTEN_FLAG for this
    status bit.  */
 #define SSA_NAME_OCCURS_IN_ABNORMAL_PHI(NODE) \
-    SSA_NAME_CHECK (NODE)->common.asm_written_flag
+    SSA_NAME_CHECK (NODE)->base.asm_written_flag
 
 /* Nonzero if this SSA_NAME expression is currently on the free list of
    SSA_NAMES.  Using NOTHROW_FLAG seems reasonably safe since throwing
    has no meaning for an SSA_NAME.  */
 #define SSA_NAME_IN_FREE_LIST(NODE) \
-    SSA_NAME_CHECK (NODE)->common.nothrow_flag
+    SSA_NAME_CHECK (NODE)->base.nothrow_flag
 
 /* Attributes for SSA_NAMEs for pointer-type variables.  */
 #define SSA_NAME_PTR_INFO(N) \
@@ -1998,10 +2060,10 @@ struct tree_block GTY(())
   (FUNCTION_TYPE_CHECK (NODE)->type.no_force_blk_flag)
 
 /* Nonzero in a type considered volatile as a whole.  */
-#define TYPE_VOLATILE(NODE) (TYPE_CHECK (NODE)->common.volatile_flag)
+#define TYPE_VOLATILE(NODE) (TYPE_CHECK (NODE)->base.volatile_flag)
 
 /* Means this type is const-qualified.  */
-#define TYPE_READONLY(NODE) (TYPE_CHECK (NODE)->common.readonly_flag)
+#define TYPE_READONLY(NODE) (TYPE_CHECK (NODE)->base.readonly_flag)
 
 /* If nonzero, this type is `restrict'-qualified, in the C sense of
    the term.  */
@@ -2033,7 +2095,7 @@ struct tree_block GTY(())
 
 /* Used to keep track of visited nodes in tree traversals.  This is set to
    0 by copy_node and make_node.  */
-#define TREE_VISITED(NODE) ((NODE)->common.visited)
+#define TREE_VISITED(NODE) ((NODE)->base.visited)
 
 /* If set in an ARRAY_TYPE, indicates a string type (for languages
    that distinguish string from array of char).
@@ -2150,7 +2212,7 @@ struct tree_type GTY(())
 /* BINFO specific flags.  */
 
 /* Nonzero means that the derivation chain is via a `virtual' declaration.  */
-#define BINFO_VIRTUAL_P(NODE) (TREE_BINFO_CHECK (NODE)->common.static_flag)
+#define BINFO_VIRTUAL_P(NODE) (TREE_BINFO_CHECK (NODE)->base.static_flag)
 
 /* Flags for language dependent use.  */
 #define BINFO_MARKED(NODE) TREE_LANG_FLAG_0(TREE_BINFO_CHECK(NODE))
@@ -3164,6 +3226,7 @@ struct tree_value_handle GTY(())
 union tree_node GTY ((ptr_alias (union lang_tree_node),
 		      desc ("tree_node_structure (&%h)")))
 {
+  struct tree_base GTY ((tag ("TS_BASE"))) base;
   struct tree_common GTY ((tag ("TS_COMMON"))) common;
   struct tree_int_cst GTY ((tag ("TS_INT_CST"))) int_cst;
   struct tree_real_cst GTY ((tag ("TS_REAL_CST"))) real_cst;
@@ -3193,6 +3256,7 @@ union tree_node GTY ((ptr_alias (union lang_tree_node),
   struct tree_block GTY ((tag ("TS_BLOCK"))) block;
   struct tree_binfo GTY ((tag ("TS_BINFO"))) binfo;
   struct tree_statement_list GTY ((tag ("TS_STATEMENT_LIST"))) stmt_list;
+  struct gimple_stmt GTY ((tag ("TS_GIMPLE_STATEMENT"))) gstmt;
   struct tree_value_handle GTY ((tag ("TS_VALUE_HANDLE"))) value_handle;
   struct tree_constructor GTY ((tag ("TS_CONSTRUCTOR"))) constructor;
   struct tree_memory_tag GTY ((tag ("TS_MEMORY_TAG"))) mtag;
@@ -3530,6 +3594,8 @@ extern tree build1_stat (enum tree_code, tree, tree MEM_STAT_DECL);
 #define build1(c,t1,t2) build1_stat (c,t1,t2 MEM_STAT_INFO)
 extern tree build2_stat (enum tree_code, tree, tree, tree MEM_STAT_DECL);
 #define build2(c,t1,t2,t3) build2_stat (c,t1,t2,t3 MEM_STAT_INFO)
+extern tree build2_gimple_stat (enum tree_code, tree, tree MEM_STAT_DECL);
+#define build2_gimple(c,t1,t2) build2_gimple_stat (c,t1,t2 MEM_STAT_INFO)
 extern tree build3_stat (enum tree_code, tree, tree, tree, tree MEM_STAT_DECL);
 #define build3(c,t1,t2,t3,t4) build3_stat (c,t1,t2,t3,t4 MEM_STAT_INFO)
 extern tree build4_stat (enum tree_code, tree, tree, tree, tree,
@@ -4353,6 +4419,29 @@ extern tree build_addr (tree, tree);
 extern bool fields_compatible_p (tree, tree);
 extern tree find_compatible_field (tree, tree);
 
+extern location_t expr_location (tree);
+extern void set_expr_location (tree, location_t);
+extern bool expr_has_location (tree);
+extern
+#ifdef USE_MAPPED_LOCATION
+source_location *
+#else
+source_locus
+#endif
+expr_locus (tree);
+extern void set_expr_locus (tree,
+#ifdef USE_MAPPED_LOCATION
+                            source_location *loc
+#else
+		            source_locus loc
+#endif
+			   );
+extern const char **expr_filename (tree);
+extern int *expr_lineno (tree);
+extern tree *tree_block (tree);
+extern tree *generic_tree_operand (tree, int);
+extern tree *generic_tree_type (tree);
+
 /* In function.c */
 extern void expand_main_function (void);
 extern void init_dummy_function_start (void);
@@ -4570,6 +4659,7 @@ typedef enum
   lang_decl,
   lang_type,
   omp_clause_kind,
+  gimple_stmt_kind,
   all_kinds
 } tree_node_kind;
 
diff --git a/gcc/treestruct.def b/gcc/treestruct.def
index b826be65242c477df3002d3e4cefd8b666ea357d..741876dd31ee34597746fc27fcd49e4785df1a15 100644
--- a/gcc/treestruct.def
+++ b/gcc/treestruct.def
@@ -28,6 +28,7 @@ Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
    tree_node for garbage collection purposes, as well as specifying what structures
    contain what other structures in the tree_contains_struct array.  */
 	
+DEFTREESTRUCT(TS_BASE, "base")
 DEFTREESTRUCT(TS_COMMON, "common")
 DEFTREESTRUCT(TS_INT_CST, "integer cst")
 DEFTREESTRUCT(TS_REAL_CST, "real cst")
@@ -57,6 +58,7 @@ DEFTREESTRUCT(TS_PHI_NODE, "phi node")
 DEFTREESTRUCT(TS_BLOCK, "block")
 DEFTREESTRUCT(TS_BINFO, "binfo")
 DEFTREESTRUCT(TS_STATEMENT_LIST, "statement list")
+DEFTREESTRUCT(TS_GIMPLE_STATEMENT, "gimple statement")
 DEFTREESTRUCT(TS_VALUE_HANDLE, "value handle")
 DEFTREESTRUCT(TS_CONSTRUCTOR, "constructor")
 DEFTREESTRUCT(TS_MEMORY_TAG, "memory tag")
diff --git a/gcc/value-prof.c b/gcc/value-prof.c
index 993bd514ad42ff7788f36cb50b51cd96fbc2c35f..93704e28410d66248c2628a1a115158859966b84 100644
--- a/gcc/value-prof.c
+++ b/gcc/value-prof.c
@@ -193,8 +193,9 @@ tree_divmod_fixed_value (tree stmt, tree operation,
 
   tmpv = create_tmp_var (optype, "PROF");
   tmp1 = create_tmp_var (optype, "PROF");
-  stmt1 = build2 (MODIFY_EXPR, optype, tmpv, fold_convert (optype, value));
-  stmt2 = build2 (MODIFY_EXPR, optype, tmp1, op2);
+  stmt1 = build2 (GIMPLE_MODIFY_STMT, optype, tmpv,
+		  fold_convert (optype, value));
+  stmt2 = build2 (GIMPLE_MODIFY_STMT, optype, tmp1, op2);
   stmt3 = build3 (COND_EXPR, void_type_node,
 	    build2 (NE_EXPR, boolean_type_node, tmp1, tmpv),
 	    build1 (GOTO_EXPR, void_type_node, label_decl2),
@@ -206,14 +207,14 @@ tree_divmod_fixed_value (tree stmt, tree operation,
 
   tmp2 = create_tmp_var (optype, "PROF");
   label1 = build1 (LABEL_EXPR, void_type_node, label_decl1);
-  stmt1 = build2 (MODIFY_EXPR, optype, tmp2,
+  stmt1 = build2 (GIMPLE_MODIFY_STMT, optype, tmp2,
 		  build2 (TREE_CODE (operation), optype, op1, tmpv));
   bsi_insert_before (&bsi, label1, BSI_SAME_STMT);
   bsi_insert_before (&bsi, stmt1, BSI_SAME_STMT);
   bb2end = stmt1;
 
   label2 = build1 (LABEL_EXPR, void_type_node, label_decl2);
-  stmt1 = build2 (MODIFY_EXPR, optype, tmp2,
+  stmt1 = build2 (GIMPLE_MODIFY_STMT, optype, tmp2,
 		  build2 (TREE_CODE (operation), optype, op1, op2));
   bsi_insert_before (&bsi, label2, BSI_SAME_STMT);
   bsi_insert_before (&bsi, stmt1, BSI_SAME_STMT);
@@ -269,11 +270,11 @@ tree_divmod_fixed_value_transform (tree stmt)
   modify = stmt;
   if (TREE_CODE (stmt) == RETURN_EXPR
       && TREE_OPERAND (stmt, 0)
-      && TREE_CODE (TREE_OPERAND (stmt, 0)) == MODIFY_EXPR)
+      && TREE_CODE (TREE_OPERAND (stmt, 0)) == GIMPLE_MODIFY_STMT)
     modify = TREE_OPERAND (stmt, 0);
-  if (TREE_CODE (modify) != MODIFY_EXPR)
+  if (TREE_CODE (modify) != GIMPLE_MODIFY_STMT)
     return false;
-  op = TREE_OPERAND (modify, 1);
+  op = GIMPLE_STMT_OPERAND (modify, 1);
   if (!INTEGRAL_TYPE_P (TREE_TYPE (op)))
     return false;
   code = TREE_CODE (op);
@@ -325,7 +326,7 @@ tree_divmod_fixed_value_transform (tree stmt)
       print_generic_stmt (dump_file, stmt, TDF_SLIM);
     }
 
-  TREE_OPERAND (modify, 1) = result;
+  GIMPLE_STMT_OPERAND (modify, 1) = result;
 
   return true;
 }
@@ -357,9 +358,9 @@ tree_mod_pow2 (tree stmt, tree operation, tree op1, tree op2, int prob,
 
   tmp2 = create_tmp_var (optype, "PROF");
   tmp3 = create_tmp_var (optype, "PROF");
-  stmt2 = build2 (MODIFY_EXPR, optype, tmp2, 
+  stmt2 = build2 (GIMPLE_MODIFY_STMT, optype, tmp2, 
 		  build2 (PLUS_EXPR, optype, op2, build_int_cst (optype, -1)));
-  stmt3 = build2 (MODIFY_EXPR, optype, tmp3,
+  stmt3 = build2 (GIMPLE_MODIFY_STMT, optype, tmp3,
 		  build2 (BIT_AND_EXPR, optype, tmp2, op2));
   stmt4 = build3 (COND_EXPR, void_type_node,
 		  build2 (NE_EXPR, boolean_type_node,
@@ -373,14 +374,14 @@ tree_mod_pow2 (tree stmt, tree operation, tree op1, tree op2, int prob,
 
   /* tmp2 == op2-1 inherited from previous block */
   label1 = build1 (LABEL_EXPR, void_type_node, label_decl1);
-  stmt1 = build2 (MODIFY_EXPR, optype, result,
+  stmt1 = build2 (GIMPLE_MODIFY_STMT, optype, result,
 		  build2 (BIT_AND_EXPR, optype, op1, tmp2));
   bsi_insert_before (&bsi, label1, BSI_SAME_STMT);
   bsi_insert_before (&bsi, stmt1, BSI_SAME_STMT);
   bb2end = stmt1;
 
   label2 = build1 (LABEL_EXPR, void_type_node, label_decl2);
-  stmt1 = build2 (MODIFY_EXPR, optype, result,
+  stmt1 = build2 (GIMPLE_MODIFY_STMT, optype, result,
 		  build2 (TREE_CODE (operation), optype, op1, op2));
   bsi_insert_before (&bsi, label2, BSI_SAME_STMT);
   bsi_insert_before (&bsi, stmt1, BSI_SAME_STMT);
@@ -436,11 +437,11 @@ tree_mod_pow2_value_transform (tree stmt)
   modify = stmt;
   if (TREE_CODE (stmt) == RETURN_EXPR
       && TREE_OPERAND (stmt, 0)
-      && TREE_CODE (TREE_OPERAND (stmt, 0)) == MODIFY_EXPR)
+      && TREE_CODE (TREE_OPERAND (stmt, 0)) == GIMPLE_MODIFY_STMT)
     modify = TREE_OPERAND (stmt, 0);
-  if (TREE_CODE (modify) != MODIFY_EXPR)
+  if (TREE_CODE (modify) != GIMPLE_MODIFY_STMT)
     return false;
-  op = TREE_OPERAND (modify, 1);
+  op = GIMPLE_STMT_OPERAND (modify, 1);
   if (!INTEGRAL_TYPE_P (TREE_TYPE (op)))
     return false;
   code = TREE_CODE (op);
@@ -483,7 +484,7 @@ tree_mod_pow2_value_transform (tree stmt)
 
   result = tree_mod_pow2 (stmt, op, op1, op2, prob, count, all);
 
-  TREE_OPERAND (modify, 1) = result;
+  GIMPLE_STMT_OPERAND (modify, 1) = result;
 
   return true;
 }
@@ -520,8 +521,8 @@ tree_mod_subtract (tree stmt, tree operation, tree op1, tree op2,
   bsi = bsi_for_stmt (stmt);
 
   tmp1 = create_tmp_var (optype, "PROF");
-  stmt1 = build2 (MODIFY_EXPR, optype, result, op1);
-  stmt2 = build2 (MODIFY_EXPR, optype, tmp1, op2);
+  stmt1 = build2 (GIMPLE_MODIFY_STMT, optype, result, op1);
+  stmt2 = build2 (GIMPLE_MODIFY_STMT, optype, tmp1, op2);
   stmt3 = build3 (COND_EXPR, void_type_node,
 	    build2 (LT_EXPR, boolean_type_node, result, tmp1),
 	    build1 (GOTO_EXPR, void_type_node, label_decl3),
@@ -535,7 +536,7 @@ tree_mod_subtract (tree stmt, tree operation, tree op1, tree op2,
   if (ncounts)	/* Assumed to be 0 or 1 */
     {
       label1 = build1 (LABEL_EXPR, void_type_node, label_decl1);
-      stmt1 = build2 (MODIFY_EXPR, optype, result,
+      stmt1 = build2 (GIMPLE_MODIFY_STMT, optype, result,
 		      build2 (MINUS_EXPR, optype, result, tmp1));
       stmt2 = build3 (COND_EXPR, void_type_node,
 		build2 (LT_EXPR, boolean_type_node, result, tmp1),
@@ -549,7 +550,7 @@ tree_mod_subtract (tree stmt, tree operation, tree op1, tree op2,
 
   /* Fallback case. */
   label2 = build1 (LABEL_EXPR, void_type_node, label_decl2);
-  stmt1 = build2 (MODIFY_EXPR, optype, result,
+  stmt1 = build2 (GIMPLE_MODIFY_STMT, optype, result,
 		    build2 (TREE_CODE (operation), optype, result, tmp1));
   bsi_insert_before (&bsi, label2, BSI_SAME_STMT);
   bsi_insert_before (&bsi, stmt1, BSI_SAME_STMT);
@@ -619,11 +620,11 @@ tree_mod_subtract_transform (tree stmt)
   modify = stmt;
   if (TREE_CODE (stmt) == RETURN_EXPR
       && TREE_OPERAND (stmt, 0)
-      && TREE_CODE (TREE_OPERAND (stmt, 0)) == MODIFY_EXPR)
+      && TREE_CODE (TREE_OPERAND (stmt, 0)) == GIMPLE_MODIFY_STMT)
     modify = TREE_OPERAND (stmt, 0);
-  if (TREE_CODE (modify) != MODIFY_EXPR)
+  if (TREE_CODE (modify) != GIMPLE_MODIFY_STMT)
     return false;
-  op = TREE_OPERAND (modify, 1);
+  op = GIMPLE_STMT_OPERAND (modify, 1);
   if (!INTEGRAL_TYPE_P (TREE_TYPE (op)))
     return false;
   code = TREE_CODE (op);
@@ -685,7 +686,7 @@ tree_mod_subtract_transform (tree stmt)
 			    histogram->hvalue.counters[0], 
 			    histogram->hvalue.counters[1], all);
 
-  TREE_OPERAND (modify, 1) = result;
+  GIMPLE_STMT_OPERAND (modify, 1) = result;
 
   return true;
 }
@@ -713,14 +714,14 @@ tree_divmod_values_to_profile (tree stmt, histogram_values *values)
     assign = stmt;
 
   if (!assign
-      || TREE_CODE (assign) != MODIFY_EXPR)
+      || TREE_CODE (assign) != GIMPLE_MODIFY_STMT)
     return;
-  lhs = TREE_OPERAND (assign, 0);
+  lhs = GIMPLE_STMT_OPERAND (assign, 0);
   type = TREE_TYPE (lhs);
   if (!INTEGRAL_TYPE_P (type))
     return;
 
-  rhs = TREE_OPERAND (assign, 1);
+  rhs = GIMPLE_STMT_OPERAND (assign, 1);
   switch (TREE_CODE (rhs))
     {
     case TRUNC_DIV_EXPR: