diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 7366371cd235533fdfef8df6215dd53c6da38f64..228d76eb14dfee734de558baa28c50c8f62f1ed0 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,72 @@
+2005-04-09  Caroline Tice  <ctice@apple.com>
+
+	* bb-reorder.c (find_rarely_executed_basic_blocks_and_crossing_edges):
+	Remove targetm.have_named_sections test.
+	(fix_edges_for_rarely_executed_code): Likewise.
+	(insert_section_boundary_note): Likewise.
+	(reorder_basic_blocks): Check partitioning flag before calling
+	verify_hot_cold_block_grouping.
+	* dbxout.c (dbxout_function_end): Get hot/cold section labels from
+	the function struct rather than global variables.
+	* dwarf2out.c (COLD_TEXT_SECTION_LABEL): New macro.
+	(COLD_END_LABEL): Likewise
+	(cold_text_section_label): New static global variable.
+	(cold_end_label): Likewise.
+	(dwarf2out_switch_text_section): Get hot/cold section labels from
+	the function struct rather than global variables.
+	(output_aranges): Use cold_text_section_label and cold_end_label;
+	check partitioning flag before putting out delta.
+	(output_ranges): Remove incorrect code attempting to use
+	hot/cold labels.
+	(output_line_info): Get cold section label from function struct.
+	(add_location_or_const_value_attribute): Likewise.
+	(get_subprogram_die): Get hot/cold section labels from function struct.
+	(dwarf2out_var_location): Likewise.
+	(dwarf2out_init): Generate cold_text_section_label and cold_end_label;
+	write out cold_text_section_label if partition flag is set.
+	(dwarf2out_finish): Write out cold_end_label if partition flag is set;
+	* function.h (struct function): Add new fields to point to hot/cold
+	section labels: hot_section_label, cold_section_label,
+	hot_section_end_label and cold_section_end_label; also add new field
+	for cold text section name, unlikely_text_section_name.
+	* opts.c (decode_options): Turn off partitioning flag if
+	!targetm.have_named_sections.
+	* output.h (hot_section_label): Remove.
+	(hot_section_end_label): Remove.
+	(cold_section_end_label): Remove.
+	(unlikely_section_label): Remove.
+	(unlikely_text_section_name): Remove.
+	* passes.c (rest_of_handle_final):  Remove code that frees
+	unlikely_text_section_name.
+	* varasm.c (unlikely_section_label): Remove.
+	(hot_section_label): Remove.
+	(hot_section_end_label): Remove.
+	(cold_section_end_label): Remove.
+	(unlikely_text_section_name):  Remove.
+	(initialize_cold_section_name): Modify to call
+	targetm.strip_name_encoding; to store cold section name in current
+	function struct, if it exists; and to only use the decl_section_name
+	if flag_named_sections is true.
+	(unlikely_text_section): Modify to get section name out of current
+	function struct, if there is one; otherwise build it from
+	UNLIKELY_EXECUTED_TEXT_SECTION_NAME.
+	(in_unlikely_text_section): Likewise.
+	(named_section): Modify to get/put cold section name in current function
+	struct, if there is one.
+	(function_section):  Change 'bool unlikely' to 'int reloc'; check
+	targetm.have_named_sections before calling named_section.
+	(current_function_section): Likewise.
+	(assemble_start_function): Modify to get/put unlikely_text_section_name
+	in current function struct; modify to get hot/cold section labels
+	from function struct; initialize labels using 
+	ASM_GENERATE_INTERNAL_LABEL;
+	test partitioning flag before writing out hot section label.
+	(assemble_end_function): Test partitioning flag before writing out
+	hot/cold section labels.
+	(default_section_type_flags_1):  Modify to use array instead of
+	 char* for unlikely_text_section_name; set flags correctly for
+	 cold text section if there is not a current function decl.
+
 2005-04-09  Jakub Jelinek  <jakub@redhat.com>
 
 	* tree.h (enum tree_index): Add TI_VA_LIST_GPR_COUNTER_FIELD
