diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 28ff3c0cd88cc79173ad39c12f8b04b7860a7694..433d599a6cdd493c68c6abd3debe274ce6265525 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,17 @@
+2004-05-13  Diego Novillo  <dnovillo@redhat.com>
+
+	* tree-gimple.c: Rename from tree-simple.c.
+	* tree-gimple.h: Rename from tree-simple.h.
+	* c-gimplify.c: Rename from c-simplify.c
+	* Makefile.in, c-decl.c, gimple-low.c, gimplify.c,
+	langhooks.c, tree-alias-ander.c, tree-alias-common.c,
+	tree-complex.c, tree-dfa.c, tree-flow.h, tree-inline.c,
+	tree-into-ssa.c, tree-iterator.c, tree-mudflap.c,
+	tree-nested.c, tree-nomudflap.c, tree-outof-ssa.c, tree-sra.c,
+	tree-ssa-alias.c, tree-ssa-ccp.c, tree-ssa-copyrename.c,
+	tree-ssa-dce.c, tree-ssa-live.c, tree-ssa-pre.c, tree-ssa.c:
+	Update.
+
 2004-05-14  Ranjit Mathew  <rmathew@hotmail.com>
 
 	* doc/sourcebuild.texi: Mention libbanshee and libmudflap.
diff --git a/gcc/Makefile.in b/gcc/Makefile.in
index bfeaa0c37ca8996da90b6650ca8ac3d1486d837d..5379c8e59d4ef56f5c96ee8b7cf407fb32248375 100644
--- a/gcc/Makefile.in
+++ b/gcc/Makefile.in
@@ -702,9 +702,9 @@ SYSTEM_H = system.h hwint.h $(srcdir)/../include/libiberty.h
 PREDICT_H = predict.h predict.def
 CPPLIB_H = cpplib.h line-map.h
 TREE_DUMP_H = tree-dump.h $(SPLAY_TREE_H)
-TREE_SIMPLE_H = tree-simple.h tree-iterator.h
+TREE_GIMPLE_H = tree-gimple.h tree-iterator.h
 TREE_FLOW_H = tree-flow.h tree-flow-inline.h tree-ssa-operands.h \
-		bitmap.h $(BASIC_BLOCK_H) hard-reg-set.h $(TREE_SIMPLE_H) \
+		bitmap.h $(BASIC_BLOCK_H) hard-reg-set.h $(TREE_GIMPLE_H) \
 		$(HASHTAB_H)
 PRETTY_PRINT_H = pretty-print.h input.h $(OBSTACK_H)
 DIAGNOSTIC_H = diagnostic.h diagnostic.def $(PRETTY_PRINT_H)
@@ -859,7 +859,7 @@ C_AND_OBJC_OBJS = attribs.o c-errors.o c-lex.o c-pragma.o c-decl.o c-typeck.o \
   c-convert.o c-aux-info.o c-common.o c-opts.o c-format.o c-semantics.o \
   c-incpath.o cppdefault.o c-ppoutput.o c-cppbuiltin.o prefix.o \
   c-objc-common.o c-dump.o c-pch.o $(C_TARGET_OBJS) \
-  c-simplify.o tree-mudflap.o c-mudflap.o c-pretty-print.o
+  c-gimplify.o tree-mudflap.o c-mudflap.o c-pretty-print.o
 
 # Language-specific object files for C.
 C_OBJS = c-parse.o c-lang.o stub-objc.o $(C_AND_OBJC_OBJS)
@@ -867,7 +867,7 @@ C_OBJS = c-parse.o c-lang.o stub-objc.o $(C_AND_OBJC_OBJS)
 # Language-independent object files.
 
 OBJS-common = \
- tree-cfg.o tree-dfa.o tree-eh.o tree-ssa.o tree-optimize.o tree-simple.o  \
+ tree-cfg.o tree-dfa.o tree-eh.o tree-ssa.o tree-optimize.o tree-gimple.o  \
  tree-alias-type.o gimplify.o tree-pretty-print.o tree-into-ssa.o          \
  tree-outof-ssa.o tree-alias-common.o tree-ssa-ccp.o			   \
  @ANDER@ tree-ssa-dce.o  tree-ssa-copy.o tree-nrv.o tree-ssa-copyrename.o  \
@@ -1545,7 +1545,7 @@ tree-inline.o : tree-inline.c $(CONFIG_H) $(SYSTEM_H) coretypes.h $(TM_H) \
    $(TREE_H) $(RTL_H) $(EXPR_H) flags.h $(PARAMS_H) input.h insn-config.h \
    $(INTEGRATE_H) $(VARRAY_H) $(HASHTAB_H) $(SPLAY_TREE_H) toplev.h \
    langhooks.h $(C_COMMON_H) tree-inline.h cgraph.h intl.h function.h \
-   $(TREE_SIMPLE_H)
+   $(TREE_GIMPLE_H)
 print-tree.o : print-tree.c $(CONFIG_H) $(SYSTEM_H) coretypes.h $(TM_H) $(TREE_H) \
    $(GGC_H) langhooks.h real.h
 stor-layout.o : stor-layout.c $(CONFIG_H) $(SYSTEM_H) coretypes.h $(TM_H) $(TREE_H) \
@@ -1622,9 +1622,9 @@ tree-tailcall.o : tree-tailcall.c $(TREE_FLOW_H) $(CONFIG_H) $(SYSTEM_H) \
    $(TREE_DUMP_H) diagnostic.h except.h tree-pass.h flags.h langhooks.h
 tree-nested.o: tree-nested.c $(CONFIG_H) $(SYSTEM_H) $(TM_H) $(TREE_H) \
    $(RTL_H) $(TM_P_H) function.h tree-dump.h tree-inline.h tree-iterator.h \
