From db2960f402c407aa41fe09d5195da5c414ae79af Mon Sep 17 00:00:00 2001
From: Sandra Loosemore <sandra@codesourcery.com>
Date: Wed, 5 Sep 2007 10:24:54 -0400
Subject: [PATCH] Add target hook invoked when cfun changes.

2007-09-05  Sandra Loosemore  <sandra@codesourcery.com>

	gcc/
	Add target hook invoked when cfun changes.

	* doc/tm.texi (TARGET_SET_CURRENT_FUNCTION): Document.
	* target.h (struct gcc_target): Add set_current_function.
	* target-def.h (TARGET_SET_CURRENT_FUNCTION): Define.
	(TARGET_INITIALIZER): Add initializer for set_current_function.
	* tree.h (push_struct_function): New.
	* tree-inline.h (push_cfun, pop_cfun): Move declarations to...
	* function.h: Here.
	(set_cfun): Declare.
	* tree-inline.c (cfun_stack, push_cfun, pop_cfun): Moved to...
	* function.c:  Here.
	(push_function_context_to): Use allocate_struct_function
	to create null context, not init_dummy_function_start.  Use set_cfun.
	(pop_function_context_from): Use set_cfun.
	(in_dummy_function): New.
	(invoke_set_current_function_hook): New.
	(set_cfun): New.
	(push_cfun, pop_cfun): Use set_cfun.
	(push_struct_function): New.
	(allocate_struct_function): Call invoke_set_current_function_hook
	before returning.
	(prepare_function_start): Don't set cfun here.  Remove unused
	argument; fix all callers.
	(init_dummy_function_start): Fiddle with in_dummy_function.  Call
	push_struct_function.
	(init_function_start): Set cfun here.
	(expand_dummy_function_end): Fiddle with in_dummy_function.  Pop cfun.
	* omp-low.c (create_omp_child_function): Use push_struct_function
	and pop_cfun to save/restore state.
	(expand_omp_parallel): Remove unused saved_cfun variable.
	* cgraphunit.c (ipa_passes): Use set_cfun.
	* gimple-low.c (record_vars_into): Use push_cfun/pop_cfun here.
	* dwarf2out.c (dwarf2out_abstract_function): Likewise.
	* matrix-reorg.c (transform_allocation_sites): Likewise.
	(matrix_reorg): Use set_cfun.
	* gimplify.c (gimplify_function_tree): Use push_cfun/pop_cfun here.
	* tree-optimize.c (tree_rest_of_compilation): Remove one redundant
	assignment to cfun; use set_cfun for the other.
	* tree-cfg.c (move_sese_region_to_fn): Use set_cfun.
	(dump_function_to_file): Use push_cfun/pop_cfun here.
	* c-decl.c (finish_function): Use set_cfun.

	gcc/ada/
	* trans.c (Compilation_unit_to_gnu): Use set_cfun.
	* utils.c (end_subprog_body): Likewise.

	gcc/cp/
	* decl.c (finish_function): Use set_cfun.
	* method.c (use_thunk): Likewise.

	gcc/fortran/
	* trans-decl.c (build_entry_thunks): Use set_cfun.
	(gfc_generate_function_code): Likewise.

	gcc/java/
	* decl.c (finish_method): Use set_cfun.

	gcc/treelang/
	* treetree.c (tree_code_create_function_wrapup):  Use set_cfun.

