diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index d1e06e7d82236ce9fd34e02805748f7a7f0196e1..16c3403e0de42258b02c120e414c13d59075bcd8 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,19 @@
+2004-11-23  Daniel Jacobowitz  <dan@codesourcery.com>
+            Joseph Myers  <joseph@codesourcery.com>
+
+	* config/sol2-c.c (solaris_register_pragmas): Use
+	c_register_pragma_with_expansion.
+	* config/sol2.h (HANDLE_PRAGMA_PACK_WITH_EXPANSION): Define.
+	* c-pragma.c (c_register_pragma): Update call to
+	cpp_register_pragma.
+	(c_register_pragma_with_expansion): New function.
+	(init_pragma): Honor HANDLE_PRAGMA_PACK_WITH_EXPANSION.
+	* c-pragma.h (c_register_pragma_with_expansion): New prototype.
+	* doc/extend.texi (Solaris Pragmas): Mention macro expansion for
+	#pragma align.
+	* doc/tm.texi (c_register_pragma_with_expansion,
+	HANDLE_PRAGMA_PACK_WITH_EXPANSION): Document.
+
 2004-11-23  Richard Henderson  <rth@redhat.com>
 
 	* emit-rtl.c, rtl.h (subreg_hard_regno): Remove.
diff --git a/gcc/c-pragma.c b/gcc/c-pragma.c
index 24c166658b4e58797e5427725a7ccb966492597a..91efc4aa384c70d7fc0f2f722018d87cca4370d8 100644
--- a/gcc/c-pragma.c
+++ b/gcc/c-pragma.c
@@ -627,13 +627,20 @@ handle_pragma_visibility (cpp_reader *dummy ATTRIBUTE_UNUSED)
 
 #endif
 
-/* Front-end wrapper for pragma registration to avoid dragging
+/* Front-end wrappers for pragma registration to avoid dragging
    cpplib.h in almost everywhere.  */
 void
 c_register_pragma (const char *space, const char *name,
 		   void (*handler) (struct cpp_reader *))
 {
-  cpp_register_pragma (parse_in, space, name, handler);
+  cpp_register_pragma (parse_in, space, name, handler, 0);
+}
+
+void
+c_register_pragma_with_expansion (const char *space, const char *name,
+				  void (*handler) (struct cpp_reader *))
+{
+  cpp_register_pragma (parse_in, space, name, handler, 1);
 }
 
 /* Set up front-end pragmas.  */
@@ -641,8 +648,12 @@ void
 init_pragma (void)
 {
 #ifdef HANDLE_PRAGMA_PACK
+#ifdef HANDLE_PRAGMA_PACK_WITH_EXPANSION
+  c_register_pragma_with_expansion (0, "pack", handle_pragma_pack);
+#else
   c_register_pragma (0, "pack", handle_pragma_pack);
 #endif
+#endif
 #ifdef HANDLE_PRAGMA_WEAK
   c_register_pragma (0, "weak", handle_pragma_weak);
 #endif
diff --git a/gcc/c-pragma.h b/gcc/c-pragma.h
index 92741ff5cb57304765dd227d6667b275b3fa57dd..669d122e695e4cec906906cbb5dcef2537d73496 100644
--- a/gcc/c-pragma.h
+++ b/gcc/c-pragma.h
@@ -53,10 +53,12 @@ extern struct cpp_reader* parse_in;
 
 extern void init_pragma (void);
 
-/* Front-end wrapper for pragma registration to avoid dragging
+/* Front-end wrappers for pragma registration to avoid dragging
    cpplib.h in almost everywhere.  */
 extern void c_register_pragma (const char *, const char *,
 			       void (*) (struct cpp_reader *));
+extern void c_register_pragma_with_expansion (const char *, const char *,
+					      void (*) (struct cpp_reader *));
 extern void maybe_apply_pragma_weak (tree);
 extern tree maybe_apply_renaming_pragma (tree, tree);
 extern void add_to_renaming_pragma_list (tree, tree);
diff --git a/gcc/config/sol2-c.c b/gcc/config/sol2-c.c
index 616448413c88a81d2ba8e68cf0fb1e8e7b1e0078..784d20b2c7a2208efdb017b1f67fe315af38a8af 100644
--- a/gcc/config/sol2-c.c
+++ b/gcc/config/sol2-c.c
@@ -266,7 +266,7 @@ solaris_pragma_fini (cpp_reader *pfile ATTRIBUTE_UNUSED)
 void
 solaris_register_pragmas (void)
 {
-  c_register_pragma (0, "align", solaris_pragma_align);
+  c_register_pragma_with_expansion (0, "align", solaris_pragma_align);
   c_register_pragma (0, "init", solaris_pragma_init);
   c_register_pragma (0, "fini", solaris_pragma_fini);
 }
diff --git a/gcc/config/sol2.h b/gcc/config/sol2.h
index 86d359c178bd77efaf995d13afb85294fe0434dd..1aa6aa84f44d8151358818c01774f835b7552944 100644
--- a/gcc/config/sol2.h
+++ b/gcc/config/sol2.h
@@ -245,3 +245,6 @@ __enable_execute_stack (void *addr)					\
 extern GTY(()) tree solaris_pending_aligns;
 extern GTY(()) tree solaris_pending_inits;
 extern GTY(()) tree solaris_pending_finis;
+
+/* Allow macro expansion in #pragma pack.  */
+#define HANDLE_PRAGMA_PACK_WITH_EXPANSION
diff --git a/gcc/doc/extend.texi b/gcc/doc/extend.texi
index ef725b1aebe306c81a5dcf12b59b3976aadcc6ee..dcb27f5642b1403b41e492a028fa67b789187b29 100644
--- a/gcc/doc/extend.texi
+++ b/gcc/doc/extend.texi
@@ -8603,7 +8603,10 @@ The Solaris target supports @code{#pragma redefine_extname}
 
 Increase the minimum alignment of each @var{variable} to @var{alignment}.
 This is the same as GCC's @code{aligned} attribute @pxref{Variable
-Attributes}).
+Attributes}).  Macro expansion occurs on the arguments to this pragma
+when compiling C and Objective-C.  It does not currently occur when
+compiling C++, but this is a bug which may be fixed in a future
+release.
 
 @item fini (@var{function} [, @var{function}]...)
 @cindex pragma, fini