-   tree-simple.h cgraph.h $(EXPR_H) langhooks.h $(GGC_H) gt-tree-nested.h
+   tree-gimple.h cgraph.h $(EXPR_H) langhooks.h $(GGC_H) gt-tree-nested.h
 tree-iterator.o : tree-iterator.c $(CONFIG_H) $(SYSTEM_H) $(TREE_H) \
-   coretypes.h $(GGC_H) tree-iterator.h tree-simple.h gt-tree-iterator.h
+   coretypes.h $(GGC_H) tree-iterator.h tree-gimple.h gt-tree-iterator.h
 tree-dfa.o : tree-dfa.c $(TREE_FLOW_H) $(CONFIG_H) $(SYSTEM_H) \
    $(RTL_H) $(TREE_H) $(TM_P_H) $(EXPR_H) $(GGC_H) output.h diagnostic.h \
    errors.h tree-inline.h $(HASHTAB_H) flags.h function.h $(TIMEVAR_H) \
@@ -1650,32 +1650,32 @@ tree-optimize.o : tree-optimize.c $(TREE_FLOW_H) $(CONFIG_H) \
    $(TIMEVAR_H) $(TM_H) coretypes.h $(TREE_DUMP_H) toplev.h function.h \
    langhooks.h flags.h cgraph.h tree-inline.h tree-mudflap.h $(GGC_H) \
    cgraph.h tree-pass.h
-c-simplify.o : c-simplify.c $(CONFIG_H) $(SYSTEM_H) $(TREE_H) errors.h \
-   $(C_TREE_H) $(C_COMMON_H) diagnostic.h $(TREE_SIMPLE_H) varray.h flags.h \
+c-gimplify.o : c-gimplify.c $(CONFIG_H) $(SYSTEM_H) $(TREE_H) errors.h \
+   $(C_TREE_H) $(C_COMMON_H) diagnostic.h $(TREE_GIMPLE_H) varray.h flags.h \
    langhooks.h toplev.h rtl.h $(TREE_FLOW_H) langhooks-def.h \
    $(TM_H) coretypes.h $(C_PRETTY_PRINT_H) cgraph.h
 gimplify.o : gimplify.c $(CONFIG_H) $(SYSTEM_H) $(TREE_H) errors.h \
-   diagnostic.h $(TREE_SIMPLE_H) tree-inline.h varray.h langhooks.h \
+   diagnostic.h $(TREE_GIMPLE_H) tree-inline.h varray.h langhooks.h \
    langhooks-def.h $(TREE_FLOW_H) $(TIMEVAR_H) $(TM_H) coretypes.h except.h \
    flags.h $(RTL_H) function.h $(EXPR_H) output.h $(GGC_H) gt-gimplify.h
 gimple-low.o : gimple-low.c $(CONFIG_H) $(SYSTEM_H) $(TREE_H) errors.h \
-   diagnostic.h $(TREE_SIMPLE_H) tree-inline.h varray.h langhooks.h \
+   diagnostic.h $(TREE_GIMPLE_H) tree-inline.h varray.h langhooks.h \
    langhooks-def.h $(TREE_FLOW_H) $(TIMEVAR_H) $(TM_H) coretypes.h except.h \
    flags.h $(RTL_H) function.h tree-pass.h
 tree-browser.o : tree-browser.c tree-browser.def $(CONFIG_H) $(SYSTEM_H) \
    $(TREE_H) errors.h tree-inline.h diagnostic.h $(HASHTAB_H) \
    $(TM_H) coretypes.h
-tree-simple.o : tree-simple.c $(CONFIG_H) $(SYSTEM_H) $(TREE_H) $(EXPR_H) \
-	$(RTL_H) $(TREE_SIMPLE_H) $(TM_H) coretypes.h bitmap.h $(GGC_H)
+tree-gimple.o : tree-gimple.c $(CONFIG_H) $(SYSTEM_H) $(TREE_H) $(EXPR_H) \
+	$(RTL_H) $(TREE_GIMPLE_H) $(TM_H) coretypes.h bitmap.h $(GGC_H)
 tree-mudflap.o : $(CONFIG_H) errors.h $(SYSTEM_H) $(TREE_H) tree-inline.h \
-   $(C_TREE_H) $(C_COMMON_H) $(TREE_SIMPLE_H) diagnostic.h $(HASHTAB_H) \
+   $(C_TREE_H) $(C_COMMON_H) $(TREE_GIMPLE_H) diagnostic.h $(HASHTAB_H) \
    output.h varray.h langhooks.h tree-mudflap.h $(TM_H) coretypes.h \
    $(TREE_DUMP_H) tree-pass.h
 c-mudflap.o : $(CONFIG_H) errors.h $(SYSTEM_H) $(TREE_H) tree-inline.h \
-   $(C_TREE_H) $(C_COMMON_H) $(TREE_SIMPLE_H) diagnostic.h $(HASHTAB_H) \
+   $(C_TREE_H) $(C_COMMON_H) $(TREE_GIMPLE_H) diagnostic.h $(HASHTAB_H) \
    output.h varray.h langhooks.h tree-mudflap.h $(TM_H) coretypes.h
 tree-nomudflap.o : $(CONFIG_H) errors.h $(SYSTEM_H) $(TREE_H) tree-inline.h \
-   $(C_TREE_H) $(C_COMMON_H) $(TREE_SIMPLE_H) diagnostic.h $(HASHTAB_H) \
+   $(C_TREE_H) $(C_COMMON_H) $(TREE_GIMPLE_H) diagnostic.h $(HASHTAB_H) \
    output.h varray.h langhooks.h tree-mudflap.h $(TM_H) coretypes.h
 tree-pretty-print.o : tree-pretty-print.c $(CONFIG_H) $(SYSTEM_H) \
    errors.h $(TREE_H) diagnostic.h real.h $(HASHTAB_H) $(TREE_FLOW_H) \
