From 17e7cb855000baa6598005571d7dd49cfac5282a Mon Sep 17 00:00:00 2001
From: Kai Tietz <kai.tietz@onevision.com>
Date: Wed, 11 Nov 2009 18:37:19 +0000
Subject: [PATCH] ChangeLog for libcpp

2009-11-11  Kai Tietz  <kai.tietz@onevision.com>

	* directives.c (do_pragma_push_macro): New pragma handler.
	(do_pragma_pop_macro): Likewise.
	(_cpp_init_internal_pragmas): Add push_macro and
	pop_macro handler to internal pragmas.
	(lex_macro_node_from_str): Removed.
	(cpp_push_definition): Replace lex_macro_node_from_str
	by _cpp_lex_identifier.
	(cpp_pop_definition): Likewise.
	* internal.h (_cpp_lex_identifier): New prototype.
	(def_pragma_macro): New structure.
	(cpp_reader): New member pushed_macros.
	* lex.c (_cpp_lex_identifier): New function.
	(lex_identifier_intern): New function.
	* init.c (cpp_create_reader): Initialize pushed_macros
	member.
	(cpp_destroy): Free elements in pushed_macros member.
	* pch.c (_cpp_save_pushed_macros): New function.
	(_cpp_restore_pushed_macros): Likewise.
	(_cpp_restore_pushed_macros): Use _cpp_save_pushed_macros.
	(cpp_read_state): Use _cpp_restore_pushed_macros.

ChangeLog for gcc

2009-11-11  Kai Tietz  <kai.tietz@onevision.com>

	* config/i386/cygming.h (HANDLE_PRAGMA_PUSH_POP_MACRO):
	Removed.
	* c-pragma.c (def_pragma_macro_value): Likewise.
	(def_pragma_macro): Likewise.
	(pushed_macro_table): Likewise.
	(HANDLE_PRAGMA_PUSH_POP_MACRO): Remove guarded
	code.
	* doc/tm.texi (HANDLE_PRAGMA_PUSH_POP_MACRO):
	Removed.

ChangeLog for gcc/testsuite

2009-11-11  Kai Tietz  <kai.tietz@onevision.com>

	* g++.dg/torture/pushpop_macro.C: New testcase.
	* gcc.c-torture/execute/pushpop_macro.c: New testcase.
	* gcc.dg/cpp/pragma-pop_macro-1.c: Allow test for all
	targets.

From-SVN: r154098
---
 gcc/ChangeLog                                 |  12 ++
 gcc/c-pragma.c                                | 142 ------------------
 gcc/config/i386/cygming.h                     |   2 -
 gcc/doc/tm.texi                               |  12 --
 gcc/testsuite/ChangeLog                       |   8 +-
 gcc/testsuite/g++.dg/torture/pushpop_macro.C  |  19 +++
 .../gcc.c-torture/execute/pushpop_macro.c     |  15 ++
 gcc/testsuite/gcc.dg/cpp/pragma-pop_macro-1.c |   2 +-
 gcc/testsuite/gcc.dg/pch/pushpop-1.c          |  11 ++
 gcc/testsuite/gcc.dg/pch/pushpop-1.hs         |   5 +
 libcpp/ChangeLog                              |  23 +++
 libcpp/directives.c                           | 115 +++++++++++---
 libcpp/init.c                                 |  15 ++
 libcpp/internal.h                             |  14 ++
 libcpp/lex.c                                  |  57 +++++++
 libcpp/pch.c                                  | 136 +++++++++++++++++
 16 files changed, 411 insertions(+), 177 deletions(-)
 create mode 100644 gcc/testsuite/g++.dg/torture/pushpop_macro.C
 create mode 100644 gcc/testsuite/gcc.c-torture/execute/pushpop_macro.c
 create mode 100644 gcc/testsuite/gcc.dg/pch/pushpop-1.c
 create mode 100644 gcc/testsuite/gcc.dg/pch/pushpop-1.hs

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index 0de0981266d8..87e6fb41091e 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,15 @@
+2009-11-11  Kai Tietz  <kai.tietz@onevision.com>
+
+	* config/i386/cygming.h (HANDLE_PRAGMA_PUSH_POP_MACRO):
+	Removed.
+	* c-pragma.c (def_pragma_macro_value): Likewise.
+	(def_pragma_macro): Likewise.
+	(pushed_macro_table): Likewise.
+	(HANDLE_PRAGMA_PUSH_POP_MACRO): Remove guarded
+	code.
+	* doc/tm.texi (HANDLE_PRAGMA_PUSH_POP_MACRO):
+	Removed.
+
 2009-11-11  Basile Starynkevitch  <basile@starynkevitch.net>
 	* doc/plugins.texi (Registering custom attributes): section
 	renamed as (Registering custom attributes or pragmas).