From-SVN: r128132
---
 gcc/ChangeLog            |  45 ++++++++++++
 gcc/ada/ChangeLog        |   5 ++
 gcc/ada/trans.c          |   2 +-
 gcc/ada/utils.c          |   2 +-
 gcc/c-decl.c             |   2 +-
 gcc/cgraphunit.c         |   2 +-
 gcc/cp/decl.c            |   2 +-
 gcc/cp/method.c          |   2 +-
 gcc/doc/tm.texi          |  17 +++++
 gcc/dwarf2out.c          |   6 +-
 gcc/fortran/ChangeLog    |   5 ++
 gcc/fortran/trans-decl.c |   4 +-
 gcc/function.c           | 145 ++++++++++++++++++++++++++++++---------
 gcc/function.h           |   5 ++
 gcc/gimple-low.c         |   6 +-
 gcc/gimplify.c           |   9 +--
 gcc/java/ChangeLog       |   4 ++
 gcc/java/decl.c          |   2 +-
 gcc/matrix-reorg.c       |   8 +--
 gcc/omp-low.c            |   7 +-
 gcc/target-def.h         |   5 ++
 gcc/target.h             |   5 ++
 gcc/tree-cfg.c           |  14 ++--
 gcc/tree-inline.c        |  21 ------
 gcc/tree-inline.h        |   2 -
 gcc/tree-optimize.c      |   3 +-
 gcc/tree.h               |   1 +
 gcc/treelang/ChangeLog   |   4 ++
 gcc/treelang/treetree.c  |   2 +-
 29 files changed, 242 insertions(+), 95 deletions(-)

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 764216d7531e..cf5891362905 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,48 @@
+2007-09-05  Sandra Loosemore  <sandra@codesourcery.com>
+
+	Add target hook invoked when cfun changes.
+
+	* doc/tm.texi (TARGET_SET_CURRENT_FUNCTION): Document.
+	* target.h (struct gcc_target): Add set_current_function.
+	* target-def.h (TARGET_SET_CURRENT_FUNCTION): Define.
+	(TARGET_INITIALIZER): Add initializer for set_current_function.
+	* tree.h (push_struct_function): New.
+	* tree-inline.h (push_cfun, pop_cfun): Move declarations to...
+	* function.h: Here.
+	(set_cfun): Declare.
+	* tree-inline.c (cfun_stack, push_cfun, pop_cfun): Moved to...
+	* function.c:  Here.
+	(push_function_context_to): Use allocate_struct_function
+	to create null context, not init_dummy_function_start.  Use set_cfun.
+	(pop_function_context_from): Use set_cfun.
+	(in_dummy_function): New.
+	(invoke_set_current_function_hook): New.
+	(set_cfun): New.
+	(push_cfun, pop_cfun): Use set_cfun.
+	(push_struct_function): New.
+	(allocate_struct_function): Call invoke_set_current_function_hook
+	before returning.
+	(prepare_function_start): Don't set cfun here.  Remove unused
+	argument; fix all callers.
+	(init_dummy_function_start): Fiddle with in_dummy_function.  Call
+	push_struct_function.
+	(init_function_start): Set cfun here.
+	(expand_dummy_function_end): Fiddle with in_dummy_function.  Pop cfun.
+	* omp-low.c (create_omp_child_function): Use push_struct_function
+	and pop_cfun to save/restore state.
+	(expand_omp_parallel): Remove unused saved_cfun variable.
+	* cgraphunit.c (ipa_passes): Use set_cfun.
+	* gimple-low.c (record_vars_into): Use push_cfun/pop_cfun here.
+	* dwarf2out.c (dwarf2out_abstract_function): Likewise.
+	* matrix-reorg.c (transform_allocation_sites): Likewise.
+	(matrix_reorg): Use set_cfun.
+	* gimplify.c (gimplify_function_tree): Use push_cfun/pop_cfun here.
+	* tree-optimize.c (tree_rest_of_compilation): Remove one redundant
+	assignment to cfun; use set_cfun for the other.
+	* tree-cfg.c (move_sese_region_to_fn): Use set_cfun.
+	(dump_function_to_file): Use push_cfun/pop_cfun here.
+	* c-decl.c (finish_function): Use set_cfun.
+
 2007-09-05  Kenneth Zadeck <zadeck@naturalbridge.com>
 
 	* regrename.c (rerename_optimize):  Use deferred rescanning and
diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index 5565cb87540c..30eab6919f97 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,8 @@
+2007-09-05  Sandra Loosemore  <sandra@codesourcery.com>
+
+	* trans.c (Compilation_unit_to_gnu): Use set_cfun.
+	* utils.c (end_subprog_body): Likewise.
+
 2007-09-03  Nick Clifton  <nickc@redhat.com>
 
 	* Make-lang.in: Change copyright header to refer to version 3 of
diff --git a/gcc/ada/trans.c b/gcc/ada/trans.c
index f6ba98c25f66..4d79cb3f9b6b 100644
--- a/gcc/ada/trans.c
+++ b/gcc/ada/trans.c
@@ -2874,7 +2874,7 @@ Compilation_Unit_to_gnu (Node_Id gnat_node)
   DECL_ELABORATION_PROC_P (gnu_elab_proc_decl) = 1;
   allocate_struct_function (gnu_elab_proc_decl);
   Sloc_to_locus (Sloc (gnat_unit_entity), &cfun->function_end_locus);
-  cfun = 0;
+  set_cfun (NULL);
 
   /* For a body, first process the spec if there is one. */
   if (Nkind (Unit (gnat_node)) == N_Package_Body
diff --git a/gcc/ada/utils.c b/gcc/ada/utils.c
index 037b3b982983..6a4cc3c7669d 100644
--- a/gcc/ada/utils.c
+++ b/gcc/ada/utils.c
@@ -2119,7 +2119,7 @@ end_subprog_body (tree body)
   DECL_SAVED_TREE (fndecl) = body;
 
   current_function_decl = DECL_CONTEXT (fndecl);
-  cfun = NULL;
+  set_cfun (NULL);
 
   /* We cannot track the location of errors past this point.  */
   error_gnat_node = Empty;
diff --git a/gcc/c-decl.c b/gcc/c-decl.c
index e265f675a3ed..bb790a2b7bb0 100644
--- a/gcc/c-decl.c
+++ b/gcc/c-decl.c
@@ -6820,7 +6820,7 @@ finish_function (void)
   /* We're leaving the context of this function, so zap cfun.
      It's still in DECL_STRUCT_FUNCTION, and we'll restore it in
      tree_rest_of_compilation.  */
-  cfun = NULL;
+  set_cfun (NULL);
   current_function_decl = NULL;
 }
 