@@ -1850,14 +1850,14 @@ tree-ssa-dce.o : tree-ssa-dce.c $(CONFIG_H) system.h errors.h $(TREE_H) \
     coretypes.h $(TREE_DUMP_H) tree-pass.h flags.h
 tree-ssa-ccp.o : tree-ssa-ccp.c $(CONFIG_H) system.h errors.h $(TREE_H) \
     $(RTL_H) $(TM_P_H) $(TREE_FLOW_H) diagnostic.h tree-inline.h \
-    $(TIMEVAR_H) $(TM_H) coretypes.h $(TREE_DUMP_H) $(TREE_SIMPLE_H) \
+    $(TIMEVAR_H) $(TM_H) coretypes.h $(TREE_DUMP_H) $(TREE_GIMPLE_H) \
     $(EXPR_H) tree-pass.h flags.h langhooks.h
 tree-sra.o : tree-sra.c $(CONFIG_H) system.h errors.h $(TREE_H) $(RTL_H) \
     $(TM_P_H) $(TREE_FLOW_H) diagnostic.h tree-inline.h \
-    $(TIMEVAR_H) $(TM_H) coretypes.h $(TREE_DUMP_H) $(TREE_SIMPLE_H) \
+    $(TIMEVAR_H) $(TM_H) coretypes.h $(TREE_DUMP_H) $(TREE_GIMPLE_H) \
     langhooks.h tree-pass.h flags.h
 tree-complex.o : tree-complex.c $(CONFIG_H) system.h $(TREE_H) \
-    $(TM_H) $(TREE_FLOW_H) $(TREE_SIMPLE_H) tree-iterator.h tree-pass.h \
+    $(TM_H) $(TREE_FLOW_H) $(TREE_GIMPLE_H) tree-iterator.h tree-pass.h \
     flags.h
 df.o : df.c $(CONFIG_H) $(SYSTEM_H) coretypes.h $(TM_H) $(RTL_H) \
    insn-config.h $(RECOG_H) function.h $(REGS_H) alloc-pool.h hard-reg-set.h \
diff --git a/gcc/c-decl.c b/gcc/c-decl.c
index d0fc708ea052911298fce3be2d238d95650d0611..8ca5b086ca2416799a30cd41dbb6e535a72b63a8 100644
--- a/gcc/c-decl.c
+++ b/gcc/c-decl.c
@@ -51,7 +51,7 @@ Software Foundation, 59 Temple Place - Suite 330, Boston, MA
 #include "c-pragma.h"
 #include "langhooks.h"
 #include "tree-mudflap.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "diagnostic.h"
 #include "tree-dump.h"
 #include "cgraph.h"
diff --git a/gcc/c-simplify.c b/gcc/c-gimplify.c
similarity index 99%
rename from gcc/c-simplify.c
rename to gcc/c-gimplify.c
index bd50b5e025b88bc2628e9729db1271f28674356a..49b3a671b75e92a7fac1f5e1fbbee957156b4f65 100644
--- a/gcc/c-simplify.c
+++ b/gcc/c-gimplify.c
@@ -33,7 +33,7 @@ Software Foundation, 59 Temple Place - Suite 330, Boston, MA
 #include "varray.h"
 #include "c-tree.h"
 #include "c-common.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "hard-reg-set.h"
 #include "basic-block.h"
 #include "tree-flow.h"
diff --git a/gcc/cp/ChangeLog b/gcc/cp/ChangeLog
index 9d990ee36429e4d815e9dee2b7a84c1514cc02a7..25c72524de40a320154a10c3a07d6833df39f73f 100644
--- a/gcc/cp/ChangeLog
+++ b/gcc/cp/ChangeLog
@@ -1,3 +1,8 @@
+2004-05-13  Diego Novillo  <dnovillo@redhat.com>
+
+	* cp-gimplify.c: Rename from cp-simplify.c.
+	* Make-lang.in, optimize.c: Update.
+
 2004-05-13  Diego Novillo  <dnovillo@redhat.com>
 
 	Merge from tree-ssa-20020619-branch.  See
diff --git a/gcc/cp/Make-lang.in b/gcc/cp/Make-lang.in
index bf4b0fe850f5e0f6ae0dc7add5e8239fc019cb83..12decae82f147fa20d3c02a2765cdab9b7f7d91e 100644
--- a/gcc/cp/Make-lang.in
+++ b/gcc/cp/Make-lang.in
@@ -74,7 +74,7 @@ g++-cross$(exeext): g++$(exeext)
 CXX_C_OBJS = attribs.o c-common.o c-format.o c-pragma.o c-semantics.o c-lex.o \
 	c-dump.o $(CXX_TARGET_OBJS) c-pretty-print.o c-opts.o c-pch.o \
 	c-incpath.o cppdefault.o c-ppoutput.o c-cppbuiltin.o prefix.o \
-	c-simplify.o tree-inline.o
+	c-gimplify.o tree-inline.o
 
 # Language-specific object files.
 CXX_OBJS = cp/call.o cp/decl.o cp/expr.o cp/pt.o cp/typeck2.o \
@@ -82,7 +82,7 @@ CXX_OBJS = cp/call.o cp/decl.o cp/expr.o cp/pt.o cp/typeck2.o \
  cp/typeck.o cp/cvt.o cp/except.o cp/friend.o cp/init.o cp/method.o \
  cp/search.o cp/semantics.o cp/tree.o cp/repo.o cp/dump.o cp/optimize.o \
  cp/mangle.o cp/cp-lang.o cp/name-lookup.o cp/cxx-pretty-print.o \
- cp/cp-simplify.o tree-mudflap.o cp/cp-mudflap.o
+ cp/cp-gimplify.o tree-mudflap.o cp/cp-mudflap.o
 
 # Use strict warnings for this front end.
 cp-warn = $(STRICT_WARN) $(WERROR)
