diff --git a/libiberty/ChangeLog b/libiberty/ChangeLog
index 5a0aba8f0b276c8dbec81857e050527b1ecd0d9e..825ddd2d1fa4bee4b20e575d0251ef4ce3b2b595 100644
--- a/libiberty/ChangeLog
+++ b/libiberty/ChangeLog
@@ -1,3 +1,26 @@
+2013-11-22  Cary Coutant  <ccoutant@google.com>
+    
+	PR other/59195
+	* cp-demangle.c (struct d_info_checkpoint): New struct.
+	(struct d_print_info): Add current_template field.
+	(d_operator_name): Set flag when processing a conversion
+	operator.
+	(cplus_demangle_type): When processing <template-args> for
+	a conversion operator, backtrack if necessary.
+	(d_expression_1): Renamed from d_expression.
+	(d_expression): New wrapper around d_expression_1.
+	(d_checkpoint): New function.
+	(d_backtrack): New function.
+	(d_print_init): Initialize current_template.
+	(d_print_comp): Set current_template.
+	(d_print_cast): Put current_template in scope for
+	printing conversion operator name.
+	(cplus_demangle_init_info): Initialize is_expression and
+	is_conversion.
+	* cp-demangle.h (struct d_info): Add is_expression and
+	is_conversion fields.
+	* testsuite/demangle-expected: New test cases.
+
 2013-11-15  Andreas Schwab  <schwab@linux-m68k.org>
 
 	* configure: Regenerate.
diff --git a/libiberty/cp-demangle.c b/libiberty/cp-demangle.c
index cbe4d8c9f63256836e5038a48c2b644f763a1c08..029151e320aadddd23642470434b5aa90761f9e1 100644
--- a/libiberty/cp-demangle.c
+++ b/libiberty/cp-demangle.c
@@ -287,6 +287,19 @@ struct d_saved_scope
   struct d_print_template *templates;
 };
 
+/* Checkpoint structure to allow backtracking.  This holds copies
+   of the fields of struct d_info that need to be restored
+   if a trial parse needs to be backtracked over.  */
+
+struct d_info_checkpoint
+{
+  const char *n;
+  int next_comp;
+  int next_sub;
+  int did_subs;
+  int expansion;
+};
+
 enum { D_PRINT_BUFFER_LENGTH = 256 };
 struct d_print_info
 {
@@ -318,6 +331,8 @@ struct d_print_info
   struct d_saved_scope *saved_scopes;
   /* Number of saved scopes in the above array.  */
   int num_saved_scopes;
+  /* The nearest enclosing template, if any.  */
+  const struct demangle_component *current_template;
 };
 
 #ifdef CP_DEMANGLE_DEBUG
@@ -444,6 +459,10 @@ d_add_substitution (struct d_info *, struct demangle_component *);
 
 static struct demangle_component *d_substitution (struct d_info *, int);
 
+static void d_checkpoint (struct d_info *, struct d_info_checkpoint *);
+
+static void d_backtrack (struct d_info *, struct d_info_checkpoint *);
+
 static void d_growable_string_init (struct d_growable_string *, size_t);
 
 static inline void
@@ -1734,8 +1753,15 @@ d_operator_name (struct d_info *di)
   if (c1 == 'v' && IS_DIGIT (c2))
     return d_make_extended_operator (di, c2 - '0', d_source_name (di));
   else if (c1 == 'c' && c2 == 'v')