diff --git a/gcc/cgraphunit.c b/gcc/cgraphunit.c
index accb6477d688..61d834dd1356 100644
--- a/gcc/cgraphunit.c
+++ b/gcc/cgraphunit.c
@@ -1264,7 +1264,7 @@ cgraph_preserve_function_body_p (tree decl)
 static void
 ipa_passes (void)
 {
-  cfun = NULL;
+  set_cfun (NULL);
   current_function_decl = NULL;
   tree_register_cfg_hooks ();
   bitmap_obstack_initialize (NULL);
diff --git a/gcc/cp/decl.c b/gcc/cp/decl.c
index 1b7012cb259f..5971bb873df9 100644
--- a/gcc/cp/decl.c
+++ b/gcc/cp/decl.c
@@ -11744,7 +11744,7 @@ finish_function (int flags)
 
   /* We're leaving the context of this function, so zap cfun.  It's still in
      DECL_STRUCT_FUNCTION, and we'll restore it in tree_rest_of_compilation.  */
-  cfun = NULL;
+  set_cfun (NULL);
   current_function_decl = NULL;
 
   /* If this is an in-class inline definition, we may have to pop the
diff --git a/gcc/cp/method.c b/gcc/cp/method.c
index efb223780daa..2130454a05a2 100644
--- a/gcc/cp/method.c
+++ b/gcc/cp/method.c
@@ -446,7 +446,7 @@ use_thunk (tree thunk_fndecl, bool emit_p)
       assemble_end_function (thunk_fndecl, fnname);
       init_insn_lengths ();
       current_function_decl = 0;
-      cfun = 0;
+      set_cfun (NULL);
       TREE_ASM_WRITTEN (thunk_fndecl) = 1;
     }
   else
diff --git a/gcc/doc/tm.texi b/gcc/doc/tm.texi
index a913b8058c65..4f8c0297d1ea 100644
--- a/gcc/doc/tm.texi
+++ b/gcc/doc/tm.texi
@@ -10139,6 +10139,23 @@ The default value of this hook is @code{NULL}, which disables any special
 allocation.
 @end deftypefn
 
+@deftypefn {Target Hook} void TARGET_SET_CURRENT_FUNCTION (tree @var{decl})
+The compiler invokes this hook whenever it changes its current function 
+context (@code{cfun}).  You can define this function if
+the back end needs to perform any initialization or reset actions on a
+per-function basis.  For example, it may be used to implement function
+attributes that affect register usage or code generation patterns.
+The argument @var{decl} is the declaration for the new function context,
+and may be null to indicate that the compiler has left a function context
+and is returning to processing at the top level.
+The default hook function does nothing.
+
+GCC sets @code{cfun} to a dummy function context during initialization of
+some parts of the back end.  The hook function is not invoked in this
+situation; you need not worry about the hook being invoked recursively,
+or when the back end is in a partially-initialized state.
+@end deftypefn
+
 @defmac TARGET_OBJECT_SUFFIX
 Define this macro to be a C string representing the suffix for object
 files on your target machine.  If you do not define this macro, GCC will
diff --git a/gcc/dwarf2out.c b/gcc/dwarf2out.c
index e1b332f71018..527de82dd5d5 100644
--- a/gcc/dwarf2out.c
+++ b/gcc/dwarf2out.c
@@ -11971,7 +11971,6 @@ dwarf2out_abstract_function (tree decl)
 {
   dw_die_ref old_die;
   tree save_fn;
-  struct function *save_cfun;
   tree context;
   int was_abstract = DECL_ABSTRACT (decl);
 
@@ -11995,9 +11994,8 @@ dwarf2out_abstract_function (tree decl)
 
   /* Pretend we've just finished compiling this function.  */
   save_fn = current_function_decl;
-  save_cfun = cfun;
   current_function_decl = decl;
-  cfun = DECL_STRUCT_FUNCTION (decl);
+  push_cfun (DECL_STRUCT_FUNCTION (decl));
 
   set_decl_abstract_flags (decl, 1);
   dwarf2out_decl (decl);
@@ -12005,7 +12003,7 @@ dwarf2out_abstract_function (tree decl)
     set_decl_abstract_flags (decl, 0);
 
   current_function_decl = save_fn;
-  cfun = save_cfun;
+  pop_cfun ();
 }
 
 /* Helper function of premark_used_types() which gets called through
diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index e1d6ecf07776..45bbac9ec82a 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,8 @@
+2007-09-05  Sandra Loosemore  <sandra@codesourcery.com>
+
+	* trans-decl.c (build_entry_thunks): Use set_cfun.
+	(gfc_generate_function_code): Likewise.
+
 2007-09-05  Paul Thomas  <pault@gcc.gnu.org>
 
 	PR fortran/31564
diff --git a/gcc/fortran/trans-decl.c b/gcc/fortran/trans-decl.c
index 0b709030d474..926a23924cea 100644
--- a/gcc/fortran/trans-decl.c
+++ b/gcc/fortran/trans-decl.c
@@ -1727,7 +1727,7 @@ build_entry_thunks (gfc_namespace * ns)
       /* We're leaving the context of this function, so zap cfun.
 	 It's still in DECL_STRUCT_FUNCTION, and we'll restore it in
 	 tree_rest_of_compilation.  */
-      cfun = NULL;
+      set_cfun (NULL);
 
       current_function_decl = NULL_TREE;
 
