diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 173cabf87e983df1b238078e1145d7b1b3ac8559..28ff1631d65056f2c06765a03f7ce9088bdb7083 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,12 @@
+2009-07-16  Jason Merrill  <jason@redhat.com>
+
+	PR libstdc++/37907
+	* c-common.c (c_common_reswords): Add __is_standard_layout
+	and __is_trivial.
+	* c-common.h (enum rid): Add RID_IS_STD_LAYOUT and RID_IS_TRIVIAL.
+	* doc/implement-cxx.texi: New.
+	* doc/gcc.texi: Include it.
+
 2009-07-16  DJ Delorie  <dj@redhat.com>
 
 	* config/m32c/m32c.c (m32c_compare_redundant): Avoid removing
diff --git a/gcc/Makefile.in b/gcc/Makefile.in
index 11a4bcb188679c41371fc7ee11c9ee9ffc1ac8b6..18f25d5529a0e222385b5e8bd53ac2241c1f00e6 100644
--- a/gcc/Makefile.in
+++ b/gcc/Makefile.in
@@ -3777,7 +3777,7 @@ TEXI_GCC_FILES = gcc.texi gcc-common.texi gcc-vers.texi frontends.texi	\
 	 gcov.texi trouble.texi bugreport.texi service.texi		\
 	 contribute.texi compat.texi funding.texi gnu.texi gpl_v3.texi	\
 	 fdl.texi contrib.texi cppenv.texi cppopts.texi			\
-	 implement-c.texi arm-neon-intrinsics.texi
+	 implement-c.texi implement-cxx.texi arm-neon-intrinsics.texi
 
 TEXI_GCCINT_FILES = gccint.texi gcc-common.texi gcc-vers.texi		\
 	 contribute.texi makefile.texi configterms.texi options.texi	\
diff --git a/gcc/c-common.c b/gcc/c-common.c
index 20dac6b2ef4250caf14454225e7dc18a3098e3fc..069452cd1984f7fecb46e01501ada4b00ef9d3ec 100644
--- a/gcc/c-common.c
+++ b/gcc/c-common.c
@@ -598,6 +598,8 @@ const struct c_common_resword c_common_reswords[] =
   { "__is_enum",	RID_IS_ENUM,	D_CXXONLY },
   { "__is_pod",		RID_IS_POD,	D_CXXONLY },
   { "__is_polymorphic",	RID_IS_POLYMORPHIC, D_CXXONLY },
+  { "__is_standard_layout", RID_IS_STD_LAYOUT, D_CXXONLY },
+  { "__is_trivial",     RID_IS_TRIVIAL, D_CXXONLY },
   { "__is_union",	RID_IS_UNION,	D_CXXONLY },
   { "__imag",		RID_IMAGPART,	0 },
   { "__imag__",		RID_IMAGPART,	0 },
diff --git a/gcc/c-common.h b/gcc/c-common.h
index 04a194597f72efa8e1d16159f72e90c42ea46845..ec5705e6ed8f3e135c42f50b60412f9d3be25a05 100644
--- a/gcc/c-common.h
+++ b/gcc/c-common.h
@@ -110,6 +110,7 @@ enum rid
   RID_IS_CONVERTIBLE_TO,       RID_IS_CLASS,
   RID_IS_EMPTY,                RID_IS_ENUM,
   RID_IS_POD,                  RID_IS_POLYMORPHIC,
+  RID_IS_STD_LAYOUT,           RID_IS_TRIVIAL,
   RID_IS_UNION,
 
   /* C++0x */
diff --git a/gcc/cp/ChangeLog b/gcc/cp/ChangeLog
index 4265fa9f9cfb83d2abd80d7ff3e1d3a9d79a6843..81cc8e0f64623dbfee25bf5ec1ea18dd394aba5c 100644
--- a/gcc/cp/ChangeLog
+++ b/gcc/cp/ChangeLog
@@ -1,3 +1,37 @@
+2009-07-16  Jason Merrill  <jason@redhat.com>
+
+	PR libstdc++/37907
+	Split POD into "standard-layout" and "trivial" as per N2230,
+	Support std::is_standard_layout and std::is_trivial traits.
+	* cp-tree.h (enum cp_trait_kind): Add CPTK_IS_STD_LAYOUT,
+	CPTK_IS_TRIVIAL.
+	(struct lang_type_class): Add non_std_layout.
+	(CLASSTYPE_NON_STD_LAYOUT): New.
+	* class.c (check_bases): Set it.
+	(check_field_decls): Likewise.
+	(check_bases_and_members): Likewise.
+	* parser.c (cp_parser_primary_expression): Handle RID_IS_STD_LAYOUT,
+	RID_IS_TRIVIAL.
+	(cp_parser_trait_expr): Likewise.
+	* semantics.c (trait_expr_value): Handle CPTK_IS_STD_LAYOUT,
+	CPTK_IS_TRIVIAL.
+	(finish_trait_expr): Likewise.
+	* tree.c (scalarish_type_p, trivial_type_p, std_layout_type_p): New.
+	(pod_type_p): Use them.
+	(type_has_nontrivial_copy_init, type_has_nontrivial_default_init): New.
+
+	Adjust bits of the language that no longer refer to POD types.
+	* call.c (convert_arg_to_ellipsis): Use type_has_nontrivial_copy_init
+	and TYPE_HAS_NONTRIVIAL_DESTRUCTOR rather than pod_type_p.
+	(build_x_va_arg): Likewise.
+	(call_builtin_trap): Remove.
+	* decl.c (declare_local_label): Use type_has_nontrivial_default_init
+	and TYPE_HAS_NONTRIVIAL_DESTRUCTOR rather than pod_type_p.
+	(cp_finish_decl): Likewise.
+	(check_previous_goto_1, check_goto): Adjust error.
+	* typeck.c (build_class_member_access_expr): Check
+	CLASSTYPE_NON_STD_LAYOUT rather than CLASSTYPE_NON_POD_P.
+
 2009-07-14  Taras Glek  <tglek@mozilla.com>
 	    Rafael Espindola  <espindola@google.com>
 
diff --git a/gcc/cp/call.c b/gcc/cp/call.c
index 588c997a34bb77fefcf595e3a664fd8640a66ab8..6a7a1b861a03ea8bb64153fc6b98066adc1e35ce 100644
--- a/gcc/cp/call.c
+++ b/gcc/cp/call.c
@@ -197,7 +197,6 @@ static conversion *direct_reference_binding (tree, conversion *);
 static bool promoted_arithmetic_type_p (tree);
 static conversion *conditional_conversion (tree, tree);
 static char *name_as_c_string (tree, tree, bool *);
-static tree call_builtin_trap (void);
 static tree prep_operand (tree);
 static void add_candidates (tree, const VEC(tree,gc) *, tree, bool, tree, tree,
 			    int, struct z_candidate **);
@@ -5042,18 +5041,6 @@ convert_like_real (conversion *convs, tree expr, tree fn, int argnum,
   return expr;
 }
 
-/* Build a call to __builtin_trap.  */
-
-static tree
-call_builtin_trap (void)
-{
-  tree fn = implicit_built_in_decls[BUILT_IN_TRAP];
-
-  gcc_assert (fn != NULL);
-  fn = build_call_n (fn, 0);
-  return fn;
-}
-
 /* ARG is being passed to a varargs function.  Perform any conversions
    required.  Return the converted value.  */
 
@@ -5082,20 +5069,23 @@ convert_arg_to_ellipsis (tree arg)
   arg = require_complete_type (arg);
 
   if (arg != error_mark_node
-      && !pod_type_p (TREE_TYPE (arg)))
+      && (type_has_nontrivial_copy_init (TREE_TYPE (arg))
+	  || TYPE_HAS_NONTRIVIAL_DESTRUCTOR (TREE_TYPE (arg))))
     {
-      /* Undefined behavior [expr.call] 5.2.2/7.  We used to just warn
-	 here and do a bitwise copy, but now cp_expr_size will abort if we
-	 try to do that.
+      /* [expr.call] 5.2.2/7:
+	 Passing a potentially-evaluated argument of class type (Clause 9)
+	 with a non-trivial copy constructor or a non-trivial destructor
+	 with no corresponding parameter is conditionally-supported, with
+	 implementation-defined semantics.
+
+	 We used to just warn here and do a bitwise copy, but now
+	 cp_expr_size will abort if we try to do that.
+
 	 If the call appears in the context of a sizeof expression,
-	 there is no need to emit a warning, since the expression won't be
-	 evaluated. We keep the builtin_trap just as a safety check.  */
+	 it is not potentially-evaluated.  */
       if (cp_unevaluated_operand == 0)
-	warning (0, "cannot pass objects of non-POD type %q#T through %<...%>; "
-		 "call will abort at runtime", TREE_TYPE (arg));
-      arg = call_builtin_trap ();
-      arg = build2 (COMPOUND_EXPR, integer_type_node, arg,
-		    integer_zero_node);
+	error ("cannot pass objects of non-trivially-copyable "
+	       "type %q#T through %<...%>", TREE_TYPE (arg));
     }
 
   return arg;