-    return d_make_comp (di, DEMANGLE_COMPONENT_CAST,
-			cplus_demangle_type (di), NULL);
+    {
+      struct demangle_component *type;
+      int was_conversion = di->is_conversion;
+
+      di->is_conversion = ! di->is_expression;
+      type = cplus_demangle_type (di);
+      di->is_conversion = was_conversion;
+      return d_make_comp (di, DEMANGLE_COMPONENT_CAST, type, NULL);
+    }
   else
     {
       /* LOW is the inclusive lower bound.  */
@@ -2284,13 +2310,61 @@ cplus_demangle_type (struct d_info *di)
       ret = d_template_param (di);
       if (d_peek_char (di) == 'I')
 	{
-	  /* This is <template-template-param> <template-args>.  The
-	     <template-template-param> part is a substitution
+	  /* This may be <template-template-param> <template-args>.
+	     If this is the type for a conversion operator, we can
+	     have a <template-template-param> here only by following
+	     a derivation like this:
+
+	     <nested-name>
+	     -> <template-prefix> <template-args>
+	     -> <prefix> <template-unqualified-name> <template-args>
+	     -> <unqualified-name> <template-unqualified-name> <template-args>
+	     -> <source-name> <template-unqualified-name> <template-args>
+	     -> <source-name> <operator-name> <template-args>
+	     -> <source-name> cv <type> <template-args>
+	     -> <source-name> cv <template-template-param> <template-args> <template-args>
+
+	     where the <template-args> is followed by another.
+	     Otherwise, we must have a derivation like this:
+
+	     <nested-name>
+	     -> <template-prefix> <template-args>
+	     -> <prefix> <template-unqualified-name> <template-args>
+	     -> <unqualified-name> <template-unqualified-name> <template-args>
+	     -> <source-name> <template-unqualified-name> <template-args>
+	     -> <source-name> <operator-name> <template-args>
+	     -> <source-name> cv <type> <template-args>
+	     -> <source-name> cv <template-param> <template-args>
+
+	     where we need to leave the <template-args> to be processed
+	     by d_prefix (following the <template-prefix>).
+
+	     The <template-template-param> part is a substitution
 	     candidate.  */
-	  if (! d_add_substitution (di, ret))
-	    return NULL;
-	  ret = d_make_comp (di, DEMANGLE_COMPONENT_TEMPLATE, ret,
-			     d_template_args (di));
+	  if (! di->is_conversion)
+	    {
+	      if (! d_add_substitution (di, ret))
+		return NULL;
+	      ret = d_make_comp (di, DEMANGLE_COMPONENT_TEMPLATE, ret,
+				 d_template_args (di));
+	    }
+	  else
+	    {
+	      struct demangle_component *args;
+	      struct d_info_checkpoint checkpoint;
+
+	      d_checkpoint (di, &checkpoint);
+	      args = d_template_args (di);
+	      if (d_peek_char (di) == 'I')
+		{
+		  if (! d_add_substitution (di, ret))
+		    return NULL;
+		  ret = d_make_comp (di, DEMANGLE_COMPONENT_TEMPLATE, ret,
+				     args);
+		}
+	      else
+		d_backtrack (di, &checkpoint);
+	    }
 	}
       break;
 
@@ -2976,8 +3050,8 @@ op_is_new_cast (struct demangle_component *op)
                 ::= <expr-primary>
 */
 
-static struct demangle_component *
-d_expression (struct d_info *di)
+static inline struct demangle_component *
+d_expression_1 (struct d_info *di)
 {
   char peek;
 
@@ -3005,7 +3079,7 @@ d_expression (struct d_info *di)
     {
       d_advance (di, 2);
       return d_make_comp (di, DEMANGLE_COMPONENT_PACK_EXPANSION,
-			  d_expression (di), NULL);
+			  d_expression_1 (di), NULL);
     }
   else if (peek == 'f' && d_peek_next_char (di) == 'p')
     {
@@ -3110,7 +3184,7 @@ d_expression (struct d_info *di)
 		&& d_check_char (di, '_'))
 	      operand = d_exprlist (di, 'E');
 	    else
-	      operand = d_expression (di);
+	      operand = d_expression_1 (di);
 
 	    if (suffix)
 	      /* Indicate the suffix variant for d_print_comp.  */
@@ -3130,7 +3204,7 @@ d_expression (struct d_info *di)
 	    if (op_is_new_cast (op))
 	      left = cplus_demangle_type (di);
 	    else
-	      left = d_expression (di);
+	      left = d_expression_1 (di);
 	    if (!strcmp (code, "cl"))
 	      right = d_exprlist (di, 'E');
 	    else if (!strcmp (code, "dt") || !strcmp (code, "pt"))
@@ -3141,7 +3215,7 @@ d_expression (struct d_info *di)
 				       right, d_template_args (di));
 	      }
 	    else