diff --git a/gcc/c-pragma.c b/gcc/c-pragma.c
index f71399fa93ee..79b3d132fd72 100644
--- a/gcc/c-pragma.c
+++ b/gcc/c-pragma.c
@@ -244,144 +244,6 @@ handle_pragma_pack (cpp_reader * ARG_UNUSED (dummy))
 }
 #endif  /* HANDLE_PRAGMA_PACK */
 
-struct GTY(()) def_pragma_macro_value {
-  struct def_pragma_macro_value *prev;
-  cpp_macro *value;
-};
-
-struct GTY(()) def_pragma_macro {
-  hashval_t hash;
-  const char *name;
-  struct def_pragma_macro_value value;
-};
-
-static GTY((param_is (struct def_pragma_macro))) htab_t pushed_macro_table;
-
-#ifdef HANDLE_PRAGMA_PUSH_POP_MACRO
-/* Hash table control functions for pushed_macro_table.  */
-static hashval_t
-dpm_hash (const void *p)
-{
-  return ((const struct def_pragma_macro *)p)->hash;
-}
-
-static int
-dpm_eq (const void *pa, const void *pb)
-{
-  const struct def_pragma_macro *const a = (const struct def_pragma_macro *) pa,
-    *const b = (const struct def_pragma_macro *) pb;
-  return a->hash == b->hash && strcmp (a->name, b->name) == 0;
-}
-
-/* #pragma push_macro("MACRO_NAME")
-   #pragma pop_macro("MACRO_NAME") */
-
-static void
-handle_pragma_push_macro (cpp_reader *reader)
-{
-  tree x, id = 0;
-  enum cpp_ttype token;
-  struct def_pragma_macro dummy, *c;
-  const char *macroname;
-  void **slot;
-
-  if (pragma_lex (&x) != CPP_OPEN_PAREN)
-    GCC_BAD ("missing %<(%> after %<#pragma push_macro%> - ignored");
-
-  token = pragma_lex (&id);
-
-  /* Silently ignore */
-  if (token == CPP_CLOSE_PAREN)
-    return;
-  if (token != CPP_STRING)
-    GCC_BAD ("invalid constant in %<#pragma push_macro%> - ignored");
-
-  if (pragma_lex (&x) != CPP_CLOSE_PAREN)
-    GCC_BAD ("missing %<)%> after %<#pragma push_macro%> - ignored");
-
-  if (pragma_lex (&x) != CPP_EOF)
-    warning (OPT_Wpragmas, "junk at end of %<#pragma push_macro%>");
-
-  /* Check for empty string, and silently ignore.  */
-  if (TREE_STRING_LENGTH (id) < 1)
-    return;
-  macroname = TREE_STRING_POINTER (id);
-
-  if (pushed_macro_table == NULL)
-    pushed_macro_table = htab_create_ggc (15, dpm_hash, dpm_eq, 0);
-
-  dummy.hash = htab_hash_string (macroname);
-  dummy.name = macroname;
-  slot = htab_find_slot_with_hash (pushed_macro_table, &dummy,
-				   dummy.hash, INSERT);
-  c = (struct def_pragma_macro *) *slot;
-  if (c == NULL)
-    {
-      *slot = c = GGC_NEW (struct def_pragma_macro);
-      c->hash = dummy.hash;
-      c->name = ggc_alloc_string (macroname, TREE_STRING_LENGTH (id) - 1);
-      c->value.prev = NULL;
-    }
-  else
-    {
-      struct def_pragma_macro_value *v;
-      v = GGC_NEW (struct def_pragma_macro_value);
-      *v = c->value;
-      c->value.prev = v;
-    }
-
-  c->value.value = cpp_push_definition (reader, macroname);
-}
-
-static void
-handle_pragma_pop_macro (cpp_reader *reader)
-{
-  tree x, id = 0;
-  enum cpp_ttype token;
-  struct def_pragma_macro dummy, *c;
-  const char *macroname;
-  void **slot = NULL;
-
-  if (pragma_lex (&x) != CPP_OPEN_PAREN)
-    GCC_BAD ("missing %<(%> after %<#pragma pop_macro%> - ignored");
-
-  token = pragma_lex (&id);
-
-  /* Silently ignore */
-  if (token == CPP_CLOSE_PAREN)
-    return;
-  if (token != CPP_STRING)
-    GCC_BAD ("invalid constant in %<#pragma pop_macro%> - ignored");
-
-  if (pragma_lex (&x) != CPP_CLOSE_PAREN)
-    GCC_BAD ("missing %<)%> after %<#pragma pop_macro%> - ignored");
-
-  if (pragma_lex (&x) != CPP_EOF)
-    warning (OPT_Wpragmas, "junk at end of %<#pragma pop_macro%>");
-
-  /* Check for empty string, and silently ignore.  */
-  if (TREE_STRING_LENGTH (id) < 1)
-    return;
-  macroname = TREE_STRING_POINTER (id);
-
-  dummy.hash = htab_hash_string (macroname);
-  dummy.name = macroname;
-  if (pushed_macro_table)
-    slot = htab_find_slot_with_hash (pushed_macro_table, &dummy,
-				     dummy.hash, NO_INSERT);
-  if (slot == NULL)
-    return;
-  c = (struct def_pragma_macro *) *slot;
-
-  cpp_pop_definition (reader, c->name, c->value.value);
-
-  if (c->value.prev)
-    c->value = *c->value.prev;
-  else
-    htab_clear_slot (pushed_macro_table, slot);
-}
-#endif /* HANDLE_PRAGMA_PUSH_POP_MACRO */
-
 static GTY(()) tree pending_weaks;
 
 #ifdef HANDLE_PRAGMA_WEAK