diff --git a/gcc/doc/tm.texi b/gcc/doc/tm.texi
index 72d49f3a9b6d5c472456ac2ba3fe7706e71d76cd..409559e5a2c8d68f03a0c8d2241857181a16a4b1 100644
--- a/gcc/doc/tm.texi
+++ b/gcc/doc/tm.texi
@@ -9029,7 +9029,8 @@ C++, which is to pretend that the file's contents are enclosed in
 @defmac REGISTER_TARGET_PRAGMAS ()
 Define this macro if you want to implement any target-specific pragmas.
 If defined, it is a C expression which makes a series of calls to
-@code{c_register_pragma} for each pragma.  The macro may also do any
+@code{c_register_pragma} or @code{c_register_pragma_with_expansion}
+for each pragma.  The macro may also do any
 setup required for the pragmas.
 
 The primary reason to define this macro is to provide compatibility with
@@ -9045,8 +9046,10 @@ silently ignored, unless the user specifies @option{-Wunknown-pragmas}.
 @end defmac
 
 @deftypefun void c_register_pragma (const char *@var{space}, const char *@var{name}, void (*@var{callback}) (struct cpp_reader *))
+@deftypefunx void c_register_pragma_with_expansion (const char *@var{space}, const char *@var{name}, void (*@var{callback}) (struct cpp_reader *))
 
-Each call to @code{c_register_pragma} establishes one pragma.  The
+Each call to @code{c_register_pragma} or
+@code{c_register_pragma_with_expansion} establishes one pragma.  The
 @var{callback} routine will be called when the preprocessor encounters a
 pragma of the form
 
@@ -9060,7 +9063,10 @@ routine receives @var{pfile} as its first argument, which can be passed
 on to cpplib's functions if necessary.  You can lex tokens after the
 @var{name} by calling @code{c_lex}.  Tokens that are not read by the
 callback will be silently ignored.  The end of the line is indicated by
-a token of type @code{CPP_EOF}
+a token of type @code{CPP_EOF}.  Macro expansion occurs on the
+arguments of pragmas registered with
+@code{c_register_pragma_with_expansion} but not on the arguments of
+pragmas registered with @code{c_register_pragma}.
 
 For an example use of this routine, see @file{c4x.h} and the callback
 routines defined in @file{c4x-c.c}.