@@ -259,13 +259,13 @@ cp/semantics.o: cp/semantics.c $(CXX_TREE_H) $(TM_H) cp/lex.h except.h toplev.h
   tree-inline.h cgraph.h
 cp/dump.o: cp/dump.c $(CXX_TREE_H) $(TM_H) tree-dump.h
 cp/optimize.o: cp/optimize.c $(CXX_TREE_H) $(TM_H) rtl.h integrate.h insn-config.h \
-  input.h $(PARAMS_H) debug.h tree-inline.h tree-simple.h
+  input.h $(PARAMS_H) debug.h tree-inline.h tree-gimple.h
 cp/mangle.o: cp/mangle.c $(CXX_TREE_H) $(TM_H) toplev.h real.h gt-cp-mangle.h \
   $(TARGET_H) $(TM_P_H)
 
 cp/parser.o: cp/parser.c $(CXX_TREE_H) $(TM_H) diagnostic.h gt-cp-parser.h \
   output.h
-cp/cp-simplify.o: cp/cp-simplify.c $(CXX_TREE_H) toplev.h c-common.h \
+cp/cp-gimplify.o: cp/cp-gimplify.c $(CXX_TREE_H) toplev.h c-common.h \
 	$(TM_H) coretypes.h
 cp/cp-mudflap.o: cp/cp-mudflap.c $(CXX_TREE_H) toplev.h c-common.h \
 	$(TM_H) coretypes.h
diff --git a/gcc/cp/cp-simplify.c b/gcc/cp/cp-gimplify.c
similarity index 98%
rename from gcc/cp/cp-simplify.c
rename to gcc/cp/cp-gimplify.c
index af302ee5476edccc5326766005fcf3262490e711..f82ed61eb7a8cac16beb2726972366f9acc6ba53 100644
--- a/gcc/cp/cp-simplify.c
+++ b/gcc/cp/cp-gimplify.c
@@ -1,4 +1,4 @@
-/* C++-specific tree lowering bits; see also c-simplify.c and tree-simple.c.
+/* C++-specific tree lowering bits; see also c-gimplify.c and tree-gimple.c.
 
    Copyright (C) 2002, 2003 Free Software Foundation, Inc.
    Contributed by Jason Merrill <jason@redhat.com>
@@ -28,7 +28,7 @@ Software Foundation, 59 Temple Place - Suite 330, Boston, MA
 #include "cp-tree.h"
 #include "c-common.h"
 #include "toplev.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 
 static void genericize_try_block (tree *);
 static void genericize_catch_block (tree *);
diff --git a/gcc/cp/optimize.c b/gcc/cp/optimize.c
index 1be4d8afdcc53e1e3c260ec30695359b570b582a..7f45ae9123c055556e015f7583f96da9850f0a81 100644
--- a/gcc/cp/optimize.c
+++ b/gcc/cp/optimize.c
@@ -40,7 +40,7 @@ Software Foundation, 59 Temple Place - Suite 330, Boston, MA
 #include "langhooks.h"
 #include "diagnostic.h"
 #include "tree-dump.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 
 /* Prototypes.  */
 
diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 8939fc452d35cb9847e6ad1ecee4b020a1035333..d8185353d25d2b6e6eae8e1cc9dcab7864b4ba62 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,9 @@
+2004-05-13  Diego Novillo  <dnovillo@redhat.com>
+
+	* Make-lang.in, f95-lang.c, trans-array.c, trans-decl.c,
+	trans-expr.c, trans-intrinsic.c, trans-io.c, trans-stmt.c,
+	trans.c: Rename tree-simple.[ch] to tree-gimple.[ch].
+
 2004-05-13  Victor Leikehman  <lei@haifasphere.co.il>
 
 	PR fortran/15314
diff --git a/gcc/fortran/Make-lang.in b/gcc/fortran/Make-lang.in
index a38834b471371bb1be293f66cfd80e9414bb3556..f1acba838bf0d6bb95b4c469c6979882a63740b5 100644
--- a/gcc/fortran/Make-lang.in
+++ b/gcc/fortran/Make-lang.in
@@ -81,7 +81,7 @@ F95_OBJS = $(F95_PARSER_OBJS) \
 # We rely on c-semantics to expand from GIMPLE to RTL.
 # This should go away once a real GIMPLE expander is available. 
 F95_ADDITIONAL_OBJS = \
-	tree-cfg.o tree-dfa.o tree-optimize.o tree-simple.o \
+	tree-cfg.o tree-dfa.o tree-optimize.o tree-gimple.o \
 	tree-ssa.o tree-ssa-ccp.o tree-ssa-dce.o \
 	tree-alias-common.o tree-alias-type.o gimplify.o stor-layout.o
 
diff --git a/gcc/fortran/f95-lang.c b/gcc/fortran/f95-lang.c
index 51ce3c4e5302ee562273a76fb32e54081c6da89c..f5cc66ec53d808de8a68c26ab0d485e6f2b1c425 100644
--- a/gcc/fortran/f95-lang.c
+++ b/gcc/fortran/f95-lang.c
@@ -28,7 +28,7 @@ Boston, MA 02111-1307, USA.  */
 #include "system.h"
 #include "coretypes.h"
 #include "tree.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "flags.h"
 #include "langhooks.h"
 #include "langhooks-def.h"
diff --git a/gcc/fortran/trans-array.c b/gcc/fortran/trans-array.c
index 452b0fec81c9b5566b2d857b884fbbedfdca1605..2d95550bc1bdb54451316a0193e35374185f190a 100644
--- a/gcc/fortran/trans-array.c
+++ b/gcc/fortran/trans-array.c
@@ -80,7 +80,7 @@ Boston, MA 02111-1307, USA.  */
 #include "system.h"
 #include "coretypes.h"
 #include "tree.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include <stdio.h>
 #include "ggc.h"
 #include "toplev.h"
