diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index e8f5b8a7eed1eb1006da3c90bf9a5ad3bfda33d0..d95cbb823287abfafe42924f2a8d55ef8d12c70a 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,31 @@
+2006-01-11  Jan Hubicka  <jh@suse.cz>
+
+	* cgraph.c (cgraph_insert_node_to_hashtable): New function.
+	* cgraph.h (cgraph_node): Add inline_decl.
+	(cgraph_insert_node_to_hashtable): Declare.
+	(save_inline_function_body): Declare.
+	* cgraphunit.c (verify_cgraph_node): Inline edges might point to inline
+	clones.
+	(cgraph_preserve_function_body_p): Do not presrve when dump is enabled.
+	(cgraph_function_versioning): Update call of tree_function_versioning.
+	(save_inline_function_body): New function.
+	* function.h (struct function): Kill saved_eh, saved_cfg, saved_args,
+	saved_static_chain_decl, saved_blocks and saved-unexpanded_var_list.
+	* ipa-inline.c (cgraph_mark_inline_edge): Look for inline clones.
+	(cgraph_default_inline_p): Likewise.
+	(cgraph_decide_inlining_incrementally): Likewise.
+	* tree-inline.c (inline_data): Kill saving_p add update_clones_p.
+	(copy_bb): Kill saving; do updating of clones.
+	(copy_cfg_body): Kill saving.
+	(initialize_inlined-parameters): Likewise.
+	(expand_call_inline): Likewise.
+	(save_body): Kill.
+	(tree_function_versioning): New parameter "update_clones".
+	(inlining_p): Kill saving.
+	* tree-inline.h (tree_function_versioning): Update prototype.
+	* tree-optimize.c (tree_rest_of_compilation): Use clonning instead of
+	saving.
+
 2006-01-11  Ian Lance Taylor <ian@airs.com>
 
 	* combine.c (struct undo): Remove is_int.  Enumify types of undos.
diff --git a/gcc/cgraph.c b/gcc/cgraph.c
index ab45f04c7cc40c61f8e74e32b3471d4d3bd010df..88cf8ac818ed0e241b044372aea4d8d4daccb8fe 100644
--- a/gcc/cgraph.c
+++ b/gcc/cgraph.c
@@ -214,6 +214,19 @@ cgraph_node (tree decl)
   return node;
 }
 
+/* Insert already constructed node into hashtable.  */
+
+void
+cgraph_insert_node_to_hashtable (struct cgraph_node *node)
+{
+  struct cgraph_node **slot;
+
+  slot = (struct cgraph_node **) htab_find_slot (cgraph_hash, node, INSERT);
+
+  gcc_assert (!*slot);
+  *slot = node;
+}
+
 /* Compare ASMNAME with the DECL_ASSEMBLER_NAME of DECL.  */
 
 static bool
diff --git a/gcc/cgraph.h b/gcc/cgraph.h
index 42a74f549b47efe0bb3644936f409ce215769af4..78b0fad3e862f3bfa77fae60d0e0bf178bc42693 100644
--- a/gcc/cgraph.h
+++ b/gcc/cgraph.h
@@ -161,6 +161,11 @@ struct cgraph_node GTY((chain_next ("%h.next"), chain_prev ("%h.previous")))
   bool externally_visible;
   /* Set for aliases once they got through assemble_alias.  */
   bool alias;
+
+  /* In non-unit-at-a-time mode the function body of inline candidates is saved
+     into clone before compiling so the function in original form can be
+     inlined later.  This pointer points to the clone.  */
+  tree inline_decl;
 };
 
 struct cgraph_edge GTY((chain_next ("%h.next_caller"), chain_prev ("%h.prev_caller")))
@@ -225,6 +230,7 @@ extern GTY(()) struct cgraph_varpool_node *cgraph_varpool_nodes_queue;
 /* In cgraph.c  */
 void dump_cgraph (FILE *);
 void dump_cgraph_node (FILE *, struct cgraph_node *);