@@ -3341,7 +3341,7 @@ gfc_generate_function_code (gfc_namespace * ns)
   /* We're leaving the context of this function, so zap cfun.
      It's still in DECL_STRUCT_FUNCTION, and we'll restore it in
      tree_rest_of_compilation.  */
-  cfun = NULL;
+  set_cfun (NULL);
 
   if (old_context)
     {
diff --git a/gcc/function.c b/gcc/function.c
index f4fc6a3ced69..a2956b363a97 100644
--- a/gcc/function.c
+++ b/gcc/function.c
@@ -209,7 +209,7 @@ static void emit_return_into_block (basic_block);
 #if defined(HAVE_epilogue) && defined(INCOMING_RETURN_ADDR_RTX)
 static rtx keep_stack_depressed (rtx);
 #endif
-static void prepare_function_start (tree);
+static void prepare_function_start (void);
 static void do_clobber_return_reg (rtx, void *);
 static void do_use_return_reg (rtx, void *);
 static void set_insn_locators (rtx, int) ATTRIBUTE_UNUSED;
@@ -244,7 +244,7 @@ push_function_context_to (tree context ATTRIBUTE_UNUSED)
   struct function *p;
 
   if (cfun == 0)
-    init_dummy_function_start ();
+    allocate_struct_function (NULL);
   p = cfun;
 
   p->outer = outer_function_chain;
@@ -252,7 +252,7 @@ push_function_context_to (tree context ATTRIBUTE_UNUSED)
 
   lang_hooks.function.enter_nested (p);
 
-  cfun = 0;
+  set_cfun (NULL);
 }
 
 void
@@ -269,7 +269,7 @@ pop_function_context_from (tree context ATTRIBUTE_UNUSED)
 {
   struct function *p = outer_function_chain;
 
-  cfun = p;
+  set_cfun (p);
   outer_function_chain = p->outer;
 
   current_function_decl = p->decl;
@@ -3781,6 +3781,61 @@ debug_find_var_in_block_tree (tree var, tree block)
   return NULL_TREE;
 }
 
+/* Keep track of whether we're in a dummy function context.  If we are,
+   we don't want to invoke the set_current_function hook, because we'll
+   get into trouble if the hook calls target_reinit () recursively or
+   when the initial initialization is not yet complete.  */
+
+static bool in_dummy_function;
+
+/* Invoke the target hook when setting cfun.  */
+
+static void
+invoke_set_current_function_hook (tree fndecl)
+{
+  if (!in_dummy_function)
+    targetm.set_current_function (fndecl);
+}
+
+/* cfun should never be set directly; use this function.  */
+
+void
+set_cfun (struct function *new_cfun)
+{
+  if (cfun != new_cfun)
+    {
+      cfun = new_cfun;
+      invoke_set_current_function_hook (new_cfun ? new_cfun->decl : NULL_TREE);
+    }
+}
+
+/* Keep track of the cfun stack.  */
+
+typedef struct function *function_p;
+
+DEF_VEC_P(function_p);
+DEF_VEC_ALLOC_P(function_p,heap);
+
+/* Initialized with NOGC, making this poisonous to the garbage collector.  */
+
+static VEC(function_p,heap) *cfun_stack;
+
+/* Push the current cfun onto the stack, and set cfun to new_cfun.  */
+
+void
+push_cfun (struct function *new_cfun)
+{
+  VEC_safe_push (function_p, heap, cfun_stack, cfun);
+  set_cfun (new_cfun);
+}
+
+/* Pop cfun from the stack.  */
+
+void
+pop_cfun (void)
+{
+  set_cfun (VEC_pop (function_p, cfun_stack));
+}
 
 /* Return value of funcdef and increase it.  */
 int
@@ -3790,7 +3845,13 @@ get_next_funcdef_no (void)
 }
 
 /* Allocate a function structure for FNDECL and set its contents
-   to the defaults.  */
+   to the defaults.  Set cfun to the newly-allocated object.
+   Some of the helper functions invoked during initialization assume
+   that cfun has already been set.  Therefore, assign the new object
+   directly into cfun and invoke the back end hook explicitly at the
+   very end, rather than initializing a temporary and calling set_cfun
+   on it.
+*/
 
 void
 allocate_struct_function (tree fndecl)
@@ -3813,42 +3874,50 @@ allocate_struct_function (tree fndecl)
   if (init_machine_status)
     cfun->machine = (*init_machine_status) ();
 
-  if (fndecl == NULL)
-    return;
-
-  DECL_STRUCT_FUNCTION (fndecl) = cfun;
-  cfun->decl = fndecl;
-
-  result = DECL_RESULT (fndecl);
-  if (aggregate_value_p (result, fndecl))
+  if (fndecl != NULL)
     {
+      DECL_STRUCT_FUNCTION (fndecl) = cfun;
+      cfun->decl = fndecl;
+
+      result = DECL_RESULT (fndecl);
+      if (aggregate_value_p (result, fndecl))
+	{
 #ifdef PCC_STATIC_STRUCT_RETURN
-      current_function_returns_pcc_struct = 1;
+	  current_function_returns_pcc_struct = 1;
 #endif
-      current_function_returns_struct = 1;
+	  current_function_returns_struct = 1;
+	}
+
+      current_function_stdarg
+	= (fntype
+	   && TYPE_ARG_TYPES (fntype) != 0
+	   && (TREE_VALUE (tree_last (TYPE_ARG_TYPES (fntype)))
+	       != void_type_node));
+      
+      /* Assume all registers in stdarg functions need to be saved.  */
+      cfun->va_list_gpr_size = VA_LIST_MAX_GPR_SIZE;
+      cfun->va_list_fpr_size = VA_LIST_MAX_FPR_SIZE;
     }
 