-	      right = d_expression (di);
+	      right = d_expression_1 (di);
 
 	    return d_make_comp (di, DEMANGLE_COMPONENT_BINARY, op,
 				d_make_comp (di,
@@ -3157,9 +3231,9 @@ d_expression (struct d_info *di)
 	    if (!strcmp (code, "qu"))
 	      {
 		/* ?: expression.  */
-		first = d_expression (di);
-		second = d_expression (di);
-		third = d_expression (di);
+		first = d_expression_1 (di);
+		second = d_expression_1 (di);
+		third = d_expression_1 (di);
 	      }
 	    else if (code[0] == 'n')
 	      {
@@ -3183,7 +3257,7 @@ d_expression (struct d_info *di)
 		else if (d_peek_char (di) == 'i'
 			 && d_peek_next_char (di) == 'l')
 		  /* initializer-list.  */
-		  third = d_expression (di);
+		  third = d_expression_1 (di);
 		else
 		  return NULL;
 	      }
@@ -3203,6 +3277,18 @@ d_expression (struct d_info *di)
     }
 }
 
+static struct demangle_component *
+d_expression (struct d_info *di)
+{
+  struct demangle_component *ret;
+  int was_expression = di->is_expression;
+
+  di->is_expression = 1;
+  ret = d_expression_1 (di);
+  di->is_expression = was_expression;
+  return ret;
+}
+
 /* <expr-primary> ::= L <type> <(value) number> E
                   ::= L <type> <(value) float> E
                   ::= L <mangled-name> E
@@ -3588,6 +3674,26 @@ d_substitution (struct d_info *di, int prefix)
     }
 }
 
+static void
+d_checkpoint (struct d_info *di, struct d_info_checkpoint *checkpoint)
+{
+  checkpoint->n = di->n;
+  checkpoint->next_comp = di->next_comp;
+  checkpoint->next_sub = di->next_sub;
+  checkpoint->did_subs = di->did_subs;
+  checkpoint->expansion = di->expansion;
+}
+
+static void
+d_backtrack (struct d_info *di, struct d_info_checkpoint *checkpoint)
+{
+  di->n = checkpoint->n;
+  di->next_comp = checkpoint->next_comp;
+  di->next_sub = checkpoint->next_sub;
+  di->did_subs = checkpoint->did_subs;
+  di->expansion = checkpoint->expansion;
+}
+
 /* Initialize a growable string.  */
 
 static void
@@ -3684,6 +3790,7 @@ d_print_init (struct d_print_info *dpi, demangle_callbackref callback,
 
   dpi->saved_scopes = NULL;
   dpi->num_saved_scopes = 0;
+  dpi->current_template = NULL;
 }
 
 /* Free a print information structure.  */