diff --git a/gcc/fortran/trans-decl.c b/gcc/fortran/trans-decl.c
index 79e8cf6927eec140101d6c1db8799d8d263fb16f..c1e80508457c41022318a8f7492b9cca5df1a844 100644
--- a/gcc/fortran/trans-decl.c
+++ b/gcc/fortran/trans-decl.c
@@ -26,7 +26,7 @@ Boston, MA 02111-1307, USA.  */
 #include "coretypes.h"
 #include "tree.h"
 #include "tree-dump.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "ggc.h"
 #include "toplev.h"
 #include "tm.h"
diff --git a/gcc/fortran/trans-expr.c b/gcc/fortran/trans-expr.c
index 1f98f9e1a89c6baaea1a0445afc95a237d0c338b..b0f4139d24d4528c4e8fc714685c3674035ca820 100644
--- a/gcc/fortran/trans-expr.c
+++ b/gcc/fortran/trans-expr.c
@@ -31,7 +31,7 @@ Boston, MA 02111-1307, USA.  */
 #include "ggc.h"
 #include "toplev.h"
 #include "real.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "flags.h"
 #include <gmp.h>
 #include <assert.h>
@@ -374,7 +374,7 @@ gfc_conv_unary_op (enum tree_code code, gfc_se * se, gfc_expr * expr)
 
   /* TRUTH_NOT_EXPR is not a "true" unary operator in GCC.
      We must convert it to a compare to 0 (e.g. EQ_EXPR (op1, 0)).
-     All other unary operators have an equivalent SIMPLE unary operator  */
+     All other unary operators have an equivalent GIMPLE unary operator  */
   if (code == TRUTH_NOT_EXPR)
     se->expr = build (EQ_EXPR, type, operand.expr, integer_zero_node);
   else
@@ -796,7 +796,7 @@ gfc_conv_expr_op (gfc_se * se, gfc_expr * expr)
       break;
 
       /* EQV and NEQV only work on logicals, but since we represent them
-         as integers, we can use EQ_EXPR and NE_EXPR for them in SIMPLE.  */
+         as integers, we can use EQ_EXPR and NE_EXPR for them in GIMPLE.  */
     case INTRINSIC_EQ:
     case INTRINSIC_EQV:
       code = EQ_EXPR;
diff --git a/gcc/fortran/trans-intrinsic.c b/gcc/fortran/trans-intrinsic.c
index fb3ceb2f6b1b53fd4f248dc16596828974375771..b58c298b0b7457d29b6a194c1cb6414dc7734cd5 100644
--- a/gcc/fortran/trans-intrinsic.c
+++ b/gcc/fortran/trans-intrinsic.c
@@ -31,7 +31,7 @@ Boston, MA 02111-1307, USA.  */
 #include "ggc.h"
 #include "toplev.h"
 #include "real.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "flags.h"
 #include <gmp.h>
 #include <assert.h>
diff --git a/gcc/fortran/trans-io.c b/gcc/fortran/trans-io.c
index d18bb7941956d7a3de1a70f38e6d3f192c07b06d..66fffab12e1599a2b6a587fc7094e7095b18645d 100644
--- a/gcc/fortran/trans-io.c
+++ b/gcc/fortran/trans-io.c
@@ -24,7 +24,7 @@ Boston, MA 02111-1307, USA.  */
 #include "system.h"
 #include "coretypes.h"
 #include "tree.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include <stdio.h>
 #include "ggc.h"
 #include "toplev.h"
diff --git a/gcc/fortran/trans-stmt.c b/gcc/fortran/trans-stmt.c
index 0de62a5367cc05a77f33b812962650891f82ddf4..6c2e669994bf60bd7925ab9fefdeb962ca277eae 100644
--- a/gcc/fortran/trans-stmt.c
+++ b/gcc/fortran/trans-stmt.c
@@ -25,7 +25,7 @@ Boston, MA 02111-1307, USA.  */
 #include "system.h"
 #include "coretypes.h"
 #include "tree.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include <stdio.h>
 #include "ggc.h"
 #include "toplev.h"
diff --git a/gcc/fortran/trans.c b/gcc/fortran/trans.c
index aed764d0a36f6a4b294a64a4284a1c3cc5b8b079..a423ac95062e5558e37f77511f6673f8f04f8d66 100644
--- a/gcc/fortran/trans.c
+++ b/gcc/fortran/trans.c
@@ -23,7 +23,7 @@ Boston, MA 02111-1307, USA.  */
 #include "system.h"
 #include "coretypes.h"
 #include "tree.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include <stdio.h>
 #include "ggc.h"
 #include "toplev.h"
@@ -443,7 +443,7 @@ gfc_trans_code (gfc_code * code)
 
   gfc_start_block (&block);
 