@@ -9124,6 +9130,12 @@ that invocations of @samp{#pragma pack(pop)} will return to the previous
 value.
 @end defmac
 
+@defmac HANDLE_PRAGMA_PACK_WITH_EXPANSION
+Define this macro, as well as
+@code{HANDLE_SYSV_PRAGMA}, if macros should be expanded in the
+arguments of @samp{#pragma pack}.
+@end defmac
+
 @defmac TARGET_DEFAULT_PACK_STRUCT
 If your target requires a structure packing default other than 0 (meaning
 the machine default), define this macro the the necessary value (in bytes).
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index b395dd02d5cd2caaf48b1aa31491de74db382ee6..36b75e007762d4454352bf9b74bbbf88ae122d9b 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,8 @@
+2004-11-23  Daniel Jacobowitz  <dan@codesourcery.com>
+
+	* gcc.dg/pragma-align-2.c: Test macro expansion.
+	* gcc.dg/pragma-pack-2.c: New test.
+
 2004-11-23  Richard Henderson  <rth@redhat.com>
 
 	* gcc.dg/vect/pr18425.c: Use effective target vect_long.
diff --git a/gcc/testsuite/gcc.dg/pragma-align-2.c b/gcc/testsuite/gcc.dg/pragma-align-2.c
index 3d5e0da32707ef30154eac0dd499aab339c90369..e33f24a27da6354fe8b2498814cd192fcaca6c7a 100644
--- a/gcc/testsuite/gcc.dg/pragma-align-2.c
+++ b/gcc/testsuite/gcc.dg/pragma-align-2.c
@@ -11,6 +11,12 @@ void abort (void);
 #pragma align 64(x64)
 #pragma align 128(x128)
 
+#define MACRO 128
+#define MACRO2(A) A
+
+#pragma align MACRO(y128)
+#pragma align MACRO2(MACRO) (z128)
+
 #pragma align 8(not_defined)
 
 #pragma align 9(odd_align)	/* { dg-error "invalid alignment" } */
@@ -19,7 +25,7 @@ void abort (void);
 #pragma align bad_align		/* { dg-error "malformed" } */
 #pragma align 1(bad_align	/* { dg-error "malformed" } */
 
-int x, x1, x2, x4, x8, y8, z8, x16, x32, x64, x128;
+int x, x1, x2, x4, x8, y8, z8, x16, x32, x64, x128, y128, z128;
 
 #pragma align 16(x)		/* { dg-error "must appear before" } */
 
@@ -50,5 +56,11 @@ main ()
   if (__alignof__ (x128) < 128)
     abort ();
 
+  if (__alignof__ (y128) < 128)
+    abort ();
+
+  if (__alignof__ (z128) < 128)
+    abort (); 
+
   return 0;
 }
diff --git a/gcc/testsuite/gcc.dg/pragma-pack-2.c b/gcc/testsuite/gcc.dg/pragma-pack-2.c
new file mode 100644
index 0000000000000000000000000000000000000000..f44f8dbba3330c5869407c59c0266ceca7f2265d
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/pragma-pack-2.c
@@ -0,0 +1,48 @@
+/* On Solaris, #pragma pack should accept macro expansion.  */
+
+/* { dg-do run { target *-*-solaris2.* } } */
+
+extern void abort (void);
+
+struct {
+        char one;
+        long two;
+} defaultalign;
+
+#define ALIGNHIGH 16
+
+#pragma pack(ALIGNHIGH)
+struct {
+        char one;
+        long two;
+} sixteen;
+
+#define ALIGN1(X) 1
+#pragma pack(ALIGN1(4))
+struct {
+        char one;
+        long two;
+} two;
+
+#define ALIGN2(X) X
+#pragma pack(ALIGN2(2))
+struct {
+        char one;
+        long two;
+} three;
+
+#define EMPTY
+#pragma pack(EMPTY)
+struct {
+        char one;
+        long two;
+} resetalign;
+
+main()
+{
+        if(sizeof(sixteen) < sizeof(defaultalign)) abort();
+        if(sizeof(two) >= sizeof(defaultalign)) abort();
+        if(sizeof(three) <= sizeof(two)) abort();
+        if(sizeof(resetalign) != sizeof(defaultalign)) abort();
+	return 0;
+}
diff --git a/libcpp/ChangeLog b/libcpp/ChangeLog
index eb5d76f7b33352cd6d1c4291dfe1a3f18e3aee34..3e8567bf05e6cc7a9a25837ceef0031b08354192 100644
--- a/libcpp/ChangeLog
+++ b/libcpp/ChangeLog
@@ -1,3 +1,16 @@
+2004-11-23  Daniel Jacobowitz  <dan@codesourcery.com>
+            Joseph Myers  <joseph@codesourcery.com>
+
+	* internal.h (struct lexer_state): Add in_deferred_pragma.
+	* directives.c (struct pragma_entry): Add allow_expansion.
+	(insert_pragma_entry): Take allow_expansion flag.
+	(register_pragma): Likewise.
+	(cpp_register_pragma): Likewise.
+	(_cpp_init_internal_pragmas): Update calls to cpp_register_pragma.
+	(do_pragma): Honor allow_expansion.
+	(cpp_handle_deferred_pragma): Set in_deferred_pragma.
+	* include/cpplib.h (cpp_register_pragma): Update prototype.
+
 2004-11-18  Daniel Jacobowitz  <dan@codesourcery.com>
             Mark Mitchell  <mark@codesourcery.com>
 
diff --git a/libcpp/directives.c b/libcpp/directives.c
index 10d080bee4429174dce821ac32caa7d0fad2ecae..a835b6812a5349dfa62c2a0f134e5fc76c155244 100644
--- a/libcpp/directives.c
+++ b/libcpp/directives.c
@@ -45,6 +45,7 @@ struct pragma_entry
   struct pragma_entry *next;
   const cpp_hashnode *pragma;	/* Name and length.  */
   bool is_nspace;
+  bool allow_expansion;
   bool is_internal;
   union {
     pragma_cb handler;
@@ -108,9 +109,9 @@ static struct pragma_entry *insert_pragma_entry (cpp_reader *,
                                                  struct pragma_entry **,
                                                  const cpp_hashnode *,
                                                  pragma_cb,
-						 bool);
+						 bool, bool);
 static void register_pragma (cpp_reader *, const char *, const char *,
-			     pragma_cb, bool);
+			     pragma_cb, bool, bool);
 static int count_registered_pragmas (struct pragma_entry *);
 static char ** save_registered_pragmas (struct pragma_entry *, char **);
 static char ** restore_registered_pragmas (cpp_reader *, struct pragma_entry *,
@@ -964,7 +965,7 @@ lookup_pragma_entry (struct pragma_entry *chain, const cpp_hashnode *pragma)
 static struct pragma_entry *
 insert_pragma_entry (cpp_reader *pfile, struct pragma_entry **chain,
 		     const cpp_hashnode *pragma, pragma_cb handler,
-		     bool internal)
+		     bool allow_expansion, bool internal)
 {
   struct pragma_entry *new;
 
@@ -982,6 +983,7 @@ insert_pragma_entry (cpp_reader *pfile, struct pragma_entry **chain,
       new->u.space = NULL;
     }
 
+  new->allow_expansion = allow_expansion;
   new->is_internal = internal;
   new->next = *chain;
   *chain = new;
@@ -990,12 +992,13 @@ insert_pragma_entry (cpp_reader *pfile, struct pragma_entry **chain,
 
 /* Register a pragma NAME in namespace SPACE.  If SPACE is null, it
    goes in the global namespace.  HANDLER is the handler it will call,
-   which must be non-NULL.  INTERNAL is true if this is a pragma
-   registered by cpplib itself, false if it is registered via
+   which must be non-NULL.  If ALLOW_EXPANSION is set, allow macro
+   expansion while parsing pragma NAME.  INTERNAL is true if this is a
+   pragma registered by cpplib itself, false if it is registered via
    cpp_register_pragma */
 static void
 register_pragma (cpp_reader *pfile, const char *space, const char *name,
-		 pragma_cb handler, bool internal)
+		 pragma_cb handler, bool allow_expansion, bool internal)
 {
   struct pragma_entry **chain = &pfile->pragmas;
   struct pragma_entry *entry;
@@ -1009,7 +1012,8 @@ register_pragma (cpp_reader *pfile, const char *space, const char *name,
       node = cpp_lookup (pfile, U space, strlen (space));
       entry = lookup_pragma_entry (*chain, node);
       if (!entry)
-	entry = insert_pragma_entry (pfile, chain, node, NULL, internal);
+	entry = insert_pragma_entry (pfile, chain, node, NULL, 
+				     allow_expansion, internal);
       else if (!entry->is_nspace)
 	goto clash;
       chain = &entry->u.space;
@@ -1032,17 +1036,20 @@ register_pragma (cpp_reader *pfile, const char *space, const char *name,
 	cpp_error (pfile, CPP_DL_ICE, "#pragma %s is already registered", name);
     }
   else
-    insert_pragma_entry (pfile, chain, node, handler, internal);
+    insert_pragma_entry (pfile, chain, node, handler, allow_expansion, 
+			 internal);
 }
 
 /* Register a pragma NAME in namespace SPACE.  If SPACE is null, it
    goes in the global namespace.  HANDLER is the handler it will call,
-   which must be non-NULL.  This function is exported from libcpp. */
+   which must be non-NULL.  If ALLOW_EXPANSION is set, allow macro
+   expansion while parsing pragma NAME.  This function is exported
+   from libcpp. */
 void
 cpp_register_pragma (cpp_reader *pfile, const char *space, const char *name,
-		     pragma_cb handler)
+		     pragma_cb handler, bool allow_expansion)
 {
-  register_pragma (pfile, space, name, handler, false);
+  register_pragma (pfile, space, name, handler, allow_expansion, false);
 }
 
 /* Register the pragmas the preprocessor itself handles.  */
@@ -1050,12 +1057,14 @@ void
 _cpp_init_internal_pragmas (cpp_reader *pfile)
 {
   /* Pragmas in the global namespace.  */
-  register_pragma (pfile, 0, "once", do_pragma_once, true);
+  register_pragma (pfile, 0, "once", do_pragma_once, false, true);
 
   /* New GCC-specific pragmas should be put in the GCC namespace.  */
-  register_pragma (pfile, "GCC", "poison", do_pragma_poison, true);
-  register_pragma (pfile, "GCC", "system_header", do_pragma_system_header, true);
-  register_pragma (pfile, "GCC", "dependency", do_pragma_dependency, true);
+  register_pragma (pfile, "GCC", "poison", do_pragma_poison, false, true);
+  register_pragma (pfile, "GCC", "system_header", do_pragma_system_header, 
+		   false, true);
+  register_pragma (pfile, "GCC", "dependency", do_pragma_dependency, 
+		   false, true);
 }
 
 /* Return the number of registered pragmas in PE.  */
@@ -1176,7 +1185,14 @@ do_pragma (cpp_reader *pfile)
 	     numbers in place.  */
 	  if (pfile->cb.line_change)
 	    (*pfile->cb.line_change) (pfile, pragma_token, false);
+	  /* Never expand macros if handling a deferred pragma, since
+	     the macro definitions now applicable may be different
+	     from those at the point the pragma appeared.  */
+	  if (p->allow_expansion && !pfile->state.in_deferred_pragma)
+	    pfile->state.prevent_expansion--;
 	  (*p->u.handler) (pfile);
+	  if (p->allow_expansion && !pfile->state.in_deferred_pragma)
+	    pfile->state.prevent_expansion++;
 	}
       else
 	{
@@ -1430,6 +1446,7 @@ cpp_handle_deferred_pragma (cpp_reader *pfile, const cpp_string *s)
   pfile->context->macro = 0;
   pfile->context->prev = 0;
   pfile->cb.line_change = NULL;
+  pfile->state.in_deferred_pragma = true;
   CPP_OPTION (pfile, defer_pragmas) = false;
 
   run_directive (pfile, T_PRAGMA, (const char *)s->text, s->len);
@@ -1439,6 +1456,7 @@ cpp_handle_deferred_pragma (cpp_reader *pfile, const cpp_string *s)
   pfile->cur_token = saved_cur_token;
   pfile->cur_run = saved_cur_run;
   pfile->cb.line_change = saved_line_change;
+  pfile->state.in_deferred_pragma = false;
   CPP_OPTION (pfile, defer_pragmas) = saved_defer_pragmas;
 }
 