diff --git a/gcc/bb-reorder.c b/gcc/bb-reorder.c
index 6925114e133ddc3ed9b24a9bb928f77f4fcde00a..4936ca409107a089d45fe1fb85db30ca0d3f6ec4 100644
--- a/gcc/bb-reorder.c
+++ b/gcc/bb-reorder.c
@@ -1241,27 +1241,24 @@ find_rarely_executed_basic_blocks_and_crossing_edges (edge *crossing_edges,
   /* Mark every edge that crosses between sections.  */
 
   i = 0;
-  if (targetm.have_named_sections)
+  FOR_EACH_BB (bb)
+    FOR_EACH_EDGE (e, ei, bb->succs)
     {
-      FOR_EACH_BB (bb)
-        FOR_EACH_EDGE (e, ei, bb->succs)
-	  {
-	    if (e->src != ENTRY_BLOCK_PTR
-		&& e->dest != EXIT_BLOCK_PTR
-		&& BB_PARTITION (e->src) != BB_PARTITION (e->dest))
-	      {
-		e->flags |= EDGE_CROSSING;
-		if (i == *max_idx)
-		  {
-		    *max_idx *= 2;
-		    crossing_edges = xrealloc (crossing_edges,
-					       (*max_idx) * sizeof (edge));
-		  }
-		crossing_edges[i++] = e;
-	      }
-	    else
-	      e->flags &= ~EDGE_CROSSING;
-	  }
+      if (e->src != ENTRY_BLOCK_PTR
+	  && e->dest != EXIT_BLOCK_PTR
+	  && BB_PARTITION (e->src) != BB_PARTITION (e->dest))
+	{
+	  e->flags |= EDGE_CROSSING;
+	  if (i == *max_idx)
+	    {
+	      *max_idx *= 2;
+	      crossing_edges = xrealloc (crossing_edges,
+					 (*max_idx) * sizeof (edge));
+	    }
+	  crossing_edges[i++] = e;
+	}
+      else
+	e->flags &= ~EDGE_CROSSING;
     }
   *n_crossing_edges = i;
 }