@@ -4165,6 +4272,12 @@ d_print_comp (struct d_print_info *dpi, int options,
       {
 	struct d_print_mod *hold_dpm;
 	struct demangle_component *dcl;
+	const struct demangle_component *hold_current;
+
+	/* This template may need to be referenced by a cast operator
+	   contained in its subtree.  */
+	hold_current = dpi->current_template;
+	dpi->current_template = dc;
 
 	/* Don't push modifiers into a template definition.  Doing so
 	   could give the wrong definition for a template argument.
@@ -4201,6 +4314,7 @@ d_print_comp (struct d_print_info *dpi, int options,
           }
 
 	dpi->modifiers = hold_dpm;
+	dpi->current_template = hold_current;
 
 	return;
       }
@@ -5418,28 +5532,32 @@ static void
 d_print_cast (struct d_print_info *dpi, int options,
               const struct demangle_component *dc)
 {
-  if (d_left (dc)->type != DEMANGLE_COMPONENT_TEMPLATE)
-    d_print_comp (dpi, options, d_left (dc));
-  else
-    {
-      struct d_print_mod *hold_dpm;
-      struct d_print_template dpt;
-
-      /* It appears that for a templated cast operator, we need to put
-	 the template parameters in scope for the operator name, but
-	 not for the parameters.  The effect is that we need to handle
-	 the template printing here.  */
-
-      hold_dpm = dpi->modifiers;
-      dpi->modifiers = NULL;
+  struct d_print_template dpt;
 
+  /* For a cast operator, we need the template parameters from
+     the enclosing template in scope for processing the type.  */
+  if (dpi->current_template != NULL)
+    {
       dpt.next = dpi->templates;
       dpi->templates = &dpt;
-      dpt.template_decl = d_left (dc);
+      dpt.template_decl = dpi->current_template;
+    }
 
+  if (d_left (dc)->type != DEMANGLE_COMPONENT_TEMPLATE)
+    {
+      d_print_comp (dpi, options, d_left (dc));
+      if (dpi->current_template != NULL)
+	dpi->templates = dpt.next;
+    }
+  else
+    {
       d_print_comp (dpi, options, d_left (d_left (dc)));
 
-      dpi->templates = dpt.next;
+      /* For a templated cast operator, we need to remove the template
+	 parameters from scope after printing the operator name,
+	 so we need to handle the template printing here.  */
+      if (dpi->current_template != NULL)
+	dpi->templates = dpt.next;
 
       if (d_last_char (dpi) == '<')
 	d_append_char (dpi, ' ');
@@ -5450,8 +5568,6 @@ d_print_cast (struct d_print_info *dpi, int options,
       if (d_last_char (dpi) == '>')
 	d_append_char (dpi, ' ');
       d_append_char (dpi, '>');
-
-      dpi->modifiers = hold_dpm;
     }
 }
 
@@ -5484,6 +5600,8 @@ cplus_demangle_init_info (const char *mangled, int options, size_t len,
   di->last_name = NULL;
 
   di->expansion = 0;
+  di->is_expression = 0;
+  di->is_conversion = 0;
 }
 
 /* Internal implementation for the demangler.  If MANGLED is a g++ v3 ABI
diff --git a/libiberty/cp-demangle.h b/libiberty/cp-demangle.h
index ae635beb4cc767eb39d3b5cba17789df08efe4de..6fce0252dc4d0665c6812047e9ad8fa73b0c9978 100644
--- a/libiberty/cp-demangle.h
+++ b/libiberty/cp-demangle.h
@@ -122,6 +122,11 @@ struct d_info
      mangled name to the demangled name, such as standard
      substitutions and builtin types.  */
   int expansion;
+  /* Non-zero if we are parsing an expression.  */
+  int is_expression;
+  /* Non-zero if we are parsing the type operand of a conversion
+     operator, but not when in an expression.  */
+  int is_conversion;
 };
 
 /* To avoid running past the ending '\0', don't:
diff --git a/libiberty/testsuite/demangle-expected b/libiberty/testsuite/demangle-expected
index ae872078d9152713e04241e11bbdc9263b82a144..3ff08e6e5f2255c483122b0606116e01c299331d 100644
--- a/libiberty/testsuite/demangle-expected
+++ b/libiberty/testsuite/demangle-expected
@@ -4297,3 +4297,23 @@ void f<int>()
 --format=gnu-v3
 _ZSt7forwardIRN1x14refobjiteratorINS0_3refINS0_4mime30multipart_section_processorObjIZ15get_body_parserIZZN14mime_processor21make_section_iteratorERKNS2_INS3_10sectionObjENS0_10ptrrefBaseEEEbENKUlvE_clEvEUlSB_bE_ZZNS6_21make_section_iteratorESB_bENKSC_clEvEUlSB_E0_ENS1_INS2_INS0_20outputrefiteratorObjIiEES8_EEEERKSsSB_OT_OT0_EUlmE_NS3_32make_multipart_default_discarderISP_EEEES8_EEEEEOT_RNSt16remove_referenceISW_E4typeE
 x::refobjiterator<x::ref<x::mime::multipart_section_processorObj<x::refobjiterator<x::ref<x::outputrefiteratorObj<int>, x::ptrrefBase> > get_body_parser<mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)#1}, mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&)#2}>(std::string const&, x::ref<x::mime::sectionObj, x::ptrrefBase> const&, mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)#1}&&, mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&)#2}&&)::{lambda(unsigned long)#1}, x::mime::make_multipart_default_discarder<mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)#1}&&> >, x::ptrrefBase> >& std::forward<x::refobjiterator<x::ref<x::mime::multipart_section_processorObj<x::refobjiterator<x::ref<x::outputrefiteratorObj<int>, x::ptrrefBase> > get_body_parser<mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)#1}, mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&)#2}>(std::string const&, x::ref<x::mime::sectionObj, x::ptrrefBase> const&, mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)#1}&&, mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&)#2}&&)::{lambda(unsigned long)#1}, x::mime::make_multipart_default_discarder<mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)#1}&&> >, x::ptrrefBase> >&>(std::remove_reference<x::mime::multipart_section_processorObj<x::refobjiterator<x::ref<x::outputrefiteratorObj<int>, x::ptrrefBase> > get_body_parser<mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)#1}, mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&)#2}>(std::string const&, x::ref<x::mime::sectionObj, x::ptrrefBase> const&, mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)#1}&&, mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&)#2}&&)::{lambda(unsigned long)#1}, x::mime::make_multipart_default_discarder<mime_processor::make_section_iterator(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)::{lambda()#1}::operator()() const::{lambda(x::ref<x::mime::sectionObj, x::ptrrefBase> const&, bool)#1}&&> > >::type&)
+#
+--format=gnu-v3 --no-params
+_ZNK7strings8internal8SplitterINS_9delimiter5AnyOfENS_9SkipEmptyEEcvT_ISt6vectorI12basic_stringIcSt11char_traitsIcESaIcEESaISD_EEvEEv
+strings::internal::Splitter<strings::delimiter::AnyOf, strings::SkipEmpty>::operator std::vector<basic_string<char, std::char_traits<char>, std::allocator<char> >, std::allocator<basic_string<char, std::char_traits<char>, std::allocator<char> > > ><std::vector<basic_string<char, std::char_traits<char>, std::allocator<char> >, std::allocator<basic_string<char, std::char_traits<char>, std::allocator<char> > > >, void>() const
+strings::internal::Splitter<strings::delimiter::AnyOf, strings::SkipEmpty>::operator std::vector<basic_string<char, std::char_traits<char>, std::allocator<char> >, std::allocator<basic_string<char, std::char_traits<char>, std::allocator<char> > > ><std::vector<basic_string<char, std::char_traits<char>, std::allocator<char> >, std::allocator<basic_string<char, std::char_traits<char>, std::allocator<char> > > >, void>
+#
+--format=gnu-v3 --no-params
+_ZN1AcvT_I1CEEv
+A::operator C<C>()
+A::operator C<C>
+#
+--format=gnu-v3 --no-params
+_ZN1AcvPT_I1CEEv
+A::operator C*<C>()
+A::operator C*<C>
+#
+--format=gnu-v3 --no-params
+_ZN1AcvT_IiEI1CEEv
+A::operator C<int><C>()
+A::operator C<int><C>