diff --git a/boehm-gc/ChangeLog b/boehm-gc/ChangeLog
index cb05810ac598540afee9b769ce2de70e8feeec62..8a1abca8ba8fb27729f1c05dc0d881d263dfacbf 100644
--- a/boehm-gc/ChangeLog
+++ b/boehm-gc/ChangeLog
@@ -1,3 +1,20 @@
+2010-11-29  Iain Sandoe  <iains@gcc.gnu.org>
+	    Mike Stump  <mrs@gcc.gnu.org>
+
+	PR target/26427
+	PR target/33120
+	PR testsuite/35710
+	* dyn_load.c (GC_register_dynamic_libraries/DARWIN):  Add new writable
+	data section names.
+	(GC_dyld_name_for_hdr): Adjust layout.
+	(GC_dyld_image_add): Adjust layout, add new Darwin sections, adjust
+	debug to name the sections.
+	(GC_dyld_image_remove): Adjust layout, remove new Darwin sections,
+	adjust debug to name the sections.
+	(GC_register_dynamic_libraries): Adjust layout.
+	(GC_init_dyld): Likewise.
+	(GC_register_main_static_data): Likewise.
+
 2010-10-29  Paolo Bonzini  <bonzini@gnu.org>
 
 	* configure: Regenerate.
diff --git a/boehm-gc/dyn_load.c b/boehm-gc/dyn_load.c
index 2133f465ef92b36e53088114273860d5b3a51593..4bfa56cac2c3f47cf9922500696eb01c28b9dd76 100644
--- a/boehm-gc/dyn_load.c
+++ b/boehm-gc/dyn_load.c
@@ -1157,72 +1157,167 @@ void GC_register_dynamic_libraries()
 
 /*#define DARWIN_DEBUG*/
 
+/* Writeable sections generally available on Darwin.  */
 const static struct { 
         const char *seg;
         const char *sect;
 } GC_dyld_sections[] = {
         { SEG_DATA, SECT_DATA },
+        /* Used by FSF GCC, but not by OSX system tools, so far.  */
+        { SEG_DATA, "__static_data" }, 
         { SEG_DATA, SECT_BSS },
-        { SEG_DATA, SECT_COMMON }
+        { SEG_DATA, SECT_COMMON },
+        /* FSF GCC - zero-sized object sections for targets supporting section
+           anchors.  */
+        { SEG_DATA, "__zobj_data" },
+        { SEG_DATA, "__zobj_bss" }
 };
-    
+
+/* Additional writeable sections:
+
+   GCC on Darwin constucts aligned sections "on demand", where the alignment
+   size is embedded in the section name.  Furthermore, there are distintions
+   between sections containing private vs. public symbols.
+
+   It also constructs sections specifically for zero-sized objects, when the
+   target supports section anchors.  */
+const char * GC_dyld_add_sect_fmts[] = 
+{
+  "__bss%u",
+  "__pu_bss%u",
+  "__zo_bss%u",
+  "__zo_pu_bss%u",
+  NULL
+} ;
+
+/* Currently, mach-o will allow up to a max of 2^15 alignment in an
+   object file.  */
+#define L2_MAX_OFILE_ALIGNMENT 15
+
+  
 #ifdef DARWIN_DEBUG