@@ -1422,10 +1284,6 @@ init_pragma (void)
   c_register_pragma (0, "pack", handle_pragma_pack);
 #endif
 #endif
-#ifdef HANDLE_PRAGMA_PUSH_POP_MACRO
-  c_register_pragma (0 ,"push_macro", handle_pragma_push_macro);
-  c_register_pragma (0 ,"pop_macro", handle_pragma_pop_macro);
-#endif
 #ifdef HANDLE_PRAGMA_WEAK
   c_register_pragma (0, "weak", handle_pragma_weak);
 #endif
diff --git a/gcc/config/i386/cygming.h b/gcc/config/i386/cygming.h
index cdab21c91a2b..ddec95a36fcd 100644
--- a/gcc/config/i386/cygming.h
+++ b/gcc/config/i386/cygming.h
@@ -127,8 +127,6 @@ along with GCC; see the file COPYING3.  If not see
 
 /* Enable parsing of #pragma pack(push,<n>) and #pragma pack(pop).  */
 #define HANDLE_PRAGMA_PACK_PUSH_POP 1
-/* Enable push_macro & pop_macro */
-#define HANDLE_PRAGMA_PUSH_POP_MACRO 1
 
 union tree_node;
 #define TREE union tree_node *
diff --git a/gcc/doc/tm.texi b/gcc/doc/tm.texi
index c69ef0c73abf..3950967b7a37 100644
--- a/gcc/doc/tm.texi
+++ b/gcc/doc/tm.texi
@@ -10476,18 +10476,6 @@ This must be a value that would also be valid to use with
 @samp{#pragma pack()} (that is, a small power of two).
 @end defmac
 
-@findex #pragma
-@findex pragma
-@defmac HANDLE_PRAGMA_PUSH_POP_MACRO
-Define this macro if you want to support the Win32 style pragmas
-@samp{#pragma push_macro(macro-name-as-string)} and @samp{#pragma
-pop_macro(macro-name-as-string)}.  The @samp{#pragma push_macro(
-macro-name-as-string)} pragma saves the named macro and via
-@samp{#pragma pop_macro(macro-name-as-string)} it will return to the
-previous value.
-@end defmac
-
-
 @defmac DOLLARS_IN_IDENTIFIERS
 Define this macro to control use of the character @samp{$} in
 identifier names for the C family of languages.  0 means @samp{$} is
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 2eec61213ff7..16340e589a77 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,4 +1,10 @@
-gcc/testsuite/
+2009-11-11  Kai Tietz  <kai.tietz@onevision.com>
+
+	* g++.dg/torture/pushpop_macro.C: New testcase.
+	* gcc.c-torture/execute/pushpop_macro.c: New testcase.
+	* gcc.dg/cpp/pragma-pop_macro-1.c: Allow test for all
+	targets.
+
 2009-11-11  Jon Beniston <jon@beniston.com>
 
         * lib/target-supports.exp (check_profiling_available): lm32 target 
diff --git a/gcc/testsuite/g++.dg/torture/pushpop_macro.C b/gcc/testsuite/g++.dg/torture/pushpop_macro.C
new file mode 100644
index 000000000000..98065e6ee79e
--- /dev/null
+++ b/gcc/testsuite/g++.dg/torture/pushpop_macro.C
@@ -0,0 +1,19 @@
+/* Do the preprocessor push_macro/pop_macro test.  */
+
+/* { dg-do run } */
+
+extern "C" void abort ();
+
+#define _ 2
+#pragma push_macro("_")
+#undef _
+#define _ 1
+#pragma pop_macro("_")
+
+int main ()
+{
+  if (_ != 2)
+    abort ();
+  return 0;
+}
+
diff --git a/gcc/testsuite/gcc.c-torture/execute/pushpop_macro.c b/gcc/testsuite/gcc.c-torture/execute/pushpop_macro.c
new file mode 100644
index 000000000000..08a82204313e
--- /dev/null
+++ b/gcc/testsuite/gcc.c-torture/execute/pushpop_macro.c
@@ -0,0 +1,15 @@
+extern void abort ();
+
+#define _ 2
+#pragma push_macro("_")
+#undef _
+#define _ 1
+#pragma pop_macro("_")
+
+int main ()
+{
+  if (_ != 2)
+    abort ();
+  return 0;
+}
+
diff --git a/gcc/testsuite/gcc.dg/cpp/pragma-pop_macro-1.c b/gcc/testsuite/gcc.dg/cpp/pragma-pop_macro-1.c
index dec67adf7f39..c9a9048646cc 100644
--- a/gcc/testsuite/gcc.dg/cpp/pragma-pop_macro-1.c
+++ b/gcc/testsuite/gcc.dg/cpp/pragma-pop_macro-1.c
@@ -1,7 +1,7 @@
 /* PR preprocessor/35061 */
 /* Do nothing if there is nothing on the macro stack to pop.  */
 
-/* { dg-do preprocess { target *-*-mingw* *-*-cygwin* } } */
+/* { dg-do preprocess } */
 
 #define X  1
 /* # pragma push_macro("X") */
diff --git a/gcc/testsuite/gcc.dg/pch/pushpop-1.c b/gcc/testsuite/gcc.dg/pch/pushpop-1.c
new file mode 100644
index 000000000000..c093e575a0e0
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/pch/pushpop-1.c
@@ -0,0 +1,11 @@
+#include "pushpop-1.hs"
+
+#if FOO != 2
+#error FOO != 2
+#endif
+#pragma pop_macro("FOO")
+
+#if FOO != 1
+#error FOR != 1
+#endif
+
diff --git a/gcc/testsuite/gcc.dg/pch/pushpop-1.hs b/gcc/testsuite/gcc.dg/pch/pushpop-1.hs
new file mode 100644
index 000000000000..e97a4f33a91a
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/pch/pushpop-1.hs
@@ -0,0 +1,5 @@
+#define FOO 1
+#pragma push_macro ("FOO")
+#undef FOO
+#define FOO 2
+
diff --git a/libcpp/ChangeLog b/libcpp/ChangeLog
index 5946b29dc566..c842e80c91de 100644
--- a/libcpp/ChangeLog
+++ b/libcpp/ChangeLog
@@ -1,3 +1,26 @@
+2009-11-11  Kai Tietz  <kai.tietz@onevision.com>
+
+	* directives.c (do_pragma_push_macro): New pragma handler.
+	(do_pragma_pop_macro): Likewise.
+	(_cpp_init_internal_pragmas): Add push_macro and
+	pop_macro handler to internal pragmas.
+	(lex_macro_node_from_str): Removed.
+	(cpp_push_definition): Replace lex_macro_node_from_str
+	by _cpp_lex_identifier.
+	(cpp_pop_definition): Likewise.
+	* internal.h (_cpp_lex_identifier): New prototype.
+	(def_pragma_macro): New structure.
+	(cpp_reader): New member pushed_macros.
+	* lex.c (_cpp_lex_identifier): New function.
+	(lex_identifier_intern): New function.
+	* init.c (cpp_create_reader): Initialize pushed_macros
+	member.
+	(cpp_destroy): Free elements in pushed_macros member.
+	* pch.c (_cpp_save_pushed_macros): New function.
+	(_cpp_restore_pushed_macros): Likewise.
+	(_cpp_restore_pushed_macros): Use _cpp_save_pushed_macros.
+	(cpp_read_state): Use _cpp_restore_pushed_macros.
+
 2009-10-19  Jakub Jelinek  <jakub@redhat.com>
 
 	* charset.c (cpp_init_iconv): Initialize utf8_cset_desc.
diff --git a/libcpp/directives.c b/libcpp/directives.c
index 01bb599e2669..aed940e56e1d 100644
--- a/libcpp/directives.c
+++ b/libcpp/directives.c
@@ -126,6 +126,8 @@ static int parse_answer (cpp_reader *, struct answer **, int, source_location);
 static cpp_hashnode *parse_assertion (cpp_reader *, struct answer **, int);
 static struct answer ** find_answer (cpp_hashnode *, const struct answer *);
 static void handle_assertion (cpp_reader *, const char *, int);
+static void do_pragma_push_macro (cpp_reader *);
+static void do_pragma_pop_macro (cpp_reader *);
 
 /* This is the table of directive handlers.  It is ordered by
    frequency of occurrence; the numbers at the end are directive
@@ -1244,6 +1246,8 @@ _cpp_init_internal_pragmas (cpp_reader *pfile)
 {
   /* Pragmas in the global namespace.  */
   register_pragma_internal (pfile, 0, "once", do_pragma_once);
+  register_pragma_internal (pfile, 0, "push_macro", do_pragma_push_macro);
+  register_pragma_internal (pfile, 0, "pop_macro", do_pragma_pop_macro);
 
   /* New GCC-specific pragmas should be put in the GCC namespace.  */
   register_pragma_internal (pfile, "GCC", "poison", do_pragma_poison);
@@ -1423,6 +1427,96 @@ do_pragma_once (cpp_reader *pfile)
   _cpp_mark_file_once_only (pfile, pfile->buffer->file);
 }
 