@@ -5114,16 +5104,16 @@ build_x_va_arg (tree expr, tree type)
   if (expr == error_mark_node || !type)
     return error_mark_node;
 
-  if (! pod_type_p (type))
+  if (type_has_nontrivial_copy_init (type)
+      || TYPE_HAS_NONTRIVIAL_DESTRUCTOR (type)
+      || TREE_CODE (type) == REFERENCE_TYPE)
     {
       /* Remove reference types so we don't ICE later on.  */
       tree type1 = non_reference (type);
-      /* Undefined behavior [expr.call] 5.2.2/7.  */
-      warning (0, "cannot receive objects of non-POD type %q#T through %<...%>; "
-	       "call will abort at runtime", type);
+      /* conditionally-supported behavior [expr.call] 5.2.2/7.  */
+      error ("cannot receive objects of non-trivially-copyable type %q#T "
+	     "through %<...%>; ", type);
       expr = convert (build_pointer_type (type1), null_node);
-      expr = build2 (COMPOUND_EXPR, TREE_TYPE (expr),
-		     call_builtin_trap (), expr);
       expr = cp_build_indirect_ref (expr, NULL, tf_warning_or_error);
       return expr;
     }
diff --git a/gcc/cp/class.c b/gcc/cp/class.c
index 4668c68d00885e27817c0e04f5be7c7668853d37..373f45781905ce4e40e981523bb1daba94c21d9c 100644
--- a/gcc/cp/class.c
+++ b/gcc/cp/class.c
@@ -1248,9 +1248,15 @@ check_bases (tree t,
   int seen_non_virtual_nearly_empty_base_p;
   tree base_binfo;
   tree binfo;
+  tree field = NULL_TREE;
 
   seen_non_virtual_nearly_empty_base_p = 0;
 
+  if (!CLASSTYPE_NON_STD_LAYOUT (t))
+    for (field = TYPE_FIELDS (t); field; field = TREE_CHAIN (field))
+      if (TREE_CODE (field) == FIELD_DECL)
+	break;
+
   for (binfo = TYPE_BINFO (t), i = 0;
        BINFO_BASE_ITERATE (binfo, i, base_binfo); i++)
     {
@@ -1305,6 +1311,36 @@ check_bases (tree t,
       CLASSTYPE_CONTAINS_EMPTY_CLASS_P (t)
 	|= CLASSTYPE_CONTAINS_EMPTY_CLASS_P (basetype);
       TYPE_HAS_COMPLEX_DFLT (t) |= TYPE_HAS_COMPLEX_DFLT (basetype);      
+
+      /*  A standard-layout class is a class that:
+	  ...
+	  * has no non-standard-layout base classes,  */
+      CLASSTYPE_NON_STD_LAYOUT (t) |= CLASSTYPE_NON_STD_LAYOUT (basetype);
+      if (!CLASSTYPE_NON_STD_LAYOUT (t))
+	{
+	  tree basefield;
+	  /* ...has no base classes of the same type as the first non-static
+	     data member...  */
+	  if (field && DECL_CONTEXT (field) == t
+	      && (same_type_ignoring_top_level_qualifiers_p
+		  (TREE_TYPE (field), basetype)))
+	    CLASSTYPE_NON_STD_LAYOUT (t) = 1;
+	  else
+	    /* ...either has no non-static data members in the most-derived
+	       class and at most one base class with non-static data
+	       members, or has no base classes with non-static data
+	       members */
+	    for (basefield = TYPE_FIELDS (basetype); basefield;
+		 basefield = TREE_CHAIN (basefield))
+	      if (TREE_CODE (basefield) == FIELD_DECL)
+		{
+		  if (field)
+		    CLASSTYPE_NON_STD_LAYOUT (t) = 1;
+		  else
+		    field = basefield;
+		  break;
+		}
+	}
     }
 }
 
@@ -2870,6 +2906,7 @@ check_field_decls (tree t, tree *access_decls,
   bool has_pointers;
   int any_default_members;
   int cant_pack = 0;
+  int field_access = -1;
 
   /* Assume there are no access declarations.  */
   *access_decls = NULL_TREE;
@@ -2883,6 +2920,7 @@ check_field_decls (tree t, tree *access_decls,
     {
       tree x = *field;
       tree type = TREE_TYPE (x);
+      int this_field_access;
 
       next = &TREE_CHAIN (x);
 
@@ -2957,10 +2995,21 @@ check_field_decls (tree t, tree *access_decls,
       if (TREE_PRIVATE (x) || TREE_PROTECTED (x))
 	CLASSTYPE_NON_AGGREGATE (t) = 1;
 
+      /* A standard-layout class is a class that:
+	 ...
+	 has the same access control (Clause 11) for all non-static data members,
+         ...  */
+      this_field_access = TREE_PROTECTED (x) ? 1 : TREE_PRIVATE (x) ? 2 : 0;
+      if (field_access == -1)
+	field_access = this_field_access;
+      else if (this_field_access != field_access)
+	CLASSTYPE_NON_STD_LAYOUT (t) = 1;
+
       /* If this is of reference type, check if it needs an init.  */
       if (TREE_CODE (type) == REFERENCE_TYPE)
 	{
-	  CLASSTYPE_NON_POD_P (t) = 1;
+	  CLASSTYPE_NON_LAYOUT_POD_P (t) = 1;
+	  CLASSTYPE_NON_STD_LAYOUT (t) = 1;
 	  if (DECL_INITIAL (x) == NULL_TREE)
 	    SET_CLASSTYPE_REF_FIELDS_NEED_INIT (t, 1);
 
@@ -2975,7 +3024,7 @@ check_field_decls (tree t, tree *access_decls,
 
       if (TYPE_PACKED (t))
 	{
-	  if (!pod_type_p (type) && !TYPE_PACKED (type))
+	  if (!layout_pod_type_p (type) && !TYPE_PACKED (type))
 	    {
 	      warning
 		(0,
@@ -3024,10 +3073,13 @@ check_field_decls (tree t, tree *access_decls,
       if (DECL_MUTABLE_P (x) || TYPE_HAS_MUTABLE_P (type))
 	CLASSTYPE_HAS_MUTABLE (t) = 1;
 
-      if (! pod_type_p (type))
+      if (! layout_pod_type_p (type))
 	/* DR 148 now allows pointers to members (which are POD themselves),
 	   to be allowed in POD structs.  */
-	CLASSTYPE_NON_POD_P (t) = 1;
+	CLASSTYPE_NON_LAYOUT_POD_P (t) = 1;
+
+      if (!std_layout_type_p (type))
+	CLASSTYPE_NON_STD_LAYOUT (t) = 1;
 
       if (! zero_init_p (type))
 	CLASSTYPE_NON_ZERO_INIT_P (t) = 1;
@@ -4280,7 +4332,7 @@ type_requires_array_cookie (tree type)
 /* Check the validity of the bases and members declared in T.  Add any
    implicitly-generated functions (like copy-constructors and
    assignment operators).  Compute various flag bits (like
-   CLASSTYPE_NON_POD_T) for T.  This routine works purely at the C++
+   CLASSTYPE_NON_LAYOUT_POD_T) for T.  This routine works purely at the C++
    level: i.e., independently of the ABI in use.  */
 
 static void
@@ -4346,9 +4398,12 @@ check_bases_and_members (tree t)
      elsewhere.  */
   CLASSTYPE_NON_AGGREGATE (t)
     |= (type_has_user_provided_constructor (t) || TYPE_POLYMORPHIC_P (t));
-  CLASSTYPE_NON_POD_P (t)
+  /* This is the C++98/03 definition of POD; it changed in C++0x, but we
+     retain the old definition internally for ABI reasons.  */
+  CLASSTYPE_NON_LAYOUT_POD_P (t)
     |= (CLASSTYPE_NON_AGGREGATE (t)
 	|| saved_nontrivial_dtor || saved_complex_asn_ref);
+  CLASSTYPE_NON_STD_LAYOUT (t) |= TYPE_CONTAINS_VPTR_P (t);
   TYPE_HAS_COMPLEX_ASSIGN_REF (t) |= TYPE_CONTAINS_VPTR_P (t);
   TYPE_HAS_COMPLEX_DFLT (t) |= TYPE_CONTAINS_VPTR_P (t);
 
@@ -5031,7 +5086,7 @@ layout_class_type (tree t, tree *virtuals_p)
   /* Create the version of T used for virtual bases.  We do not use
      make_class_type for this version; this is an artificial type.  For
      a POD type, we just reuse T.  */
-  if (CLASSTYPE_NON_POD_P (t) || CLASSTYPE_EMPTY_P (t))
+  if (CLASSTYPE_NON_LAYOUT_POD_P (t) || CLASSTYPE_EMPTY_P (t))
     {
       base_t = make_node (TREE_CODE (t));
 
diff --git a/gcc/cp/cp-tree.h b/gcc/cp/cp-tree.h
index 933da1992d24619c40d8e41c18475b138d390136..6ad039ae3cf083c24bfb33a9b29d3e4748232798 100644
--- a/gcc/cp/cp-tree.h
+++ b/gcc/cp/cp-tree.h
@@ -494,6 +494,8 @@ typedef enum cp_trait_kind
   CPTK_IS_ENUM,
   CPTK_IS_POD,
   CPTK_IS_POLYMORPHIC,
+  CPTK_IS_STD_LAYOUT,
+  CPTK_IS_TRIVIAL,
   CPTK_IS_UNION
 } cp_trait_kind;
 
@@ -1124,6 +1126,7 @@ struct GTY(()) lang_type_class {
   unsigned non_aggregate : 1;
   unsigned has_complex_dflt : 1;
   unsigned has_list_ctor : 1;
+  unsigned non_std_layout : 1;
 
   /* When adding a flag here, consider whether or not it ought to
      apply to a template instance if it applies to the template.  If
@@ -1132,7 +1135,7 @@ struct GTY(()) lang_type_class {
   /* There are some bits left to fill out a 32-bit word.  Keep track
      of this by updating the size of this bitfield whenever you add or
      remove a flag.  */
-  unsigned dummy : 10;
+  unsigned dummy : 9;
 
   tree primary_base;
   VEC(tree_pair_s,gc) *vcall_indices;
@@ -1385,8 +1388,14 @@ struct GTY(()) lang_type {
 #define CLASSTYPE_HAS_MUTABLE(NODE) (LANG_TYPE_CLASS_CHECK (NODE)->has_mutable)
 #define TYPE_HAS_MUTABLE_P(NODE) (cp_has_mutable_p (NODE))
 
-/* Nonzero means that this class type is a non-POD class.  */
-#define CLASSTYPE_NON_POD_P(NODE) (LANG_TYPE_CLASS_CHECK (NODE)->non_pod_class)
+/* Nonzero means that this class type is not POD for the purpose of layout
+   (as defined in the ABI).  This is different from the language's POD.  */
+#define CLASSTYPE_NON_LAYOUT_POD_P(NODE) \
+  (LANG_TYPE_CLASS_CHECK (NODE)->non_pod_class)
+
+/* Nonzero means that this class type is a non-standard-layout class.  */
+#define CLASSTYPE_NON_STD_LAYOUT(NODE) \
+  (LANG_TYPE_CLASS_CHECK (NODE)->non_std_layout)
 
 /* Nonzero means that this class contains pod types whose default
    initialization is not a zero initialization (namely, pointers to
@@ -4877,7 +4886,12 @@ extern void stabilize_aggr_init			(tree, tree *);
 extern bool stabilize_init			(tree, tree *);
 extern tree add_stmt_to_compound		(tree, tree);
 extern void init_tree				(void);
-extern int pod_type_p				(const_tree);
+extern bool pod_type_p				(const_tree);
+extern bool layout_pod_type_p			(const_tree);
+extern bool std_layout_type_p			(const_tree);
+extern bool trivial_type_p			(const_tree);
+extern bool type_has_nontrivial_default_init	(const_tree);
+extern bool type_has_nontrivial_copy_init	(const_tree);
 extern bool class_tmpl_impl_spec_p		(const_tree);
 extern int zero_init_p				(const_tree);
 extern tree strip_typedefs			(tree);
diff --git a/gcc/cp/cxx-pretty-print.c b/gcc/cp/cxx-pretty-print.c
index b8732896aa45be1caedd9953e96924b6d773a969..0b13bc1eb8d5fef8b59630fd693331da1254eae1 100644
--- a/gcc/cp/cxx-pretty-print.c
+++ b/gcc/cp/cxx-pretty-print.c
@@ -2296,6 +2296,12 @@ pp_cxx_trait_expression (cxx_pretty_printer *pp, tree t)
     case CPTK_IS_POLYMORPHIC:
       pp_cxx_ws_string (pp, "__is_polymorphic");
       break;
+    case CPTK_IS_STD_LAYOUT:
+      pp_cxx_ws_string (pp, "__is_std_layout");
+      break;
+    case CPTK_IS_TRIVIAL:
+      pp_cxx_ws_string (pp, "__is_trivial");
+      break;
     case CPTK_IS_UNION:
       pp_cxx_ws_string (pp, "__is_union");
       break;
diff --git a/gcc/cp/decl.c b/gcc/cp/decl.c
index e1b6678ea2d037f8ddcf3f207b8b7803a98645f8..e65e6360cb6a409373a6cb34e2d408873f61e187 100644
--- a/gcc/cp/decl.c
+++ b/gcc/cp/decl.c
@@ -2473,20 +2473,28 @@ declare_local_label (tree id)
 static int
 decl_jump_unsafe (tree decl)
 {
+  /* [stmt.dcl]/3: A program that jumps from a point where a local variable
+     with automatic storage duration is not in scope to a point where it is
+     in scope is ill-formed unless the variable has scalar type, class type
+     with a trivial default constructor and a trivial destructor, a
+     cv-qualified version of one of these types, or an array of one of the
+     preceding types and is declared without an initializer (8.5).  */
+  tree type = TREE_TYPE (decl);
+
   if (TREE_CODE (decl) != VAR_DECL || TREE_STATIC (decl)
-      || TREE_TYPE (decl) == error_mark_node)
+      || type == error_mark_node)
     return 0;
 
-  if (TYPE_NEEDS_CONSTRUCTING (TREE_TYPE (decl))
+  type = strip_array_types (type);
+
+  if (type_has_nontrivial_default_init (TREE_TYPE (decl))
       || DECL_NONTRIVIALLY_INITIALIZED_P (decl))
     return 2;
 
-  if (pod_type_p (TREE_TYPE (decl)))
-    return 0;
+  if (TYPE_HAS_NONTRIVIAL_DESTRUCTOR (TREE_TYPE (decl)))
+    return 1;
 
-  /* The POD stuff is just pedantry; why should it matter if the class
-     contains a field of pointer to member type?  */
-  return 1;
+  return 0;
 }
 
 /* A subroutine of check_previous_goto_1 to identify a branch to the user.  */
@@ -2541,7 +2549,8 @@ check_previous_goto_1 (tree decl, struct cp_binding_level* level, tree names,
 	  if (problem > 1)
 	    error ("  crosses initialization of %q+#D", new_decls);
 	  else
-	    permerror (input_location, "  enters scope of non-POD %q+#D", new_decls);
+	    permerror (input_location, "  enters scope of %q+#D which has "
+		       "non-trivial destructor", new_decls);
 	}
 
       if (b == level)
@@ -2656,7 +2665,8 @@ check_goto (tree decl)
       else if (u > 1)
 	error ("  skips initialization of %q+#D", b);
       else
-	permerror (input_location, "  enters scope of non-POD %q+#D", b);
+	permerror (input_location, "  enters scope of %q+#D which has "
+		   "non-trivial destructor", b);
     }
 
   if (ent->in_try_scope)
@@ -5687,11 +5697,13 @@ cp_finish_decl (tree decl, tree init, bool init_const_expr_p,
 
   if (TREE_CODE (decl) == VAR_DECL)
     {
-      /* Only PODs can have thread-local storage.  Other types may require
-	 various kinds of non-trivial initialization.  */
-      if (DECL_THREAD_LOCAL_P (decl) && !pod_type_p (TREE_TYPE (decl)))
-	error ("%qD cannot be thread-local because it has non-POD type %qT",
-	       decl, TREE_TYPE (decl));
+      /* Only variables with trivial initialization and destruction can
+	 have thread-local storage.  */
+      if (DECL_THREAD_LOCAL_P (decl)
+	  && (type_has_nontrivial_default_init (TREE_TYPE (decl))
+	      || TYPE_HAS_NONTRIVIAL_DESTRUCTOR (TREE_TYPE (decl))))
+	error ("%qD cannot be thread-local because it has non-trivial "
+	       "type %qT", decl, TREE_TYPE (decl));
       /* If this is a local variable that will need a mangled name,
 	 register it now.  We must do this before processing the
 	 initializer for the variable, since the initialization might
diff --git a/gcc/cp/init.c b/gcc/cp/init.c
index 19b24895e55bb3b46d9ac87e2ff1cd4234806aeb..9118c61928b4c388b8d2a059e0e63446871dc3a7 100644
--- a/gcc/cp/init.c
+++ b/gcc/cp/init.c
@@ -2703,7 +2703,7 @@ build_vec_init (tree base, tree maxindex, tree init,
 	       || ! TYPE_HAS_NONTRIVIAL_DESTRUCTOR (inner_elt_type)))
 	  || from_array))
     {
-      /* Do non-default initialization of POD arrays resulting from
+      /* Do non-default initialization of trivial arrays resulting from
 	 brace-enclosed initializers.  In this case, digest_init and
 	 store_constructor will handle the semantics for us.  */
 
@@ -2769,7 +2769,7 @@ build_vec_init (tree base, tree maxindex, tree init,
 
   if (init != NULL_TREE && TREE_CODE (init) == CONSTRUCTOR)
     {
-      /* Do non-default initialization of non-POD arrays resulting from
+      /* Do non-default initialization of non-trivial arrays resulting from
 	 brace-enclosed initializers.  */
       unsigned HOST_WIDE_INT idx;
       tree elt;
diff --git a/gcc/cp/parser.c b/gcc/cp/parser.c
index 94fba02aa343cfa9e990f3b421f71db57a033624..e64d0bf7cbdcce7a8dd7831d12036b30ea2166a4 100644
--- a/gcc/cp/parser.c
+++ b/gcc/cp/parser.c
@@ -3399,6 +3399,8 @@ cp_parser_primary_expression (cp_parser *parser,
 	case RID_IS_ENUM:
 	case RID_IS_POD:
 	case RID_IS_POLYMORPHIC:
+	case RID_IS_STD_LAYOUT:
+	case RID_IS_TRIVIAL:
 	case RID_IS_UNION:
 	  return cp_parser_trait_expr (parser, token->keyword);
 
@@ -6865,6 +6867,12 @@ cp_parser_trait_expr (cp_parser* parser, enum rid keyword)
     case RID_IS_POLYMORPHIC:
       kind = CPTK_IS_POLYMORPHIC;
       break;
+    case RID_IS_STD_LAYOUT:
+      kind = CPTK_IS_STD_LAYOUT;
+      break;
+    case RID_IS_TRIVIAL:
+      kind = CPTK_IS_TRIVIAL;
+      break;
     case RID_IS_UNION:
       kind = CPTK_IS_UNION;
       break;
diff --git a/gcc/cp/semantics.c b/gcc/cp/semantics.c
index 61dff51ba7516e34417cd09e33eaaa231688409f..4473c4927b40a465baee81a89ac8e7f602a537af 100644
--- a/gcc/cp/semantics.c
+++ b/gcc/cp/semantics.c
@@ -4878,6 +4878,7 @@ trait_expr_value (cp_trait_kind kind, tree type1, tree type2)
   switch (kind)
     {
     case CPTK_HAS_NOTHROW_ASSIGN:
+      type1 = strip_array_types (type1);
       return (!CP_TYPE_CONST_P (type1) && type_code1 != REFERENCE_TYPE
 	      && (trait_expr_value (CPTK_HAS_TRIVIAL_ASSIGN, type1, type2)
 		  || (CLASS_TYPE_P (type1)
@@ -4885,8 +4886,11 @@ trait_expr_value (cp_trait_kind kind, tree type1, tree type2)
 								 true))));
 
     case CPTK_HAS_TRIVIAL_ASSIGN:
+      /* ??? The standard seems to be missing the "or array of such a class
+	 type" wording for this trait.  */
+      type1 = strip_array_types (type1);
       return (!CP_TYPE_CONST_P (type1) && type_code1 != REFERENCE_TYPE
-	      && (pod_type_p (type1)
+	      && (trivial_type_p (type1)
 		    || (CLASS_TYPE_P (type1)
 			&& TYPE_HAS_TRIVIAL_ASSIGN_REF (type1))));
 
@@ -4899,21 +4903,25 @@ trait_expr_value (cp_trait_kind kind, tree type1, tree type2)
 
     case CPTK_HAS_TRIVIAL_CONSTRUCTOR:
       type1 = strip_array_types (type1);
-      return (pod_type_p (type1)
+      return (trivial_type_p (type1)
 	      || (CLASS_TYPE_P (type1) && TYPE_HAS_TRIVIAL_DFLT (type1)));
 
     case CPTK_HAS_NOTHROW_COPY:
+      type1 = strip_array_types (type1);
       return (trait_expr_value (CPTK_HAS_TRIVIAL_COPY, type1, type2)
 	      || (CLASS_TYPE_P (type1)
 		  && classtype_has_nothrow_assign_or_copy_p (type1, false)));
 
     case CPTK_HAS_TRIVIAL_COPY:
-      return (pod_type_p (type1) || type_code1 == REFERENCE_TYPE
+      /* ??? The standard seems to be missing the "or array of such a class
+	 type" wording for this trait.  */
+      type1 = strip_array_types (type1);
+      return (trivial_type_p (type1) || type_code1 == REFERENCE_TYPE
 	      || (CLASS_TYPE_P (type1) && TYPE_HAS_TRIVIAL_INIT_REF (type1)));
 
     case CPTK_HAS_TRIVIAL_DESTRUCTOR:
       type1 = strip_array_types (type1);
-      return (pod_type_p (type1) || type_code1 == REFERENCE_TYPE
+      return (trivial_type_p (type1) || type_code1 == REFERENCE_TYPE
 	      || (CLASS_TYPE_P (type1)
 		  && TYPE_HAS_TRIVIAL_DESTRUCTOR (type1)));
 
@@ -4947,6 +4955,12 @@ trait_expr_value (cp_trait_kind kind, tree type1, tree type2)
     case CPTK_IS_POLYMORPHIC:
       return (CLASS_TYPE_P (type1) && TYPE_POLYMORPHIC_P (type1));
 
+    case CPTK_IS_STD_LAYOUT:
+      return (std_layout_type_p (type1));
+
+    case CPTK_IS_TRIVIAL:
+      return (trivial_type_p (type1));
+
     case CPTK_IS_UNION:
       return (type_code1 == UNION_TYPE);
 
@@ -4995,6 +5009,8 @@ finish_trait_expr (cp_trait_kind kind, tree type1, tree type2)
 	      || kind == CPTK_IS_ENUM
 	      || kind == CPTK_IS_POD
 	      || kind == CPTK_IS_POLYMORPHIC
+	      || kind == CPTK_IS_STD_LAYOUT
+	      || kind == CPTK_IS_TRIVIAL
 	      || kind == CPTK_IS_UNION);
 
   if (kind == CPTK_IS_CONVERTIBLE_TO)
@@ -5036,6 +5052,8 @@ finish_trait_expr (cp_trait_kind kind, tree type1, tree type2)
     case CPTK_IS_EMPTY:
     case CPTK_IS_POD:
     case CPTK_IS_POLYMORPHIC:
+    case CPTK_IS_STD_LAYOUT:
+    case CPTK_IS_TRIVIAL:
       if (!check_trait_type (type1))
 	{
 	  error ("incomplete type %qT not allowed", type1);
diff --git a/gcc/cp/tree.c b/gcc/cp/tree.c
index a003b44e9de4e74ca3f32822d8180defa78b063a..255a297de6fed37b5ea9c663c7f6ea8f3d78e161 100644
--- a/gcc/cp/tree.c
+++ b/gcc/cp/tree.c
@@ -2238,36 +2238,108 @@ is_dummy_object (const_tree ob)
 	  && TREE_OPERAND (ob, 0) == void_zero_node);
 }
 
+/* Returns 1 iff type T is something we want to treat as a scalar type for
+   the purpose of deciding whether it is trivial/POD/standard-layout.  */
+
+static bool
+scalarish_type_p (const_tree t)
+{
+  if (t == error_mark_node)
+    return 1;
+
+  return (SCALAR_TYPE_P (t)
+	  || TREE_CODE (t) == VECTOR_TYPE);
+}
+
+/* Returns true iff T requires non-trivial default initialization.  */
+
+bool
+type_has_nontrivial_default_init (const_tree t)
+{
+  t = strip_array_types (CONST_CAST_TREE (t));
+
+  if (CLASS_TYPE_P (t))
+    return TYPE_HAS_COMPLEX_DFLT (t);
+  else
+    return 0;
+}
+
+/* Returns true iff copying an object of type T is non-trivial.  */
+
+bool
+type_has_nontrivial_copy_init (const_tree t)
+{
+  t = strip_array_types (CONST_CAST_TREE (t));
+
+  if (CLASS_TYPE_P (t))
+    return TYPE_HAS_COMPLEX_INIT_REF (t);
+  else
+    return 0;
+}
+
+/* Returns 1 iff type T is a trivial type, as defined in [basic.types].  */
+
+bool
+trivial_type_p (const_tree t)
+{
+  t = strip_array_types (CONST_CAST_TREE (t));
+
+  if (CLASS_TYPE_P (t))
+    return !(TYPE_HAS_COMPLEX_DFLT (t)
+	     || TYPE_HAS_COMPLEX_INIT_REF (t)
+	     || TYPE_HAS_COMPLEX_ASSIGN_REF (t)
+	     || TYPE_HAS_NONTRIVIAL_DESTRUCTOR (t));
+  else
+    return scalarish_type_p (t);
+}
+
 /* Returns 1 iff type T is a POD type, as defined in [basic.types].  */
 
-int
+bool
 pod_type_p (const_tree t)
 {
   /* This CONST_CAST is okay because strip_array_types returns its
      argument unmodified and we assign it to a const_tree.  */
   t = strip_array_types (CONST_CAST_TREE(t));
 
-  if (t == error_mark_node)
-    return 1;
-  if (INTEGRAL_OR_ENUMERATION_TYPE_P (t))
-    return 1;  /* integral, character or enumeral type */
-  if (FLOAT_TYPE_P (t))
-    return 1;
-  if (TYPE_PTR_P (t))
-    return 1; /* pointer to non-member */
-  if (TYPE_PTR_TO_MEMBER_P (t))
-    return 1; /* pointer to member */
-
-  if (TREE_CODE (t) == VECTOR_TYPE)
-    return 1; /* vectors are (small) arrays of scalars */
-
-  if (! RECORD_OR_UNION_CODE_P (TREE_CODE (t)))
-    return 0; /* other non-class type (reference or function) */
-  if (! CLASS_TYPE_P (t))
-    return 1; /* struct created by the back end */
-  if (CLASSTYPE_NON_POD_P (t))
-    return 0;
-  return 1;
+  if (CLASS_TYPE_P (t))
+    /* [class]/10: A POD struct is a class that is both a trivial class and a
+       standard-layout class, and has no non-static data members of type
+       non-POD struct, non-POD union (or array of such types).
+
+       We don't need to check individual members because if a member is
+       non-std-layout or non-trivial, the class will be too.  */
+    return (std_layout_type_p (t) && trivial_type_p (t));
+  else
+    return scalarish_type_p (t);
+}
+
+/* Returns true iff T is POD for the purpose of layout, as defined in the
+   C++ ABI.  */
+
+bool
+layout_pod_type_p (const_tree t)
+{
+  t = strip_array_types (CONST_CAST_TREE (t));
+
+  if (CLASS_TYPE_P (t))
+    return !CLASSTYPE_NON_LAYOUT_POD_P (t);
+  else
+    return scalarish_type_p (t);
+}
+
+/* Returns true iff T is a standard-layout type, as defined in
+   [basic.types].  */
+
+bool
+std_layout_type_p (const_tree t)
+{
+  t = strip_array_types (CONST_CAST_TREE (t));
+
+  if (CLASS_TYPE_P (t))
+    return !CLASSTYPE_NON_STD_LAYOUT (t);
+  else
+    return scalarish_type_p (t);
 }
 
 /* Nonzero iff type T is a class template implicit specialization.  */
diff --git a/gcc/cp/typeck.c b/gcc/cp/typeck.c
index 6a4802e3375d5d44d6084e7d1dbbb0e5f4b49784..9e49ce58b4bc1525b816266706a9e77610ce48cc 100644
--- a/gcc/cp/typeck.c
+++ b/gcc/cp/typeck.c
@@ -2017,7 +2017,7 @@ build_class_member_access_expr (tree object, tree member,
 	 in various testsuite cases where a null object is passed where a
 	 vtable access is required.  */
       if (null_object_p && warn_invalid_offsetof
-	  && CLASSTYPE_NON_POD_P (object_type)
+	  && CLASSTYPE_NON_STD_LAYOUT (object_type)
 	  && !DECL_FIELD_IS_BASE (member)
 	  && cp_unevaluated_operand == 0
 	  && (complain & tf_warning))
@@ -3134,7 +3134,7 @@ convert_arguments (tree typelist, VEC(tree,gc) **values, tree fndecl,
 	  if (fndecl && DECL_BUILT_IN (fndecl)
 	      && DECL_FUNCTION_CODE (fndecl) == BUILT_IN_CONSTANT_P)
 	    /* Don't do ellipsis conversion for __built_in_constant_p
-	       as this will result in spurious warnings for non-POD
+	       as this will result in spurious errors for non-trivial
 	       types.  */
 	    val = require_complete_type (val);
 	  else
diff --git a/gcc/doc/gcc.texi b/gcc/doc/gcc.texi
index 41031752bf2c47cd635a39f7a0df95359a524a90..34b896340337b213446e867a03e4074d5cbc0d8b 100644
--- a/gcc/doc/gcc.texi
+++ b/gcc/doc/gcc.texi
@@ -134,6 +134,7 @@ Introduction, gccint, GNU Compiler Collection (GCC) Internals}.
 * Invoking GCC::    Command options supported by @samp{gcc}.
 * C Implementation:: How GCC implements the ISO C specification.
 * C Extensions::    GNU extensions to the C language family.
+* C++ Implementation:: How GCC implements the ISO C++ specification.
 * C++ Extensions::  GNU extensions to the C++ language.
 * Objective-C::     GNU Objective-C runtime features.
 * Compatibility::   Binary Compatibility
@@ -159,6 +160,7 @@ Introduction, gccint, GNU Compiler Collection (GCC) Internals}.
 @include standards.texi
 @include invoke.texi
 @include implement-c.texi
+@include implement-cxx.texi
 @include extend.texi
 @include objc.texi
 @include compat.texi
diff --git a/gcc/doc/implement-cxx.texi b/gcc/doc/implement-cxx.texi
new file mode 100644
index 0000000000000000000000000000000000000000..9968f592473e96a5841a3a1602ee9833e512331a
--- /dev/null
+++ b/gcc/doc/implement-cxx.texi
@@ -0,0 +1,47 @@
+@c Copyright (C) 2009
+@c Free Software Foundation, Inc.
+@c This is part of the GCC manual.
+@c For copying conditions, see the file gcc.texi.
+
+@node C++ Implementation
+@chapter C++ Implementation-defined behavior
+@cindex implementation-defined behavior, C++ language
+
+A conforming implementation of ISO C++ is required to document its
+choice of behavior in each of the areas that are designated
+``implementation defined''.  The following lists all such areas,
+along with the section numbers from the ISO/IEC 14822:1998 and ISO/IEC
+14822:2003 standards.  Some areas are only implementation-defined in
+one version of the standard.
+
+Some choices depend on the externally determined ABI for the platform
+(including standard character encodings) which GCC follows; these are
+listed as ``determined by ABI'' below.  @xref{Compatibility, , Binary
+Compatibility}, and @uref{http://gcc.gnu.org/readings.html}.  Some
+choices are documented in the preprocessor manual.
+@xref{Implementation-defined behavior, , Implementation-defined
+behavior, cpp, The C Preprocessor}.  Some choices are documented in
+the corresponding document for the C language.  @xref{C
+Implementation}.  Some choices are made by the library and operating
+system (or other environment when compiling for a freestanding
+environment); refer to their documentation for details.
+
+@menu
+* Conditionally-supported behavior::
+@end menu
+
+@node Conditionally-supported behavior
+@section Conditionally-supported behavior
+
+@cite{Each implementation shall include documentation that identifies
+all conditionally-supported constructs that it does not support (C++0x
+1.4).}
+
+@itemize @bullet
+@item
+@cite{Whether an argument of class type with a non-trivial copy
+constructor or destructor can be passed to ... (C++0x 5.2.2).}
+
+Such argument passing is not supported.
+
+@end itemize
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 989f5772fab0064b06654960d2a88afe710201eb..7ab159ad5cec36400771a776204d0e8c73971362 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,21 @@
+2009-07-16  Jason Merrill  <jason@redhat.com>
+
+	PR libstdc++/37907
+	* g++.dg/cpp0x/std-layout1.C: New.
+	* g++.dg/ext/has_nothrow_assign.C: Fix.
+	* g++.dg/ext/has_nothrow_copy.C: Fix.
+	* g++.dg/ext/has_trivial_assign.C: Fix.
+	* g++.dg/ext/has_trivial_copy.C: Fix.
+	* g++.dg/ext/is_pod.C: Fix.
+	* g++.dg/other/offsetof3.C: Adjust.
+	* g++.dg/overload/ellipsis1.C: Adjust.
+	* g++.dg/warn/var-args1.C: Adjust.
+	* g++.old-deja/g++.brendan/crash63.C: Adjust.
+	* g++.old-deja/g++.brendan/crash64.C: Adjust.
+	* g++.old-deja/g++.brendan/overload8.C: Adjust.
+	* g++.old-deja/g++.other/vaarg3.C: Adjust.
+	* g++.old-deja/g++.pt/vaarg3.C: Adjust.
+
 2009-07-16  Kaveh R. Ghazi  <ghazi@caip.rutgers.edu>
 
 	* gcc.dg/torture/builtin-math-5.c: Add more cases.
diff --git a/gcc/testsuite/g++.dg/cpp0x/std-layout1.C b/gcc/testsuite/g++.dg/cpp0x/std-layout1.C
new file mode 100644
index 0000000000000000000000000000000000000000..bdad8211145ef121960fa8ce00ec30c2eb53b480
--- /dev/null
+++ b/gcc/testsuite/g++.dg/cpp0x/std-layout1.C
@@ -0,0 +1,91 @@
+// { dg-options "-std=c++0x" }
+
+// [basic.types]/10:
+// Scalar types, standard-layout class types (Clause 9), arrays of such
+// types and cv-qualified versions of these types (3.9.3) are collectively
+// called standard-layout types.
+
+// [class]/7:
+// A standard-layout class is a class that:
+// * has no non-static data members of type non-standard-layout class (or
+// array of such types) or reference,
+// * has no virtual functions (10.3) and no virtual base classes (10.1),
+// * has the same access control (Clause 11) for all non-static data members,
+// * has no non-standard-layout base classes,
+// * either has no non-static data members in the most-derived class and at
+// most one base class with non-static data members, or has no base classes
+// with non-static data members, and
+// * has no base classes of the same type as the first non-static data member.
+
+#include <type_traits>
+
+#define TRY(expr) static_assert (expr, #expr)
+#define YES(type) TRY(std::is_standard_layout<type>::value); \
+  TRY(std::is_standard_layout<type[]>::value); \
+  TRY(std::is_standard_layout<const volatile type>::value);
+#define NO(type) TRY(!std::is_standard_layout<type>::value); \
+  TRY(!std::is_standard_layout<type[]>::value); \
+  TRY(!std::is_standard_layout<const volatile type>::value);
+#define NONPOD(type) TRY(!std::is_pod<type>::value); \
+  TRY(!std::is_pod<type[]>::value); \
+  TRY(!std::is_pod<const volatile type>::value);
+
+struct A;
+
+YES(int);
+YES(__complex int);
+YES(void *);
+YES(int A::*);
+typedef int (A::*pmf)();
+YES(pmf);
+
+struct A { ~A(); };
+YES(A);
+NONPOD(A);
+struct F: public A { int i; };
+YES(F);
+NONPOD(F);
+struct G: public A { A a; };
+NO(G);
+struct M { A a; };
+YES(M);
+
+class B
+{
+  int i;
+  __complex int c;
+  void *p;
+  double ar[4];
+  int A::* pm;
+  int (A::*pmf)();
+};
+YES(B);
+struct D: public B { };
+YES(D);
+struct E: public B { int q; };
+NO(E);
+struct D2: public B { };
+YES(D2);
+struct I: public D, public D2 { };
+NO(I);
+
+struct C
+{
+  int i;
+private:
+  int j;
+};
+NO(C);
+struct H: public C { };
+NO(H);
+struct N { C c; };
+NO(N);
+
+struct J { virtual void f(); };
+struct J2: J { };
+NO(J);
+NO(J2);
+struct K { };
+struct L: virtual K {};
+YES(K);
+NO(L);
diff --git a/gcc/testsuite/g++.dg/cpp0x/trivial1.C b/gcc/testsuite/g++.dg/cpp0x/trivial1.C
new file mode 100644
index 0000000000000000000000000000000000000000..62173ac0caf128f60058a1ff2b3dc752c5411abd
--- /dev/null
+++ b/gcc/testsuite/g++.dg/cpp0x/trivial1.C
@@ -0,0 +1,82 @@
+// { dg-options "-std=c++0x" }
+
+// [basic.types]/10:
+// Scalar types, trivial class types (Clause 9), arrays of such types and
+// cv-qualified versions of these types (3.9.3) are collectively called
+// trivial types.
+
+// [class]/6:
+// A trivially copyable class is a class that:
+// * has no non-trivial copy constructors (12.8),
+// * has no non-trivial copy assignment operators (13.5.3, 12.8), and
+// * has a trivial destructor (12.4).
+// A trivial class is a class that has a trivial default constructor (12.1)
+// and is trivially copyable.
+
+#include <type_traits>
+
+#define TRY(expr) static_assert (expr, #expr)
+#define YES(type) TRY(std::is_trivial<type>::value); \
+  TRY(std::is_trivial<type[]>::value); \
+  TRY(std::is_trivial<const volatile type>::value);
+#define NO(type) TRY(!std::is_trivial<type>::value); \
+  TRY(!std::is_trivial<type[]>::value); \
+  TRY(!std::is_trivial<const volatile type>::value);
+
+struct A;
+
+YES(int);
+YES(__complex int);
+YES(void *);
+YES(int A::*);
+typedef int (A::*pmf)();
+YES(pmf);
+
+struct A { ~A(); };
+NO(A);
+struct F: public A { int i; };
+NO(F);
+struct G: public A { A a; };
+NO(G);
+struct M { A a; };
+NO(M);
+
+class B
+{
+  int i;
+  __complex int c;
+  void *p;
+  double ar[4];
+  int A::* pm;
+  int (A::*pmf)();
+};
+YES(B);
+struct D: public B { };
+YES(D);
+struct E: public B { int q; };
+YES(E);
+struct D2: public B { };
+YES(D2);
+struct I: public D, public D2 { };
+YES(I);
+
+struct C
+{
+  int i;
+private:
+  int j;
+};
+YES(C);
+struct H: public C { };
+YES(H);
+struct N { C c; };
+YES(N);
+
+struct J { virtual void f(); };
+struct J2: J { };
+NO(J);
+NO(J2);
+struct K { };
+struct L: virtual K {};
+YES(K);
+NO(L);
diff --git a/gcc/testsuite/g++.dg/ext/has_nothrow_assign.C b/gcc/testsuite/g++.dg/ext/has_nothrow_assign.C
index 73a904eac25761c9e8ff856d7b3cd3f7d70e8146..f3b4a8b2556dec36620d3035cfe9a7f4f4b2fd0c 100644
--- a/gcc/testsuite/g++.dg/ext/has_nothrow_assign.C
+++ b/gcc/testsuite/g++.dg/ext/has_nothrow_assign.C
@@ -134,7 +134,7 @@ int main()
   assert (PTEST (A));
   assert (PTEST (B));
   assert (PTEST (C));
-  assert (NTEST (C[]));
+  assert (PTEST (C[]));
   assert (PTEST (D));
   assert (NTEST (E));
   assert (NTEST (E1));
diff --git a/gcc/testsuite/g++.dg/ext/has_nothrow_copy-1.C b/gcc/testsuite/g++.dg/ext/has_nothrow_copy-1.C
index e8507cf582c4b152de647938736e9d6599d5c2bf..056c9be61f666139c486f6243983379a398b9f7c 100644
--- a/gcc/testsuite/g++.dg/ext/has_nothrow_copy-1.C
+++ b/gcc/testsuite/g++.dg/ext/has_nothrow_copy-1.C
@@ -124,7 +124,7 @@ int main()
   assert (PTEST (A));
   assert (PTEST (B));
   assert (PTEST (C));
-  assert (NTEST (C[]));
+  assert (PTEST (C[]));
   assert (PTEST (D));
   assert (NTEST (E));
   assert (NTEST (E1));
diff --git a/gcc/testsuite/g++.dg/ext/has_trivial_assign.C b/gcc/testsuite/g++.dg/ext/has_trivial_assign.C
index 97bcbf239974ac017255e008d2fe2bbceec280cf..46d8c34bb3f76220eb25025d890e6cc1ac6c2bad 100644
--- a/gcc/testsuite/g++.dg/ext/has_trivial_assign.C
+++ b/gcc/testsuite/g++.dg/ext/has_trivial_assign.C
@@ -96,7 +96,7 @@ int main()
   assert (NTEST (C));
   assert (NTEST (D));
   assert (PTEST (E));
-  assert (NTEST (E[]));
+  assert (PTEST (E[]));
   assert (PTEST (F));
   assert (NTEST (G));
   assert (NTEST (const A));
diff --git a/gcc/testsuite/g++.dg/ext/has_trivial_copy.C b/gcc/testsuite/g++.dg/ext/has_trivial_copy.C
index ca2eeec4bdb888e3a106298ebcf5e80d98ac3f70..4b8cc1541477c7966c5c4e4cea5bb8ec96ee5cb4 100644
--- a/gcc/testsuite/g++.dg/ext/has_trivial_copy.C
+++ b/gcc/testsuite/g++.dg/ext/has_trivial_copy.C
@@ -96,7 +96,7 @@ int main()
   assert (NTEST (C));
   assert (NTEST (D));
   assert (PTEST (E));
-  assert (NTEST (E[]));
+  assert (PTEST (E[]));
   assert (PTEST (F));
   assert (NTEST (G));
   assert (PTEST (B&));
diff --git a/gcc/testsuite/g++.dg/ext/is_pod.C b/gcc/testsuite/g++.dg/ext/is_pod.C
index 5c1f0cd3bcd289ea1050b3eaad4f5c10cae37f5c..c984283a0e93c0b95d2169fd0fb1b081dd215c53 100644
--- a/gcc/testsuite/g++.dg/ext/is_pod.C
+++ b/gcc/testsuite/g++.dg/ext/is_pod.C
@@ -68,8 +68,8 @@ int main()
   assert (PTEST (A));
   assert (PTEST (A[]));
   assert (NTEST (B));
-  assert (NTEST (C));
-  assert (NTEST (C[]));
+  assert (PTEST (C));
+  assert (PTEST (C[]));
 
   return 0;
 }
diff --git a/gcc/testsuite/g++.dg/other/offsetof3.C b/gcc/testsuite/g++.dg/other/offsetof3.C
index 1e83af980718ed7eaf4d31f711a0a33c21975c91..5946c812ced7a983857c64c9a678fe7be8e7605d 100644
--- a/gcc/testsuite/g++.dg/other/offsetof3.C
+++ b/gcc/testsuite/g++.dg/other/offsetof3.C
@@ -1,16 +1,17 @@
-/* Verify that offsetof warns if given a non-POD */
+/* Verify that offsetof warns if given a non-standard-layout class */
 /* Copyright (C) 2003 Free Software Foundation, Inc. */
 /* Contributed by Matt Austern <austern@apple.com> 15 May 2003 */
 /* { dg-do compile } */
 
 struct X
 {
-  X() : x(3), y(4) { }
   int x, y;
+protected:
+  int z;
 };
 
 typedef X* pX;
 typedef __SIZE_TYPE__ size_t;
 
 size_t yoff = size_t(&(pX(0)->y)); /* { dg-warning "invalid access" "" } */
-/* { dg-warning "macro was used incorrectly" "macro" { target *-*-* } 15 } */
+/* { dg-warning "macro was used incorrectly" "macro" { target *-*-* } 16 } */
diff --git a/gcc/testsuite/g++.dg/overload/ellipsis1.C b/gcc/testsuite/g++.dg/overload/ellipsis1.C
index bdd3cd2311ba1a2a8f8096b306bc2beb12c932e8..3dedaa6be4a83c376349e6f5fe008e8388198957 100644
--- a/gcc/testsuite/g++.dg/overload/ellipsis1.C
+++ b/gcc/testsuite/g++.dg/overload/ellipsis1.C
@@ -1,9 +1,6 @@
 // PR c++/15142
 // Bug: We were aborting after giving a warning about passing a non-POD.
 
-// Suppress the warning about undefined behavior.
-// { dg-options "-w" }
-
 struct B { 
     B() throw() { } 
     B(const B&) throw() { } 
@@ -17,5 +14,5 @@ struct X {
 struct S { S(...); }; 
  
 void SillyFunc() { 
-  throw S(X()); 
+  throw S(X()); 		// { dg-error "copy" }
 } 
diff --git a/gcc/testsuite/g++.dg/warn/var-args1.C b/gcc/testsuite/g++.dg/warn/var-args1.C
index aadac20e84a990c75a2d8985375fce7e762a1225..9bd84a7dd55ae934e03288cd3f7c9da45699df28 100644
--- a/gcc/testsuite/g++.dg/warn/var-args1.C
+++ b/gcc/testsuite/g++.dg/warn/var-args1.C
@@ -6,6 +6,6 @@ void foo(int, ...)
 {
     va_list va;
     int i;
-    i = va_arg(va, int&); /* { dg-warning "cannot receive objects" } */
+    i = va_arg(va, int&); /* { dg-error "cannot receive objects" } */
 }
 
diff --git a/gcc/testsuite/g++.old-deja/g++.brendan/crash63.C b/gcc/testsuite/g++.old-deja/g++.brendan/crash63.C
index 13f8339b3421012d0b4d64c99e45e6682eed9674..89685fcaeb5496e2fb0659dd15209a90377e64d2 100644
--- a/gcc/testsuite/g++.old-deja/g++.brendan/crash63.C
+++ b/gcc/testsuite/g++.old-deja/g++.brendan/crash63.C
@@ -4,6 +4,7 @@ class String
    {
  public:
    String (const char *str);
+   String (const String&);
    };
 
 class UnitList 
@@ -12,4 +13,4 @@ class UnitList
    UnitList (...);
    };
 
-UnitList unit_list (String("keV")); // { dg-warning "" } cannot pass non-pod
+UnitList unit_list (String("keV")); // { dg-error "" } cannot pass non-pod
diff --git a/gcc/testsuite/g++.old-deja/g++.brendan/crash64.C b/gcc/testsuite/g++.old-deja/g++.brendan/crash64.C
index 6046cb1c9ee2b814138a208e1154708b50ac388d..3c98692833176240e9e7ba39455465474a3df845 100644
--- a/gcc/testsuite/g++.old-deja/g++.brendan/crash64.C
+++ b/gcc/testsuite/g++.old-deja/g++.brendan/crash64.C
@@ -16,4 +16,4 @@ struct metatype { int base_list; };
 
 static _type_desc _type_metatype("metatype", sizeof(metatype),
   (RF_Ptr)0, 0, 1, 1,
-  _im_pers_mem_spec( ((size_t)&((( metatype *)0)-> base_list )) , 1)); // { dg-warning "" } cannot pass non-pod
+  _im_pers_mem_spec( ((size_t)&((( metatype *)0)-> base_list )) , 1));
diff --git a/gcc/testsuite/g++.old-deja/g++.brendan/overload8.C b/gcc/testsuite/g++.old-deja/g++.brendan/overload8.C
index fc1b23b75b4b0530204ce615b971ea2db72cd85d..bf129b02c2b03309d22f0de42d4d70722b732f0c 100644
--- a/gcc/testsuite/g++.old-deja/g++.brendan/overload8.C
+++ b/gcc/testsuite/g++.old-deja/g++.brendan/overload8.C
@@ -6,4 +6,4 @@ class Complex{public:double re,im;
 void zxcvbnm(int n,...){n=1;}
 int main(){complex c; Complex C;
 zxcvbnm(1,c);
-zxcvbnm(1,C);} // { dg-warning "" } cannot pass non pod
+zxcvbnm(1,C);}
diff --git a/gcc/testsuite/g++.old-deja/g++.other/vaarg3.C b/gcc/testsuite/g++.old-deja/g++.other/vaarg3.C
index f852b08ce5ab23dd11a617a619980b850d4df854..3408a1811885da9172432d7040f1b692e87a4904 100644
--- a/gcc/testsuite/g++.old-deja/g++.other/vaarg3.C
+++ b/gcc/testsuite/g++.old-deja/g++.other/vaarg3.C
@@ -9,14 +9,14 @@
 #include <stdarg.h>
 
 struct X {int m;};
-struct Y : X {int m;};
+struct Y { Y(const Y&); };
 struct Z;   // { dg-error "forward decl" } 
 void fn1(va_list args)
 {
   int i = va_arg (args, int);
-  Y x = va_arg (args, Y);         // { dg-warning "cannot receive" } 
-  Y y = va_arg (args, struct Y);  // { dg-warning "cannot receive" } 
-  int &r = va_arg (args, int &);  // { dg-warning "cannot receive" } 
+  Y x = va_arg (args, Y);         // { dg-error "cannot receive" }
+  Y y = va_arg (args, struct Y);  // { dg-error "cannot receive" }
+  int &r = va_arg (args, int &);  // { dg-error "cannot receive" }
   
   Z z1 = va_arg (args, Z);        // { dg-error "incomplete" } 
   const Z &z2 = va_arg (args, Z);       // { dg-error "incomplete" } 
@@ -25,7 +25,8 @@ void fn1(va_list args)
   // { dg-message "should pass" "pass" { target *-*-* } 24 }
   // { dg-message "abort" "abort" { target *-*-* } 24 }
   va_arg (args, int []);  // { dg-error "array with unspecified bounds" } promote
-  va_arg (args, int ());  // { dg-warning "non-POD" } promote
+  va_arg (args, int ());  // { dg-warning "promoted" } promote
+  // { dg-message "abort" "abort" { target *-*-* } 28 }
   va_arg (args, bool);    // { dg-warning "promote" "promote" } 
-  // { dg-message "abort" "abort" { target *-*-* } 29 }
+  // { dg-message "abort" "abort" { target *-*-* } 30 }
 }
diff --git a/gcc/testsuite/g++.old-deja/g++.pt/vaarg3.C b/gcc/testsuite/g++.old-deja/g++.pt/vaarg3.C
index dced89d17ab85a80c45674db643548638f2d2811..07fb18d77d898d37566b275c141a923970719d26 100644
--- a/gcc/testsuite/g++.old-deja/g++.pt/vaarg3.C
+++ b/gcc/testsuite/g++.old-deja/g++.pt/vaarg3.C
@@ -14,14 +14,14 @@ void PrintArgs (Type somearg, ...)
 va_list argp;
 va_start (argp, somearg);
 Type value;
-value = va_arg (argp, Type); // { dg-warning "non-POD" } cannot pass non-POD
+value = va_arg (argp, Type); // { dg-error "cannot receive" } cannot pass non-POD
 va_end (argp);
 }
 
 int main (void)
 {
 A dummy;
-PrintArgs (dummy, dummy); // { dg-warning "non-POD" } cannot pass non-POD
+PrintArgs (dummy, dummy); // { dg-error "cannot pass" } cannot pass non-POD
 // { dg-message "instantiated" "inst" { target *-*-* } 24 }
 return 0;
 }
diff --git a/libstdc++-v3/ChangeLog b/libstdc++-v3/ChangeLog
index 39b9749553ecc82c91d4b440f8a25c710a63180f..60c1c3fe3ad00bef0f23e026748a8acd065eb620 100644
--- a/libstdc++-v3/ChangeLog
+++ b/libstdc++-v3/ChangeLog
@@ -1,3 +1,11 @@
+2009-07-16  Jason Merrill  <jason@redhat.com>
+
+	PR libstdc++/37907
+	* include/std/type_traits: Add is_standard_layout, is_trivial.
+	* testsuite/20_util/make_signed/requirements/typedefs_neg.cc,
+	testsuite/20_util/make_unsigned/requirements/typedefs_neg.cc:
+	Update line numbers.
+
 2009-07-16  Phil Muldoon <pmuldoon@redhat.com>
 	    Tom Tromey <tromey@redhat.com>
 
diff --git a/libstdc++-v3/include/std/type_traits b/libstdc++-v3/include/std/type_traits
index 94c40df97b8f7e659d3275d0160fa86c9d158408..dd26bb84dbfff7f057c7916f47cda49f23d50361 100644
--- a/libstdc++-v3/include/std/type_traits
+++ b/libstdc++-v3/include/std/type_traits
@@ -173,11 +173,18 @@ namespace std
   // Member introspection.
 
   /// is_pod
+  // Could use is_standard_layout && is_trivial instead of the builtin.
   template<typename _Tp>
     struct is_pod
     : public integral_constant<bool, __is_pod(_Tp)>
     { };
 
+  /// is_standard_layout
+  template<typename _Tp>
+    struct is_standard_layout
+    : public integral_constant<bool, __is_standard_layout(_Tp)>
+    { };
+
   /// has_trivial_default_constructor
   template<typename _Tp>
     struct has_trivial_default_constructor
@@ -202,6 +209,12 @@ namespace std
     : public integral_constant<bool, __has_trivial_destructor(_Tp)>
     { };
 
+  /// is_trivial
+  template<typename _Tp>
+    struct is_trivial
+    : public integral_constant<bool, __is_trivial(_Tp)>
+    { };
+
   /// has_nothrow_default_constructor
   template<typename _Tp>
     struct has_nothrow_default_constructor
diff --git a/libstdc++-v3/testsuite/20_util/make_signed/requirements/typedefs_neg.cc b/libstdc++-v3/testsuite/20_util/make_signed/requirements/typedefs_neg.cc
index ca7ee97af0ce06c0d1c00818bb211f8db680c398..3455462869b0273474b3e79833b7b66dc2aa0e9f 100644
--- a/libstdc++-v3/testsuite/20_util/make_signed/requirements/typedefs_neg.cc
+++ b/libstdc++-v3/testsuite/20_util/make_signed/requirements/typedefs_neg.cc
@@ -48,8 +48,8 @@ void test01()
 // { dg-error "instantiated from here" "" { target *-*-* } 40 }
 // { dg-error "instantiated from here" "" { target *-*-* } 42 }
 
-// { dg-error "invalid use of incomplete type" "" { target *-*-* } 557 }
-// { dg-error "declaration of" "" { target *-*-* } 519 }
+// { dg-error "invalid use of incomplete type" "" { target *-*-* } 570 }
+// { dg-error "declaration of" "" { target *-*-* } 532 }
 
 // { dg-excess-errors "At global scope" }
 // { dg-excess-errors "In instantiation of" }
diff --git a/libstdc++-v3/testsuite/20_util/make_unsigned/requirements/typedefs_neg.cc b/libstdc++-v3/testsuite/20_util/make_unsigned/requirements/typedefs_neg.cc
index ac9fef16e778e3d50750a4894e26e8cd44902059..3d3a10a9ba8ee245d8baba5e039fb9f983f8c04e 100644
--- a/libstdc++-v3/testsuite/20_util/make_unsigned/requirements/typedefs_neg.cc
+++ b/libstdc++-v3/testsuite/20_util/make_unsigned/requirements/typedefs_neg.cc
@@ -48,8 +48,8 @@ void test01()
 // { dg-error "instantiated from here" "" { target *-*-* } 40 }
 // { dg-error "instantiated from here" "" { target *-*-* } 42 }
 
-// { dg-error "invalid use of incomplete type" "" { target *-*-* } 478 }
-// { dg-error "declaration of" "" { target *-*-* } 440 }
+// { dg-error "invalid use of incomplete type" "" { target *-*-* } 491 }
+// { dg-error "declaration of" "" { target *-*-* } 453 }
 
 // { dg-excess-errors "At global scope" }
 // { dg-excess-errors "In instantiation of" }