-  current_function_stdarg
-    = (fntype
-       && TYPE_ARG_TYPES (fntype) != 0
-       && (TREE_VALUE (tree_last (TYPE_ARG_TYPES (fntype)))
-	   != void_type_node));
+  invoke_set_current_function_hook (fndecl);
+}
+
+/* This is like allocate_struct_function, but pushes a new cfun for FNDECL
+   instead of just setting it.  */
 
-  /* Assume all registers in stdarg functions need to be saved.  */
-  cfun->va_list_gpr_size = VA_LIST_MAX_GPR_SIZE;
-  cfun->va_list_fpr_size = VA_LIST_MAX_FPR_SIZE;
+void
+push_struct_function (tree fndecl)
+{
+  VEC_safe_push (function_p, heap, cfun_stack, cfun);
+  allocate_struct_function (fndecl);
 }
 
 /* Reset cfun, and other non-struct-function variables to defaults as
    appropriate for emitting rtl at the start of a function.  */
 
 static void
-prepare_function_start (tree fndecl)
+prepare_function_start (void)
 {
-  if (fndecl && DECL_STRUCT_FUNCTION (fndecl))
-    cfun = DECL_STRUCT_FUNCTION (fndecl);
-  else
-    allocate_struct_function (fndecl);
   init_emit ();
   init_varasm_status (cfun);
   init_expr ();
@@ -3873,11 +3942,16 @@ prepare_function_start (tree fndecl)
 
 /* Initialize the rtl expansion mechanism so that we can do simple things
    like generate sequences.  This is used to provide a context during global
-   initialization of some passes.  */
+   initialization of some passes.  You must call expand_dummy_function_end
+   to exit this context.  */
+
 void
 init_dummy_function_start (void)
 {
-  prepare_function_start (NULL);
+  gcc_assert (!in_dummy_function);
+  in_dummy_function = true;
+  push_struct_function (NULL_TREE);
+  prepare_function_start ();
 }
 
 /* Generate RTL for the start of the function SUBR (a FUNCTION_DECL tree node)
@@ -3887,7 +3961,11 @@ init_dummy_function_start (void)
 void
 init_function_start (tree subr)
 {
-  prepare_function_start (subr);
+  if (subr && DECL_STRUCT_FUNCTION (subr))
+    set_cfun (DECL_STRUCT_FUNCTION (subr));
+  else
+    allocate_struct_function (subr);
+  prepare_function_start ();
 
   /* Warn if this value is an aggregate type,
      regardless of which calling convention we are using for it.  */
@@ -4201,6 +4279,8 @@ expand_function_start (tree subr)
 void
 expand_dummy_function_end (void)
 {
+  gcc_assert (in_dummy_function);
+
   /* End any sequences that failed to be closed due to syntax errors.  */
   while (in_sequence_p ())
     end_sequence ();
@@ -4210,7 +4290,8 @@ expand_dummy_function_end (void)
 
   free_after_parsing (cfun);
   free_after_compilation (cfun);
-  cfun = 0;
+  pop_cfun ();
+  in_dummy_function = false;
 }
 
 /* Call DOIT for each hard register used as a return value from
diff --git a/gcc/function.h b/gcc/function.h
index 084f05b77b12..1317d81f4e67 100644
--- a/gcc/function.h
+++ b/gcc/function.h
@@ -474,6 +474,11 @@ extern int virtuals_instantiated;
 /* Nonzero if at least one trampoline has been created.  */
 extern int trampolines_created;
 
+/* cfun shouldn't be set directly; use one of these functions instead.  */
+extern void set_cfun (struct function *new_cfun);
+extern void push_cfun (struct function *new_cfun);
+extern void pop_cfun (void);
+
 /* For backward compatibility... eventually these should all go away.  */
 #define current_function_pops_args (cfun->pops_args)
 #define current_function_returns_struct (cfun->returns_struct)
diff --git a/gcc/gimple-low.c b/gcc/gimple-low.c
index 6de6eaeb6a18..69aa2bf27442 100644
--- a/gcc/gimple-low.c
+++ b/gcc/gimple-low.c
@@ -718,10 +718,8 @@ lower_builtin_setjmp (tree_stmt_iterator *tsi)
 void
 record_vars_into (tree vars, tree fn)
 {
-  struct function *saved_cfun = cfun;
-
   if (fn != current_function_decl)
-    cfun = DECL_STRUCT_FUNCTION (fn);
+    push_cfun (DECL_STRUCT_FUNCTION (fn));
 
   for (; vars; vars = TREE_CHAIN (vars))
     {
@@ -742,7 +740,7 @@ record_vars_into (tree vars, tree fn)
     }
 
   if (fn != current_function_decl)
-    cfun = saved_cfun;
+    pop_cfun ();
 }
 
 
diff --git a/gcc/gimplify.c b/gcc/gimplify.c
index 572a34fa6b3f..5c376ac50601 100644
--- a/gcc/gimplify.c
+++ b/gcc/gimplify.c
@@ -6466,9 +6466,10 @@ gimplify_function_tree (tree fndecl)
 
   oldfn = current_function_decl;
   current_function_decl = fndecl;
-  cfun = DECL_STRUCT_FUNCTION (fndecl);
-  if (cfun == NULL)
-    allocate_struct_function (fndecl);
+  if (DECL_STRUCT_FUNCTION (fndecl))
+    push_cfun (DECL_STRUCT_FUNCTION (fndecl));
+  else
+    push_struct_function (fndecl);
 
   for (parm = DECL_ARGUMENTS (fndecl); parm ; parm = TREE_CHAIN (parm))
     {
@@ -6520,7 +6521,7 @@ gimplify_function_tree (tree fndecl)
 
   cfun->gimplified = true;
   current_function_decl = oldfn;
-  cfun = oldfn ? DECL_STRUCT_FUNCTION (oldfn) : NULL;
+  pop_cfun ();
 }
 
 /* Expands EXPR to list of gimple statements STMTS.  If SIMPLE is true,
diff --git a/gcc/java/ChangeLog b/gcc/java/ChangeLog
index 6e27bb323699..3e8a3a490ac5 100644
--- a/gcc/java/ChangeLog
+++ b/gcc/java/ChangeLog
@@ -1,3 +1,7 @@
+2007-09-05  Sandra Loosemore  <sandra@codesourcery.com>
+
+	* decl.c (finish_method): Use set_cfun.
+
 2007-09-04  Andrew Haley  <aph@redhat.com>
 
 	* decl.c (java_init_decl_processing): Call "__cxa_end_cleanup"
diff --git a/gcc/java/decl.c b/gcc/java/decl.c
index 5340617e1c30..594ccf13d0c7 100644
--- a/gcc/java/decl.c
+++ b/gcc/java/decl.c
@@ -1848,7 +1848,7 @@ finish_method (tree fndecl)
   /* Store the end of the function, so that we get good line number
      info for the epilogue.  */
   if (DECL_STRUCT_FUNCTION (fndecl))
-    cfun = DECL_STRUCT_FUNCTION (fndecl);
+    set_cfun (DECL_STRUCT_FUNCTION (fndecl));
   else
     allocate_struct_function (fndecl);
 #ifdef USE_MAPPED_LOCATION
diff --git a/gcc/matrix-reorg.c b/gcc/matrix-reorg.c
index 46fd6e25a598..f70b048cd64d 100644
--- a/gcc/matrix-reorg.c
+++ b/gcc/matrix-reorg.c
@@ -2045,7 +2045,7 @@ transform_allocation_sites (void **slot, void *data ATTRIBUTE_UNUSED)
   /* To be able to produce gimple temporaries.  */
   oldfn = current_function_decl;
   current_function_decl = mi->allocation_function_decl;
-  cfun = DECL_STRUCT_FUNCTION (mi->allocation_function_decl);
+  push_cfun (DECL_STRUCT_FUNCTION (mi->allocation_function_decl));
 
   /* Set the dimension sizes as follows:
      DIM_SIZE[i] = DIM_SIZE[n] * ... * DIM_SIZE[i]
@@ -2169,13 +2169,13 @@ transform_allocation_sites (void **slot, void *data ATTRIBUTE_UNUSED)
       gcc_assert (e);
       cgraph_remove_edge (e);
       current_function_decl = mi->free_stmts[i].func;
-      cfun = DECL_STRUCT_FUNCTION (mi->free_stmts[i].func);
+      set_cfun (DECL_STRUCT_FUNCTION (mi->free_stmts[i].func));
       bsi = bsi_for_stmt (mi->free_stmts[i].stmt);
       bsi_remove (&bsi, true);
     }
   /* Return to the previous situation.  */
   current_function_decl = oldfn;
-  cfun = oldfn ? DECL_STRUCT_FUNCTION (oldfn) : NULL;
+  pop_cfun ();
   return 1;
 
 }