+/* Handle #pragma push_macro(STRING).  */
+static void
+do_pragma_push_macro (cpp_reader *pfile)
+{
+  char *macroname, *dest;
+  const char *limit, *src;
+  const cpp_token *txt;
+  struct def_pragma_macro *c;
+
+  txt = get__Pragma_string (pfile);
+  if (!txt)
+    {
+      source_location src_loc = pfile->cur_token[-1].src_loc;
+      cpp_error_with_line (pfile, CPP_DL_ERROR, src_loc, 0,
+		 "invalid #pragma push_macro directive");
+      check_eol (pfile, false);
+      skip_rest_of_line (pfile);
+      return;
+    }
+  dest = macroname = (char *) alloca (txt->val.str.len + 2);
+  src = (const char *) (txt->val.str.text + 1 + (txt->val.str.text[0] == 'L'));
+  limit = (const char *) (txt->val.str.text + txt->val.str.len - 1);
+  while (src < limit)
+    {
+      /* We know there is a character following the backslash.  */
+      if (*src == '\\' && (src[1] == '\\' || src[1] == '"'))
+	src++;
+      *dest++ = *src++;
+    }
+  *dest = 0;
+  check_eol (pfile, false);
+  skip_rest_of_line (pfile);
+  c = XNEW (struct def_pragma_macro);
+  c->name = XNEWVAR (char, strlen (macroname) + 1);
+  strcpy (c->name, macroname);
+  c->next = pfile->pushed_macros;
+  c->value = cpp_push_definition (pfile, c->name);
+  pfile->pushed_macros = c;
+}
+
+/* Handle #pragma pop_macro(STRING).  */
+static void
+do_pragma_pop_macro (cpp_reader *pfile)
+{
+  char *macroname, *dest;
+  const char *limit, *src;
+  const cpp_token *txt;
+  struct def_pragma_macro *l = NULL, *c = pfile->pushed_macros;
+  txt = get__Pragma_string (pfile);
+  if (!txt)
+    {
+      source_location src_loc = pfile->cur_token[-1].src_loc;
+      cpp_error_with_line (pfile, CPP_DL_ERROR, src_loc, 0,
+		 "invalid #pragma pop_macro directive");
+      check_eol (pfile, false);
+      skip_rest_of_line (pfile);
+      return;
+    }
+  dest = macroname = (char *) alloca (txt->val.str.len + 2);
+  src = (const char *) (txt->val.str.text + 1 + (txt->val.str.text[0] == 'L'));
+  limit = (const char *) (txt->val.str.text + txt->val.str.len - 1);
+  while (src < limit)
+    {
+      /* We know there is a character following the backslash.  */
+      if (*src == '\\' && (src[1] == '\\' || src[1] == '"'))
+	src++;
+      *dest++ = *src++;
+    }
+  *dest = 0;
+  check_eol (pfile, false);
+  skip_rest_of_line (pfile);
+
+  while (c != NULL)
+    {
+      if (!strcmp (c->name, macroname))
+	{
+	  if (!l)
+	    pfile->pushed_macros = c->next;
+	  else
+	    l->next = c->next;
+	  cpp_pop_definition (pfile, c->name, c->value);
+	  free (c->name);
+	  free (c);
+	  break;
+	}
+      l = c;
+      c = c->next;
+    }
+}
+
 /* Handle #pragma GCC poison, to poison one or more identifiers so
    that the lexer produces a hard error for each subsequent usage.  */
 static void