diff --git a/libcpp/include/cpplib.h b/libcpp/include/cpplib.h
index 4ee626ecd1c1138f44e8fd141dca3652cc798633..13213882aa812eaa9c3492324fe125eaaee3aeeb 100644
--- a/libcpp/include/cpplib.h
+++ b/libcpp/include/cpplib.h
@@ -638,7 +638,7 @@ extern unsigned char *cpp_token_as_text (cpp_reader *, const cpp_token *);
 extern unsigned char *cpp_spell_token (cpp_reader *, const cpp_token *,
 				       unsigned char *);
 extern void cpp_register_pragma (cpp_reader *, const char *, const char *,
-				 void (*) (cpp_reader *));
+				 void (*) (cpp_reader *), bool);
 extern void cpp_handle_deferred_pragma (cpp_reader *, const cpp_string *);
 extern int cpp_avoid_paste (cpp_reader *, const cpp_token *,
 			    const cpp_token *);
diff --git a/libcpp/internal.h b/libcpp/internal.h
index 15a3dfada9e5fd08757f00d8738a91f2ea8188a8..70694fd039de652d61e86713f1a8fa5abdc8c13d 100644
--- a/libcpp/internal.h
+++ b/libcpp/internal.h
@@ -205,6 +205,9 @@ struct lexer_state
   /* Nonzero to prevent macro expansion.  */
   unsigned char prevent_expansion;
 
+  /* Nonzero when handling a deferred pragma.  */
+  unsigned char in_deferred_pragma;
+
   /* Nonzero when parsing arguments to a function-like macro.  */
   unsigned char parsing_args;