@@ -2304,7 +2304,7 @@ matrix_reorg (void)
   htab_traverse (matrices_to_reorg, dump_matrix_reorg_analysis, NULL);
 
   current_function_decl = NULL;
-  cfun = NULL;
+  set_cfun (NULL);
   matrices_to_reorg = NULL;
   return 0;
 }
diff --git a/gcc/omp-low.c b/gcc/omp-low.c
index 5aaa7fe86823..c1ab3f311932 100644
--- a/gcc/omp-low.c
+++ b/gcc/omp-low.c
@@ -1144,10 +1144,10 @@ create_omp_child_function (omp_context *ctx)
   /* Allocate memory for the function structure.  The call to 
      allocate_struct_function clobbers CFUN, so we need to restore
      it afterward.  */
-  allocate_struct_function (decl);
+  push_struct_function (decl);
   DECL_SOURCE_LOCATION (decl) = EXPR_LOCATION (ctx->stmt);
   cfun->function_end_locus = EXPR_LOCATION (ctx->stmt);
-  cfun = ctx->cb.src_cfun;
+  pop_cfun ();
 }
 
 
@@ -2403,7 +2403,7 @@ static void
 expand_omp_parallel (struct omp_region *region)
 {
   basic_block entry_bb, exit_bb, new_bb;
-  struct function *child_cfun, *saved_cfun;
+  struct function *child_cfun;
   tree child_fn, block, t, ws_args;
   block_stmt_iterator si;
   tree entry_stmt;
@@ -2413,7 +2413,6 @@ expand_omp_parallel (struct omp_region *region)
   entry_stmt = last_stmt (region->entry);
   child_fn = OMP_PARALLEL_FN (entry_stmt);
   child_cfun = DECL_STRUCT_FUNCTION (child_fn);
-  saved_cfun = cfun;
 
   entry_bb = region->entry;
   exit_bb = region->exit;
diff --git a/gcc/target-def.h b/gcc/target-def.h
index 0ffad7c836a4..c195af2004e1 100644
--- a/gcc/target-def.h
+++ b/gcc/target-def.h
@@ -479,6 +479,10 @@
 #define TARGET_MANGLE_TYPE hook_constcharptr_const_tree_null
 #define TARGET_ALLOCATE_INITIAL_VALUE NULL
 
+#ifndef TARGET_SET_CURRENT_FUNCTION
+#define TARGET_SET_CURRENT_FUNCTION hook_void_tree
+#endif
+
 #ifndef TARGET_INIT_LIBFUNCS
 #define TARGET_INIT_LIBFUNCS hook_void_void
 #endif
@@ -720,6 +724,7 @@
   TARGET_MAX_ANCHOR_OFFSET,			\
   TARGET_USE_ANCHORS_FOR_SYMBOL_P,		\
   TARGET_FUNCTION_OK_FOR_SIBCALL,		\
+  TARGET_SET_CURRENT_FUNCTION,			\
   TARGET_IN_SMALL_DATA_P,			\
   TARGET_BINDS_LOCAL_P,				\
   TARGET_MANGLE_DECL_ASSEMBLER_NAME,		\
diff --git a/gcc/target.h b/gcc/target.h
index 5918aed743f1..bf76402eaa5f 100644
--- a/gcc/target.h
+++ b/gcc/target.h
@@ -570,6 +570,11 @@ struct gcc_target
      this is an indirect call.  */
   bool (*function_ok_for_sibcall) (tree decl, tree exp);
 
+  /* Establish appropriate back-end context for processing the function
+     FNDECL.  The argument might be NULL to indicate processing at top
+     level, outside of any function scope.  */
+  void (*set_current_function) (tree fndecl);
+
   /* True if EXP should be placed in a "small data" section.  */
   bool (* in_small_data_p) (const_tree);
 
diff --git a/gcc/tree-cfg.c b/gcc/tree-cfg.c
index b01d7ab8b93e..95f27141c0fb 100644
--- a/gcc/tree-cfg.c
+++ b/gcc/tree-cfg.c
@@ -5582,7 +5582,7 @@ move_sese_region_to_fn (struct function *dest_cfun, basic_block entry_bb,
 
   /* Switch context to the child function to initialize DEST_FN's CFG.  */
   gcc_assert (dest_cfun->cfg == NULL);
-  cfun = dest_cfun;
+  set_cfun (dest_cfun);
 
   init_empty_tree_cfg ();
 
@@ -5605,7 +5605,7 @@ move_sese_region_to_fn (struct function *dest_cfun, basic_block entry_bb,
 	}
     }
 
-  cfun = saved_cfun;
+  set_cfun (saved_cfun);
 
   /* Move blocks from BBS into DEST_CFUN.  */
   gcc_assert (VEC_length (basic_block, bbs) >= 2);
@@ -5655,11 +5655,11 @@ move_sese_region_to_fn (struct function *dest_cfun, basic_block entry_bb,
 
      FIXME, this is silly.  The CFG ought to become a parameter to
      these helpers.  */
-  cfun = dest_cfun;
+  set_cfun (dest_cfun);
   make_edge (ENTRY_BLOCK_PTR, entry_bb, EDGE_FALLTHRU);
   if (exit_bb)
     make_edge (exit_bb,  EXIT_BLOCK_PTR, 0);
-  cfun = saved_cfun;
+  set_cfun (saved_cfun);
 
   /* Back in the original function, the SESE region has disappeared,
      create a new basic block in its place.  */
@@ -5695,7 +5695,6 @@ dump_function_to_file (tree fn, FILE *file, int flags)
   bool ignore_topmost_bind = false, any_var = false;
   basic_block bb;
   tree chain;
-  struct function *saved_cfun;
 
   fprintf (file, "%s (", lang_hooks.decl_printable_name (fn, 2));
 
@@ -5720,8 +5719,7 @@ dump_function_to_file (tree fn, FILE *file, int flags)
     }
 
   /* Switch CFUN to point to FN.  */
-  saved_cfun = cfun;
-  cfun = DECL_STRUCT_FUNCTION (fn);
+  push_cfun (DECL_STRUCT_FUNCTION (fn));
 
   /* When GIMPLE is lowered, the variables are no longer available in
      BIND_EXPRs, so display them separately.  */
@@ -5792,7 +5790,7 @@ dump_function_to_file (tree fn, FILE *file, int flags)
   fprintf (file, "\n\n");
 
   /* Restore CFUN.  */
-  cfun = saved_cfun;
+  pop_cfun ();
 }
 
 