@@ -2225,28 +2319,11 @@ cpp_undef (cpp_reader *pfile, const char *macro)
   run_directive (pfile, T_UNDEF, buf, len);
 }
 
-/* Like lex_macro_node, but read the input from STR.  */
-static cpp_hashnode *
-lex_macro_node_from_str (cpp_reader *pfile, const char *str)
-{
-  size_t len = strlen (str);
-  uchar *buf = (uchar *) alloca (len + 1);
-  cpp_hashnode *node;
-
-  memcpy (buf, str, len);
-  buf[len] = '\n';
-  cpp_push_buffer (pfile, buf, len, true);
-  node = lex_macro_node (pfile, true);
-  _cpp_pop_buffer (pfile);
-
-  return node;
-}
-
 /* If STR is a defined macro, return its definition node, else return NULL.  */
 cpp_macro *
 cpp_push_definition (cpp_reader *pfile, const char *str)
 {
-  cpp_hashnode *node = lex_macro_node_from_str (pfile, str);
+  cpp_hashnode *node = _cpp_lex_identifier (pfile, str);
   if (node && node->type == NT_MACRO)
     return node->value.macro;
   else
@@ -2258,7 +2335,7 @@ cpp_push_definition (cpp_reader *pfile, const char *str)
 void
 cpp_pop_definition (cpp_reader *pfile, const char *str, cpp_macro *dfn)
 {
-  cpp_hashnode *node = lex_macro_node_from_str (pfile, str);
+  cpp_hashnode *node = _cpp_lex_identifier (pfile, str);
   if (node == NULL)
     return;
 
diff --git a/libcpp/init.c b/libcpp/init.c
index e5be4e2b1b46..522ddbbb6381 100644
--- a/libcpp/init.c
+++ b/libcpp/init.c
@@ -216,6 +216,9 @@ cpp_create_reader (enum c_lang lang, hash_table *table,
   pfile->a_buff = _cpp_get_buff (pfile, 0);
   pfile->u_buff = _cpp_get_buff (pfile, 0);
 
+  /* Initialize table for push_macro/pop_macro.  */
+  pfile->pushed_macros = 0;
+
   /* The expression parser stack.  */
   _cpp_expand_op_stack (pfile);
 
@@ -245,6 +248,7 @@ void
 cpp_destroy (cpp_reader *pfile)
 {
   cpp_context *context, *contextn;
+  struct def_pragma_macro *pmacro;
   tokenrun *run, *runn;
   int i;
 
@@ -296,6 +300,17 @@ cpp_destroy (cpp_reader *pfile)
 
       free (pfile->comments.entries);
     }
+  if (pfile->pushed_macros)
+    {
+      do
+	{
+	  pmacro = pfile->pushed_macros;
+	  pfile->pushed_macros = pmacro->next;
+	  free (pmacro->name);
+	  free (pmacro);
+	}
+      while (pfile->pushed_macros);
+    }
 
   free (pfile);
 }
diff --git a/libcpp/internal.h b/libcpp/internal.h
index aaa231c2ab1c..555874c1d47b 100644
--- a/libcpp/internal.h
+++ b/libcpp/internal.h
@@ -305,6 +305,16 @@ struct cpp_buffer
   struct cset_converter input_cset_desc;
 };
 
+/* The list of saved macros by push_macro pragma.  */
+struct def_pragma_macro {
+  /* Chain element to previous saved macro.  */
+  struct def_pragma_macro *next;
+  /* Name of the macro.  */
+  char *name;
+  /* The stored macro content.  */
+  cpp_macro *value;
+};
+
 /* A cpp_reader encapsulates the "state" of a pre-processor run.
    Applying cpp_get_token repeatedly yields a stream of pre-processor
    tokens.  Usually, there is only one cpp_reader object active.  */
@@ -475,6 +485,9 @@ struct cpp_reader
 
   /* Table of comments, when state.save_comments is true.  */
   cpp_comment_table comments;
+
+  /* List of saved macros by push_macro.  */
+  struct def_pragma_macro *pushed_macros;
 };
 
 /* Character classes.  Based on the more primitive macros in safe-ctype.h.
@@ -575,6 +588,7 @@ extern const cpp_token *_cpp_lex_token (cpp_reader *);
 extern cpp_token *_cpp_lex_direct (cpp_reader *);
 extern int _cpp_equiv_tokens (const cpp_token *, const cpp_token *);
 extern void _cpp_init_tokenrun (tokenrun *, unsigned int);
+extern cpp_hashnode *_cpp_lex_identifier (cpp_reader *, const char *);
 
 /* In init.c.  */
 extern void _cpp_maybe_push_include_file (cpp_reader *);