@@ -1825,36 +1822,26 @@ fix_edges_for_rarely_executed_code (edge *crossing_edges,
   
   fix_up_fall_thru_edges ();
   
-  /* Only do the parts necessary for writing separate sections if
-     the target architecture has the ability to write separate sections
-     (i.e. it has named sections).  Otherwise, the hot/cold partitioning
-     information will be used when reordering blocks to try to put all
-     the hot blocks together, then all the cold blocks, but no actual
-     section partitioning will be done.  */
-
-  if (targetm.have_named_sections)
-    {
-      /* If the architecture does not have conditional branches that can
-	 span all of memory, convert crossing conditional branches into
-	 crossing unconditional branches.  */
+  /* If the architecture does not have conditional branches that can
+     span all of memory, convert crossing conditional branches into
+     crossing unconditional branches.  */
   
-      if (!HAS_LONG_COND_BRANCH)
-	fix_crossing_conditional_branches ();
+  if (!HAS_LONG_COND_BRANCH)
+    fix_crossing_conditional_branches ();
   
-      /* If the architecture does not have unconditional branches that
-	 can span all of memory, convert crossing unconditional branches
-	 into indirect jumps.  Since adding an indirect jump also adds
-	 a new register usage, update the register usage information as
-	 well.  */
-      
-      if (!HAS_LONG_UNCOND_BRANCH)
-	{
-	  fix_crossing_unconditional_branches ();
-	  reg_scan (get_insns(), max_reg_num ());
-	}
-
-      add_reg_crossing_jump_notes ();
+  /* If the architecture does not have unconditional branches that
+     can span all of memory, convert crossing unconditional branches
+     into indirect jumps.  Since adding an indirect jump also adds
+     a new register usage, update the register usage information as
+     well.  */
+  
+  if (!HAS_LONG_UNCOND_BRANCH)
+    {
+      fix_crossing_unconditional_branches ();
+      reg_scan (get_insns(), max_reg_num ());
     }
+  
+  add_reg_crossing_jump_notes ();
 }
 
 /* Verify, in the basic block chain, that there is at most one switch
@@ -1946,7 +1933,8 @@ reorder_basic_blocks (unsigned int flags)
     dump_flow_info (dump_file);
 
   cfg_layout_finalize ();
-  verify_hot_cold_block_grouping ();
+  if (flag_reorder_blocks_and_partition)
+    verify_hot_cold_block_grouping ();
 
   timevar_pop (TV_REORDER_BLOCKS);
 }
@@ -1966,8 +1954,7 @@ insert_section_boundary_note (void)
   rtx new_note;
   int first_partition = 0;
   
-  if (flag_reorder_blocks_and_partition
-      && targetm.have_named_sections)
+  if (flag_reorder_blocks_and_partition)
     FOR_EACH_BB (bb)
     {
       if (!first_partition)
diff --git a/gcc/dbxout.c b/gcc/dbxout.c
index c645edbeec2d00346c656032664c0dd76dfe72c2..33bbd716b1713efa132623c3c864f56485a4b595 100644
--- a/gcc/dbxout.c
+++ b/gcc/dbxout.c
@@ -938,11 +938,14 @@ dbxout_function_end (tree decl)
 #else
   if (flag_reorder_blocks_and_partition)
     {
+      struct function *cfun = DECL_STRUCT_FUNCTION (decl);
+
       dbxout_begin_empty_stabs (N_FUN);
-      dbxout_stab_value_label_diff (hot_section_end_label, hot_section_label);
+      dbxout_stab_value_label_diff (cfun->hot_section_end_label, 
+				    cfun->hot_section_label);
       dbxout_begin_empty_stabs (N_FUN);
-      dbxout_stab_value_label_diff (cold_section_end_label, 
-				    unlikely_section_label);
+      dbxout_stab_value_label_diff (cfun->cold_section_end_label, 
+				    cfun->cold_section_label);
     }
   else
     {
diff --git a/gcc/dwarf2out.c b/gcc/dwarf2out.c
index 6b08ab649c4fc6bde4f0de5330e34aaf56ff54e3..a7b2b86a0098f1ad0995f4670d5bbb648c174840 100644
--- a/gcc/dwarf2out.c
+++ b/gcc/dwarf2out.c
@@ -4122,6 +4122,9 @@ static int maybe_emit_file (int);
 #ifndef TEXT_SECTION_LABEL
 #define TEXT_SECTION_LABEL		"Ltext"
 #endif
+#ifndef COLD_TEXT_SECTION_LABEL
+#define COLD_TEXT_SECTION_LABEL         "Ltext_cold"
+#endif
 #ifndef DEBUG_LINE_SECTION_LABEL
 #define DEBUG_LINE_SECTION_LABEL	"Ldebug_line"
 #endif
@@ -4149,6 +4152,8 @@ static int maybe_emit_file (int);
 
 static char text_end_label[MAX_ARTIFICIAL_LABEL_BYTES];
 static char text_section_label[MAX_ARTIFICIAL_LABEL_BYTES];
+static char cold_text_section_label[MAX_ARTIFICIAL_LABEL_BYTES];
+static char cold_end_label[MAX_ARTIFICIAL_LABEL_BYTES]; 
 static char abbrev_section_label[MAX_ARTIFICIAL_LABEL_BYTES];
 static char debug_info_section_label[MAX_ARTIFICIAL_LABEL_BYTES];
 static char debug_line_section_label[MAX_ARTIFICIAL_LABEL_BYTES];
@@ -4159,6 +4164,9 @@ static char ranges_section_label[2 * MAX_ARTIFICIAL_LABEL_BYTES];
 #ifndef TEXT_END_LABEL
 #define TEXT_END_LABEL		"Letext"
 #endif
+#ifndef COLD_END_LABEL
+#define COLD_END_LABEL          "Letext_cold"
+#endif
 #ifndef BLOCK_BEGIN_LABEL
 #define BLOCK_BEGIN_LABEL	"LBB"
 #endif
@@ -6799,13 +6807,14 @@ static void
 dwarf2out_switch_text_section (void)
 {
   dw_fde_ref fde;
+  struct function *cfun = DECL_STRUCT_FUNCTION (current_function_decl);
 
   fde = &fde_table[fde_table_in_use - 1];
   fde->dw_fde_switched_sections = true;
-  fde->dw_fde_hot_section_label = xstrdup (hot_section_label);
-  fde->dw_fde_hot_section_end_label = xstrdup (hot_section_end_label);
-  fde->dw_fde_unlikely_section_label = xstrdup (unlikely_section_label);
-  fde->dw_fde_unlikely_section_end_label = xstrdup (cold_section_end_label);
+  fde->dw_fde_hot_section_label = cfun->hot_section_label;
+  fde->dw_fde_hot_section_end_label = cfun->hot_section_end_label;
+  fde->dw_fde_unlikely_section_label = cfun->cold_section_label;
+  fde->dw_fde_unlikely_section_end_label = cfun->cold_section_end_label;
   separate_line_info_table_in_use++;
 }
 
@@ -7235,14 +7244,15 @@ output_aranges (void)
     }
 
   dw2_asm_output_addr (DWARF2_ADDR_SIZE, text_section_label, "Address");
-  if (last_text_section == in_unlikely_executed_text
-      || (last_text_section == in_named
-	  && last_text_section_name == unlikely_text_section_name))
-    dw2_asm_output_delta (DWARF2_ADDR_SIZE, text_end_label,
-			  unlikely_section_label, "Length");
-  else
-    dw2_asm_output_delta (DWARF2_ADDR_SIZE, text_end_label,
-			  text_section_label, "Length");
+  dw2_asm_output_delta (DWARF2_ADDR_SIZE, text_end_label,
+			text_section_label, "Length");
+  if (flag_reorder_blocks_and_partition)
+    {
+      dw2_asm_output_addr (DWARF2_ADDR_SIZE, cold_text_section_label, 
+			   "Address");
+      dw2_asm_output_delta (DWARF2_ADDR_SIZE, cold_end_label,
+			    cold_text_section_label, "Length");
+    }
 
   for (i = 0; i < arange_table_in_use; i++)
     {
@@ -7332,24 +7342,11 @@ output_ranges (void)
 	     base of the text section.  */
 	  if (separate_line_info_table_in_use == 0)
 	    {
-	      if (last_text_section == in_unlikely_executed_text
-		  || (last_text_section == in_named
-		      && last_text_section_name == unlikely_text_section_name))
-		{
-		  dw2_asm_output_delta (DWARF2_ADDR_SIZE, blabel,
-					unlikely_section_label,
-					fmt, i * 2 * DWARF2_ADDR_SIZE);
-		  dw2_asm_output_delta (DWARF2_ADDR_SIZE, elabel,
-					unlikely_section_label, NULL);
-		}
-	      else
-		{
-		  dw2_asm_output_delta (DWARF2_ADDR_SIZE, blabel,
-					text_section_label,
-					fmt, i * 2 * DWARF2_ADDR_SIZE);
-		  dw2_asm_output_delta (DWARF2_ADDR_SIZE, elabel,
-					text_section_label, NULL);
-		}
+	      dw2_asm_output_delta (DWARF2_ADDR_SIZE, blabel,
+				    text_section_label,
+				    fmt, i * 2 * DWARF2_ADDR_SIZE);
+	      dw2_asm_output_delta (DWARF2_ADDR_SIZE, elabel,
+				    text_section_label, NULL);
 	    }
 
 	  /* Otherwise, we add a DW_AT_entry_pc attribute to force the
@@ -7665,6 +7662,7 @@ output_line_info (void)
   long line_delta;
   unsigned long current_file;
   unsigned long function;
+  struct function *cfun = DECL_STRUCT_FUNCTION (current_function_decl);
 
   ASM_GENERATE_INTERNAL_LABEL (l1, LINE_NUMBER_BEGIN_LABEL, 0);
   ASM_GENERATE_INTERNAL_LABEL (l2, LINE_NUMBER_END_LABEL, 0);
@@ -7736,8 +7734,8 @@ output_line_info (void)
   current_line = 1;
   if (last_text_section == in_unlikely_executed_text
       || (last_text_section == in_named
-	  && last_text_section_name == unlikely_text_section_name))
-    strcpy (prev_line_label, unlikely_section_label);
+	  && last_text_section_name == cfun->unlikely_text_section_name))
+    strcpy (prev_line_label, cfun->cold_section_label);
   else
     strcpy (prev_line_label, text_section_label);
   for (lt_index = 1; lt_index < line_info_table_in_use; ++lt_index)
@@ -10110,6 +10108,7 @@ add_location_or_const_value_attribute (dw_die_ref die, tree decl,
       const char *endname;
       dw_loc_list_ref list;
       rtx varloc;
+      struct function *cfun = DECL_STRUCT_FUNCTION (current_function_decl);
 
 
       /* We need to figure out what section we should use as the base
@@ -10135,8 +10134,8 @@ add_location_or_const_value_attribute (dw_die_ref die, tree decl,
 	}
       else if (last_text_section == in_unlikely_executed_text
 	       || (last_text_section == in_named
-		   && last_text_section_name == unlikely_text_section_name))
-	secname = unlikely_section_label;
+		   && last_text_section_name == cfun->unlikely_text_section_name))
+	secname = cfun->cold_section_label;
       else
 	secname = text_section_label;
 
@@ -13229,6 +13228,7 @@ dwarf2out_var_location (rtx loc_note)
   static rtx last_insn;
   static const char *last_label;
   tree decl;
+  struct function *cfun = DECL_STRUCT_FUNCTION (current_function_decl);
 
   if (!DECL_P (NOTE_VAR_LOCATION_DECL (loc_note)))
     return;
@@ -13257,8 +13257,8 @@ dwarf2out_var_location (rtx loc_note)
 
   if (last_text_section == in_unlikely_executed_text
       || (last_text_section == in_named
-	  && last_text_section_name == unlikely_text_section_name))
-    newloc->section_label = unlikely_section_label;
+	  && last_text_section_name == cfun->unlikely_text_section_name))
+    newloc->section_label = cfun->cold_section_label;
   else
     newloc->section_label = text_section_label;
 
@@ -13496,6 +13496,9 @@ dwarf2out_init (const char *filename ATTRIBUTE_UNUSED)
   ASM_GENERATE_INTERNAL_LABEL (abbrev_section_label,
 			       DEBUG_ABBREV_SECTION_LABEL, 0);
   ASM_GENERATE_INTERNAL_LABEL (text_section_label, TEXT_SECTION_LABEL, 0);
+  ASM_GENERATE_INTERNAL_LABEL (cold_text_section_label, 
+			       COLD_TEXT_SECTION_LABEL, 0);
+  ASM_GENERATE_INTERNAL_LABEL (cold_end_label, COLD_END_LABEL, 0);
 
   ASM_GENERATE_INTERNAL_LABEL (debug_info_section_label,
 			       DEBUG_INFO_SECTION_LABEL, 0);
@@ -13520,6 +13523,11 @@ dwarf2out_init (const char *filename ATTRIBUTE_UNUSED)
 
   text_section ();
   ASM_OUTPUT_LABEL (asm_out_file, text_section_label);
+  if (flag_reorder_blocks_and_partition)
+    {
+      unlikely_text_section ();
+      ASM_OUTPUT_LABEL (asm_out_file, cold_text_section_label);
+    }
 }
 
 /* A helper function for dwarf2out_finish called through
@@ -13851,6 +13859,11 @@ dwarf2out_finish (const char *filename)
   /* Output a terminator label for the .text section.  */
   text_section ();
   targetm.asm_out.internal_label (asm_out_file, TEXT_END_LABEL, 0);
+  if (flag_reorder_blocks_and_partition)
+    {
+      unlikely_text_section ();
+      targetm.asm_out.internal_label (asm_out_file, COLD_END_LABEL, 0);
+    }
 
   /* Output the source line correspondence table.  We must do this
      even if there is no line information.  Otherwise, on an empty
diff --git a/gcc/function.h b/gcc/function.h
index b772752552f27877ad0ad05ff1f47a91ca2b9934..d1f006ba1e82617416779619934f9b6910531d79 100644
--- a/gcc/function.h
+++ b/gcc/function.h
@@ -349,6 +349,20 @@ struct function GTY(())
   /* The variables unexpanded so far.  */
   tree unexpanded_var_list;
 
+  /* Assembly labels for the hot and cold text sections, to
+     be used by debugger functions for determining the size of text
+     sections.  */
+
+  const char * hot_section_label;
+  const char * cold_section_label;
+  const char * hot_section_end_label;
+  const char * cold_section_end_label;
+
+  /* String to be used for name of cold text sections, via
+     targetm.asm_out.named_section.  */
+
+  const char *unlikely_text_section_name;
+
   /* Collected bit flags.  */
 
   /* Nonzero if function being compiled needs to be given an address
diff --git a/gcc/opts.c b/gcc/opts.c
index 70a9b22ac5b6b460a2cc444c32278a12c9b1f20d..c2cf1251cc9a804ced5b58199a6ddaddd4af4cf1 100644
--- a/gcc/opts.c
+++ b/gcc/opts.c
@@ -678,6 +678,15 @@ decode_options (unsigned int argc, const char **argv)
       flag_reorder_blocks_and_partition = 0;
       flag_reorder_blocks = 1;
     }
+
+  if (flag_reorder_blocks_and_partition
+      && !targetm.have_named_sections)
+    {
+      inform 
+       ("-freorder-blocks-and-partition does not work on this architecture.");
+      flag_reorder_blocks_and_partition = 0;
+      flag_reorder_blocks = 1;
+    }
 }
 
 /* Handle target- and language-independent options.  Return zero to
diff --git a/gcc/output.h b/gcc/output.h
index 4d9eabb49f75b5a7a3b7a3eddf4e654274640dfc..ac90908baf87c8b82d70781a7fefb123a19d5f73 100644
--- a/gcc/output.h
+++ b/gcc/output.h
@@ -453,11 +453,6 @@ enum in_section { no_section, in_text, in_unlikely_executed_text, in_data,
 #endif
 };
 
-extern char *unlikely_section_label;
-extern char *hot_section_label;
-extern char *hot_section_end_label;
-extern char *cold_section_end_label;
-extern char *unlikely_text_section_name;
 extern const char *last_text_section_name;
 extern enum in_section last_text_section;
 extern bool first_function_block_is_cold;
diff --git a/gcc/passes.c b/gcc/passes.c
index 2ea2a48fa170ac49071e4efe46a4d4c69ee68f01..fa9bc22fbd30abf960d4a53a9009cae35fe0b8a3 100644
--- a/gcc/passes.c
+++ b/gcc/passes.c
@@ -329,11 +329,6 @@ rest_of_handle_final (void)
 
   timevar_push (TV_SYMOUT);
   (*debug_hooks->function_decl) (current_function_decl);
-  if (unlikely_text_section_name)
-    {
-      free (unlikely_text_section_name);
-      unlikely_text_section_name = NULL;
-    }
   timevar_pop (TV_SYMOUT);
 
   ggc_collect ();
diff --git a/gcc/varasm.c b/gcc/varasm.c
index d9bcbacb7d3e9da1df385ee79684f01832f4484f..a1859836a0a065031bb4aea11da6a962343e7932 100644
--- a/gcc/varasm.c
+++ b/gcc/varasm.c
@@ -101,40 +101,6 @@ tree last_assemble_variable_decl;
 
 bool first_function_block_is_cold;
 
-/* The following global variable indicates the label name to be put at
-   the start of the first cold section within each function, when
-   partitioning basic blocks into hot and cold sections.  Used for
-   debug info.  */
-
-char *unlikely_section_label;
-
-/* The following global variable indicates the label name to be put at
-   the start of the first hot section within each function, when
-   partitioning basic blocks into hot and cold sections.  Used for
-   debug info.  */
-
-char *hot_section_label;
-
-/* The following global variable indicates the label name to be put at
-   the end of the last hot section within each function, when
-   partitioning basic blocks into hot and cold sections.  Used for
-   debug info.  */
-
-char *hot_section_end_label;
-
-/* The following global variable indicates the label name to be put at
-   the end of the last cold section within each function, when
-   partitioning basic blocks into hot and cold sections.  Used for 
-   debug info.*/
-
-char *cold_section_end_label;
- 
-/* The following global variable indicates the section name to be used
-   for the current cold section, when partitiong hot and cold basic 
-   blocks into separate sections.  */
-
-char *unlikely_text_section_name;
-
 /* We give all constants their own alias set.  Perhaps redundant with
    MEM_READONLY_P, but pre-dates it.  */
 
@@ -210,29 +176,38 @@ EXTRA_SECTION_FUNCTIONS
 static void
 initialize_cold_section_name (void)
 {
-  const char* name;
+  const char *name;
+  const char *stripped_name;
+  char *buffer;
   int len;
+  struct function *cfun;
 
-  if (! unlikely_text_section_name)
+  if (current_function_decl)
     {
-      if (DECL_SECTION_NAME (current_function_decl)
-	  && (strcmp (TREE_STRING_POINTER (DECL_SECTION_NAME
-					   (current_function_decl)),
-		      HOT_TEXT_SECTION_NAME) != 0)
-	  && (strcmp (TREE_STRING_POINTER (DECL_SECTION_NAME
-					   (current_function_decl)),
-		      UNLIKELY_EXECUTED_TEXT_SECTION_NAME) != 0))
+      cfun = DECL_STRUCT_FUNCTION (current_function_decl);
+      if (!cfun->unlikely_text_section_name)
 	{
-	  name = TREE_STRING_POINTER (DECL_SECTION_NAME 
-				                   (current_function_decl));
-	  len = strlen (name);
-	  unlikely_text_section_name = xmalloc (len + 10);
-	  sprintf (unlikely_text_section_name, "%s%s", name, "_unlikely");
+	  if (flag_function_sections
+	      && DECL_SECTION_NAME (current_function_decl))
+	    {
+	      name = xstrdup (TREE_STRING_POINTER (DECL_SECTION_NAME 
+						   (current_function_decl)));
+	      stripped_name = targetm.strip_name_encoding (name);
+	      len = strlen (stripped_name);
+	      buffer = (char *) xmalloc (len + 10);
+	      sprintf (buffer, "%s%s", stripped_name, "_unlikely");
+	      cfun->unlikely_text_section_name = ggc_strdup (buffer);
+	      free (buffer);
+	      free ((char *) name);
+	    }
+	  else
+	    cfun->unlikely_text_section_name = 
+	                                UNLIKELY_EXECUTED_TEXT_SECTION_NAME;
 	}
-      else
-	unlikely_text_section_name = 
-	                      xstrdup (UNLIKELY_EXECUTED_TEXT_SECTION_NAME);
     }
+  else
+   internal_error 
+     ("initialize_cold_section_name called without valid current_function_decl.");
 }
 
 /* Tell assembler to switch to text section.  */
@@ -253,14 +228,25 @@ text_section (void)
 void
 unlikely_text_section (void)
 {
-  if (! unlikely_text_section_name)
-    initialize_cold_section_name ();
+  if (current_function_decl)
+    {
+      struct function *cfun = DECL_STRUCT_FUNCTION (current_function_decl);
 
-  if ((in_section != in_unlikely_executed_text)
-      &&  (in_section != in_named 
-	   || strcmp (in_named_name, unlikely_text_section_name) != 0))
+      if (!cfun->unlikely_text_section_name)
+	initialize_cold_section_name ();
+
+      if ((in_section != in_unlikely_executed_text)
+	  &&  (in_section != in_named 
+	       || strcmp (in_named_name, cfun->unlikely_text_section_name) != 0))
+	{
+	  named_section (NULL_TREE, cfun->unlikely_text_section_name, 0);
+	  in_section = in_unlikely_executed_text;
+	  last_text_section = in_unlikely_executed_text;
+	}
+    }
+  else
     {
-      named_section (NULL_TREE, unlikely_text_section_name, 0);
+      named_section (NULL_TREE, UNLIKELY_EXECUTED_TEXT_SECTION_NAME, 0);
       in_section = in_unlikely_executed_text;
       last_text_section = in_unlikely_executed_text;
     }
@@ -314,11 +300,25 @@ int
 in_unlikely_text_section (void)
 {
   bool ret_val;
+  struct function *cfun;
 
-  ret_val = ((in_section == in_unlikely_executed_text)
-	     || (in_section == in_named
-		 && unlikely_text_section_name
-		 && strcmp (in_named_name, unlikely_text_section_name) == 0));
+  if (current_function_decl)
+    {
+      cfun = DECL_STRUCT_FUNCTION (current_function_decl);
+
+      ret_val = ((in_section == in_unlikely_executed_text)
+		 || (in_section == in_named
+		     && cfun->unlikely_text_section_name
+		     && strcmp (in_named_name, 
+				cfun->unlikely_text_section_name) == 0));
+    }
+  else
+    {
+      ret_val = ((in_section == in_unlikely_executed_text)
+		 || (in_section == in_named
+		     && strcmp (in_named_name,
+				UNLIKELY_EXECUTED_TEXT_SECTION_NAME) == 0));
+    }
 
   return ret_val;
 }
@@ -463,9 +463,12 @@ named_section (tree decl, const char *name, int reloc)
     name = TREE_STRING_POINTER (DECL_SECTION_NAME (decl));
 
   if (strcmp (name, UNLIKELY_EXECUTED_TEXT_SECTION_NAME) == 0
-      && !unlikely_text_section_name)
-      unlikely_text_section_name =
-	xstrdup (UNLIKELY_EXECUTED_TEXT_SECTION_NAME);
+      && current_function_decl
+      && !(DECL_STRUCT_FUNCTION (current_function_decl))->unlikely_text_section_name)
+    {
+      struct function *cfun = DECL_STRUCT_FUNCTION (current_function_decl);
+      cfun->unlikely_text_section_name = UNLIKELY_EXECUTED_TEXT_SECTION_NAME;
+    }
 
   flags = targetm.section_type_flags (decl, name, reloc);
 
@@ -574,16 +577,17 @@ asm_output_aligned_bss (FILE *file, tree decl ATTRIBUTE_UNUSED,
 void
 function_section (tree decl)
 {
-  bool unlikely = false;
+  int reloc = 0;
     
   if (first_function_block_is_cold)
-    unlikely = true;
+    reloc = 1;
   
 #ifdef USE_SELECT_SECTION_FOR_FUNCTIONS
-  targetm.asm_out.select_section (decl, unlikely, DECL_ALIGN (decl));
+  targetm.asm_out.select_section (decl, reloc, DECL_ALIGN (decl));
 #else
   if (decl != NULL_TREE
-      && DECL_SECTION_NAME (decl) != NULL_TREE)
+      && DECL_SECTION_NAME (decl) != NULL_TREE
+      && targetm.have_named_sections)
     named_section (decl, (char *) 0, 0);
   else
     text_section ();
@@ -594,16 +598,20 @@ void
 current_function_section (tree decl)
 {
 #ifdef USE_SELECT_SECTION_FOR_FUNCTIONS
-  bool unlikely = (in_unlikely_text_section () 
-		   || (last_text_section == in_unlikely_executed_text));
-  
-  targetm.asm_out.select_section (decl, unlikely, DECL_ALIGN (decl));
+  int reloc = 0; 
+
+  if (in_unlikely_text_section () 
+      || last_text_section == in_unlikely_executed_text)
+    reloc = 1;
+ 
+  targetm.asm_out.select_section (decl, reloc, DECL_ALIGN (decl));
 #else
   if (last_text_section == in_unlikely_executed_text)
     unlikely_text_section ();
   else if (last_text_section == in_text)
     text_section ();
-  else if (last_text_section == in_named)
+  else if (last_text_section == in_named
+	   && targetm.have_named_sections)
     named_section (NULL_TREE, last_text_section_name, 0);
   else
     function_section (decl);
@@ -1224,18 +1232,32 @@ void
 assemble_start_function (tree decl, const char *fnname)
 {
   int align;
+  char tmp_label[100];
   bool hot_label_written = false;
+  struct function *cfun = DECL_STRUCT_FUNCTION (decl);
 
-  unlikely_text_section_name = NULL;
-  
+  cfun->unlikely_text_section_name = NULL;
+ 
   first_function_block_is_cold = false;
-  hot_section_label = reconcat (hot_section_label, fnname, ".hot_section", NULL);
-  unlikely_section_label = reconcat (unlikely_section_label, 
-				     fnname, ".unlikely_section", NULL);
-  hot_section_end_label = reconcat (hot_section_end_label,
-				    fnname, ".end", NULL);
-  cold_section_end_label = reconcat (cold_section_end_label,
-				    fnname, ".end.cold", NULL);
+  if (flag_reorder_blocks_and_partition)
+    {
+      ASM_GENERATE_INTERNAL_LABEL (tmp_label, "HOTB", const_labelno);
+      cfun->hot_section_label = ggc_strdup (tmp_label);
+      ASM_GENERATE_INTERNAL_LABEL (tmp_label, "COLDB", const_labelno);
+      cfun->cold_section_label = ggc_strdup (tmp_label);
+      ASM_GENERATE_INTERNAL_LABEL (tmp_label, "HOTE", const_labelno);
+      cfun->hot_section_end_label = ggc_strdup (tmp_label);
+      ASM_GENERATE_INTERNAL_LABEL (tmp_label, "COLDE", const_labelno);
+      cfun->cold_section_end_label = ggc_strdup (tmp_label);
+      const_labelno++;
+    }
+  else
+    {
+      cfun->hot_section_label = NULL;
+      cfun->cold_section_label = NULL;
+      cfun->hot_section_end_label = NULL;
+      cfun->cold_section_end_label = NULL;
+    }
 
   /* The following code does not need preprocessing in the assembler.  */
 
@@ -1253,7 +1275,7 @@ assemble_start_function (tree decl, const char *fnname)
     {
       unlikely_text_section ();
       assemble_align (FUNCTION_BOUNDARY);
-      ASM_OUTPUT_LABEL (asm_out_file, unlikely_section_label);
+      ASM_OUTPUT_LABEL (asm_out_file, cfun->cold_section_label);
       if (BB_PARTITION (ENTRY_BLOCK_PTR->next_bb) == BB_COLD_PARTITION)
 	{
 	  /* Since the function starts with a cold section, we need to
@@ -1261,7 +1283,7 @@ assemble_start_function (tree decl, const char *fnname)
 	     section label.  */
 	  text_section ();
 	  assemble_align (FUNCTION_BOUNDARY);
-	  ASM_OUTPUT_LABEL (asm_out_file, hot_section_label);
+	  ASM_OUTPUT_LABEL (asm_out_file, cfun->hot_section_label);
 	  hot_label_written = true;
 	  first_function_block_is_cold = true;
 	}
@@ -1291,8 +1313,8 @@ assemble_start_function (tree decl, const char *fnname)
 	s[i] = (TREE_STRING_POINTER (DECL_SECTION_NAME (decl)))[i];
       s[len] = '\0';
       
-      if (unlikely_text_section_name 
-	  && (strcmp (s, unlikely_text_section_name) == 0))
+      if (cfun->unlikely_text_section_name 
+	  && (strcmp (s, cfun->unlikely_text_section_name) == 0))
 	first_function_block_is_cold = true;
     }
 
@@ -1303,8 +1325,8 @@ assemble_start_function (tree decl, const char *fnname)
   /* Switch to the correct text section for the start of the function.  */
 
   function_section (decl);
-  if (!hot_label_written)
-    ASM_OUTPUT_LABEL (asm_out_file, hot_section_label);
+  if (flag_reorder_blocks_and_partition && !hot_label_written)
+    ASM_OUTPUT_LABEL (asm_out_file, cfun->hot_section_label);
 
   /* Tell assembler to move to target machine's alignment for functions.  */
   align = floor_log2 (FUNCTION_BOUNDARY / BITS_PER_UNIT);
@@ -1366,7 +1388,6 @@ assemble_start_function (tree decl, const char *fnname)
 void
 assemble_end_function (tree decl, const char *fnname)
 {
-  enum in_section save_text_section;
 #ifdef ASM_DECLARE_FUNCTION_SIZE
   ASM_DECLARE_FUNCTION_SIZE (asm_out_file, fnname, decl);
 #endif
@@ -1377,13 +1398,19 @@ assemble_end_function (tree decl, const char *fnname)
     }
   /* Output labels for end of hot/cold text sections (to be used by
      debug info.)  */
-  save_text_section = in_section;
-  unlikely_text_section ();
-  ASM_OUTPUT_LABEL (asm_out_file, cold_section_end_label);
-  text_section ();
-  ASM_OUTPUT_LABEL (asm_out_file, hot_section_end_label);
-  if (save_text_section == in_unlikely_executed_text)
-    unlikely_text_section ();
+  if (flag_reorder_blocks_and_partition)
+    {
+      enum in_section save_text_section;
+      struct function *cfun = DECL_STRUCT_FUNCTION (decl);
+
+      save_text_section = in_section;
+      unlikely_text_section ();
+      ASM_OUTPUT_LABEL (asm_out_file, cfun->cold_section_end_label);
+      text_section ();
+      ASM_OUTPUT_LABEL (asm_out_file, cfun->hot_section_end_label);
+      if (save_text_section == in_unlikely_executed_text)
+	unlikely_text_section ();
+    }
 }
 
 /* Assemble code to leave SIZE bytes of zeros.  */
@@ -4766,14 +4793,23 @@ default_section_type_flags_1 (tree decl, const char *name, int reloc,
 			      int shlib)
 {
   unsigned int flags;
+  struct function *cfun = NULL;
+
+  if (current_function_decl)
+    cfun = DECL_STRUCT_FUNCTION (current_function_decl);
 
   if (decl && TREE_CODE (decl) == FUNCTION_DECL)
     flags = SECTION_CODE;
   else if (decl && decl_readonly_section_1 (decl, reloc, shlib))
     flags = 0;
-  else if (unlikely_text_section_name
-	   && strcmp (name, unlikely_text_section_name) == 0)
+  else if (current_function_decl
+	   && cfun->unlikely_text_section_name
+	   && strcmp (name, cfun->unlikely_text_section_name) == 0)
     flags = SECTION_CODE;
+  else if (!decl 
+	   && !current_function_decl
+	   && strcmp (name, UNLIKELY_EXECUTED_TEXT_SECTION_NAME) == 0)
+    flags = SECTION_CODE; 
   else
     flags = SECTION_WRITE;