diff --git a/gcc/tree-inline.c b/gcc/tree-inline.c
index b2b959097cd1..b655b79ac01d 100644
--- a/gcc/tree-inline.c
+++ b/gcc/tree-inline.c
@@ -2333,27 +2333,6 @@ init_inline_once (void)
   eni_time_weights.omp_cost = 40;
 }
 
-typedef struct function *function_p;
-
-DEF_VEC_P(function_p);
-DEF_VEC_ALLOC_P(function_p,heap);
-
-/* Initialized with NOGC, making this poisonous to the garbage collector.  */
-static VEC(function_p,heap) *cfun_stack;
-
-void
-push_cfun (struct function *new_cfun)
-{
-  VEC_safe_push (function_p, heap, cfun_stack, cfun);
-  cfun = new_cfun;
-}
-
-void
-pop_cfun (void)
-{
-  cfun = VEC_pop (function_p, cfun_stack);
-}
-
 /* Install new lexical TREE_BLOCK underneath 'current_block'.  */
 static void
 add_lexical_block (tree current_block, tree new_block)
diff --git a/gcc/tree-inline.h b/gcc/tree-inline.h
index 200a9a68fc36..574b1d70040f 100644
--- a/gcc/tree-inline.h
+++ b/gcc/tree-inline.h
@@ -134,8 +134,6 @@ tree copy_tree_r (tree *, int *, void *);
 void clone_body (tree, tree, void *);
 void save_body (tree, tree *, tree *);
 int estimate_move_cost (tree type);