diff --git a/libcpp/lex.c b/libcpp/lex.c
index 55bffa9a326e..ac28f92e6409 100644
--- a/libcpp/lex.c
+++ b/libcpp/lex.c
@@ -504,6 +504,63 @@ forms_identifier_p (cpp_reader *pfile, int first,
   return false;
 }
 
+/* Helper function to get the cpp_hashnode of the identifier BASE.  */
+static cpp_hashnode *
+lex_identifier_intern (cpp_reader *pfile, const uchar *base)
+{
+  cpp_hashnode *result;
+  const uchar *cur;
+  unsigned int len;
+  unsigned int hash = HT_HASHSTEP (0, *base);
+
+  cur = base + 1;
+  while (ISIDNUM (*cur))
+    {
+      hash = HT_HASHSTEP (hash, *cur);
+      cur++;
+    }
+  len = cur - base;
+  hash = HT_HASHFINISH (hash, len);
+  result = CPP_HASHNODE (ht_lookup_with_hash (pfile->hash_table,
+					      base, len, hash, HT_ALLOC));
+
+  /* Rarely, identifiers require diagnostics when lexed.  */
+  if (__builtin_expect ((result->flags & NODE_DIAGNOSTIC)
+			&& !pfile->state.skipping, 0))
+    {
+      /* It is allowed to poison the same identifier twice.  */
+      if ((result->flags & NODE_POISONED) && !pfile->state.poisoned_ok)
+	cpp_error (pfile, CPP_DL_ERROR, "attempt to use poisoned \"%s\"",
+		   NODE_NAME (result));
+
+      /* Constraint 6.10.3.5: __VA_ARGS__ should only appear in the
+	 replacement list of a variadic macro.  */
+      if (result == pfile->spec_nodes.n__VA_ARGS__
+	  && !pfile->state.va_args_ok)
+	cpp_error (pfile, CPP_DL_PEDWARN,
+		   "__VA_ARGS__ can only appear in the expansion"
+		   " of a C99 variadic macro");
+
+      /* For -Wc++-compat, warn about use of C++ named operators.  */
+      if (result->flags & NODE_WARN_OPERATOR)
+	cpp_error (pfile, CPP_DL_WARNING,
+		   "identifier \"%s\" is a special operator name in C++",
+		   NODE_NAME (result));
+    }
+
+  return result;
+}
+
+/* Get the cpp_hashnode of an identifier specified by NAME in
+   the current cpp_reader object.  If none is found, NULL is returned.  */
+cpp_hashnode *
+_cpp_lex_identifier (cpp_reader *pfile, const char *name)
+{
+  cpp_hashnode *result;
+  result = lex_identifier_intern (pfile, (uchar *) name);
+  return result;
+}
+
 /* Lex an identifier starting at BUFFER->CUR - 1.  */
 static cpp_hashnode *
 lex_identifier (cpp_reader *pfile, const uchar *base, bool starts_ucn,
diff --git a/libcpp/pch.c b/libcpp/pch.c
index f656418a1928..c70759a996d9 100644
--- a/libcpp/pch.c
+++ b/libcpp/pch.c
@@ -33,6 +33,8 @@ static int comp_hashnodes (const void *, const void *);
 static int collect_ht_nodes (cpp_reader *, cpp_hashnode *, void *);
 static int write_defs (cpp_reader *, cpp_hashnode *, void *);
 static int save_macros (cpp_reader *, cpp_hashnode *, void *);
+static int _cpp_save_pushed_macros (cpp_reader *, FILE *);
+static int _cpp_restore_pushed_macros (cpp_reader *, FILE *);
 
 /* This structure represents a macro definition on disk.  */
 struct macrodef_struct
@@ -378,9 +380,140 @@ cpp_write_pch_state (cpp_reader *r, FILE *f)
       return -1;
     }
 