-static const char *GC_dyld_name_for_hdr(const struct GC_MACH_HEADER *hdr) {
-    unsigned long i,c;
-    c = _dyld_image_count();
-    for(i=0;i<c;i++) if(_dyld_get_image_header(i) == hdr)
-        return _dyld_get_image_name(i);
-    return NULL;
+static const char *
+GC_dyld_name_for_hdr (const struct GC_MACH_HEADER *hdr)
+{
+  unsigned long i,c;
+  c = _dyld_image_count();
+  for (i=0;i<c;i++) 
+    if(_dyld_get_image_header(i) == hdr)
+      return _dyld_get_image_name(i);
+  return NULL;
 }
 #endif
-        
+
+
 /* This should never be called by a thread holding the lock */
-static void GC_dyld_image_add(const struct GC_MACH_HEADER *hdr, intptr_t slide)
+static void 
+GC_dyld_image_add (const struct GC_MACH_HEADER *hdr, intptr_t slide)
 {
-    unsigned long start,end,i;
-    const struct GC_MACH_SECTION *sec;
-    if (GC_no_dls) return;
-    for(i=0;i<sizeof(GC_dyld_sections)/sizeof(GC_dyld_sections[0]);i++) {
+  char secnam[16];
+  unsigned long start,end,i,j;
+  const struct GC_MACH_SECTION *sec;
+  const char *fmt;
 
+  if (GC_no_dls)
+    return;
+
+  for (i=0; i<sizeof(GC_dyld_sections)/sizeof(GC_dyld_sections[0]); i++)
+    {
       sec = GC_GETSECTBYNAME (hdr, GC_dyld_sections[i].seg,
 			      GC_dyld_sections[i].sect);
-        if(sec == NULL || sec->size == 0) continue;
-        start = slide + sec->addr;
-        end = start + sec->size;
-#	ifdef DARWIN_DEBUG
-            GC_printf4("Adding section at %p-%p (%lu bytes) from image %s\n",
-                start,end,sec->size,GC_dyld_name_for_hdr(hdr));
-#       endif
-        GC_add_roots((char*)start,(char*)end);
+      if(sec == NULL || sec->size == 0)
+	continue;
+
+      start = slide + sec->addr;
+      end = start + sec->size;
+
+#     ifdef DARWIN_DEBUG
+      GC_printf5("Adding section __DATA,%s at %p-%p (%lu bytes) from image %s\n",
+                GC_dyld_sections[i].sect, start,end,sec->size,GC_dyld_name_for_hdr(hdr));
+#      endif
+      GC_add_roots((char*)start,(char*)end);
     }
-#   ifdef DARWIN_DEBUG
-        GC_print_static_roots();
-#   endif
+
+  /* Sections constructed on demand.  */
+  j=0;
+  while ((fmt = GC_dyld_add_sect_fmts[j]) != NULL)
+    {
+      /* Add our manufactured aligned BSS sections.  */
+      for (i=0; i<=L2_MAX_OFILE_ALIGNMENT; i++)
+	{
+	  snprintf (secnam, 16, fmt, (unsigned)i);
+	  sec = GC_GETSECTBYNAME (hdr, SEG_DATA, secnam);
+	  if (sec == NULL || sec->size == 0)
+	    continue;
+	  start = slide + sec->addr;
+	  end = start + sec->size;
+#	  ifdef DARWIN_DEBUG
+	  GC_printf5("Adding section __DATA,%s at %p-%p (%lu bytes) from image %s\n",
+		 secnam, start,end,sec->size,GC_dyld_name_for_hdr(hdr));
+#	  endif
+	  GC_add_roots((char*)start,(char*)end);
+	}
+      j++;
+    } 
+# ifdef DARWIN_DEBUG
+  GC_print_static_roots();
+# endif
 }
 
 /* This should never be called by a thread holding the lock */
-static void GC_dyld_image_remove(const struct GC_MACH_HEADER *hdr,
-				 intptr_t slide) {
-    unsigned long start,end,i;
-    const struct GC_MACH_SECTION *sec;
-    for(i=0;i<sizeof(GC_dyld_sections)/sizeof(GC_dyld_sections[0]);i++) {
+static void 
+GC_dyld_image_remove (const struct GC_MACH_HEADER *hdr, intptr_t slide)
+{
+  char secnam[16];
+  unsigned long start,end,i,j;
+  const struct GC_MACH_SECTION *sec;
+  const char *fmt;
+
+  for (i=0; i<sizeof(GC_dyld_sections)/sizeof(GC_dyld_sections[0]); i++)
+    {
       sec = GC_GETSECTBYNAME (hdr, GC_dyld_sections[i].seg,
 			      GC_dyld_sections[i].sect);
-        if(sec == NULL || sec->size == 0) continue;
-        start = slide + sec->addr;
-        end = start + sec->size;
-#	ifdef DARWIN_DEBUG
-            GC_printf4("Removing section at %p-%p (%lu bytes) from image %s\n",
-                start,end,sec->size,GC_dyld_name_for_hdr(hdr));
-#		endif
-        GC_remove_roots((char*)start,(char*)end);
+      if(sec == NULL || sec->size == 0)
+	continue;
+
+      start = slide + sec->addr;
+      end = start + sec->size;
+#     ifdef DARWIN_DEBUG
+      GC_printf5("Removing section __DATA,%s at %p-%p (%lu bytes) from image %s\n",
+                  GC_dyld_sections[i].sect, start,end,sec->size,GC_dyld_name_for_hdr(hdr));
+#      endif
+      GC_remove_roots((char*)start,(char*)end);
     }
-#   ifdef DARWIN_DEBUG
-        GC_print_static_roots();
-#   endif
+
+  /* Remove our on-demand sections.  */
+  j=0;
+  while ((fmt = GC_dyld_add_sect_fmts[j]) != NULL)
+    {
+      for (i=0; i<=L2_MAX_OFILE_ALIGNMENT; i++)
+	{
+	  snprintf (secnam, 16, fmt, (unsigned)i);
+	  sec = GC_GETSECTBYNAME (hdr, SEG_DATA, secnam);
+	  if (sec == NULL || sec->size == 0)
+	    continue;
+	  start = slide + sec->addr;
+	  end = start + sec->size;
+#	  ifdef DARWIN_DEBUG
+	  GC_printf5("Removing section __DATA,%s at %p-%p (%lu bytes) from image %s\n",
+		      secnam, start,end,sec->size,GC_dyld_name_for_hdr(hdr));
+#	  endif
+	  GC_remove_roots((char*)start,(char*)end);
+	}
+      j++;
+    }
+
+# ifdef DARWIN_DEBUG
+  GC_print_static_roots();
+# endif
 }
 
-void GC_register_dynamic_libraries() {
+void 
+GC_register_dynamic_libraries() 
+{
     /* Currently does nothing. The callbacks are setup by GC_init_dyld() 
     The dyld library takes it from there. */
 }
@@ -1233,15 +1328,18 @@ void GC_register_dynamic_libraries() {
    This should be called BEFORE any thread in created and WITHOUT the
    allocation lock held. */
    
-void GC_init_dyld() {
+void 
+GC_init_dyld()
+{
   static GC_bool initialized = FALSE;
   char *bind_fully_env = NULL;
   
-  if(initialized) return;
+  if(initialized)
+    return;
   
-#   ifdef DARWIN_DEBUG
+# ifdef DARWIN_DEBUG
   GC_printf0("Registering dyld callbacks...\n");
-#   endif
+# endif
   
   /* Apple's Documentation:
      When you call _dyld_register_func_for_add_image, the dynamic linker runtime
@@ -1254,27 +1352,28 @@ void GC_init_dyld() {
      linked in the future
   */
   
-    _dyld_register_func_for_add_image(GC_dyld_image_add);
-    _dyld_register_func_for_remove_image(GC_dyld_image_remove);
+  _dyld_register_func_for_add_image(GC_dyld_image_add);
+  _dyld_register_func_for_remove_image(GC_dyld_image_remove);
 
-    /* Set this early to avoid reentrancy issues. */
-    initialized = TRUE;
+  /* Set this early to avoid reentrancy issues. */
+  initialized = TRUE;
 
-    bind_fully_env = getenv("DYLD_BIND_AT_LAUNCH");
+  bind_fully_env = getenv("DYLD_BIND_AT_LAUNCH");
     
-    if (bind_fully_env == NULL) {
-#   ifdef DARWIN_DEBUG
+  if (bind_fully_env == NULL)
+    {
+#     ifdef DARWIN_DEBUG
       GC_printf0("Forcing full bind of GC code...\n");
-#   endif
+#     endif
       
-      if(!_dyld_bind_fully_image_containing_address((unsigned long*)GC_malloc))
-        GC_abort("_dyld_bind_fully_image_containing_address failed");
+      if (!_dyld_bind_fully_image_containing_address((unsigned long*)GC_malloc))
+	GC_abort("_dyld_bind_fully_image_containing_address failed");
     }
-
 }
 
 #define HAVE_REGISTER_MAIN_STATIC_DATA
-GC_bool GC_register_main_static_data()
+GC_bool 
+GC_register_main_static_data (void)
 {
   /* Already done through dyld callbacks */
   return FALSE;
diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 585429c21af8cb99cacbfbc5ecac033d23430fb6..27c9bf66b21b7a40ee02b98ebf1dd528bf3f7207 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,57 @@
+2010-11-29  Iain Sandoe  <iains@gcc.gnu.org>
+	    Mike Stump  <mrs@gcc.gnu.org>
+
+	PR target/26427
+	PR target/33120
+	PR testsuite/35710
+	* config/i386/darwin.h (ASM_OUTPUT_COMMON): Remove
+	(ASM_OUTPUT_LOCAL): Likewise.
+	* config/darwin-protos.h (darwin_asm_declare_object_name): New.
+	(darwin_output_aligned_bss): Likewise.
+	(darwin_asm_output_aligned_decl_local): Likewise.
+	(darwin_asm_output_aligned_decl_common): Likewise.
+	(darwin_use_anchors_for_symbol_p): Likewise.
+	* config/rs6000/darwin.h (ASM_OUTPUT_COMMON): Remove.
+	(TARGET_ASM_OUTPUT_ANCHOR): Define.
+	(TARGET_USE_ANCHORS_FOR_SYMBOL_P): Define.
+	(DARWIN_SECTION_ANCHORS): Set to 1.
+	* config/darwin.c (emit_aligned_common): New var.
+	(darwin_init_sections): Check that the Darwin private zero-size section
+	marker is in range.
+	(darwin_text_section): Check for zero-sized objects.
+	(darwin_mergeable_string_section): Likewise.
+	(darwin_mergeable_constant_section): Likewise.
+	(machopic_select_section): Adjust to check for zero-sized objects.
+	Assert that OBJC meta data are non-zero sized.
+	(darwin_asm_declare_object_name): New.
+	(darwin_asm_declare_constant_name): Adjust for zero-sized
+	object sections.
+	(BYTES_ZFILL): Define.
+	(darwin_emit_weak_or_comdat): New.
+	(darwin_emit_local_bss): New.
+	(darwin_emit_common): New.
+	(darwin_output_aligned_bss): New.
+	(darwin_asm_output_aligned_decl_common): New.
+	(darwin_asm_output_aligned_decl_local): New.
+	(darwin_file_end): Disable subsections_via_symbols when section
+	anchoring is active.
+	(darwin_asm_output_anchor): Re-enable.
+	(darwin_use_anchors_for_symbol_p): New.
+	(darwin_override_options): Check for versions that can emit
+	aligned common.  Update usage of flags to current.
+	* config/darwin-sections.def: Update comments and flags for
+	non-anchor sections.  zobj_const_section, zobj_data_section,
+	zobj_bss_section, zobj_const_data_section: New.
+	* config/darwin.h (ASM_DECLARE_OBJECT_NAME): Redefine.
+	(ASM_OUTPUT_ALIGN): Make whitespace output consistent.
+	(L2_MAX_OFILE_ALIGNMENT): Define.
+	(ASM_OUTPUT_ALIGNED_BSS): Define.
+	(ASM_OUTPUT_ALIGNED_DECL_LOCAL): Define.
+	(ASM_OUTPUT_ALIGNED_DECL_COMMON): Define.
+	(SECTION_NO_ANCHOR): Define.
+	(TARGET_ASM_OUTPUT_ANCHOR) Define with a default of NULL.
+	(DARWIN_SECTION_ANCHORS): Define with a default of 0.
+	
 2010-11-29  Joseph Myers  <joseph@codesourcery.com>
 
 	* system.h: Include "safe-ctype.h" instead of <safe-ctype.h>.
diff --git a/gcc/config/darwin-protos.h b/gcc/config/darwin-protos.h
index 08cacc14234bfc2fbe63ab67e0f8e37923066201..fca8065e074dbb2d0b2f138825a65f31a52082d5 100644
--- a/gcc/config/darwin-protos.h
+++ b/gcc/config/darwin-protos.h
@@ -85,12 +85,26 @@ extern tree darwin_handle_weak_import_attribute (tree *node, tree name,
 extern void machopic_output_stub (FILE *, const char *, const char *);
 extern void darwin_globalize_label (FILE *, const char *);
 extern void darwin_assemble_visibility (tree, int);
+
 extern void darwin_asm_output_dwarf_delta (FILE *, int, const char *,
 					   const char *);
 extern void darwin_asm_output_dwarf_offset (FILE *, int, const char *,
 					    section *);
+
+extern void darwin_asm_declare_object_name (FILE *, const char *, tree);
 extern void darwin_asm_declare_constant_name (FILE *, const char *,
 					      const_tree, HOST_WIDE_INT);
+
+extern void darwin_output_aligned_bss (FILE *, tree, const char *,
+				       unsigned HOST_WIDE_INT, unsigned int);
+
+extern void darwin_asm_output_aligned_decl_local (FILE *, tree, const char *, 
+						  unsigned HOST_WIDE_INT, 
+						  unsigned int);
+extern void darwin_asm_output_aligned_decl_common (FILE *, tree, const char *,
+						   unsigned HOST_WIDE_INT, 
+						   unsigned int);
+
 extern bool darwin_binds_local_p (const_tree);
 extern void darwin_cpp_builtins (struct cpp_reader *);
 
@@ -104,6 +118,7 @@ extern tree darwin_build_constant_cfstring (tree);
 extern void darwin_enter_string_into_cfstring_table (tree);
 
 extern void darwin_asm_output_anchor (rtx symbol);
+extern bool darwin_use_anchors_for_symbol_p (const_rtx symbol);
 extern bool darwin_kextabi_p (void);
 extern void darwin_override_options (void);
 extern void darwin_patch_builtins (void);
diff --git a/gcc/config/darwin-sections.def b/gcc/config/darwin-sections.def
index 476d9aa018cabe5bec005374d20a79c6131d4977..198fdcbb29ca839dc3f3e59a56ba64ac2f63ab41 100644
--- a/gcc/config/darwin-sections.def
+++ b/gcc/config/darwin-sections.def
@@ -16,30 +16,70 @@ You should have received a copy of the GNU General Public License
 along with GCC; see the file COPYING3.  If not see
 <http://www.gnu.org/licenses/>.  */
 
-DEF_SECTION (text_coal_section, SECTION_CODE,
+/* Since Darwin's ld will not allow zero-sized objects, and gcc wants them,
+   we emit one byte (in darwin.c) when such an object is encountered.
+
+   This messes up section anchoring because the emitted byte is not counted
+   outside the port.  To cope with this, we set aside sections for zero-sized
+   objects and disallow those sections from  participating in section anchors
+   ("zobj_" sections, below).
+   
+   Items that might be coalesced by the linker are prevented from participating,
+   (and those in mergeable sections are disallowed in varasm.c).  */
+
+/* .text handled in varasm.c  */
+DEF_SECTION (text_coal_section, SECTION_CODE|SECTION_NO_ANCHOR,
 	     ".section __TEXT,__textcoal_nt,coalesced,pure_instructions", 0)
-DEF_SECTION (text_unlikely_coal_section, SECTION_CODE,
+DEF_SECTION (text_unlikely_coal_section, SECTION_CODE|SECTION_NO_ANCHOR,
 	     ".section __TEXT,__text_unlikely_coal,"
 	     "coalesced,pure_instructions", 0)
+
+/* const */
 DEF_SECTION (const_section, 0, ".const", 0)
-DEF_SECTION (const_coal_section, 0,
+DEF_SECTION (const_coal_section, SECTION_NO_ANCHOR,
 	     ".section __TEXT,__const_coal,coalesced", 0)
+/* Place to put zero-sized to avoid issues with section anchors.  */
+DEF_SECTION (zobj_const_section, SECTION_NO_ANCHOR, 
+	     ".section\t__DATA,__zobj_const", 0)
+
+/* Write-able data.  '.data'  handled in varasm.c  */
+DEF_SECTION (static_data_section, SECTION_WRITE, ".static_data", 0)
+DEF_SECTION (data_coal_section, SECTION_WRITE|SECTION_NO_ANCHOR,
+	     ".section __DATA,__datacoal_nt,coalesced", 0)
+/* Place to put zero-sized to avoid issues with section anchors.  */
+DEF_SECTION (zobj_data_section, SECTION_WRITE|SECTION_NO_ANCHOR, 
+	     ".section\t__DATA,__zobj_data", 0)
+
+/* BSS - .lcomm / .zerofill __DATA,__bss sections cannot be switched to
+   explicitly (will create an assembler error).  */
+DEF_SECTION (zobj_bss_section, SECTION_WRITE|SECTION_BSS|SECTION_NO_ANCHOR, 
+	     ".section\t__DATA,__zobj_bss", 0)
+
+/* const data */
 DEF_SECTION (const_data_section, 0, ".const_data", 0)
-DEF_SECTION (const_data_coal_section, 0,
+DEF_SECTION (const_data_coal_section, SECTION_NO_ANCHOR,
 	     ".section __DATA,__const_coal,coalesced", 0)
-DEF_SECTION (data_coal_section, SECTION_WRITE,
-	     ".section __DATA,__datacoal_nt,coalesced", 0)
+/* Place to put zero-sized to avoid issues with section anchors.  */
+DEF_SECTION (zobj_const_data_section, SECTION_NO_ANCHOR, 
+	     ".section\t__DATA,__zobj_const_data", 0)
+
+/* Strings and other literals.  */
 DEF_SECTION (cstring_section, SECTION_MERGE | SECTION_STRINGS, ".cstring", 0)
 DEF_SECTION (literal4_section, SECTION_MERGE, ".literal4", 0)
 DEF_SECTION (literal8_section, SECTION_MERGE, ".literal8", 0)
 DEF_SECTION (literal16_section, SECTION_MERGE, ".literal16", 0)
-/* Unlike constant NSStrings, constant CFStrings do not live  in the __OBJC segment
-  since they may also occur in pure C  or C++ programs.  */
-DEF_SECTION (cfstring_constant_object_section, 0, ".section __DATA, __cfstring", 0)
-DEF_SECTION (constructor_section, 0, ".constructor", 0)
+/* Unlike constant NSStrings, constant CFStrings do not live  in the
+   __OBJC segment since they may also occur in pure C  or C++ programs.  */
+DEF_SECTION (cfstring_constant_object_section, 0, 
+	     ".section __DATA, __cfstring", 0)
+
+/* Module init, term, constructors & destructors.  */
 DEF_SECTION (mod_init_section, 0, ".mod_init_func", 0)
 DEF_SECTION (mod_term_section, 0, ".mod_term_func", 0)
+DEF_SECTION (constructor_section, 0, ".constructor", 0)
 DEF_SECTION (destructor_section, 0, ".destructor", 0)
+
+/* Objective-C (V1) sections.  */
 DEF_SECTION (objc_class_section, 0, ".objc_class", 1)
 DEF_SECTION (objc_meta_class_section, 0, ".objc_meta_class", 1)
 DEF_SECTION (objc_category_section, 0, ".objc_category", 1)
@@ -66,32 +106,38 @@ DEF_SECTION (objc_class_names_section, 0, ".objc_class_names", 1)
 DEF_SECTION (objc_meth_var_names_section, 0, ".objc_meth_var_names", 1)
 DEF_SECTION (objc_meth_var_types_section, 0, ".objc_meth_var_types", 1)
 DEF_SECTION (objc_cls_refs_section, SECTION_MERGE, ".objc_cls_refs", 1)
+
+/* Stubs and symbol indirection sections.  */
 /* lazy symbol pointers.  */
-DEF_SECTION (machopic_lazy_symbol_ptr_section, 0, ".lazy_symbol_pointer", 0)
-DEF_SECTION (machopic_lazy_symbol_ptr2_section,	0,
+DEF_SECTION (machopic_lazy_symbol_ptr_section, SECTION_NO_ANCHOR, 
+	     ".lazy_symbol_pointer", 0)
+DEF_SECTION (machopic_lazy_symbol_ptr2_section,	SECTION_NO_ANCHOR,
 	     ".section __DATA, __la_sym_ptr2,lazy_symbol_pointers", 0)
-DEF_SECTION (machopic_lazy_symbol_ptr3_section, 0,
+DEF_SECTION (machopic_lazy_symbol_ptr3_section, SECTION_NO_ANCHOR,
 	     ".section __DATA, __la_sym_ptr3,lazy_symbol_pointers", 0)
 /* non-lazy symbol pointers.  */
-DEF_SECTION (machopic_nl_symbol_ptr_section, 0,
+DEF_SECTION (machopic_nl_symbol_ptr_section, SECTION_NO_ANCHOR,
 	     MACHOPIC_NL_SYMBOL_PTR_SECTION, 0)
 /* Symbol stubs.  */
-DEF_SECTION (machopic_symbol_stub_section, 0, ".symbol_stub", 0)
-DEF_SECTION (machopic_symbol_stub1_section, 0,
+DEF_SECTION (machopic_symbol_stub_section, SECTION_NO_ANCHOR, 
+	     ".symbol_stub", 0)
+DEF_SECTION (machopic_symbol_stub1_section, SECTION_NO_ANCHOR,
 	     ".section __TEXT,__symbol_stub1,symbol_stubs,"
 	     "pure_instructions,16", 0)
 /* PIC symbol stubs.  */
-DEF_SECTION (machopic_picsymbol_stub_section, 0, ".picsymbol_stub", 0)
-DEF_SECTION (machopic_picsymbol_stub1_section, 0,
+DEF_SECTION (machopic_picsymbol_stub_section, SECTION_NO_ANCHOR, 
+	     ".picsymbol_stub", 0)
+DEF_SECTION (machopic_picsymbol_stub1_section, SECTION_NO_ANCHOR,
 	     ".section __TEXT,__picsymbolstub1,symbol_stubs,"
 	     "pure_instructions,32", 0)
-DEF_SECTION (machopic_picsymbol_stub2_section, 0,
+DEF_SECTION (machopic_picsymbol_stub2_section, SECTION_NO_ANCHOR,
 	     ".section __TEXT,__picsymbolstub2,symbol_stubs,pure_instructions,25", 0)
-DEF_SECTION (machopic_picsymbol_stub3_section, 0,
+DEF_SECTION (machopic_picsymbol_stub3_section, SECTION_NO_ANCHOR,
 	     ".section __IMPORT,__jump_table,symbol_stubs,self_modifying_code+pure_instructions,5", 0)
+
 /* Exception-related.  */
-DEF_SECTION (darwin_exception_section, 0,
+DEF_SECTION (darwin_exception_section, SECTION_NO_ANCHOR,
 	     ".section __DATA,__gcc_except_tab", 0)
-DEF_SECTION (darwin_eh_frame_section, 0,
+DEF_SECTION (darwin_eh_frame_section, SECTION_NO_ANCHOR,
 	     ".section " EH_FRAME_SECTION_NAME ",__eh_frame"
 	     EH_FRAME_SECTION_ATTR, 0)
diff --git a/gcc/config/darwin.c b/gcc/config/darwin.c
index e8da4f1e6998db268dbcbe76e08c02e72fdbdf22..596ed11501997fd1429d7920b90358d49d2aece3 100644
--- a/gcc/config/darwin.c
+++ b/gcc/config/darwin.c
@@ -105,6 +105,10 @@ section * darwin_sections[NUM_DARWIN_SECTIONS];
 /* True if we're setting __attribute__ ((ms_struct)).  */
 int darwin_ms_struct = false;
 
+/* Earlier versions of Darwin as do not recognize an alignment field in 
+   .comm directives, this should be set for versions that allow it.  */
+int emit_aligned_common = false;
+
 /* A get_unnamed_section callback used to switch to an ObjC section.
    DIRECTIVE is as for output_section_asm_op.  */
 
@@ -172,6 +176,10 @@ darwin_init_sections (void)
   readonly_data_section = darwin_sections[const_section];
   exception_section = darwin_sections[darwin_exception_section];
   eh_frame_section = darwin_sections[darwin_eh_frame_section];
+
+  /* Make sure that there is no conflict between the 'no anchor' section
+     flag declared in darwin.h and the section flags declared in output.h.  */
+  gcc_assert (SECTION_NO_ANCHOR > SECTION_MACH_DEP);
 }
 
 int
@@ -1152,17 +1160,19 @@ darwin_text_section (int reloc, int weak)
 }
 
 static section *
-darwin_rodata_section (int weak)
+darwin_rodata_section (int weak, bool zsize)
 {
   return (weak
 	  ? darwin_sections[const_coal_section]
-	  : darwin_sections[const_section]);
+	  : (zsize ? darwin_sections[zobj_const_section]
+		   : darwin_sections[const_section]));
 }
 
 static section *
 darwin_mergeable_string_section (tree exp,
 				 unsigned HOST_WIDE_INT align)
 {
+
   if (flag_merge_constants
       && TREE_CODE (exp) == STRING_CST
       && TREE_CODE (TREE_TYPE (exp)) == ARRAY_TYPE
@@ -1173,6 +1183,11 @@ darwin_mergeable_string_section (tree exp,
 	  == strlen (TREE_STRING_POINTER (exp)) + 1))
     return darwin_sections[cstring_section];
 
+  if (DARWIN_SECTION_ANCHORS && flag_section_anchors
+      && TREE_CODE (exp) == STRING_CST
+      && TREE_STRING_LENGTH (exp) == 0)
+    return darwin_sections[zobj_const_section];
+
   return readonly_data_section;
 }
 
@@ -1182,11 +1197,17 @@ darwin_mergeable_string_section (tree exp,
 
 static section *
 darwin_mergeable_constant_section (tree exp,
-				   unsigned HOST_WIDE_INT align)
+				   unsigned HOST_WIDE_INT align,
+				   bool zsize)
 {
   enum machine_mode mode = DECL_MODE (exp);
   unsigned int modesize = GET_MODE_BITSIZE (mode);
 
+  if (DARWIN_SECTION_ANCHORS 
+      && flag_section_anchors 
+      && zsize)
+    return darwin_sections[zobj_const_section];
+
   if (flag_merge_constants
       && mode != VOIDmode
       && mode != BLKmode
@@ -1229,12 +1250,23 @@ machopic_select_section (tree decl,
 			 int reloc,
 			 unsigned HOST_WIDE_INT align)
 {
-  bool weak = (DECL_P (decl)
-	       && DECL_WEAK (decl)
-	       && !lookup_attribute ("weak_import",
-				     DECL_ATTRIBUTES (decl)));
+  bool zsize, one, weak, ro;
   section *base_section = NULL;
 
+  weak = (DECL_P (decl)
+	  && DECL_WEAK (decl)
+	  && !lookup_attribute ("weak_import", DECL_ATTRIBUTES (decl)));
+
+  zsize = (DECL_P (decl) 
+	   && (TREE_CODE (decl) == VAR_DECL || TREE_CODE (decl) == CONST_DECL) 
+	   && tree_low_cst (DECL_SIZE_UNIT (decl), 1) == 0);
+
+  one = DECL_P (decl) 
+	&& TREE_CODE (decl) == VAR_DECL 
+	&& DECL_ONE_ONLY (decl);
+
+  ro = TREE_READONLY (decl) || TREE_CONSTANT (decl) ;
+
   switch (categorize_decl_for_section (decl, reloc))
     {
     case SECCAT_TEXT:
@@ -1253,7 +1285,7 @@ machopic_select_section (tree decl,
 
     case SECCAT_RODATA:
     case SECCAT_SRODATA:
-      base_section = darwin_rodata_section (weak);
+      base_section = darwin_rodata_section (weak, zsize);
       break;
 
     case SECCAT_RODATA_MERGE_STR:
@@ -1265,7 +1297,7 @@ machopic_select_section (tree decl,
       break;
 
     case SECCAT_RODATA_MERGE_CONST:
-      base_section =  darwin_mergeable_constant_section (decl, align);
+      base_section =  darwin_mergeable_constant_section (decl, align, zsize);
       break;
 
     case SECCAT_DATA:
@@ -1275,14 +1307,46 @@ machopic_select_section (tree decl,
     case SECCAT_DATA_REL_RO_LOCAL:
     case SECCAT_SDATA:
     case SECCAT_TDATA:
+      if (weak || one)
+	{
+	  if (ro)
+	    base_section = darwin_sections[const_data_coal_section];
+	  else 
+	    base_section = darwin_sections[data_coal_section];
+	}
+      else if (DARWIN_SECTION_ANCHORS 
+	       && flag_section_anchors
+	       && zsize)
+	{
+	  /* If we're doing section anchors, then punt zero-sized objects into
+	     their own sections so that they don't interfere with offset
+	     computation for the remaining vars.  This does not need to be done
+	     for stuff in mergeable sections, since these are ineligible for 
+	     anchors.  */
+	  if (ro)
+	    base_section = darwin_sections[zobj_const_data_section];
+	  else
+	    base_section = darwin_sections[zobj_data_section];
+	}
+      else if (ro)
+	base_section = darwin_sections[const_data_section];
+      else
+	base_section = data_section;
+      break;
     case SECCAT_BSS:
     case SECCAT_SBSS:
     case SECCAT_TBSS:
-      if (TREE_READONLY (decl) || TREE_CONSTANT (decl))
-	base_section = weak ? darwin_sections[const_data_coal_section]
-			    : darwin_sections[const_data_section];
+      if (weak || one) 
+	base_section = darwin_sections[data_coal_section];
       else
-	base_section = weak ? darwin_sections[data_coal_section] : data_section;
+	{
+	  if (!TREE_PUBLIC (decl))
+	    base_section = lcomm_section;
+	  else if (bss_noswitch_section)
+	    base_section = bss_noswitch_section;
+	  else
+	    base_section = data_section;
+	}
       break;
 
     default:
@@ -1319,13 +1383,16 @@ machopic_select_section (tree decl,
     {
       const char *name = IDENTIFIER_POINTER (DECL_NAME (decl));
 
+      /* We shall assert that zero-sized objects are an error in ObjC 
+         meta-data.  */
+      gcc_assert (tree_low_cst (DECL_SIZE_UNIT (decl), 1) != 0);
       if (!strncmp (name, "_OBJC_CLASS_METHODS_", 20))
         return darwin_sections[objc_cls_meth_section];
       else if (!strncmp (name, "_OBJC_INSTANCE_METHODS_", 23))
         return darwin_sections[objc_inst_meth_section];
-      else if (!strncmp (name, "_OBJC_CATEGORY_CLASS_METHODS_", 20))
+      else if (!strncmp (name, "_OBJC_CATEGORY_CLASS_METHODS_", 29))
         return darwin_sections[objc_cat_cls_meth_section];
-      else if (!strncmp (name, "_OBJC_CATEGORY_INSTANCE_METHODS_", 23))
+      else if (!strncmp (name, "_OBJC_CATEGORY_INSTANCE_METHODS_", 32))
         return darwin_sections[objc_cat_inst_meth_section];
       else if (!strncmp (name, "_OBJC_CLASS_VARIABLES_", 22))
         return darwin_sections[objc_class_vars_section];
@@ -1688,18 +1755,514 @@ darwin_non_lazy_pcrel (FILE *file, rtx addr)
   fputs ("-.", file);
 }
 
-/* The implementation of ASM_DECLARE_CONSTANT_NAME.  */
+/* If this is uncommented, details of each allocation will be printed
+   in the asm right before the actual code.  WARNING - this will cause some
+   test-suite fails (since the printout will contain items that some tests
+   are not expecting) -- so don't leave it on by default (it bloats the
+   asm too).  */
+/*#define DEBUG_DARWIN_MEM_ALLOCATORS*/
+
+/* The first two of these routines are ostensibly just intended to put
+   names into the asm.  However, they are both hijacked in order to ensure
+   that zero-sized items do not make their way into the output.  Consequently,
+   we also need to make these participate in provisions for dealing with
+   such items in section anchors.  */
+
+/* The implementation of ASM_DECLARE_OBJECT_NAME.  */
+/* The RTTI data (e.g., __ti4name) is common and public (and static),
+   but it does need to be referenced via indirect PIC data pointers.
+   The machopic_define_symbol calls are telling the machopic subsystem
+   that the name *is* defined in this module, so it doesn't need to
+   make them indirect.  */
+void 
+darwin_asm_declare_object_name (FILE *file, 
+				const char *nam, tree decl)
+{
+  const char *xname = nam;
+  unsigned HOST_WIDE_INT size;
+  bool local_def, weak;
+
+  weak = (DECL_P (decl)
+	  && DECL_WEAK (decl)
+	  && !lookup_attribute ("weak_import", 
+				 DECL_ATTRIBUTES (decl)));
+
+  local_def = DECL_INITIAL (decl) || (TREE_STATIC (decl) 
+				      && (!DECL_COMMON (decl) 
+					  || !TREE_PUBLIC (decl)));
+
+  if (GET_CODE (XEXP (DECL_RTL (decl), 0)) != SYMBOL_REF)
+    xname = IDENTIFIER_POINTER (DECL_NAME (decl));
+
+  if (local_def)
+    {
+      (* targetm.encode_section_info) (decl, DECL_RTL (decl), false);
+      if (!weak)
+	machopic_define_symbol (DECL_RTL (decl));
+    }
+
+  size = tree_low_cst (DECL_SIZE_UNIT (decl), 1);
+
+#ifdef DEBUG_DARWIN_MEM_ALLOCATORS
+fprintf (file, "# dadon: %s %s (%llu, %u) local %d weak %d"
+	       " stat %d com %d pub %d t-const %d t-ro %d init %lx\n",
+	xname, (TREE_CODE (decl) == VAR_DECL?"var":"const"), 
+	(unsigned long long)size, DECL_ALIGN (decl), local_def, 
+	DECL_WEAK (decl), TREE_STATIC (decl), DECL_COMMON (decl),
+	TREE_PUBLIC (decl), TREE_CONSTANT (decl), TREE_READONLY (decl),
+	(unsigned long)DECL_INITIAL (decl)); 
+#endif
+
+  /* Darwin needs help to support local zero-sized objects. 
+     They must be made at least one byte, and the section containing must be
+     marked as unsuitable for section-anchors (see storage allocators below).
+     
+     For non-zero objects this output is handled by varasm.c.
+  */
+  if (!size)
+    {
+      unsigned int l2align = 0;
 
+      /* The align must be honoured, even for zero-sized.  */
+      if (DECL_ALIGN (decl))
+	{
+	  l2align = floor_log2 (DECL_ALIGN (decl) / BITS_PER_UNIT);
+	  fprintf (file, "\t.align\t%u\n", l2align);
+	}
+
+      ASM_OUTPUT_LABEL (file, xname);
+      size = 1;
+      fprintf (file, "\t.space\t"HOST_WIDE_INT_PRINT_UNSIGNED"\n", size);
+
+      /* Check that we've correctly picked up the zero-sized item and placed it
+         properly.  */
+      gcc_assert ((!DARWIN_SECTION_ANCHORS || !flag_section_anchors)
+		  || (in_section 
+		      && (in_section->common.flags & SECTION_NO_ANCHOR)));
+    }
+  else
+    ASM_OUTPUT_LABEL (file, xname);
+}
+
+/* The implementation of ASM_DECLARE_CONSTANT_NAME.  */
 void
 darwin_asm_declare_constant_name (FILE *file, const char *name,
 				  const_tree exp ATTRIBUTE_UNUSED,
 				  HOST_WIDE_INT size)
 {
   assemble_label (file, name);
+  /* As for other items, we need at least one byte.  */
+  if (!size)
+    {
+      fputs ("\t.space\t1\n", file);
+      /* Check that we've correctly picked up the zero-sized item and placed it
+         properly.  */
+      gcc_assert ((!DARWIN_SECTION_ANCHORS || !flag_section_anchors)
+		  || (in_section 
+		      && (in_section->common.flags & SECTION_NO_ANCHOR)));
+    }
+}
+
+/* Darwin storage allocators.
+
+   Zerofill sections are desirable for large blank data since, otherwise, these
+   data bloat objects (PR33210).
+
+   However, section anchors don't work in .zerofill sections (one cannot switch
+   to a zerofill section).  Ergo, for Darwin targets using section anchors we need
+   to put (at least some) data into 'normal' switchable sections.
+
+   Here we set a relatively arbitrary value for the size of an object to trigger
+   zerofill when section anchors are enabled (anything bigger than a page for
+   current Darwin implementations).  FIXME: there ought to be some objective way
+   to make this choice.
+
+   When section anchor are off this is ignored anyway.  */
+
+#define BYTES_ZFILL 4096
+
+/* Emit a chunk of data for items coalesced by the linker.  */
+static void
+darwin_emit_weak_or_comdat (FILE *fp, tree decl, const char *name,
+				  unsigned HOST_WIDE_INT size, 
+				  unsigned int align)
+{
+  /* Since the sections used here are coalesed, they will not be eligible
+     for section anchors, and therefore we don't need to break that out.  */
+ if (TREE_READONLY (decl) || TREE_CONSTANT (decl))
+    switch_to_section (darwin_sections[const_data_coal_section]);
+  else
+    switch_to_section (darwin_sections[data_coal_section]);
+
+  /* To be consistent, we'll allow darwin_asm_declare_object_name to assemble
+     the align info for zero-sized items... but do it here otherwise.  */
+  if (size && align)
+    fprintf (fp, "\t.align\t%d\n", floor_log2 (align / BITS_PER_UNIT));
+
+  if (TREE_PUBLIC (decl))
+    darwin_globalize_label (fp, name);
+
+  /* ... and we let it deal with outputting one byte of zero for them too.  */ 
+  darwin_asm_declare_object_name (fp, name, decl);
+  if (size)
+    assemble_zeros (size);
+}
+
+/* This routine emits 'local' storage:
+
+   When Section Anchors are off this routine emits .zerofill commands in 
+   sections named for their alignment.
+
+   When Section Anchors are on, smaller (non-zero-sized) items are placed in
+   the .static_data section so that the section anchoring system can see them.
+   Larger items are still placed in .zerofill sections, addressing PR33210.
+   The routine has no checking - it is all assumed to be done by the caller.
+*/
+static void
+darwin_emit_local_bss (FILE *fp, tree decl, const char *name, 
+			unsigned HOST_WIDE_INT size, 
+			unsigned int l2align)
+{
+   /* FIXME: We have a fudge to make this work with Java even when the target does
+   not use sections anchors -- Java seems to need at least one small item in a
+   non-zerofill segment.   */
+   if ((DARWIN_SECTION_ANCHORS && flag_section_anchors && size < BYTES_ZFILL)
+       || (size && size <= 2))
+    {
+      /* Put smaller objects in _static_data, where the section anchors system
+	 can get them.
+	 However, if they are zero-sized punt them to yet a different section
+	 (that is not allowed to participate in anchoring).  */
+      if (!size)
+	{
+	  fputs ("\t.section\t__DATA,__zobj_bss\n", fp);
+	  in_section = darwin_sections[zobj_bss_section];
+	  size = 1;
+	}
+      else
+	{
+	  fputs ("\t.static_data\n", fp);
+	  in_section = darwin_sections[static_data_section];
+	}
+
+      if (l2align)
+	fprintf (fp, "\t.align\t%u\n", l2align);
+
+      assemble_name (fp, name);        
+      fprintf (fp, ":\n\t.space\t"HOST_WIDE_INT_PRINT_UNSIGNED"\n", size);
+    }
+  else 
+    {
+      /* When we are on a non-section anchor target, we can get zero-sized
+	 items here.  However, all we need to do is to bump them to one byte
+	 and the section alignment will take care of the rest.  */
+      char secnam[64];
+      unsigned int flags ;
+      snprintf (secnam, 64, "__DATA,__%sbss%u", ((size)?"":"zo_"), 
+						(unsigned) l2align);
+      /* We can't anchor (yet, if ever) in zerofill sections, because we can't
+	 switch to them and emit a label.  */
+      flags = SECTION_BSS|SECTION_WRITE|SECTION_NO_ANCHOR;
+      in_section = get_section (secnam, flags, NULL);
+      fprintf (fp, "\t.zerofill %s,", secnam);
+      assemble_name (fp, name);
+      if (!size)
+	size = 1;
+
+      if (l2align)
+	fprintf (fp, ","HOST_WIDE_INT_PRINT_UNSIGNED",%u\n",
+		 size, (unsigned) l2align);
+      else
+	fprintf (fp, ","HOST_WIDE_INT_PRINT_UNSIGNED"\n", size);
+    }
+
+  (*targetm.encode_section_info) (decl, DECL_RTL (decl), false);
+  /* This is defined as a file-scope var, so we know to notify machopic.  */
+  machopic_define_symbol (DECL_RTL (decl));
+}
+
+/* Emit a chunk of common.  */
+static void
+darwin_emit_common (FILE *fp, const char *name,
+		    unsigned HOST_WIDE_INT size, unsigned int align) 
+{
+  unsigned HOST_WIDE_INT rounded;
+  unsigned int l2align;
+
+  /* Earlier systems complain if the alignment exceeds the page size. 
+     The magic number is 4096 * 8 - hard-coded for legacy systems.  */
+  if (!emit_aligned_common && (align > 32768UL))
+    align = 4096UL; /* In units.  */
+  else
+    align /= BITS_PER_UNIT;
+
+  /* Make sure we have a meaningful align.  */
+  if (!align)
+    align = 1;
 
-  /* Darwin doesn't support zero-size objects, so give them a byte.  */
-  if ((size) == 0)
-    assemble_zeros (1);
+  /* For earlier toolchains, we need to emit the var as a rounded size to 
+     tell ld the alignment.  */
+  if (size < align) 
+    rounded = align;
+  else
+    rounded = (size + (align-1)) & ~(align-1);
+
+  l2align = floor_log2 (align);
+  gcc_assert (l2align <= L2_MAX_OFILE_ALIGNMENT);
+
+  in_section = comm_section;
+  /* We mustn't allow multiple public symbols to share an address when using
+     the normal OSX toolchain.  */
+  if (!size)
+    {
+      /* Put at least one byte.  */
+      size = 1;
+      /* This section can no longer participate in section anchoring.  */
+      comm_section->common.flags |= SECTION_NO_ANCHOR;
+    }
+
+  fputs ("\t.comm\t", fp);
+  assemble_name (fp, name);
+  fprintf (fp, "," HOST_WIDE_INT_PRINT_UNSIGNED, 
+	   emit_aligned_common?size:rounded);
+  if (l2align && emit_aligned_common)
+    fprintf (fp, ",%u", l2align);
+  fputs ("\n", fp);
+}
+
+/* Output a var which is all zero - into aligned BSS sections, common, lcomm
+   or coalescable data sections (for weak or comdat) as appropriate.  */
+
+void
+darwin_output_aligned_bss (FILE *fp, tree decl, const char *name,
+			  unsigned HOST_WIDE_INT size, unsigned int align)
+{
+  unsigned int l2align;
+  bool one, pub, weak;
+
+  pub = TREE_PUBLIC (decl);
+  one = DECL_ONE_ONLY (decl);
+  weak = (DECL_P (decl)
+	  && DECL_WEAK (decl)
+	  && !lookup_attribute ("weak_import", 
+				 DECL_ATTRIBUTES (decl)));
+
+#ifdef DEBUG_DARWIN_MEM_ALLOCATORS
+fprintf (fp, "# albss: %s (%lld,%d) ro %d cst %d stat %d com %d"
+	     " pub %d weak %d one %d init %lx\n",
+	name, (long long)size, (int)align, TREE_READONLY (decl), 
+	TREE_CONSTANT (decl), TREE_STATIC (decl), DECL_COMMON (decl),
+	pub, weak, one, (unsigned long)DECL_INITIAL (decl)); 
+#endif
+
+  /* Check that any initializer is valid.  */
+  gcc_assert ((DECL_INITIAL (decl) == NULL) 
+	       || (DECL_INITIAL (decl) == error_mark_node) 
+	       || initializer_zerop (DECL_INITIAL (decl)));
+
+  gcc_assert (DECL_SECTION_NAME (decl) == NULL);
+  gcc_assert (!DECL_COMMON (decl));
+
+  /*  Pick up the correct alignment.  */
+  if (!size || !align)
+    align = DECL_ALIGN (decl);
+
+  l2align = floor_log2 (align / BITS_PER_UNIT);
+  gcc_assert (l2align <= L2_MAX_OFILE_ALIGNMENT);
+  
+  last_assemble_variable_decl = decl;
+
+  /* We would rather not have to check this here - but it seems that we might
+     be passed a decl that should be in coalesced space.  */
+  if (one || weak)
+    {
+      /* Weak or COMDAT objects are put in mergable sections.  */
+      darwin_emit_weak_or_comdat (fp, decl, name, size, 
+					DECL_ALIGN (decl));
+      return;
+    } 
+
+  /* If this is not public, then emit according to local rules.  */
+  if (!pub)
+    {
+      darwin_emit_local_bss (fp, decl, name, size, l2align);	
+      return;
+    }
+
+  /* So we have a public symbol (small item fudge for Java, see above).  */
+  if ((DARWIN_SECTION_ANCHORS && flag_section_anchors && size < BYTES_ZFILL) 
+       || (size && size <= 2))
+    {
+      /* Put smaller objects in data, where the section anchors system can get
+	 them.  However, if they are zero-sized punt them to yet a different 
+	 section (that is not allowed to participate in anchoring).  */
+      if (!size)
+	{
+	  fputs ("\t.section\t__DATA,__zobj_data\n", fp);
+	  in_section = darwin_sections[zobj_data_section];
+	  size = 1;
+	}
+      else
+	{
+	  fputs ("\t.data\n", fp);
+	  in_section = data_section;
+	}
+
+      if (l2align)
+	fprintf (fp, "\t.align\t%u\n", l2align);
+
+      assemble_name (fp, name);
+      fprintf (fp, ":\n\t.space\t"HOST_WIDE_INT_PRINT_UNSIGNED"\n", size);
+    }
+  else 
+    {
+      char secnam[64];
+      unsigned int flags ;
+      /* When we are on a non-section anchor target, we can get zero-sized
+	 items here.  However, all we need to do is to bump them to one byte
+	 and the section alignment will take care of the rest.  */
+      snprintf (secnam, 64, "__DATA,__%spu_bss%u", ((size)?"":"zo_"), l2align);
+
+      /* We can't anchor in zerofill sections, because we can't switch
+	 to them and emit a label.  */
+      flags = SECTION_BSS|SECTION_WRITE|SECTION_NO_ANCHOR;
+      in_section = get_section (secnam, flags, NULL);
+      fprintf (fp, "\t.zerofill %s,", secnam);
+      assemble_name (fp, name);
+      if (!size)
+	size = 1;
+
+      if (l2align)
+	fprintf (fp, ","HOST_WIDE_INT_PRINT_UNSIGNED",%u\n", size, l2align);
+      else
+	fprintf (fp, ","HOST_WIDE_INT_PRINT_UNSIGNED"\n", size);
+    }
+  (* targetm.encode_section_info) (decl, DECL_RTL (decl), false);
+}
+
+/* Output a chunk of common, with alignment specified (where the target
+   supports this).  */
+void
+darwin_asm_output_aligned_decl_common (FILE *fp, tree decl, const char *name,
+				       unsigned HOST_WIDE_INT size, 
+				       unsigned int align)
+{
+  unsigned int l2align;
+  bool one, weak;
+  /* No corresponding var.  */
+  if (decl==NULL)
+    {
+#ifdef DEBUG_DARWIN_MEM_ALLOCATORS
+fprintf (fp, "# adcom: %s (%d,%d) decl=0x0\n", name, (int)size, (int)align); 
+#endif
+      darwin_emit_common (fp, name, size, align);
+      return;
+    }
+
+  one = DECL_ONE_ONLY (decl);
+  weak = (DECL_P (decl)
+	  && DECL_WEAK (decl)
+	  && !lookup_attribute ("weak_import", 
+				 DECL_ATTRIBUTES (decl)));
+
+#ifdef DEBUG_DARWIN_MEM_ALLOCATORS
+fprintf (fp, "# adcom: %s (%lld,%d) ro %d cst %d stat %d com %d pub %d"
+	     " weak %d one %d init %lx\n",
+	name,  (long long)size, (int)align, TREE_READONLY (decl), 
+	TREE_CONSTANT (decl), TREE_STATIC (decl), DECL_COMMON (decl),
+	TREE_PUBLIC (decl), weak, one, (unsigned long)DECL_INITIAL (decl)); 
+#endif
+
+  /* We shouldn't be messing with this if the decl has a section name.  */
+  gcc_assert (DECL_SECTION_NAME (decl) == NULL);
+
+  /* We would rather not have to check this here - but it seems that we might
+     be passed a decl that should be in coalesced space.  */
+  if (one || weak)
+    {
+      /* Weak or COMDAT objects are put in mergable sections.  */
+      darwin_emit_weak_or_comdat (fp, decl, name, size, 
+					DECL_ALIGN (decl));
+      return;
+    } 
+
+  /* We should only get here for DECL_COMMON, with a zero init (and, in 
+     principle, only for public symbols too - although we deal with local
+     ones below).  */
+
+  /* Check the initializer is OK.  */
+  gcc_assert (DECL_COMMON (decl) 
+	      && ((DECL_INITIAL (decl) == NULL) 
+	       || (DECL_INITIAL (decl) == error_mark_node) 
+	       || initializer_zerop (DECL_INITIAL (decl))));
+
+  last_assemble_variable_decl = decl;
+
+  if (!size || !align) 
+    align = DECL_ALIGN (decl);
+
+  l2align = floor_log2 (align / BITS_PER_UNIT);
+  /* Check we aren't asking for more aligment than the platform allows.  */
+  gcc_assert (l2align <= L2_MAX_OFILE_ALIGNMENT);
+
+  if (TREE_PUBLIC (decl) != 0)
+    darwin_emit_common (fp, name, size, align);
+  else
+    darwin_emit_local_bss (fp, decl, name, size, l2align);	
+}
+
+/* Output a chunk of BSS with alignment specfied.  */
+void
+darwin_asm_output_aligned_decl_local (FILE *fp, tree decl, const char *name, 
+				      unsigned HOST_WIDE_INT size, 
+				      unsigned int align)
+{
+  unsigned long l2align;
+  bool one, weak;
+
+  one = DECL_ONE_ONLY (decl);
+  weak = (DECL_P (decl)
+	  && DECL_WEAK (decl)
+	  && !lookup_attribute ("weak_import", 
+				 DECL_ATTRIBUTES (decl)));
+
+#ifdef DEBUG_DARWIN_MEM_ALLOCATORS
+fprintf (fp, "# adloc: %s (%lld,%d) ro %d cst %d stat %d one %d pub %d"
+	     " weak %d init %lx\n",
+	name, (long long)size, (int)align, TREE_READONLY (decl), 
+	TREE_CONSTANT (decl), TREE_STATIC (decl), one, TREE_PUBLIC (decl),
+	weak , (unsigned long)DECL_INITIAL (decl)); 
+#endif
+
+  /* We shouldn't be messing with this if the decl has a section name.  */
+  gcc_assert (DECL_SECTION_NAME (decl) == NULL);
+
+  /* We would rather not have to check this here - but it seems that we might
+     be passed a decl that should be in coalesced space.  */
+  if (one || weak)
+    {
+      /* Weak or COMDAT objects are put in mergable sections.  */
+      darwin_emit_weak_or_comdat (fp, decl, name, size, 
+					DECL_ALIGN (decl));
+      return;
+    } 
+
+  /* .. and it should be suitable for placement in local mem.  */
+  gcc_assert(!TREE_PUBLIC (decl) && !DECL_COMMON (decl));
+  /* .. and any initializer must be all-zero.  */
+  gcc_assert ((DECL_INITIAL (decl) == NULL) 
+	       || (DECL_INITIAL (decl) == error_mark_node) 
+	       || initializer_zerop (DECL_INITIAL (decl)));
+
+  last_assemble_variable_decl = decl;
+
+  if (!size || !align)
+    align = DECL_ALIGN (decl);
+
+  l2align = floor_log2 (align / BITS_PER_UNIT);
+  gcc_assert (l2align <= L2_MAX_OFILE_ALIGNMENT);
+
+  darwin_emit_local_bss (fp, decl, name, size, l2align);
 }
 
 /* Emit an assembler directive to set visibility for a symbol.  The
@@ -1813,6 +2376,7 @@ darwin_asm_output_dwarf_delta (FILE *file, int size,
     fprintf (file, "\t.set L$set$%d,", darwin_dwarf_label_counter);
   else
     fprintf (file, "\t%s\t", directive);
+
   assemble_name_raw (file, lab1);
   fprintf (file, "-");
   assemble_name_raw (file, lab2);
@@ -1916,7 +2480,10 @@ darwin_file_end (void)
     }
   obstack_free (&lto_section_names_obstack, NULL);
 
-  fprintf (asm_out_file, "\t.subsections_via_symbols\n");
+  /* If we have section anchors, then we must prevent the linker from
+     re-arranging data.  */
+  if (!DARWIN_SECTION_ANCHORS || !flag_section_anchors)
+    fprintf (asm_out_file, "\t.subsections_via_symbols\n");
 }
 
 /* TODO: Add a language hook for identifying if a decl is a vtable.  */
@@ -1932,12 +2499,9 @@ darwin_binds_local_p (const_tree decl)
 				  TARGET_KEXTABI && DARWIN_VTABLE_P (decl));
 }
 
-#if 0
-/* See TARGET_ASM_OUTPUT_ANCHOR for why we can't do this yet.  */
 /* The Darwin's implementation of TARGET_ASM_OUTPUT_ANCHOR.  Define the
    anchor relative to ".", the current section position.  We cannot use
    the default one because ASM_OUTPUT_DEF is wrong for Darwin.  */
-
 void
 darwin_asm_output_anchor (rtx symbol)
 {
@@ -1946,7 +2510,28 @@ darwin_asm_output_anchor (rtx symbol)
   fprintf (asm_out_file, ", . + " HOST_WIDE_INT_PRINT_DEC "\n",
 	   SYMBOL_REF_BLOCK_OFFSET (symbol));
 }
-#endif
+
+/* Disable section anchoring on any section containing a zero-sized 
+   object.  */
+bool
+darwin_use_anchors_for_symbol_p (const_rtx symbol)
+{
+  if (DARWIN_SECTION_ANCHORS && flag_section_anchors) 
+    {
+      section *sect;
+      /* If the section contains a zero-sized object it's ineligible.  */
+      sect = SYMBOL_REF_BLOCK (symbol)->sect;
+      /* This should have the effect of disabling anchors for vars that follow
+         any zero-sized one, in a given section.  */     
+      if (sect->common.flags & SECTION_NO_ANCHOR)
+	return false;
+
+        /* Also check the normal reasons for suppressing.  */
+        return default_use_anchors_for_symbol_p (symbol);
+    }
+  else
+    return false;
+}
 
 /* Set the darwin specific attributes on TYPE.  */
 void
@@ -1969,9 +2554,12 @@ darwin_kextabi_p (void) {
 void
 darwin_override_options (void)
 {
+  bool darwin9plus = (darwin_macosx_version_min
+		      && strverscmp (darwin_macosx_version_min, "10.5") >= 0);
+
   /* Don't emit DWARF3/4 unless specifically selected.  This is a 
      workaround for tool bugs.  */
-  if (dwarf_strict < 0) 
+  if (!global_options_set.x_dwarf_strict) 
     dwarf_strict = 1;
 
   /* Disable -freorder-blocks-and-partition for darwin_emit_unwind_label.  */
@@ -1997,11 +2585,15 @@ darwin_override_options (void)
       flag_exceptions = 0;
       /* No -fnon-call-exceptions data in kexts.  */
       flag_non_call_exceptions = 0;
+      /* so no tables either.. */
+      flag_unwind_tables = 0;
+      flag_asynchronous_unwind_tables = 0;
       /* We still need to emit branch islands for kernel context.  */
       darwin_emit_branch_islands = true;
     }
+
   if (flag_var_tracking
-      && strverscmp (darwin_macosx_version_min, "10.5") >= 0
+      && darwin9plus
       && debug_info_level >= DINFO_LEVEL_NORMAL
       && debug_hooks->var_location != do_nothing_debug_hooks.var_location)
     flag_var_tracking_uninit = 1;
@@ -2019,9 +2611,10 @@ darwin_override_options (void)
     }
 
   /* It is assumed that branch island stubs are needed for earlier systems.  */
-  if (darwin_macosx_version_min
-      && strverscmp (darwin_macosx_version_min, "10.5") < 0)
+  if (!darwin9plus)
     darwin_emit_branch_islands = true;
+  else
+    emit_aligned_common = true; /* Later systems can support aligned common.  */
 
   /* The c_dialect...() macros are not available to us here.  */
   darwin_running_cxx = (strstr (lang_hooks.name, "C++") != 0);
diff --git a/gcc/config/darwin.h b/gcc/config/darwin.h
index 854cb95b407741c3e863d30b73323c046168943e..eb1ff8984c15b2b263caecdce9240f0ad8e69f7a 100644
--- a/gcc/config/darwin.h
+++ b/gcc/config/darwin.h
@@ -529,34 +529,16 @@ extern GTY(()) int darwin_ms_struct;
 		  (CLASS_NAME), (SEL_NAME));				\
      } while (0)
 
+#undef ASM_DECLARE_OBJECT_NAME
+#define ASM_DECLARE_OBJECT_NAME(FILE, NAME, DECL) \
+	darwin_asm_declare_object_name ((FILE), (NAME), (DECL))
+
 /* The RTTI data (e.g., __ti4name) is common and public (and static),
    but it does need to be referenced via indirect PIC data pointers.
    The machopic_define_symbol calls are telling the machopic subsystem
    that the name *is* defined in this module, so it doesn't need to
    make them indirect.  */
 
-#undef ASM_DECLARE_OBJECT_NAME
-#define ASM_DECLARE_OBJECT_NAME(FILE, NAME, DECL)			\
-  do {									\
-    const char *xname = NAME;						\
-    if (GET_CODE (XEXP (DECL_RTL (DECL), 0)) != SYMBOL_REF)		\
-      xname = IDENTIFIER_POINTER (DECL_NAME (DECL));			\
-    if (! DECL_WEAK (DECL)						\
-        && ((TREE_STATIC (DECL)						\
-	     && (!DECL_COMMON (DECL) || !TREE_PUBLIC (DECL)))		\
-            || DECL_INITIAL (DECL)))					\
-        machopic_define_symbol (DECL_RTL (DECL));			\
-    if ((TREE_STATIC (DECL)						\
-	 && (!DECL_COMMON (DECL) || !TREE_PUBLIC (DECL)))		\
-        || DECL_INITIAL (DECL))						\
-      (* targetm.encode_section_info) (DECL, DECL_RTL (DECL), false);	\
-    ASM_OUTPUT_LABEL (FILE, xname);					\
-    /* Darwin doesn't support zero-size objects, so give them a		\
-       byte.  */							\
-    if (tree_low_cst (DECL_SIZE_UNIT (DECL), 1) == 0)			\
-      assemble_zeros (1);						\
-  } while (0)
-
 #define ASM_DECLARE_FUNCTION_NAME(FILE, NAME, DECL)			\
   do {									\
     const char *xname = NAME;						\
@@ -581,7 +563,6 @@ extern GTY(()) int darwin_ms_struct;
    Make Objective-C internal symbols local and in doing this, we need 
    to accommodate the name mangling done by c++ on file scope locals.  */
 
-
 int darwin_label_is_anonymous_local_objc_name (const char *name);
 
 #undef	ASM_OUTPUT_LABELREF
@@ -633,27 +614,7 @@ int darwin_label_is_anonymous_local_objc_name (const char *name);
 #undef	ASM_OUTPUT_ALIGN
 #define ASM_OUTPUT_ALIGN(FILE,LOG)	\
   if ((LOG) != 0)			\
-    fprintf (FILE, "\t%s %d\n", ALIGN_ASM_OP, (LOG))
-
-/* Ensure correct alignment of bss data.  */
-
-#undef	ASM_OUTPUT_ALIGNED_DECL_LOCAL
-#define ASM_OUTPUT_ALIGNED_DECL_LOCAL(FILE, DECL, NAME, SIZE, ALIGN)	\
-  do {									\
-    unsigned HOST_WIDE_INT _new_size = SIZE;				\
-    fputs ("\t.lcomm ", (FILE));						\
-    assemble_name ((FILE), (NAME));					\
-    if (_new_size == 0) _new_size = 1;					\
-    fprintf ((FILE), ","HOST_WIDE_INT_PRINT_UNSIGNED",%u\n", _new_size,	\
-	     floor_log2 ((ALIGN) / BITS_PER_UNIT));			\
-    if ((DECL) && ((TREE_STATIC (DECL)					\
-	 && (!DECL_COMMON (DECL) || !TREE_PUBLIC (DECL)))		\
-        || DECL_INITIAL (DECL)))					\
-      {									\
-	(* targetm.encode_section_info) (DECL, DECL_RTL (DECL), false);	\
-	machopic_define_symbol (DECL_RTL (DECL));			\
-      }									\
-  } while (0)
+    fprintf (FILE, "\t%s\t%d\n", ALIGN_ASM_OP, (LOG))
 
 /* The maximum alignment which the object file format can support in
    bits.  For Mach-O, this is 2^15 bytes.  */
@@ -661,9 +622,30 @@ int darwin_label_is_anonymous_local_objc_name (const char *name);
 #undef	MAX_OFILE_ALIGNMENT
 #define MAX_OFILE_ALIGNMENT (0x8000 * 8)
 
+#define L2_MAX_OFILE_ALIGNMENT 15
+
+/*  These are the three variants that emit referenced blank space.  */
+#define ASM_OUTPUT_ALIGNED_BSS(FILE, DECL, NAME, SIZE, ALIGN)		\
+	darwin_output_aligned_bss ((FILE), (DECL), (NAME), (SIZE), (ALIGN))
+
+#undef	ASM_OUTPUT_ALIGNED_DECL_LOCAL
+#define ASM_OUTPUT_ALIGNED_DECL_LOCAL(FILE, DECL, NAME, SIZE, ALIGN)	\
+	darwin_asm_output_aligned_decl_local				\
+				  ((FILE), (DECL), (NAME), (SIZE), (ALIGN))
+
+#undef  ASM_OUTPUT_ALIGNED_DECL_COMMON
+#define ASM_OUTPUT_ALIGNED_DECL_COMMON(FILE, DECL, NAME, SIZE, ALIGN)	\
+	darwin_asm_output_aligned_decl_common				\
+				   ((FILE), (DECL), (NAME), (SIZE), (ALIGN))
+
 /* The generic version, archs should over-ride where required.  */
 #define MACHOPIC_NL_SYMBOL_PTR_SECTION ".non_lazy_symbol_pointer"
 
+/* Private flag applied to disable section-anchors in a particular section.
+   This needs to be kept in sync with the flags used by varasm.c (defined in
+   output.h).  */
+#define SECTION_NO_ANCHOR 0x2000000
+
 /* Declare the section variables.  */
 #ifndef USED_FOR_TARGET
 enum darwin_section_enum {
@@ -911,17 +893,10 @@ void add_framework_path (char *);
 #undef GOMP_SELF_SPECS
 #define GOMP_SELF_SPECS ""
 
-/* Darwin can't support anchors until we can cope with the adjustments
-   to size that ASM_DECLARE_OBJECT_NAME and ASM_DECLARE_CONSTANT_NAME
-   when outputting members of an anchor block and the linker can be
-   taught to keep them together or we find some other suitable
-   code-gen technique.  */
-
-#if 0
-#define TARGET_ASM_OUTPUT_ANCHOR darwin_asm_output_anchor
-#else
+/* Darwin disables section anchors by default.  
+   They should be enabled per arch where support exists in that arch.  */
 #define TARGET_ASM_OUTPUT_ANCHOR NULL
-#endif
+#define DARWIN_SECTION_ANCHORS 0
 
 /* Attempt to turn on execute permission for the stack.  This may be
     used by TARGET_TRAMPOLINE_INIT if the target needs it (that is,
diff --git a/gcc/config/i386/darwin.h b/gcc/config/i386/darwin.h
index 1f2c2e4bb699417bc4c0d2fa211374ced2669136..a9a2da4040e6688fb6d2470a528a3de864eab4e3 100644
--- a/gcc/config/i386/darwin.h
+++ b/gcc/config/i386/darwin.h
@@ -213,22 +213,6 @@ extern int darwin_emit_branch_islands;
         }				\
     } while (0)
 
-/* This says how to output an assembler line
-   to define a global common symbol.  */
-
-#define ASM_OUTPUT_COMMON(FILE, NAME, SIZE, ROUNDED)  \
-( fputs ("\t.comm ", (FILE)),			\
-  assemble_name ((FILE), (NAME)),		\
-  fprintf ((FILE), ","HOST_WIDE_INT_PRINT_UNSIGNED"\n", (ROUNDED)))
-
-/* This says how to output an assembler line
-   to define a local common symbol.  */
-
-#define ASM_OUTPUT_LOCAL(FILE, NAME, SIZE, ROUNDED)  \
-( fputs ("\t.lcomm ", (FILE)),			\
-  assemble_name ((FILE), (NAME)),		\
-  fprintf ((FILE), ","HOST_WIDE_INT_PRINT_UNSIGNED"\n", (ROUNDED)))
-
 /* Darwin profiling -- call mcount.  */
 #undef FUNCTION_PROFILER
 #define FUNCTION_PROFILER(FILE, LABELNO)				\
diff --git a/gcc/config/rs6000/darwin.h b/gcc/config/rs6000/darwin.h
index 5f2cace341c2166c8e7db1323b8be66570cf8623..bd4b19581313c906e6ddeea3251b08bc92d75e20 100644
--- a/gcc/config/rs6000/darwin.h
+++ b/gcc/config/rs6000/darwin.h
@@ -232,17 +232,6 @@ extern int darwin_emit_branch_islands;
 #define ASM_OUTPUT_INTERNAL_LABEL_PREFIX(FILE,PREFIX)	\
   fprintf (FILE, "%s", PREFIX)
 
-/* This says how to output an assembler line to define a global common
-   symbol.  */
-#define ASM_OUTPUT_COMMON(FILE, NAME, SIZE, ROUNDED)			\
-  do {									\
-    unsigned HOST_WIDE_INT _new_size = SIZE;				\
-    fputs ("\t.comm ", (FILE));						\
-    RS6000_OUTPUT_BASENAME ((FILE), (NAME));				\
-    if (_new_size == 0) _new_size = 1;					\
-    fprintf ((FILE), ","HOST_WIDE_INT_PRINT_UNSIGNED"\n", _new_size);	\
-  } while (0)
-
 /* Override the standard rs6000 definition.  */
 
 #undef ASM_COMMENT_START
@@ -423,6 +412,22 @@ extern int darwin_emit_branch_islands;
    default, as kernel code doesn't save/restore those registers.  */
 #define OS_MISSING_ALTIVEC (flag_mkernel || flag_apple_kext)
 
+/* Darwin has support for section anchors on powerpc*.  
+   It is disabled for any section containing a "zero-sized item" (because these
+   are re-written as size=1 to be compatible with the OSX ld64).
+   The re-writing would interfere with the computation of anchor offsets.
+   Therefore, we place zero-sized items in their own sections and make such
+   sections unavailable to section anchoring.  */
+
+#undef TARGET_ASM_OUTPUT_ANCHOR 
+#define TARGET_ASM_OUTPUT_ANCHOR darwin_asm_output_anchor
+
+#undef TARGET_USE_ANCHORS_FOR_SYMBOL_P
+#define TARGET_USE_ANCHORS_FOR_SYMBOL_P darwin_use_anchors_for_symbol_p
+
+#undef DARWIN_SECTION_ANCHORS
+#define DARWIN_SECTION_ANCHORS 1
+
 /* PPC Darwin has to rename some of the long double builtins.  */
 #undef  SUBTARGET_INIT_BUILTINS
 #define SUBTARGET_INIT_BUILTINS						\
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 6185f595b4d71678b8fe4157b68bddb9aa695b9a..7e7ef57da946e48a76c52bd7eb5fb7c0430ab3da 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,15 @@
+2010-11-29  Iain Sandoe  <iains@gcc.gnu.org>
+	    Mike Stump  <mrs@gcc.gnu.org>
+
+	PR target/26427
+	PR target/33120
+	PR testsuite/35710
+	* gcc.target/powerpc/darwin-abi-12.c: Adjust for new allocators.
+	* gcc.dg/pr26427.c: Remove redundant warning for powerpc.
+	* gcc.dg/darwin-comm.c: Adjust for new allocators.
+	* gcc.dg/darwin-sections.c: New test.
+	* g++.dg/ext/instantiate2.C: Adjust for new allocators.
+
 2010-11-29  Nicola Pero  <nicola.pero@meta-innovation.com>
 
 	* objc.dg/exceptions-1.m: New.
diff --git a/gcc/testsuite/g++.dg/ext/instantiate2.C b/gcc/testsuite/g++.dg/ext/instantiate2.C
index 97ef45c874dd9b728c584984d976ce2356b07989..a6292892b38309bd3d295cf0977bc74ce8989ff7 100644
--- a/gcc/testsuite/g++.dg/ext/instantiate2.C
+++ b/gcc/testsuite/g++.dg/ext/instantiate2.C
@@ -8,7 +8,8 @@ template <class T> struct A {
 template <class T> T A<T>::t = 0;
 static template struct A<int>;
 
-// { dg-final { scan-assembler "\n_?_ZN1AIiE1tE(:|\n|\t)" } }
+// { dg-final { scan-assembler "\n_?_ZN1AIiE1tE(:|\n|\t)" { target { ! *-*-darwin* } } } }
+// { dg-final { scan-assembler ".zerofill __DATA,__pu_bss2,__ZN1AIiE1tE" { target *-*-darwin* } } } 
 void test_int() { A<int>::t = 42; }
 
 // { dg-final { scan-assembler-not "\n_?_ZN1AIcE1tE(:|\n|\t)" } }
diff --git a/gcc/testsuite/gcc.dg/darwin-comm.c b/gcc/testsuite/gcc.dg/darwin-comm.c
index 8c8619c87a61dc1e48c172d23b8e2fe33b57cca8..a743fc6d4edb8f242b820e814368d0767d645ffd 100644
--- a/gcc/testsuite/gcc.dg/darwin-comm.c
+++ b/gcc/testsuite/gcc.dg/darwin-comm.c
@@ -1,4 +1,4 @@
 /* { dg-do compile { target *-*-darwin[912]* } } */
-/* { dg-final { scan-assembler ".comm _foo,1,15" } } */
+/* { dg-final { scan-assembler ".comm\[ \t\]_foo,1,15" } } */
 
 char foo __attribute__ ((aligned(32768)));
diff --git a/gcc/testsuite/gcc.dg/darwin-sections.c b/gcc/testsuite/gcc.dg/darwin-sections.c
new file mode 100644
index 0000000000000000000000000000000000000000..79d48bd7da26c865603059ad2273b9bff42ea92a
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/darwin-sections.c
@@ -0,0 +1,73 @@
+/* { dg-do compile {target *-*-darwin* } } */
+/* { dg-options "-std=c99 -w" } */
+
+/* This has been designed to give the same section usage for
+   -m32 and -m64 - so don't put any ints or longs in it ... */
+
+/* A zero-sized object.  */
+typedef struct _empty {} e_s;
+
+/* These should go in .comm */
+char ub;
+e_s ea;
+/* { dg-final { scan-assembler ".comm\[\t \]_ub,1" } } */
+/* { dg-final { scan-assembler ".comm\[\t \]_ea,1" } } */
+
+/* These should go into .data */
+char a = 0;
+short b = 0;
+/* { dg-final { scan-assembler ".globl _a.*.data.*.space\[\t \]1" } } */
+/* { dg-final { scan-assembler ".globl _b.*.data.*.space\[\t \]2" } } */
+
+/* These should go into __pu_bssN */
+long long d = 0;
+float e = 0;
+double f = 0;
+long double g = 0.L;
+long long al_256 __attribute__((aligned (256))) = 0;
+/* { dg-final { scan-assembler ".zerofill __DATA,__pu_bss3,_d,8,3" } } */
+/* { dg-final { scan-assembler ".zerofill __DATA,__pu_bss2,_e,4,2" } } */
+/* { dg-final { scan-assembler ".zerofill __DATA,__pu_bss3,_f,8,3" } } */
+/* { dg-final { scan-assembler ".zerofill __DATA,__pu_bss4,_g,16,4" } } */
+/* { dg-final { scan-assembler ".zerofill __DATA,__pu_bss8,_al_256,8,8" } } */
+
+/* This should go into __zo_bss0 */
+static e_s sea;
+/* { dg-final { scan-assembler ".zerofill __DATA,__zo_bss0,_sea,1" } } */
+
+/* These should go into .static_data */
+static char sa ;
+static short sb ;
+/* { dg-final { scan-assembler ".static_data.*_sa:.*.space\[\t \]1" } } */
+/* { dg-final { scan-assembler ".static_data.*_sb:.*.space\[\t \]2" } } */
+
+/* These should go into _bssN */
+static long long sd;
+static float se ;
+static double sf ;
+static long double sg;
+static long long sal_256 __attribute__((aligned (2048)));
+/* { dg-final { scan-assembler ".zerofill __DATA,__bss3,_sd,8,3" } } */
+/* { dg-final { scan-assembler ".zerofill __DATA,__bss2,_se,4,2" } } */
+/* { dg-final { scan-assembler ".zerofill __DATA,__bss3,_sf,8,3" } } */
+/* { dg-final { scan-assembler ".zerofill __DATA,__bss4,_sg,16,4" } } */
+/* { dg-final { scan-assembler ".zerofill __DATA,__bss11,_sal_256,8,11" } } */
+
+long long foo (int x)
+{
+  e_s *s;
+  a += x + sa;
+  b += a + sb;
+  d += b + sd;
+  e += d + se;
+  f += e + sf;
+  g += f + sg;
+ 
+  s = &ea;
+  s = &sea;
+  
+  b += al_256;
+  b += sal_256;
+
+  return (long long) sd + b;
+}
diff --git a/gcc/testsuite/gcc.dg/pr26427.c b/gcc/testsuite/gcc.dg/pr26427.c
index 3077221c7c78696726ffb22652c07d7f511823d9..add13ca209e74bfd71deab0555f579ce4acd2955 100644
--- a/gcc/testsuite/gcc.dg/pr26427.c
+++ b/gcc/testsuite/gcc.dg/pr26427.c
@@ -1,4 +1,4 @@
-/* { dg-warning "this target does not support" } */
+/* { dg-warning "this target does not support" "" {target *86*-*-darwin* } 0 } */
 /* { dg-do run { target { *-*-darwin* } } } */
 /* { dg-options { -fsection-anchors -O } } */
 /* PR target/26427 */
diff --git a/gcc/testsuite/gcc.target/powerpc/darwin-abi-12.c b/gcc/testsuite/gcc.target/powerpc/darwin-abi-12.c
index d02c4868a59211a29fbe29d3239d105c5a3bc3f3..5f5764368c1ebe4ef5966e0a8d2b7ddd9b9c5b4e 100644
--- a/gcc/testsuite/gcc.target/powerpc/darwin-abi-12.c
+++ b/gcc/testsuite/gcc.target/powerpc/darwin-abi-12.c
@@ -1,5 +1,5 @@
 /* { dg-do compile { target powerpc*-*-darwin* } } */
-/* { dg-final { scan-assembler ".comm _x,12,2" } } */
+/* { dg-final { scan-assembler ".comm\[\t \]_x,12,2" } } */
 /* { dg-final { scan-assembler-not ".space 7" } } */
 /* PR 23071 */