-  /* Translate statements one by one to SIMPLE trees until we reach
+  /* Translate statements one by one to GIMPLE trees until we reach
      the end of this gfc_code branch.  */
   for (; code; code = code->next)
     {
diff --git a/gcc/gimple-low.c b/gcc/gimple-low.c
index af2760279bc10ca92f744d528449d7acaaf44582..56f02b7a1ee47bdde6f8cd575e7cffb3fe48442e 100644
--- a/gcc/gimple-low.c
+++ b/gcc/gimple-low.c
@@ -27,7 +27,7 @@ Software Foundation, 59 Temple Place - Suite 330, Boston, MA
 #include "rtl.h"
 #include "errors.h"
 #include "varray.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-inline.h"
 #include "diagnostic.h"
 #include "langhooks.h"
diff --git a/gcc/gimplify.c b/gcc/gimplify.c
index dda218beab4e0dd282919a2b18789484a00faa0e..787dbc3499921b296f0ac8a1caa862d1de0f20f3 100644
--- a/gcc/gimplify.c
+++ b/gcc/gimplify.c
@@ -30,7 +30,7 @@ Software Foundation, 59 Temple Place - Suite 330, Boston, MA
 #include "rtl.h"
 #include "errors.h"
 #include "varray.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-inline.h"
 #include "diagnostic.h"
 #include "langhooks.h"
@@ -3029,7 +3029,7 @@ gimplify_to_stmt_list (tree *stmt_p)
 
     GIMPLE_TEST_F points to a function that takes a tree T and
 	returns nonzero if T is in the GIMPLE form requested by the
-	caller.  The GIMPLE predicates are in tree-simple.c.
+	caller.  The GIMPLE predicates are in tree-gimple.c.
 
 	This test is used twice.  Before gimplification, the test is
 	invoked to determine whether *EXPR_P is already gimple enough.  If
diff --git a/gcc/java/ChangeLog b/gcc/java/ChangeLog
index b7cb8c4630ceb611fab322c57af243c672d8966b..dfbf10d5acd1cc68d4548d25f7b12480c01f9133 100644
--- a/gcc/java/ChangeLog
+++ b/gcc/java/ChangeLog
@@ -1,3 +1,8 @@
+2004-05-13  Diego Novillo  <dnovillo@redhat.com>
+
+	* Make-lang.in, expr.c, java-gimplify.c: Rename
+	tree-simple.[ch] to tree-gimple.[ch].
+
 2004-05-14  Ranjit Mathew  <rmathew@hotmail.com>
 
 	* java-gimplify.c (java_gimplify_expr): Correct minor typos.
diff --git a/gcc/java/Make-lang.in b/gcc/java/Make-lang.in
index db3ac9d55312789cbcb5eaff5dcf96587d7920b4..367627362dcb15ff3cfcb8db907e8951951c37bf 100644
--- a/gcc/java/Make-lang.in
+++ b/gcc/java/Make-lang.in
@@ -334,7 +334,7 @@ java/xref.o: java/xref.c java/xref.h $(CONFIG_H) $(JAVA_TREE_H) toplev.h \
 java/zextract.o: java/zextract.c $(CONFIG_H) $(SYSTEM_H) coretypes.h $(TM_H) \
   java/zipfile.h
 java/java-gimplify.o: java/java-gimplify.c $(CONFIG_H) $(SYSTEM_H) \
-  coretypes.h $(TM_H) $(JAVA_TREE_H) tree-simple.h toplev.h
+  coretypes.h $(TM_H) $(JAVA_TREE_H) tree-gimple.h toplev.h
 
 java/parse-scan.o: java/parse-scan.c $(CONFIG_H) $(SYSTEM_H) \
   coretypes.h $(TM_H) toplev.h $(JAVA_LEX_C) java/parse.h java/lex.h input.h
diff --git a/gcc/java/expr.c b/gcc/java/expr.c
index a63309ec9a43661ceba6c07b9f3dc5fe37c4467e..aa0697420a07d6f7bdfbdf4b5207679e61b43dde 100644
--- a/gcc/java/expr.c
+++ b/gcc/java/expr.c
@@ -43,7 +43,7 @@ The Free Software Foundation is independent of Sun Microsystems, Inc.  */
 #include "toplev.h"
 #include "except.h"
 #include "ggc.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "target.h"
 
 static void flush_quick_stack (void);
diff --git a/gcc/java/java-gimplify.c b/gcc/java/java-gimplify.c
index f32a4c809b0d31772d702de1cb0d8d8c0271404d..987351c2102f40238b6a70972044a297188b676b 100644
--- a/gcc/java/java-gimplify.c
+++ b/gcc/java/java-gimplify.c
@@ -30,7 +30,7 @@ The Free Software Foundation is independent of Sun Microsystems, Inc.  */
 #include "tree.h"
 #include "java-tree.h"
 #include "tree-dump.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "toplev.h"
 
 static tree java_gimplify_case_expr (tree);
diff --git a/gcc/langhooks.c b/gcc/langhooks.c
index 58e4eb6b21d896be862e48f410e308be21016a69..c82b5fd4f3fdb8af1803f5844dd98030e5b7efea 100644
--- a/gcc/langhooks.c
+++ b/gcc/langhooks.c
@@ -26,7 +26,7 @@ Boston, MA 02111-1307, USA.  */
 #include "toplev.h"
 #include "tree.h"
 #include "tree-inline.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "rtl.h"
 #include "insn-config.h"
 #include "integrate.h"
diff --git a/gcc/tree-alias-ander.c b/gcc/tree-alias-ander.c
index b3b14d1fa123ec687452f99328ab049872803bda..3f2773428360cbbc6a0471ddbc8ae92489308301 100644
--- a/gcc/tree-alias-ander.c
+++ b/gcc/tree-alias-ander.c
@@ -41,7 +41,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
 #include "tree-flow.h"
 #include "tree-inline.h"
 #include "varray.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "splay-tree.h"
 #include "engine/util.h"
 #include "libcompat/regions.h"
diff --git a/gcc/tree-alias-common.c b/gcc/tree-alias-common.c
index cd36eef594243d884150a9fc2500c0208505c3f3..f7b6fed5f34168df57b9d7760c441b60ac76cb02 100644
--- a/gcc/tree-alias-common.c
+++ b/gcc/tree-alias-common.c
@@ -45,7 +45,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
 #include "tree-inline.h"
 #include "varray.h"
 #include "c-tree.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "hashtab.h"
 #include "function.h"
 #include "cgraph.h"
diff --git a/gcc/tree-complex.c b/gcc/tree-complex.c
index fe963041a051f22e36a5ea2e566b32ec018d9658..8094d950da3b60632b8f18d3e892c5d2771b8185 100644
--- a/gcc/tree-complex.c
+++ b/gcc/tree-complex.c
@@ -24,7 +24,7 @@ Software Foundation, 59 Temple Place - Suite 330, Boston, MA
 #include "tree.h"
 #include "tm.h"
 #include "tree-flow.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-iterator.h"
 #include "tree-pass.h"
 #include "flags.h"
diff --git a/gcc/tree-dfa.c b/gcc/tree-dfa.c
index cda68487efb41a419e4e47e73e0490c5581e6f72..2a71ef20fe681d6f2596c1090481b99c705e6b95 100644
--- a/gcc/tree-dfa.c
+++ b/gcc/tree-dfa.c
@@ -39,7 +39,7 @@ Boston, MA 02111-1307, USA.  */
 #include "function.h"
 #include "diagnostic.h"
 #include "tree-dump.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-flow.h"
 #include "tree-inline.h"
 #include "tree-alias-common.h"
diff --git a/gcc/tree-flow.h b/gcc/tree-flow.h
index 853eb1a41eb4a1dabe959a855056ff8b8d5bcd47..76f97a4ebf59227fc77dd567fb881613bc3d1d01 100644
--- a/gcc/tree-flow.h
+++ b/gcc/tree-flow.h
@@ -26,7 +26,7 @@ Boston, MA 02111-1307, USA.  */
 #include "hard-reg-set.h"
 #include "basic-block.h"
 #include "hashtab.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-ssa-operands.h"
 
 /* Forward declare structures for the garbage collector GTY markers.  */
diff --git a/gcc/tree-simple.c b/gcc/tree-gimple.c
similarity index 99%
rename from gcc/tree-simple.c
rename to gcc/tree-gimple.c
index 0215088deca7a1dc00ee80dd040f1c1dd5173d46..dbe2966e1e95f306f64280b313752d178f5302f6 100644
--- a/gcc/tree-simple.c
+++ b/gcc/tree-gimple.c
@@ -26,7 +26,7 @@ Boston, MA 02111-1307, USA.  */
 #include "ggc.h"
 #include "tm.h"
 #include "tree.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "output.h"
 #include "rtl.h"
 #include "expr.h"
diff --git a/gcc/tree-simple.h b/gcc/tree-gimple.h
similarity index 100%
rename from gcc/tree-simple.h
rename to gcc/tree-gimple.h
diff --git a/gcc/tree-inline.c b/gcc/tree-inline.c
index feb395f5c4b6bb4b4af9f199f3d820b5f3f7706c..cf50b9b18c247693b7aacf2699cc1b2c9a104c2e 100644
--- a/gcc/tree-inline.c
+++ b/gcc/tree-inline.c
@@ -46,7 +46,7 @@ Boston, MA 02111-1307, USA.  */
 /* I'm not real happy about this, but we need to handle gimple and
    non-gimple trees.  */
 #include "tree-iterator.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 
 /* 0 if we should not perform inlining.
    1 if we should expand functions calls inline at the tree level.
diff --git a/gcc/tree-into-ssa.c b/gcc/tree-into-ssa.c
index 4e19142afd0f6bcdaa4eac84421a9289cc478290..a569d0536b1937693989c40071a9ede4b0fac89e 100644
--- a/gcc/tree-into-ssa.c
+++ b/gcc/tree-into-ssa.c
@@ -37,7 +37,7 @@ Boston, MA 02111-1307, USA.  */
 #include "diagnostic.h"
 #include "bitmap.h"
 #include "tree-flow.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-inline.h"
 #include "varray.h"
 #include "timevar.h"
diff --git a/gcc/tree-iterator.c b/gcc/tree-iterator.c
index 3f0eb5c9dc37b129ff9b1a7d9b5a006e050735d3..ebc477b68d043ceb707569359ac2512bbf8a7e14 100644
--- a/gcc/tree-iterator.c
+++ b/gcc/tree-iterator.c
@@ -23,7 +23,7 @@ Boston, MA 02111-1307, USA.  */
 #include "system.h"
 #include "coretypes.h"
 #include "tree.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-iterator.h"
 #include "ggc.h"
 
diff --git a/gcc/tree-mudflap.c b/gcc/tree-mudflap.c
index 9172541af39b6e264f530c982b25ad2343ff8e96..474c7c455469d2e70913ab94ced1cfaa5765de66 100644
--- a/gcc/tree-mudflap.c
+++ b/gcc/tree-mudflap.c
@@ -30,7 +30,7 @@ Software Foundation, 59 Temple Place - Suite 330, Boston, MA
 #include "flags.h"
 #include "function.h"
 #include "tree-inline.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-flow.h"
 #include "tree-mudflap.h"
 #include "tree-dump.h"
diff --git a/gcc/tree-nested.c b/gcc/tree-nested.c
index 7b92a75db30d4b06caa51cdd60bd1584cec1d7f4..1a00ff30f864fed5dc11740f1db38d4fac81ed71 100644
--- a/gcc/tree-nested.c
+++ b/gcc/tree-nested.c
@@ -28,7 +28,7 @@
 #include "function.h"
 #include "tree-dump.h"
 #include "tree-inline.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-iterator.h"
 #include "tree-flow.h"
 #include "cgraph.h"
diff --git a/gcc/tree-nomudflap.c b/gcc/tree-nomudflap.c
index 420fc39a88b5d3ef8da0256d4890dfd00396b71f..1e30194f77eac3aaf565ceb6e3456a7945507468 100644
--- a/gcc/tree-nomudflap.c
+++ b/gcc/tree-nomudflap.c
@@ -29,7 +29,7 @@ Software Foundation, 59 Temple Place - Suite 330, Boston, MA
 #include "tree-inline.h"
 #include "c-tree.h"
 #include "c-common.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "diagnostic.h"
 #include "hashtab.h"
 #include "output.h"
diff --git a/gcc/tree-outof-ssa.c b/gcc/tree-outof-ssa.c
index af5bf51f2acf3ed9503fcec3e7da8f9b9cd35492..97b0b4a3e82cdb5b38ca7108cb6a2499fbb54972 100644
--- a/gcc/tree-outof-ssa.c
+++ b/gcc/tree-outof-ssa.c
@@ -38,7 +38,7 @@ Boston, MA 02111-1307, USA.  */
 #include "diagnostic.h"
 #include "bitmap.h"
 #include "tree-flow.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-inline.h"
 #include "varray.h"
 #include "timevar.h"
diff --git a/gcc/tree-sra.c b/gcc/tree-sra.c
index 2131d0047f20b48a6dcfd337859a5383d34f23e4..d447b82d7682588c6a9c7e442c108d17263f1f41 100644
--- a/gcc/tree-sra.c
+++ b/gcc/tree-sra.c
@@ -38,7 +38,7 @@ Software Foundation, 59 Temple Place - Suite 330, Boston, MA
 #include "langhooks.h"
 #include "tree-inline.h"
 #include "tree-flow.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-dump.h"
 #include "tree-pass.h"
 #include "timevar.h"
diff --git a/gcc/tree-ssa-alias.c b/gcc/tree-ssa-alias.c
index 02eb5139698f9d5de5f9d234fdffa82ec59082e3..2bcb4efec9bb4682cc69d7a55dc520d54e5cd45d 100644
--- a/gcc/tree-ssa-alias.c
+++ b/gcc/tree-ssa-alias.c
@@ -36,7 +36,7 @@ Boston, MA 02111-1307, USA.  */
 #include "function.h"
 #include "diagnostic.h"
 #include "tree-dump.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-flow.h"
 #include "tree-inline.h"
 #include "tree-alias-common.h"
diff --git a/gcc/tree-ssa-ccp.c b/gcc/tree-ssa-ccp.c
index ef655629abd0c3848754a674256a5b128e8eea1e..bb7939cd10c10e730a4efc7d5ef49d3b4864b61b 100644
--- a/gcc/tree-ssa-ccp.c
+++ b/gcc/tree-ssa-ccp.c
@@ -51,7 +51,7 @@ Software Foundation, 59 Temple Place - Suite 330, Boston, MA
 #include "diagnostic.h"
 #include "tree-inline.h"
 #include "tree-flow.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-dump.h"
 #include "tree-pass.h"
 #include "timevar.h"
diff --git a/gcc/tree-ssa-copyrename.c b/gcc/tree-ssa-copyrename.c
index 91c0f74ac5519bcd92bb91031796eed6d667a0f2..dd698835f0682ce89f0f982386b689a1b65b43db 100644
--- a/gcc/tree-ssa-copyrename.c
+++ b/gcc/tree-ssa-copyrename.c
@@ -30,7 +30,7 @@ Boston, MA 02111-1307, USA.  */
 #include "diagnostic.h"
 #include "bitmap.h"
 #include "tree-flow.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-inline.h"
 #include "timevar.h"
 #include "tree-alias-common.h"
diff --git a/gcc/tree-ssa-dce.c b/gcc/tree-ssa-dce.c
index c8ff7eb9d9827e1c3417e11e9a2a75eb1e0f9caf..7921a9f0cf6c0034ffbd198f184a6c3124c5dff5 100644
--- a/gcc/tree-ssa-dce.c
+++ b/gcc/tree-ssa-dce.c
@@ -59,7 +59,7 @@ Software Foundation, 59 Temple Place - Suite 330, Boston, MA
 #include "tree.h"
 #include "diagnostic.h"
 #include "tree-flow.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-dump.h"
 #include "tree-pass.h"
 #include "timevar.h"
diff --git a/gcc/tree-ssa-live.c b/gcc/tree-ssa-live.c
index aedcbc1e3979eef7cc43d101e9f0bb64beb1a68a..28c3d578581693a19bc6d4961b286c4702b9f8c5 100644
--- a/gcc/tree-ssa-live.c
+++ b/gcc/tree-ssa-live.c
@@ -30,7 +30,7 @@ Boston, MA 02111-1307, USA.  */
 #include "diagnostic.h"
 #include "bitmap.h"
 #include "tree-flow.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-inline.h"
 #include "varray.h"
 #include "timevar.h"
diff --git a/gcc/tree-ssa-pre.c b/gcc/tree-ssa-pre.c
index 76a9a56c7e25f1b282cc7efd3ee0b71c77678658..c249441dd7ca487819ec2812ff2b6a7443afed85 100644
--- a/gcc/tree-ssa-pre.c
+++ b/gcc/tree-ssa-pre.c
@@ -34,7 +34,7 @@ Boston, MA 02111-1307, USA.  */
 #include "diagnostic.h"
 #include "tree-inline.h"
 #include "tree-flow.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-dump.h"
 #include "timevar.h"
 #include "fibheap.h"
diff --git a/gcc/tree-ssa.c b/gcc/tree-ssa.c
index 58d44c2d5e6d50525bd10ce46af03c6cb88b6f7c..8ecce07e4f4dd8118ad0e57678c996bc177838de 100644
--- a/gcc/tree-ssa.c
+++ b/gcc/tree-ssa.c
@@ -37,7 +37,7 @@ Boston, MA 02111-1307, USA.  */
 #include "diagnostic.h"
 #include "bitmap.h"
 #include "tree-flow.h"
-#include "tree-simple.h"
+#include "tree-gimple.h"
 #include "tree-inline.h"
 #include "varray.h"
 #include "timevar.h"