+  /* Write saved macros.  */
+  if (! _cpp_save_pushed_macros (r, f))
+    {
+      cpp_errno (r, CPP_DL_ERROR, "while writing precompiled header");
+      return -1;
+    }
+
   return 0;
 }
 
+static int
+_cpp_restore_pushed_macros (cpp_reader *r, FILE *f)
+{
+  size_t count_saved = 0;
+  size_t i;
+  struct def_pragma_macro *p;
+  size_t nlen;
+  cpp_hashnode *h = NULL;
+  cpp_macro *m;
+  uchar *defn;
+  size_t defnlen;
+
+  if (fread (&count_saved, sizeof (count_saved), 1, f) != 1)
+    return 0;
+  if (! count_saved)
+    return 1;
+  for (i = 0; i < count_saved; i++)
+    {
+      if (fread (&nlen, sizeof (nlen), 1, f) != 1)
+	return 0;
+      p = XNEW (struct def_pragma_macro);
+      p->name = XNEWVAR (char, nlen + 1);
+      p->name[nlen] = 0;
+      if (fread (p->name, nlen, 1, f) != 1)
+	return 0;
+      /* Save old state.  */
+      m = cpp_push_definition (r, p->name);
+      if (fread (&defnlen, sizeof (defnlen), 1, f) != 1)
+	return 0;
+      defn = XNEWVAR (uchar, defnlen + 2);
+      defn[defnlen] = '\n';
+      defn[defnlen + 1] = 0;
+
+      if (fread (defn, defnlen, 1, f) != 1)
+	return 0;
+      cpp_pop_definition (r, p->name, NULL);
+      {
+	size_t namelen;
+	uchar *dn;
+
+	namelen = ustrcspn (defn, "( \n");
+	h = cpp_lookup (r, defn, namelen);
+	dn = defn + namelen;
+
+	h->type = NT_VOID;
+	h->flags &= ~(NODE_POISONED|NODE_BUILTIN|NODE_DISABLED|NODE_USED);
+	if (cpp_push_buffer (r, dn, ustrchr (dn, '\n') - dn, true)
+	    != NULL)
+	  {
+	    _cpp_clean_line (r);
+	    if (!_cpp_create_definition (r, h))
+	      abort ();
+	    _cpp_pop_buffer (r);
+	  }
+	else
+	  abort ();
+      }
+      p->value = cpp_push_definition (r, p->name);
+
+      free (defn);
+      p->next = r->pushed_macros;
+      r->pushed_macros = p;
+      /* Restore current state.  */
+      cpp_pop_definition (r, p->name, m);
+    }
+  return 1;
+}
+
+static int
+_cpp_save_pushed_macros (cpp_reader *r, FILE *f)
+{
+  size_t count_saved = 0;
+  size_t i;
+  struct def_pragma_macro *p,**pp;
+  cpp_hashnode *node;
+  cpp_macro *m;
+  size_t defnlen;
+  const uchar *defn;
+
+  /* Get count. */
+  p = r->pushed_macros;
+  while (p != NULL)
+    {
+      count_saved++;
+      p = p->next;
+    }
+  if (fwrite (&count_saved, sizeof (count_saved), 1, f) != 1)
+    return 0;
+  if (!count_saved)
+    return 1;
+
+  pp = (struct def_pragma_macro **) alloca (sizeof (struct def_pragma_macro *)
+					    * count_saved);
+  /* Store them in reverse order.  */
+  p = r->pushed_macros;
+  i = count_saved;
+  while (p != NULL)
+    {
+      --i;
+      pp[i] = p;
+      p = p->next;
+    }
+  for (i = 0; i < count_saved; i++)
+    {
+      /* Save old state.  */
+      m = cpp_push_definition (r, pp[i]->name);
+      /* Set temporary macro name to saved state.  */
+      cpp_pop_definition (r, pp[i]->name, pp[i]->value);
+      node = _cpp_lex_identifier (r, pp[i]->name);
+      defnlen = strlen (pp[i]->name);
+      if (fwrite (&defnlen, sizeof (size_t), 1, f) != 1
+	  || fwrite (pp[i]->name, defnlen, 1, f) != 1)
+	return 0;
+      defn = cpp_macro_definition (r, node);
+      defnlen = ustrlen (defn);
+      if (fwrite (&defnlen, sizeof (size_t), 1, f) != 1
+	  || fwrite (defn, defnlen, 1, f) != 1)
+	return 0;
+      /* Restore current state.  */
+      cpp_pop_definition (r, pp[i]->name, m);
+    }
+  return 1;
+}
+
 
 /* Data structure to transform hash table nodes into a sorted list */
 
@@ -752,6 +885,9 @@ cpp_read_state (cpp_reader *r, const char *name, FILE *f,
   if (!r->counter)
     r->counter = counter;
 
+  /* Read pushed macros. */
+  if (! _cpp_restore_pushed_macros (r, f))
+    goto error;
   return 0;
 
  error:
-- 
GitLab