diff --git a/gcc/cobol/cbldiag.h b/gcc/cobol/cbldiag.h
index aeef96ebab6624fe7a294d29393e5bc0129d71d0..b6b4ac75d7d81030228571271abf61f0080e84bd 100644
--- a/gcc/cobol/cbldiag.h
+++ b/gcc/cobol/cbldiag.h
@@ -35,4 +35,7 @@ const char * cobol_filename();
 void yyerror( const char fmt[], ... );
 void yyerrorvl( int line, const char *filename, const char fmt[], ... );
 
+void cbl_unimplementedw(const char *gmsgid, ...);
+void cbl_unimplemented(const char *gmsgid, ...);
+
 bool yywarn( const char fmt[], ... );
diff --git a/gcc/cobol/cdf.y b/gcc/cobol/cdf.y
index adc46f3d884402a3c82a2f1f995d4f4153f84352..be9040a3e3bc2fc4843bf63db8c7e5515952f606 100644
--- a/gcc/cobol/cdf.y
+++ b/gcc/cobol/cdf.y
@@ -145,7 +145,7 @@ static class exception_turns_t {
   bool add_exception( ec_type_t type, const filelist_t files = filelist_t() ) {
     ec_disposition_t disposition = ec_type_disposition(type);
     if( disposition != ec_implemented(disposition) ) {
-      yywarn("CDF: exception '%s' is not implemented", ec_type_str(type));
+	cbl_unimplementedw("CDF: exception '%s'", ec_type_str(type));
     }
     auto elem = exceptions.find(type);
     if( elem != exceptions.end() ) return false; // cannot add twice
diff --git a/gcc/cobol/cobol1.cc b/gcc/cobol/cobol1.cc
index 6c69c0426a35eb659b5356b45342a432c5a8ec1a..320a76ca61164caafa639f02cea88132c53b816a 100644
--- a/gcc/cobol/cobol1.cc
+++ b/gcc/cobol/cobol1.cc
@@ -165,7 +165,7 @@ enable_exceptions( bool enable ) {
     }
     ec_disposition_t disposition = ec_type_disposition(type);
     if( disposition != ec_implemented(disposition) ) {
-      yyerror("exception '%s' is not implemented", name);
+      cbl_unimplemented("exception '%s'", name);
     }
     add_cobol_exception(type, enable );
   }
diff --git a/gcc/cobol/genapi.cc b/gcc/cobol/genapi.cc
index bff4b49cb3fed850c489e2d83724c934f31e75eb..59b32b9c04570466aa947a8f61fb3256ddf6f5c1 100644
--- a/gcc/cobol/genapi.cc
+++ b/gcc/cobol/genapi.cc
@@ -12225,8 +12225,8 @@ create_and_call(size_t narg,
         if(    (args[i].refer.field->attr & intermediate_e)
             && is_valuable(args[i].refer.field->type) )
           {
-          yyerror("CALL USING BY CONTENT <temporary> is not possible "
-                    "until REPOSITORY PROTOTYPES are implemented.");
+          cbl_unimplemented("CALL USING BY CONTENT <temporary> would require "
+			    "REPOSITORY PROTOTYPES.");
           }
 
         // BY CONTENT means that the called program gets a copy of the data.
diff --git a/gcc/cobol/parse.y b/gcc/cobol/parse.y
index a692bdc7741c96f37c56bb89bb1a8bc428fa4cc8..9753dee9f7f59ecd3b0184e189681763db693f2d 100644
--- a/gcc/cobol/parse.y
+++ b/gcc/cobol/parse.y
@@ -997,12 +997,16 @@ cobol_words1:	COBOL_WORDS EQUATE NAME[keyword] WITH NAME[name] {
 
 program_id:     PROGRAM_ID dot namestr[name] program_as program_attrs[attr] dot
                 {
-                  const char *name = string_of($name);
-
                   internal_ebcdic_lock();
                   current_division = identification_div_e;
                   parser_division( identification_div_e, NULL, 0, NULL );
                   location_set(@1);
+
+                  const char *name = string_of($name);
+		  if( 0 == strcasecmp(name, "main") ) {
+                    yyerror("PROGRAM-ID 'main' is invalid under Posix");
+		  }
+
                   parser_enter_program( name, false );
                   if( symbols_begin() == symbols_end() ) {
                     symbol_table_init();
@@ -1031,6 +1035,11 @@ function_id:    FUNCTION '.' NAME program_as program_attrs[attr] '.'
                   current_division = identification_div_e;
                   parser_division( identification_div_e, NULL, 0, NULL );
                   location_set(@1);
+
+		  if( 0 == strcasecmp($NAME, "main") ) {
+                    yyerror("FUNCTION 'main' is invalid under Posix");
+		  }
+
                   parser_enter_program( $NAME, true );
                   if( symbols_begin() == symbols_end() ) {
                     symbol_table_init();
@@ -1053,7 +1062,7 @@ function_id:    FUNCTION '.' NAME program_as program_attrs[attr] '.'
                 }
         |       FUNCTION '.' NAME program_as is PROTOTYPE '.'
                 {
-                  yyerror("FUNCTION PROTOTYPE: not implemented");
+                  cbl_unimplemented("FUNCTION PROTOTYPE");
                 }
                 ;
 
@@ -1070,7 +1079,7 @@ opt_clause:     opt_arith
         |       opt_entry
         |       opt_binary
         |       opt_decimal {
-		  yywarn("unimplemented type FLOAT-DECIMAL was ignored");
+		  cbl_unimplementedw("type FLOAT-DECIMAL was ignored");
 		}
         |       opt_intermediate
         |       opt_init
@@ -1097,14 +1106,14 @@ opt_entry:      ENTRY_CONVENTION is COBOL {
                 ;
 opt_binary:     FLOAT_BINARY default_kw is HIGH_ORDER_LEFT
 		{
-		  yywarn("unimplemented type HIGH-ORDER-LEFT was ignored");
+		  cbl_unimplementedw("HIGH-ORDER-LEFT was ignored");
 		  if( ! current.option_binary(cbl_options_t::high_order_left_e) ) {
 		    yyerror("unable to set HIGH_ORDER_LEFT");
 		  }
 		}
         |       FLOAT_BINARY default_kw is HIGH_ORDER_RIGHT
 		{
-		  yywarn("unimplemented type HIGH-ORDER-RIGHT was ignored");
+		  cbl_unimplementedw("HIGH-ORDER-RIGHT was ignored");
 		  if( ! current.option_binary(cbl_options_t::high_order_right_e) ) {
 		    yyerror("unable to set HIGH_ORDER_RIGHT");
 		  }
@@ -1115,28 +1124,28 @@ default_kw:     %empty
                 ;
 opt_decimal:    FLOAT_DECIMAL default_kw is HIGH_ORDER_LEFT
 		{
-		  yywarn("unimplemented type HIGH-ORDER-LEFT was ignored");
+		  cbl_unimplementedw("HIGH-ORDER-LEFT was ignored");
 		  if( ! current.option_decimal(cbl_options_t::high_order_left_e) ) {
 		    yyerror("unable to set HIGH_ORDER_LEFT");
 		  }
 		}
         |       FLOAT_DECIMAL default_kw is HIGH_ORDER_RIGHT
 		{
-		  yywarn("unimplemented type HIGH-ORDER-RIGHT was ignored");
+		  cbl_unimplementedw("HIGH-ORDER-RIGHT was ignored");
 		  if( ! current.option_decimal(cbl_options_t::high_order_right_e) ) {
 		    yyerror("unable to set HIGH_ORDER_RIGHT");
 		  }
 		}
         |       FLOAT_DECIMAL default_kw is BINARY_ENCODING
 		{
-		  yywarn("unimplemented type BINARY-ENCODING was ignored");
+		  cbl_unimplementedw("BINARY-ENCODING was ignored");
 		  if( ! current.option(cbl_options_t::binary_encoding_e) ) {
 		    yyerror("unable to set BINARY-ENCODING option");
 		  }
 		}
         |       FLOAT_DECIMAL default_kw is DECIMAL_ENCODING
 		{
-		  yywarn("unimplemented type DECIMAL-ENCODING was ignored");
+		  cbl_unimplementedw("DECIMAL-ENCODING was ignored");
 		  if( ! current.option(cbl_options_t::decimal_encoding_e) ) {
 		    yyerror("unable to set DECIMAL-ENCODING option");
 		  }
@@ -1190,7 +1199,7 @@ opt_init_sects: ALL { $$.local = $$.working = true; }
 		}
                 ;
 opt_init_sect:  LOCAL_STORAGE   { $$ = local_sect_e; }
-        |       SCREEN { yyerror("SCREEN SECTION is not implemented"); }
+        |       SCREEN { cbl_unimplemented("SCREEN SECTION"); }
         |       WORKING_STORAGE { $$ = working_sect_e; }
         ;
 opt_init_value: BINARY ZERO { $$ = constant_index(NULLS); }
@@ -1321,7 +1330,7 @@ io_control_clause:
                 }
         |       APPLY COMMIT on field_list
                 {
-                  yywarn("I-O-CONTROL APPLY COMMIT is not implemented");
+                  cbl_unimplementedw("I-O-CONTROL APPLY COMMIT");
                 }
                 ;
 area:           %empty
@@ -1630,12 +1639,12 @@ assign_clause:  ASSIGN to selected_name[selected]  {
                 }
         |       ASSIGN to device_name USING name {
                   $$.clause = assign_clause_e;
-		  yyerror("ASSIGN TO DEVICE not implemented");
+		  cbl_unimplemented("ASSIGN TO DEVICE");
 		  YYERROR;
                 }
         |       ASSIGN to device_name {
                   $$.clause = assign_clause_e;
-		  yyerror("ASSIGN TO DEVICE not implemented");
+		  cbl_unimplemented("ASSIGN TO DEVICE");
 		  YYERROR;
                 }
         |       ASSIGN USING name {
@@ -1811,13 +1820,13 @@ repo_members:   repo_member
         |       repo_members repo_member
                 ;
 repo_member:    repo_class
-                { yyerror("CLASS not implemented"); }
+                { cbl_unimplemented("CLASS"); }
         |       repo_interface
-                { yyerror("INTERFACE not implemented"); }
+                { cbl_unimplemented("INTERFACE"); }
         |       repo_func
         |       repo_program
         |       repo_property
-                { yyerror("PROPERTY not implemented"); }
+                { cbl_unimplemented("PROPERTY"); }
                 ;
 
 repo_class:     CLASS NAME repo_as repo_expands
@@ -1973,14 +1982,14 @@ special_name:   dev_mnemonic
         |       LOCALE NAME is locale_spec
                 {
                   current.locale($NAME, $locale_spec);
-                  yyerror("%s:%d: LOCALE syntax not implemented",
+                  cbl_unimplemented("%s:%d: LOCALE syntax",
                            __FILE__, __LINE__);
                 }
                 ;
         |       upsi
         |       SYMBOLIC characters symbolic is_alphabet
                 {
-                  yyerror("%s:%d: SYMBOLIC syntax not implemented",
+                  cbl_unimplemented("%s:%d: SYMBOLIC syntax",
                            __FILE__, __LINE__);
                 }
                 ;
@@ -2399,7 +2408,7 @@ data_section:   FILE_SECT '.'
                   current_data_section_set(linkage_datasect_e);
                 } fields_maybe
 	|	SCREEN SECTION '.' {
-		  yyerror("SCREEN SECTION not implemented");
+		  cbl_unimplemented("SCREEN SECTION");
 		}
                 ;
 
@@ -2468,11 +2477,11 @@ fd_clause:      record_desc
                 {
                   auto f = cbl_file_of(symbol_at(file_section_fd));
                   f->attr |= external_e;
-                  yyerror("AS LITERAL  not implemented");
+                  cbl_unimplemented("AS LITERAL ");
                 }
         |       fd_linage
         |       fd_report {
-                  yyerror("REPORT WRITER not implemented");
+                  cbl_unimplemented("REPORT WRITER");
                   YYERROR;
                 }
                 ;
@@ -3903,7 +3912,7 @@ usage_clause1:  usage COMPUTATIONAL[comp]   native
                 }
         |       usage POINTER TO error
                 {
-                  yyerror("POINTER TO is not implemented");
+                  cbl_unimplemented("POINTER TO");
                   $$ = FldPointer;
                 }
 		;
@@ -5249,7 +5258,7 @@ exit_raising:   RAISING EXCEPTION EXCEPTION_NAME[ec]
 		  $$ = $ec;
 		}
 	|	RAISING error {
-		  yyerror("RAISING exception-object not implemented");
+		  cbl_unimplemented("RAISING exception-object");
 		  $$ = ec_none_e;
 		}
 	|	RAISING LAST /* lexer swallows EXCEPTION */
@@ -6550,9 +6559,9 @@ section_kw:     SECTION
                 {
                   if( $1 ) {
 		    if( *$1 == '-' ) {
-		      yyerror("section segment %s is negative", $1);
+		      yyerror("SECTION segment %s is negative", $1);
                     } else {
-                      yywarn("section segment %s was ignored", $1);
+                      cbl_unimplementedw("SECTION segment %s was ignored", $1);
                     }
 		  }
                 }
@@ -7301,7 +7310,7 @@ raise:          RAISE EXCEPTION NAME
                              "EXCEPTION CONDITION: %s", $NAME);
                     YYERROR;
                   }
-                  yyerror("RAISE <EXCEPTION OBJECT> is not implemented");
+                  cbl_unimplemented("RAISE <EXCEPTION OBJECT>");
                   YYERROR;
                 }
                 ;
@@ -7995,7 +8004,7 @@ set:            SET set_tgts[tgts] TO set_operand[src]
         |       SET LENGTH_OF scalar TO scalar
                 {
                   statement_begin(@1, SET);
-                  yyerror("SET LENGTH OF is not implemented");
+                  cbl_unimplemented("SET LENGTH OF");
                   YYERROR;
                 }
         |       SET scalar88s[names] TO true_false[yn]
@@ -9141,7 +9150,7 @@ alter_tgt:      label_1[old] alter_to label_1[new]
 
                   auto prog = cbl_label_of( symbol_at(symbol_elem_of($old)->program));
                   if( prog->initial ) {
-                    yyerror("ALTER %s is not implemented", $old->name);
+                    cbl_unimplemented("ALTER %s", $old->name);
                   }
                 }
                 ;
@@ -9179,7 +9188,7 @@ go_to:          GOTO labels[args]
                 }
         |       GOTO
                 {
-                  yyerror("%s:%d: altered GO TO syntax (format 3) not implemented",
+                  cbl_unimplemented("%s:%d: altered GO TO syntax (format 3)",
                            __FILE__, __LINE__);
                   YYERROR;
                 }
@@ -9612,7 +9621,7 @@ intrinsic:      function_udf
 	|       BASECONVERT  '(' varg[r1] varg[r2] varg[r3] ')' {
                   location_set(@1);
                   $$ = new_tempnumeric();
-		  yyerror("BASECONVERT not implemented");
+		  cbl_unimplemented("BASECONVERT");
                   if( ! intrinsic_call_3($$, BASECONVERT, $r1, $r2, $r3 )) YYERROR;
                 }
         |       BIT_OF  '(' expr[r1] ')' {
@@ -9629,7 +9638,7 @@ intrinsic:      function_udf
 	|       CONVERT  '(' varg[r1] convert_src[src] convert_dst[dst] ')' {
                   location_set(@1);
                   $$ = new_alphanumeric(1);
-		  yyerror("CONVERT not implemented");
+		  cbl_unimplemented("CONVERT");
                   /* if( ! intrinsic_call_3($$, CONVERT, $r1, $src, $dst) ) YYERROR; */
                 }
 
@@ -9657,7 +9666,7 @@ intrinsic:      function_udf
                   location_set(@1);
                   $$ = new_alphanumeric($r1->field->data.capacity);
                   /* auto r1 = new_reference(new_literal(strlen($r1), $r1, quoted_e)); */
-		  yyerror("FIND_STRING not implemented");
+		  cbl_unimplemented("FIND_STRING");
                   /* if( ! intrinsic_call_4($$, FIND_STRING, r1, $r2) ) YYERROR; */
                 }
 
@@ -9826,21 +9835,21 @@ intrinsic:      function_udf
                 {
                   location_set(@1);
                   $$ = new_tempnumeric();
-		  yyerror("STANDARD-COMPARE not implemented");
+		  cbl_unimplemented("STANDARD-COMPARE");
                   /* if( ! intrinsic_call_4($$, STANDARD_COMPARE, $r1) ) YYERROR; */
                 }
         |       STANDARD_COMPARE  '(' varg[r1] varg[r2] varg[r3]  ')'
                 {
                   location_set(@1);
                   $$ = new_tempnumeric();
-		  yyerror("STANDARD-COMPARE not implemented");
+		  cbl_unimplemented("STANDARD-COMPARE");
                   /* if( ! intrinsic_call_4($$, STANDARD_COMPARE, $r1) ) YYERROR; */
                 }
         |       STANDARD_COMPARE  '(' varg[r1] varg[r2] ')'
                 {
                   location_set(@1);
                   $$ = new_tempnumeric();
-		  yyerror("STANDARD-COMPARE not implemented");
+		  cbl_unimplemented("STANDARD-COMPARE");
                   /* if( ! intrinsic_call_4($$, STANDARD_COMPARE, $r1) ) YYERROR; */
                 }
 
@@ -10136,7 +10145,7 @@ numval_locale:  %empty {
                   $$.arg2 = cbl_refer_t::empty();
                 }
         |       LOCALE NAME  { $$.is_locale = true;  $$.arg2 = NULL;
-                  yyerror("NUMVAL_C LOCALE is not implemented"); YYERROR;
+                  cbl_unimplemented("NUMVAL_C LOCALE"); YYERROR;
                 }
         |       varg         { $$.is_locale = false; $$.arg2 = $1; }
                 ;
@@ -10280,10 +10289,10 @@ intrinsic0:     CURRENT_DATE {
                 ;
 
 intrinsic_I:    BOOLEAN_OF_INTEGER     { $$ = BOOLEAN_OF_INTEGER;
-		  yyerror("BOOLEAN-OF-INTEGER not implemented");
+		  cbl_unimplemented("BOOLEAN-OF-INTEGER");
 		}
         |       CHAR_NATIONAL          { $$ = CHAR_NATIONAL;
-		    yyerror("CHAR-NATIONAL not implemented");
+		    cbl_unimplemented("CHAR-NATIONAL");
 		}
         |       DATE_OF_INTEGER        { $$ = DATE_OF_INTEGER; }
         |       DAY_OF_INTEGER         { $$ = DAY_OF_INTEGER; }
@@ -10292,7 +10301,7 @@ intrinsic_I:    BOOLEAN_OF_INTEGER     { $$ = BOOLEAN_OF_INTEGER;
         |       HIGHEST_ALGEBRAIC      { $$ = HIGHEST_ALGEBRAIC; }
         |       INTEGER                { $$ = INTEGER; }
         |       INTEGER_OF_BOOLEAN     { $$ = INTEGER_OF_BOOLEAN; 
-		    yyerror("INTEGER-OF-BOOLEAN not implemented");
+		    cbl_unimplemented("INTEGER-OF-BOOLEAN");
 		}
         |       INTEGER_OF_DATE        { $$ = INTEGER_OF_DATE; }
         |       INTEGER_OF_DAY         { $$ = INTEGER_OF_DAY; }
@@ -10322,7 +10331,7 @@ intrinsic_N:    ABS                    { $$ = ABS; }
         |       LOG10                  { $$ = LOG10; }
         |       SIN                    { $$ = SIN; }
         |       SMALLEST_ALGEBRAIC     { $$ = SMALLEST_ALGEBRAIC;  
-		    yyerror("SMALLEST-ALGEBRAIC not implemented");
+		    cbl_unimplemented("SMALLEST-ALGEBRAIC");
 		}
         |       SQRT                   { $$ = SQRT; }
         |       TAN                    { $$ = TAN; }
@@ -12328,7 +12337,7 @@ dump_inspect_oper( const cbl_inspect_oper_t& op ) {
 }
 
 #pragma GCC diagnostic push
-#pragma GCC diagnostic ignored "-Wunused-function"
+#pragma GCC diagnostic ignored "-Wunused-function"e
 
 static void
 dump_inspect( const cbl_inspect_t& I ) {
@@ -12498,7 +12507,7 @@ literal_attr( const char prefix[] ) {
   case 1:
     switch(prefix[0]) {
     case 'B': return bool_encoded_e;
-    case 'N': yyerror("National not implemented"); return none_e;
+    case 'N': cbl_unimplemented("National"); return none_e;
     case 'X': return hex_encoded_e;
     case 'Z': return quoted_e;
     }
@@ -12509,7 +12518,7 @@ literal_attr( const char prefix[] ) {
     case 'X':
       switch(prefix[0]) {
       case 'B': return cbl_field_attr_t(hex_encoded_e | bool_encoded_e);
-      case 'N': yyerror("National not implemented"); return none_e;
+      case 'N': cbl_unimplemented("National"); return none_e;
       }
       break;
     }
diff --git a/gcc/cobol/parse_ante.h b/gcc/cobol/parse_ante.h
index 22e9bde627602b054485ea37ffab248e51f2f0f2..867ac9c5a88e7ce574bc3058af69a0b5d9ad6082 100644
--- a/gcc/cobol/parse_ante.h
+++ b/gcc/cobol/parse_ante.h
@@ -1706,8 +1706,8 @@ static class current_t {
     } else {
       parser_entry_activate( iprog, eval );
       auto name = cbl_label_of(symbol_at(iprog))->name;
-      yyerror("not implemented: Global declarative %s for %s",
-               eval->name, name);
+      cbl_unimplemented("Global declarative %s for %s",
+			eval->name, name);
       parser_call( new_literal(strlen(name), name, quoted_e),
                    cbl_refer_t(), 0, NULL, NULL, NULL, false );
     }
diff --git a/gcc/cobol/scan.l b/gcc/cobol/scan.l
index 32891b4c8d1885478d0c91f3812b8207ae3283ef..4bb0f6b4c947f24e69c379cd9c5abe7595b17543 100644
--- a/gcc/cobol/scan.l
+++ b/gcc/cobol/scan.l
@@ -974,12 +974,12 @@ USE({SPC}FOR)?		{ return USE; }
   BINARY-{DBLLONG}{SIGNED}	{ return scomputable(FldNumericBin5, 8); }
   BINARY-{DBLLONG}{UNSIGNED}	{ return ucomputable(FldNumericBin5, 8); }
   BINARY-{DBLLONG}		{ return scomputable(FldNumericBin5, 8); }
-  BIT				{ yyerror("unimplemented USAGE type: BIT");
+  BIT				{ cbl_unimplemented("USAGE type: BIT");
 				  return BIT; }
   FLOAT-BINARY-32		{ return ucomputable(FldFloat, 4); }
   FLOAT-BINARY-64		{ return ucomputable(FldFloat, 8); }
   FLOAT-BINARY-128		{ return ucomputable(FldFloat, 16); }
-  FLOAT-DECIMAL-(16|34)		{ yyerror("unimplemented USAGE type: FLOAT_DECIMAL");
+  FLOAT-DECIMAL-(16|34)		{ cbl_unimplemented("USAGE type: FLOAT_DECIMAL");
 				  return FLOAT_DECIMAL; // causes syntax error
 				}
   /* 21) The representation and length of a data item described with USAGE
@@ -990,10 +990,10 @@ USE({SPC}FOR)?		{ return USE; }
   FLOAT-SHORT    		{ return ucomputable(FldFloat, 4); }
 
   INDEX				{ return INDEX; }
-  MESSAGE-TAG			{ yyerror("unimplemented USAGE type: MESSAGE-TAG"); }
-  NATIONAL			{ yyerror("unimplemented USAGE type: NATIONAL");
+  MESSAGE-TAG			{ cbl_unimplemented("USAGE type: MESSAGE-TAG"); }
+  NATIONAL			{ cbl_unimplemented("USAGE type: NATIONAL");
 				  return NATIONAL; }
-  OBJECT{SPC}REFERENCE		{ yyerror("unimplemented USAGE type: OBJECT REFERENCE"); }
+  OBJECT{SPC}REFERENCE		{ cbl_unimplemented("USAGE type: OBJECT REFERENCE"); }
 
   PACKED-DECIMAL		{ return PACKED_DECIMAL; }
 
diff --git a/gcc/cobol/symfind.cc b/gcc/cobol/symfind.cc
index 4b4deac1691de3ea600e5d7ab2cc4de39f6f075b..c31446c810054b05905a3511392df5d3487e3313 100644
--- a/gcc/cobol/symfind.cc
+++ b/gcc/cobol/symfind.cc
@@ -138,9 +138,8 @@ dump_symbol_map2( const field_key_t& key, const std::list<size_t>& candidates )
 
   for( auto candidate : candidates ) {
     char *tmp = fields;
-    asprintf(&fields, "%s%s %3zu", tmp? tmp : "", sep, candidate);
+    fields = xasprintf("%s%s %3zu", tmp? tmp : "", sep, candidate);
     sep[0] = ',';
-    assert(fields);
     free(tmp);
   }
 
@@ -171,9 +170,8 @@ dump_symbol_map_value( const char name[], const symbol_map_t::value_type& value
 
   for( ; p != value.second.end(); p++ ) {
     char *tmp = ancestry;
-    asprintf(&ancestry, "%s%s %3zu", tmp? tmp : "", sep, *p);
+    ancestry = xasprintf("%s%s %3zu", tmp? tmp : "", sep, *p);
     sep[0] = ',';
-    assert(ancestry);
     free(tmp);
   }
 
diff --git a/gcc/cobol/util.cc b/gcc/cobol/util.cc
index fdfad0e2481445c759a0ba8fb1a3663c7db59f53..a91e1312613aaebd71a90f40a1b1e8c8cae9a855 100644
--- a/gcc/cobol/util.cc
+++ b/gcc/cobol/util.cc
@@ -2122,14 +2122,12 @@ yyerror( const char gmsgid[], ... ) {
 
 bool
 yywarn( const char gmsgid[], ... ) {
-  global_dc->begin_group();
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
-  rich_location richloc (line_table, token_location);
-  bool ret = global_dc->diagnostic_impl (&richloc, nullptr, option_id,
-					 gmsgid, &ap, DK_WARNING);
+  auto ret = emit_diagnostic_valist( DK_WARNING, token_location,
+				     option_id, gmsgid, &ap );
   va_end (ap);
-  global_dc->end_group();
   return ret;
 }
 
@@ -2319,18 +2317,40 @@ cbl_message(int fd, const char *format_string, ...)
 
 void
 cbl_internal_error(const char *gmsgid, ...) {
+  auto_diagnostic_group d;
   va_list ap;
   va_start(ap, gmsgid);
   emit_diagnostic_valist( DK_ICE, token_location, option_id, gmsgid, &ap );
   va_end(ap);
 }
 
+void
+cbl_unimplementedw(const char *gmsgid, ...) {
+  auto_diagnostic_group d;
+  va_list ap;
+  va_start(ap, gmsgid);
+  emit_diagnostic_valist( DK_SORRY, token_location, option_id, gmsgid, &ap );
+  va_end(ap);
+}
+
+void
+cbl_unimplemented(const char *gmsgid, ...) {
+  auto_diagnostic_group d;
+  va_list ap;
+  va_start(ap, gmsgid);
+  emit_diagnostic_valist( DK_SORRY, token_location, option_id, gmsgid, &ap );
+  yyerror("Program requires unimplemented syntax.");
+  va_end(ap);
+}
+
+
 /*  This is the analog to err(3) from "err .h".  The formatted message is sent to
     stderr, the message from xstrerror() is appended, and processing terminates
     with the retcode */
 
 void
 cbl_err(const char *fmt, ...) {
+  auto_diagnostic_group d;
   char *gmsgid = xasprintf("%m: %s", fmt);
   va_list ap;
   va_start(ap, fmt);
@@ -2343,6 +2363,7 @@ cbl_err(const char *fmt, ...) {
 
 void
 cbl_errx(const char *gmsgid, ...) {
+  auto_diagnostic_group d;
   va_list ap;
   va_start(ap, gmsgid);
   emit_diagnostic_valist( DK_FATAL, token_location, option_id, gmsgid, &ap );