-void push_cfun (struct function *new_cfun);
-void pop_cfun (void);
 int estimate_num_insns (tree expr, eni_weights *);
 bool tree_versionable_function_p (tree);
 void tree_function_versioning (tree, tree, varray_type, bool);
diff --git a/gcc/tree-optimize.c b/gcc/tree-optimize.c
index b4bd069b6175..e367bb7b4451 100644
--- a/gcc/tree-optimize.c
+++ b/gcc/tree-optimize.c
@@ -387,7 +387,6 @@ tree_rest_of_compilation (tree fndecl)
 
   /* Initialize the RTL code for the function.  */
   current_function_decl = fndecl;
-  cfun = DECL_STRUCT_FUNCTION (fndecl);
   saved_loc = input_location;
   input_location = DECL_SOURCE_LOCATION (fndecl);
   init_function_start (fndecl);
@@ -410,7 +409,7 @@ tree_rest_of_compilation (tree fndecl)
   bitmap_obstack_release (NULL);
   
   DECL_SAVED_TREE (fndecl) = NULL;
-  cfun = 0;
+  set_cfun (NULL);
 
   /* If requested, warn about function definitions where the function will
      return a value (usually of some struct or union type) which itself will
diff --git a/gcc/tree.h b/gcc/tree.h
index 3b773445a856..5fda4d4b3a18 100644
--- a/gcc/tree.h
+++ b/gcc/tree.h
@@ -4859,6 +4859,7 @@ extern void init_dummy_function_start (void);
 extern void expand_dummy_function_end (void);
 extern unsigned int init_function_for_compilation (void);
 extern void allocate_struct_function (tree);
+extern void push_struct_function (tree fndecl);
 extern void init_function_start (tree);
 extern bool use_register_for_decl (const_tree);
 extern void generate_setjmp_warnings (void);
diff --git a/gcc/treelang/ChangeLog b/gcc/treelang/ChangeLog
index db987d001d39..8c464d69940c 100644
--- a/gcc/treelang/ChangeLog
+++ b/gcc/treelang/ChangeLog
@@ -1,3 +1,7 @@
+2007-09-05  Sandra Loosemore  <sandra@codesourcery.com>
+
+	* treetree.c (tree_code_create_function_wrapup):  Use set_cfun.
+
 2007-08-21  Paul Brook  <paul@codesourcery.com>
 	    Nathan Sidwell  <nathan@codesourcery.com>
 	    Mark Mitchell  <mark@codesourcery.com>
diff --git a/gcc/treelang/treetree.c b/gcc/treelang/treetree.c
index 295d882cb298..dd4489b42a82 100644
--- a/gcc/treelang/treetree.c
+++ b/gcc/treelang/treetree.c
@@ -473,7 +473,7 @@ tree_code_create_function_wrapup (location_t loc)
 
   /* We are not inside of any scope now.  */
   current_function_decl = NULL_TREE;
-  cfun = NULL;
+  set_cfun (NULL);
 
   /* Pass the current function off to the middle end.  */
   (void)cgraph_node (fn_decl);
-- 
GitLab