+void cgraph_insert_node_to_hashtable (struct cgraph_node *node);
 void dump_varpool (FILE *);
 void dump_cgraph_varpool_node (FILE *, struct cgraph_varpool_node *);
 void cgraph_remove_edge (struct cgraph_edge *);
@@ -281,6 +287,7 @@ void cgraph_reset_static_var_maps (void);
 void init_cgraph (void);
 struct cgraph_node *cgraph_function_versioning (struct cgraph_node *,
                                                 varray_type, varray_type);
+struct cgraph_node *save_inline_function_body (struct cgraph_node *);
 
 /* In ipa.c  */
 bool cgraph_remove_unreachable_nodes (bool, FILE *);
diff --git a/gcc/cgraphunit.c b/gcc/cgraphunit.c
index 244367d2899fe67ddddb2195f5e1d3e575b1b353..ae2dd51f887dc20f3c6b5f4e396f7a99efd83f8b 100644
--- a/gcc/cgraphunit.c
+++ b/gcc/cgraphunit.c
@@ -748,7 +748,8 @@ verify_cgraph_node (struct cgraph_node *node)
 			    debug_generic_stmt (stmt);
 			    error_found = true;
 			  }
-			if (e->callee->decl != cgraph_node (decl)->decl)
+			if (e->callee->decl != cgraph_node (decl)->decl
+			    && e->inline_failed)
 			  {
 			    error ("edge points to wrong declaration:");
 			    debug_tree (e->callee->decl);
@@ -1202,9 +1203,6 @@ bool
 cgraph_preserve_function_body_p (tree decl)
 {
   struct cgraph_node *node;
-  /* Keep the body; we're going to dump it.  */
-  if (dump_enabled_p (TDI_tree_all))
-    return true;
   if (!cgraph_global_info_ready)
     return (DECL_INLINE (decl) && !flag_really_no_inline);
   /* Look if there is any clone around.  */
@@ -1504,7 +1502,7 @@ cgraph_function_versioning (struct cgraph_node *old_version_node,
 				     redirect_callers);
 
   /* Copy the OLD_VERSION_NODE function tree to the new version.  */
-  tree_function_versioning (old_decl, new_decl, tree_map);
+  tree_function_versioning (old_decl, new_decl, tree_map, false);
   /* Update the call_expr on the edges to call the new version node. */
   update_call_expr (new_version_node);
 
@@ -1521,3 +1519,57 @@ cgraph_function_versioning (struct cgraph_node *old_version_node,
   new_version_node->lowered = true;
   return new_version_node;
 }
+
+/* Produce separate function body for inline clones so the offline copy can be
+   modified without affecting them.  */
+struct cgraph_node *
+save_inline_function_body (struct cgraph_node *node)
+{
+  struct cgraph_node *first_clone;
+
+  gcc_assert (node == cgraph_node (node->decl));
+
+  cgraph_lower_function (node);
+
+  /* In non-unit-at-a-time we construct full fledged clone we never output to
+     assembly file.  This clone is pointed out by inline_decl of orginal function
+     and inlining infrastructure knows how to deal with this.  */
+  if (!flag_unit_at_a_time)
+    {
+      struct cgraph_edge *e;
+
+      first_clone = cgraph_clone_node (node, node->count, 0, false);
+      first_clone->needed = 0;
+      first_clone->reachable = 1;
+      /* Recursively clone all bodies.  */
+      for (e = first_clone->callees; e; e = e->next_callee)
+	if (!e->inline_failed)
+	  cgraph_clone_inlined_nodes (e, true, false);
+    }
+  else
+    first_clone = node->next_clone;
+
+  first_clone->decl = copy_node (node->decl);
+  node->next_clone = NULL;
+  if (!flag_unit_at_a_time)
+    node->inline_decl = first_clone->decl;
+  first_clone->prev_clone = NULL;
+  cgraph_insert_node_to_hashtable (first_clone);
+  gcc_assert (first_clone == cgraph_node (first_clone->decl));
+
+  /* Copy the OLD_VERSION_NODE function tree to the new version.  */
+  tree_function_versioning (node->decl, first_clone->decl, NULL, true);
+
+  DECL_EXTERNAL (first_clone->decl) = 0;
+  DECL_ONE_ONLY (first_clone->decl) = 0;
+  TREE_PUBLIC (first_clone->decl) = 0;
+  DECL_COMDAT (first_clone->decl) = 0;
+
+  for (node = first_clone->next_clone; node; node = node->next_clone)
+    node->decl = first_clone->decl;
+#ifdef ENABLE_CHECKING
+  verify_cgraph_node (first_clone);
+#endif
+  return first_clone;
+}
+
diff --git a/gcc/function.h b/gcc/function.h
index c1482ac328e659d59871ab2a8528bc489066ab22..e1e173b33b2891da689e724fca46e64a136b2aee 100644
--- a/gcc/function.h
+++ b/gcc/function.h
@@ -162,25 +162,14 @@ struct expr_status GTY(())
 struct function GTY(())
 {
   struct eh_status *eh;
-  struct eh_status *saved_eh;
   struct expr_status *expr;
   struct emit_status *emit;
   struct varasm_status *varasm;
 
   /* The control flow graph for this function.  */
   struct control_flow_graph *cfg;
-  struct control_flow_graph *saved_cfg;
   bool after_inlining;
 
-  /* For tree-optimize.c.  */
-
-  /* Saved tree and arguments during tree optimization.  Used later for
-     inlining */
-  tree saved_args;
-  tree saved_static_chain_decl;
-  tree saved_blocks;
-  tree saved_unexpanded_var_list;
-
   /* For function.c.  */
 
   /* Points to the FUNCTION_DECL of this function.  */
diff --git a/gcc/ipa-inline.c b/gcc/ipa-inline.c
index ceadb23261f0363499dc752b4e213ea872836b10..fa91cbd96dc50840d31f92cdaf1423534055aa87 100644
--- a/gcc/ipa-inline.c
+++ b/gcc/ipa-inline.c
@@ -158,6 +158,9 @@ cgraph_mark_inline_edge (struct cgraph_edge *e, bool update_original)
   int old_insns = 0, new_insns = 0;
   struct cgraph_node *to = NULL, *what;
 
+  if (e->callee->inline_decl)
+    cgraph_redirect_edge_callee (e, cgraph_node (e->callee->inline_decl));
+
   gcc_assert (e->inline_failed);
   e->inline_failed = NULL;
 
@@ -283,21 +286,25 @@ cgraph_check_inline_limits (struct cgraph_node *to, struct cgraph_node *what,
 bool
 cgraph_default_inline_p (struct cgraph_node *n, const char **reason)
 {
-  if (!DECL_INLINE (n->decl))
+  tree decl = n->decl;
+
+  if (n->inline_decl)
+    decl = n->inline_decl;
+  if (!DECL_INLINE (decl))
     {
       if (reason)
 	*reason = N_("function not inlinable");
       return false;
     }
 
-  if (!DECL_SAVED_TREE (n->decl))
+  if (!DECL_STRUCT_FUNCTION (decl)->cfg)
     {
       if (reason)
 	*reason = N_("function body not available");
       return false;
     }
 
-  if (DECL_DECLARED_INLINE_P (n->decl))
+  if (DECL_DECLARED_INLINE_P (decl))
     {
       if (n->global.insns >= MAX_INLINE_INSNS_SINGLE)
 	{
@@ -1046,7 +1053,7 @@ cgraph_decide_inlining_incrementally (struct cgraph_node *node, bool early)
         && !cgraph_recursive_inlining_p (node, e->callee, &e->inline_failed)
 	/* ??? It is possible that renaming variable removed the function body
 	   in duplicate_decls. See gcc.c-torture/compile/20011119-2.c  */
-	&& DECL_SAVED_TREE (e->callee->decl))
+	&& (DECL_SAVED_TREE (e->callee->decl) || e->callee->inline_decl))
       {
         if (dump_file && early)
 	  {
@@ -1069,7 +1076,7 @@ cgraph_decide_inlining_incrementally (struct cgraph_node *node, bool early)
 	      || (cgraph_estimate_size_after_inlining (1, e->caller, node)
 	          <= e->caller->global.insns))
 	  && cgraph_check_inline_limits (node, e->callee, &e->inline_failed)
-	  && DECL_SAVED_TREE (e->callee->decl))
+	  && (DECL_SAVED_TREE (e->callee->decl) || e->callee->inline_decl))
 	{
 	  if (cgraph_default_inline_p (e->callee, &failed_reason))
 	    {
diff --git a/gcc/tree-inline.c b/gcc/tree-inline.c
index 0dafbc244c9ef23781832816ccb04292c8c02f84..be38fc937e11734692ae9a79d9d9d743dfd4cc2a 100644
--- a/gcc/tree-inline.c
+++ b/gcc/tree-inline.c
@@ -111,9 +111,7 @@ typedef struct inline_data
   tree callee;
   /* FUNCTION_DECL for function being inlined into.  */
   tree caller;
-  /* struct function for function being inlined.  Usually this is the same
-     as DECL_STRUCT_FUNCTION (callee), but can be different if saved_cfg
-     and saved_eh are in use.  */
+  /* struct function for function being inlined.  */
   struct function *callee_cfun;
   /* The VAR_DECL for the return value.  */
   tree retvar;
@@ -125,10 +123,11 @@ typedef struct inline_data
      distinguish between those two situations.  This flag is true if
      we are cloning, rather than inlining.  */
   bool cloning_p;
-  /* Similarly for saving function body.  */
-  bool saving_p;
   /* Versioning function is slightly different from inlining. */
   bool versioning_p;
+  /* If set, the call_stmt of edges in clones of caller functions will
+     be updated.  */
+  bool update_clones_p;
   /* Callgraph node of function we are inlining into.  */
   struct cgraph_node *node;
   /* Callgraph node of currently inlined function.  */
@@ -750,46 +749,33 @@ copy_bb (inline_data *id, basic_block bb, int frequency_scale, int count_scale)
 	     callgraph edges and update or duplicate them.  */
 	  if (call && (decl = get_callee_fndecl (call)))
 	    {
-	      if (id->saving_p)
-		{
-		  struct cgraph_node *node;
-		  struct cgraph_edge *edge;
-
-		  /* We're saving a copy of the body, so we'll update the
-		     callgraph nodes in place.  Note that we avoid
-		     altering the original callgraph node; we begin with
-		     the first clone.  */
-		  for (node = id->node->next_clone;
-		       node;
-		       node = node->next_clone)
-		    {
-		      edge = cgraph_edge (node, orig_stmt);
-		      gcc_assert (edge);
-		      edge->call_stmt = stmt;
-		    }
-		}
-	      else
+	      if (!id->versioning_p)
 		{
 		  struct cgraph_edge *edge;
 
 		  /* We're cloning or inlining this body; duplicate the
 		     associate callgraph nodes.  */
-		  if (!id->versioning_p)
-		    {
-		      edge = cgraph_edge (id->current_node, orig_stmt);
-		      if (edge)
-			cgraph_clone_edge (edge, id->node, stmt,
-					   REG_BR_PROB_BASE, 1, true);
-		    }
+		  edge = cgraph_edge (id->current_node, orig_stmt);
+		  if (edge)
+		    cgraph_clone_edge (edge, id->node, stmt,
+				       REG_BR_PROB_BASE, 1, true);
 		}
-	      if (id->versioning_p)
+	      else
 		{
 		  /* Update the call_expr on the edges from the new version
 		     to its callees. */
 		  struct cgraph_edge *edge;
 		  edge = cgraph_edge (id->node, orig_stmt);
 		  if (edge)
-		    edge->call_stmt = stmt;
+		    {
+		      edge->call_stmt = stmt;
+		      if (id->update_clones_p)
+			{
+			  struct cgraph_node *n;
+			  for (n = id->node->next_clone; n; n = n->next_clone)
+		            cgraph_edge (n, orig_stmt)->call_stmt = stmt;
+			}
+		     }
 		}
 	    }
 	  /* If you think we can abort here, you are wrong.
@@ -917,7 +903,7 @@ copy_cfg_body (inline_data * id, gcov_type count, int frequency,
     (struct function *) ggc_alloc_cleared (sizeof (struct function));
   basic_block bb;
   tree new_fndecl = NULL;
-  bool saving_or_cloning;
+  bool versioning_or_cloning;
   int count_scale, frequency_scale;
 
   if (ENTRY_BLOCK_PTR_FOR_FUNCTION (callee_cfun)->count)
@@ -942,24 +928,14 @@ copy_cfg_body (inline_data * id, gcov_type count, int frequency,
 
   *cfun_to_copy = *DECL_STRUCT_FUNCTION (callee_fndecl);
 
-  /* If there is a saved_cfg+saved_args lurking in the
-     struct function, a copy of the callee body was saved there, and
-     the 'struct cgraph edge' nodes have been fudged to point into the
-     saved body.  Accordingly, we want to copy that saved body so the
-     callgraph edges will be recognized and cloned properly.  */
-  if (cfun_to_copy->saved_cfg)
-    {
-      cfun_to_copy->cfg = cfun_to_copy->saved_cfg;
-      cfun_to_copy->eh = cfun_to_copy->saved_eh;
-    }
   id->callee_cfun = cfun_to_copy;
 
   /* If saving or cloning a function body, create new basic_block_info
      and label_to_block_maps.  Otherwise, we're duplicating a function
      body for inlining; insert our new blocks and labels into the
      existing varrays.  */
-  saving_or_cloning = (id->saving_p || id->cloning_p || id->versioning_p);
-  if (saving_or_cloning)
+  versioning_or_cloning = (id->cloning_p || id->versioning_p);
+  if (versioning_or_cloning)
     {
       new_cfun =
 	(struct function *) ggc_alloc_cleared (sizeof (struct function));
@@ -995,7 +971,7 @@ copy_cfg_body (inline_data * id, gcov_type count, int frequency,
   /* Duplicate any exception-handling regions.  */
   if (cfun->eh)
     {
-      if (saving_or_cloning)
+      if (versioning_or_cloning)
         init_eh_for_function ();
       id->eh_region_offset = duplicate_eh_regions (cfun_to_copy,
 		     				   remap_decl_1,
@@ -1011,7 +987,7 @@ copy_cfg_body (inline_data * id, gcov_type count, int frequency,
   FOR_ALL_BB_FN (bb, cfun_to_copy)
     bb->aux = NULL;
 
-  if (saving_or_cloning)
+  if (versioning_or_cloning)
     pop_cfun ();
 
   return new_fndecl;
@@ -1183,8 +1159,6 @@ initialize_inlined_parameters (inline_data *id, tree args, tree static_chain,
 
   /* Figure out what the parameters are.  */
   parms = DECL_ARGUMENTS (fn);
-  if (fn == current_function_decl)
-    parms = cfun->saved_args;
 
   /* Loop through the parameter declarations, replacing each with an
      equivalent VAR_DECL, appropriately initialized.  */
@@ -1204,8 +1178,7 @@ initialize_inlined_parameters (inline_data *id, tree args, tree static_chain,
 
   /* Initialize the static chain.  */
   p = DECL_STRUCT_FUNCTION (fn)->static_chain_decl;
-  if (fn == current_function_decl)
-    p = DECL_STRUCT_FUNCTION (fn)->saved_static_chain_decl;
+  gcc_assert (fn != current_function_decl);
   if (p)
     {
       /* No static chain?  Seems like a bug in tree-nested.c.  */
@@ -2039,6 +2012,7 @@ expand_call_inline (basic_block bb, tree stmt, tree *tp, void *data)
 	}
       goto egress;
     }
+  fn = cg_edge->callee->decl;
 
 #ifdef ENABLE_CHECKING
   if (cg_edge->callee->decl != id->node->decl)
@@ -2095,9 +2069,7 @@ expand_call_inline (basic_block bb, tree stmt, tree *tp, void *data)
   /* Record the function we are about to inline.  */
   id->callee = fn;
 
-  if (DECL_STRUCT_FUNCTION (fn)->saved_blocks)
-    add_lexical_block (id->block, remap_blocks (DECL_STRUCT_FUNCTION (fn)->saved_blocks, id));
-  else if (DECL_INITIAL (fn))
+  if (DECL_INITIAL (fn))
     add_lexical_block (id->block, remap_blocks (DECL_INITIAL (fn), id));
 
   /* Return statements in the function body will be replaced by jumps
@@ -2155,8 +2127,6 @@ expand_call_inline (basic_block bb, tree stmt, tree *tp, void *data)
 
   /* Add local vars in this inlined callee to caller.  */
   t_step = id->callee_cfun->unexpanded_var_list;
-  if (id->callee_cfun->saved_unexpanded_var_list)
-    t_step = id->callee_cfun->saved_unexpanded_var_list;
   for (; t_step; t_step = TREE_CHAIN (t_step))
     {
       var = TREE_VALUE (t_step);
@@ -2331,86 +2301,6 @@ clone_body (tree clone, tree fn, void *arg_map)
   append_to_statement_list_force (copy_generic_body (&id), &DECL_SAVED_TREE (clone));
 }
 
-/* Save duplicate body in FN.  MAP is used to pass around splay tree
-   used to update arguments in restore_body.  */
-
-/* Make and return duplicate of body in FN.  Put copies of DECL_ARGUMENTS
-   in *arg_copy and of the static chain, if any, in *sc_copy.  */
-
-void
-save_body (tree fn, tree *arg_copy, tree *sc_copy)
-{
-  inline_data id;
-  tree newdecl, *parg;
-  basic_block fn_entry_block;
-  tree t_step;
-
-  memset (&id, 0, sizeof (id));
-  id.callee = fn;
-  id.callee_cfun = DECL_STRUCT_FUNCTION (fn);
-  id.caller = fn;
-  id.node = cgraph_node (fn);
-  id.saving_p = true;
-  id.decl_map = splay_tree_new (splay_tree_compare_pointers, NULL, NULL);
-  *arg_copy = DECL_ARGUMENTS (fn);
-
-  for (parg = arg_copy; *parg; parg = &TREE_CHAIN (*parg))
-    {
-      tree new = copy_node (*parg);
-
-      lang_hooks.dup_lang_specific_decl (new);
-      DECL_ABSTRACT_ORIGIN (new) = DECL_ORIGIN (*parg);
-      insert_decl_map (&id, *parg, new);
-      TREE_CHAIN (new) = TREE_CHAIN (*parg);
-      *parg = new;
-    }
-
-  *sc_copy = DECL_STRUCT_FUNCTION (fn)->static_chain_decl;
-  if (*sc_copy)
-    {
-      tree new = copy_node (*sc_copy);
-
-      lang_hooks.dup_lang_specific_decl (new);
-      DECL_ABSTRACT_ORIGIN (new) = DECL_ORIGIN (*sc_copy);
-      insert_decl_map (&id, *sc_copy, new);
-      TREE_CHAIN (new) = TREE_CHAIN (*sc_copy);
-      *sc_copy = new;
-    }
-
-  /* We're not inside any EH region.  */
-  id.eh_region = -1;
-
-  insert_decl_map (&id, DECL_RESULT (fn), DECL_RESULT (fn));
-
-  DECL_STRUCT_FUNCTION (fn)->saved_blocks
-    = remap_blocks (DECL_INITIAL (fn), &id);
-  for (t_step = id.callee_cfun->unexpanded_var_list;
-       t_step;
-       t_step = TREE_CHAIN (t_step))
-    {
-      tree var = TREE_VALUE (t_step);
-      if (TREE_STATIC (var) && !TREE_ASM_WRITTEN (var))
-	cfun->saved_unexpanded_var_list
-	  = tree_cons (NULL_TREE, var, cfun->saved_unexpanded_var_list);
-      else 
-	cfun->saved_unexpanded_var_list
-	  = tree_cons (NULL_TREE, remap_decl (var, &id),
-		       cfun->saved_unexpanded_var_list);
-    }
-
-  /* Actually copy the body, including a new (struct function *) and CFG.
-     EH info is also duplicated so its labels point into the copied
-     CFG, not the original.  */
-  fn_entry_block = ENTRY_BLOCK_PTR_FOR_FUNCTION (DECL_STRUCT_FUNCTION (fn));
-  newdecl = copy_body (&id, fn_entry_block->count, fn_entry_block->frequency,
-		       NULL, NULL);
-  DECL_STRUCT_FUNCTION (fn)->saved_cfg = DECL_STRUCT_FUNCTION (newdecl)->cfg;
-  DECL_STRUCT_FUNCTION (fn)->saved_eh = DECL_STRUCT_FUNCTION (newdecl)->eh;
-
-  /* Clean up.  */
-  splay_tree_delete (id.decl_map);
-}
-
 /* Passed to walk_tree.  Copies the node pointed to, if appropriate.  */
 
 tree
@@ -2807,9 +2697,11 @@ tree_versionable_function_p (tree fndecl)
    respectively.  In case we want to replace a DECL 
    tree with another tree while duplicating the function's 
    body, TREE_MAP represents the mapping between these 
-   trees.  */
+   trees. If UPDATE_CLONES is set, the call_stmt fields
+   of edges of clones of the function will be updated.  */
 void
-tree_function_versioning (tree old_decl, tree new_decl, varray_type tree_map)
+tree_function_versioning (tree old_decl, tree new_decl, varray_type tree_map,
+			  bool update_clones)
 {
   struct cgraph_node *old_version_node;
   struct cgraph_node *new_version_node;
@@ -2835,8 +2727,9 @@ tree_function_versioning (tree old_decl, tree new_decl, varray_type tree_map)
   DECL_ABSTRACT_ORIGIN (new_decl) = DECL_ORIGIN (old_decl);
 
   /* Generate a new name for the new version. */
-  DECL_NAME (new_decl) =
-    create_tmp_var_name (NULL);
+  if (!update_clones)
+    DECL_NAME (new_decl) =
+      create_tmp_var_name (NULL);
   /* Create a new SYMBOL_REF rtx for the new name. */
   if (DECL_RTL (old_decl) != NULL)
     {
@@ -2856,6 +2749,7 @@ tree_function_versioning (tree old_decl, tree new_decl, varray_type tree_map)
   id.current_node = cgraph_node (old_decl);
   
   id.versioning_p = true;
+  id.update_clones_p = update_clones;
   id.decl_map = splay_tree_new (splay_tree_compare_pointers, NULL, NULL);
   id.caller = new_decl;
   id.callee = old_decl;
@@ -2982,7 +2876,7 @@ replace_ref_tree (inline_data * id, tree * tp)
 static inline bool
 inlining_p (inline_data * id)
 {
-  return (!id->saving_p && !id->cloning_p && !id->versioning_p);
+  return (!id->cloning_p && !id->versioning_p);
 }
 
 /* Duplicate a type, fields and all.  */
diff --git a/gcc/tree-inline.h b/gcc/tree-inline.h
index 65ffed29b8d1eca9af678995c27a3f3e4328fc57..7c53239e24427b264172f28a35f9478edc718767 100644
--- a/gcc/tree-inline.h
+++ b/gcc/tree-inline.h
@@ -35,7 +35,7 @@ void push_cfun (struct function *new_cfun);
 void pop_cfun (void);
 int estimate_num_insns (tree expr);
 bool tree_versionable_function_p (tree);
-void tree_function_versioning (tree, tree, varray_type);
+void tree_function_versioning (tree, tree, varray_type, bool);
 
 /* Copy a declaration when one function is substituted inline into
    another.  It is used also for versioning.  */
diff --git a/gcc/tree-optimize.c b/gcc/tree-optimize.c
index 8bed9154d9045f24657533296a840c0265102a3f..34f2d4630772a1c9cab4209df023a041cfd495bd 100644
--- a/gcc/tree-optimize.c
+++ b/gcc/tree-optimize.c
@@ -348,12 +348,19 @@ void
 tree_rest_of_compilation (tree fndecl)
 {
   location_t saved_loc;
-  struct cgraph_node *saved_node = NULL, *node;
+  struct cgraph_node *node;
 
   timevar_push (TV_EXPAND);
 
   gcc_assert (!flag_unit_at_a_time || cgraph_global_info_ready);
 
+  node = cgraph_node (fndecl);
+
+  /* We might need the body of this function so that we can expand
+     it inline somewhere else.  */
+  if (cgraph_preserve_function_body_p (fndecl))
+    save_inline_function_body (node);
+
   /* Initialize the RTL code for the function.  */
   current_function_decl = fndecl;
   saved_loc = input_location;
@@ -367,26 +374,6 @@ tree_rest_of_compilation (tree fndecl)
   cfun->x_dont_save_pending_sizes_p = 1;
   cfun->after_inlining = true;
 
-  node = cgraph_node (fndecl);
-
-  /* We might need the body of this function so that we can expand
-     it inline somewhere else.  This means not lowering some constructs
-     such as exception handling.  */
-  if (cgraph_preserve_function_body_p (fndecl))
-    {
-      if (!flag_unit_at_a_time)
-	{
-	  struct cgraph_edge *e;
-
-	  saved_node = cgraph_clone_node (node, node->count, 1, false);
-	  for (e = saved_node->callees; e; e = e->next_callee)
-	    if (!e->inline_failed)
-	      cgraph_clone_inlined_nodes (e, true, false);
-	}
-      cfun->saved_static_chain_decl = cfun->static_chain_decl;
-      save_body (fndecl, &cfun->saved_args, &cfun->saved_static_chain_decl);
-    }
-
   if (flag_inline_trees)
     {
       struct cgraph_edge *e;
@@ -429,40 +416,7 @@ tree_rest_of_compilation (tree fndecl)
   /* Release the default bitmap obstack.  */
   bitmap_obstack_release (NULL);
   
-  /* Restore original body if still needed.  */
-  if (cfun->saved_cfg)
-    {
-      DECL_ARGUMENTS (fndecl) = cfun->saved_args;
-      cfun->cfg = cfun->saved_cfg;
-      cfun->eh = cfun->saved_eh;
-      DECL_INITIAL (fndecl) = cfun->saved_blocks;
-      cfun->unexpanded_var_list = cfun->saved_unexpanded_var_list;
-      cfun->saved_cfg = NULL;
-      cfun->saved_eh = NULL;
-      cfun->saved_args = NULL_TREE;
-      cfun->saved_blocks = NULL_TREE;
-      cfun->saved_unexpanded_var_list = NULL_TREE;
-      cfun->static_chain_decl = cfun->saved_static_chain_decl;
-      cfun->saved_static_chain_decl = NULL;
-      /* When not in unit-at-a-time mode, we must preserve out of line copy
-	 representing node before inlining.  Restore original outgoing edges
-	 using clone we created earlier.  */
-      if (!flag_unit_at_a_time)
-	{
-	  struct cgraph_edge *e;
-
-	  node = cgraph_node (current_function_decl);
-	  cgraph_node_remove_callees (node);
-	  node->callees = saved_node->callees;
-	  saved_node->callees = NULL;
-	  update_inlined_to_pointers (node, node);
-	  for (e = node->callees; e; e = e->next_callee)
-	    e->caller = node;
-	  cgraph_remove_node (saved_node);
-	}
-    }
-  else
-    DECL_SAVED_TREE (fndecl) = NULL;
+  DECL_SAVED_TREE (fndecl) = NULL;
   cfun = 0;
 
   /* If requested, warn about function definitions where the function will