From 96cad30797b190eeefc90475ed6f5e88c67f1a1c Mon Sep 17 00:00:00 2001
From: Bob Dubner <rdubner@symas.com>
Date: Tue, 24 Dec 2024 15:41:18 -0500
Subject: [PATCH] Convert parse.y to cbl_warning

---
 gcc/cobol/ChangeLog |  2 +
 gcc/cobol/parse.y   | 92 ++++++++++++++++++++++-----------------------
 2 files changed, 48 insertions(+), 46 deletions(-)

diff --git a/gcc/cobol/ChangeLog b/gcc/cobol/ChangeLog
index f1e036991f52..5f4dd264a6d7 100644
--- a/gcc/cobol/ChangeLog
+++ b/gcc/cobol/ChangeLog
@@ -29,10 +29,12 @@
 	convert cobol1.cc to cbl_warning
 	convert copybook.h to cbl_warning
 	convert except.cc to cbl_internal_error and cbl_message
+	convert genapi.cc to cbl_internal_error and cbl_message
 	convert gengen.cc to cbl_internal_error and cbl_message
 	convert genmath.cc to cbl_internal_error and cbl_message
 	convert inspect.h to cbl_warning
 	convert lexio.cc to cbl_warning
+	convert parse.y cbl_warning
 
 
 
diff --git a/gcc/cobol/parse.y b/gcc/cobol/parse.y
index be0f86d8d7f0..f69cf799c48c 100644
--- a/gcc/cobol/parse.y
+++ b/gcc/cobol/parse.y
@@ -1316,7 +1316,7 @@ io_control_clause:
                 }
         |       APPLY COMMIT on field_list
                 {
-                  warnx("not implemented: I-O-CONTROL APPLY COMMIT");
+                  cbl_warning("not implemented: I-O-CONTROL APPLY COMMIT");
                 }
                 ;
 area:           %empty
@@ -2444,7 +2444,7 @@ fd_clause:      record_desc
                               $NAME);
                     YYERROR;
                   }
-                  warnx("warning: RECORDING MODE ignored, not defined by ISO 2023");
+                  cbl_warning("warning: RECORDING MODE ignored, not defined by ISO 2023");
                 }
         |       VALUE OF fd_values
         |       CODESET is NAME
@@ -2713,7 +2713,7 @@ field:          cdf
                       $data_descr->data.initial = initial;
                       if( yydebug ) {
                         const char *value_str = string_of(field.data.value);
-                        warnx("%s::data.initial is (%%%d.%d) %s ==> '%s'",
+                        cbl_warning("%s::data.initial is (%%%d.%d) %s ==> '%s'",
                             field.name,
                               field.data.digits,
                               rdigits,
@@ -2898,7 +2898,7 @@ data_descr:     data_descr1
                   $$ = current_field($1); // make available for occurs, etc.
                   char *env = getenv("symbols_update");
                   if( env && env[0] == 'P' ) {
-                    warnx("parse.y:%d: %-15s %s (%s)", __LINE__,
+                    cbl_warning("parse.y:%d: %-15s %s (%s)", __LINE__,
                           cbl_field_type_str($$->type) + 3,
                           field_str($$),
                           cbl_field_type_str($$->usage) + 3);
@@ -3223,7 +3223,7 @@ data_descr1:    level_name
                     $field->attr &= ~group_sign;
 
                     if( $field->attr & sign_attrs ) {
-                      if( yydebug ) warnx("%s:%d: %s", __func__, __LINE__,
+                      if( yydebug ) cbl_warning("%s:%d: %s", __func__, __LINE__,
                                           field_str($field));
                       yyerrorv( "error: %s must be signed for SIGN IS",
                                 $field->name );
@@ -3302,7 +3302,7 @@ literalism:     LITERAL { $$ = $1; }
 
                   if( $second.prefix[0] ) { strcpy(output.prefix, $second.prefix); }
                   if( ! $first.compatible_prefix($second) ) {
-                    warnx("warning: dissimilar literals, '%s' prevails",
+                    cbl_warning("warning: dissimilar literals, '%s' prevails",
                           output.prefix);
                   }
                 }
@@ -3414,7 +3414,7 @@ data_clauses:   data_clause
                       auto redefined = symbol_redefines(field);
                       if( redefined && redefined->type == FldPointer ) {
                         if( yydebug ) {
-                          warnx("expanding %s size from %u bytes to %zu "
+                          cbl_warning("expanding %s size from %u bytes to %zu "
                                 "because it redefines %s with USAGE POINTER", 
                                 field->name, field->size(), sizeof(void*),
                                 redefined->name);
@@ -3599,7 +3599,7 @@ picture_clause: PIC signed nps[fore] nines nps[aft]
                   field->data.capacity = $size;
                   field->data.picture = NULL;
 
-                  if( 0 && yydebug ) warnx("PIC alphanum_pic[size]:%d: %s",
+                  if( 0 && yydebug ) cbl_warning("PIC alphanum_pic[size]:%d: %s",
                                       field->line, field_str(field));
                 }
 
@@ -3663,7 +3663,7 @@ alphanum_pic:   alphanum_part {
                 {
 		  auto field = current_field();
 		  if( yydebug ) 
-		    warnx("%s has %s against %s",
+		    cbl_warning("%s has %s against %s",
 			  field->name, field_attr_str(field),
 			  cbl_field_attr_str($2.attr));
 		  
@@ -3673,7 +3673,7 @@ alphanum_pic:   alphanum_part {
                   $$ += $2.nbyte;
 
 		  if( yydebug ) 
-		    warnx("%s attrs: %s",
+		    cbl_warning("%s attrs: %s",
 			  field->name, field_attr_str(field));
                 }
                 ;
@@ -3875,7 +3875,7 @@ usage_clause1:  usage COMPUTATIONAL[comp]   native
                     // For now, we allow POINTER to expand a 32-bit item to 64 bits.
                     field->data.capacity = sizeof(void *);
                     if( yydebug ) {
-                      warnx("%s: expanding #%zu %s capacity %u => %u", __func__,
+                      cbl_warning("%s: expanding #%zu %s capacity %u => %u", __func__,
                           field_index(redefined), redefined->name,
                           redefined->data.capacity, field->data.capacity);
                     }
@@ -4382,7 +4382,7 @@ sentence:       statements  '.'
                   std::set<std::string> externals = current.end_program();
                   if( !externals.empty() ) {
                     for( const auto& name : externals ) {
-                      warnx("%s calls external symbol '%s'",
+                      cbl_warning("%s calls external symbol '%s'",
                              prog->name, name.c_str());
                     }
                     YYERROR;
@@ -7774,7 +7774,7 @@ start_body:     filename[file]
                   auto ksize = new_tempnumeric();
                   parser_set_numeric(ksize, size);
                   if( yydebug ) {
-                    warnx("START: key #%d '%s' has size %d",
+                    cbl_warning("START: key #%d '%s' has size %d",
                           key, $key->name, size);
                   }
                   file_start_args.init($file);
@@ -8113,7 +8113,7 @@ search_1_cases: search_1_case
                         lookahead = keyword_str(yychar);
                       }
                     }
-                    warnx("Just one case, lookahead is '%s'", lookahead);
+                    cbl_warning("Just one case, lookahead is '%s'", lookahead);
                   }
                 }
         |       search_1_cases search_1_case
@@ -9216,7 +9216,7 @@ label_1:        qname
 
                   $$ = paragraph_reference(para, isect);
                   assert($$);
-                  if( yydebug ) warnx( "using procedure %s of line %d",
+                  if( yydebug ) cbl_warning( "using procedure %s of line %d",
                                        $$->name, $$->line );
                 }
         |       NUMSTR
@@ -10685,7 +10685,7 @@ void parser_call2( cbl_refer_t name, cbl_refer_t returning,
   }
 
   if( getenv("parser_call2") && yydebug ) {
-    warnx("%s: calling %s returning %s with %zu args:", __func__,
+    cbl_warning("%s: calling %s returning %s with %zu args:", __func__,
           name_of(name.field),
           (returning.field)? returning.field->name : "[none]",
           narg);
@@ -10697,7 +10697,7 @@ void parser_call2( cbl_refer_t name, cbl_refer_t returning,
       case by_content_e: crv = "con"; break;
       case by_value_e: crv = "val"; break;
       }
-      warnx("%s: %4zu: %s @%p %s", __func__,
+      cbl_warning("%s: %4zu: %s @%p %s", __func__,
             i, crv, args[i].refer.field, args[i].refer.field->name);
     }
   }
@@ -10961,7 +10961,7 @@ relop_debug_str(int token) {
   case GE:  return "GE";
   case '>': return ">";
   }
-  warnx("%s:%d: invalid relop token %d", __func__, __LINE__, token);
+  cbl_warning("%s:%d: invalid relop token %d", __func__, __LINE__, token);
   return "???";
 }
 
@@ -11098,7 +11098,7 @@ label_add( enum cbl_label_type_t type, const char name[], int line ) {
   assert( !(p->type == LblSection && p->parent > 0) );
 
   if( getenv(__func__) ) {
-    warnx("%s: added label %3zu %10s for '%s' of %zu", __func__,
+    cbl_warning("%s: added label %3zu %10s for '%s' of %zu", __func__,
           symbol_elem_of(p) - symbols_begin(), p->type_str()+3, p->name, p->parent);
   }
 
@@ -11160,7 +11160,7 @@ paragraph_reference( const char name[], size_t section )
   procedure_reference_add(sect_name, p->name, yylineno, current.program_section());
 
   if( getenv(__func__) ) {
-    warnx("%s: %s label %3zu %10s for '%s' of %zu", __func__,
+    cbl_warning("%s: %s label %3zu %10s for '%s' of %zu", __func__,
           symbols_end() == last? "added" : "found",
           symbol_index(symbol_elem_of(p)), p->type_str()+3, p->name, p->parent);
   }
@@ -11172,7 +11172,7 @@ paragraph_reference( const char name[], size_t section )
 static void
 complain_move_impl(const char func[], int line,
               struct cbl_field_t *tgt, struct cbl_field_t *src ) {
-  warnx( "%s:%d: cannot move '%s' (%s) to '%s' (%s)",
+  cbl_warning( "%s:%d: cannot move '%s' (%s) to '%s' (%s)",
          func, line,
          src->name, cbl_field_type_str(src->type),
          tgt->name, cbl_field_type_str(tgt->type) );
@@ -11181,7 +11181,7 @@ complain_move_impl(const char func[], int line,
 
 #if 0
 static void show_refer( cbl_refer_t& refer ) {
-  warnx( "n=%zu, %s", refer.noffset, field_str(refer.field) );
+  cbl_warning( "n=%zu, %s", refer.noffset, field_str(refer.field) );
 };
 #endif
 
@@ -11308,7 +11308,7 @@ current_t::repository_add( const char name[]) {
   auto p = programs.top().function_repository.insert(*parg);
   if( yydebug ) {
     for( auto descr : programs.top().function_repository ) {
-      warnx("%s:%d: %-20s %-20s %-20s", __func__, __LINE__,
+      cbl_warning("%s:%d: %-20s %-20s %-20s", __func__, __LINE__,
 	    keyword_str(descr.token), descr.name, descr.cname);
     }
   }
@@ -11405,7 +11405,7 @@ ast_add( arith_t *arith ) {
   pA = use_any(arith->A, A);
 
   if( getenv(__func__) ) {
-    warnx("%s:%d: %-12s C{%zu %p} A{%zu %p}", __func__, __LINE__,
+    cbl_warning("%s:%d: %-12s C{%zu %p} A{%zu %p}", __func__, __LINE__,
           arith->format_str(), nC, pC, nA, pA );
   }
   parser_add( nC, pC, nA, pA, arith->format, arith->on_error, arith->not_error );
@@ -11481,7 +11481,7 @@ struct stringify_src_t : public cbl_string_src_t {
   }
 
   static void dump( const cbl_string_src_t& src ) {
-    warnx( "%s:%d:, %zu inputs delimited by %s:", __func__, __LINE__,
+    cbl_warning( "%s:%d:, %zu inputs delimited by %s:", __func__, __LINE__,
            src.ninput,
            src.delimited_by.field? field_str(src.delimited_by.field) : "SIZE" );
     std::for_each(src.inputs, src.inputs + src.ninput, dump_input);
@@ -11489,7 +11489,7 @@ struct stringify_src_t : public cbl_string_src_t {
 
  protected:
   static void dump_input( const cbl_refer_t& refer ) {
-    warnx( "%s:\t%s", __func__, field_str(refer.field) );
+    cbl_warning( "%s:\t%s", __func__, field_str(refer.field) );
   }
 };
 
@@ -11635,7 +11635,7 @@ lang_check_failed (const char* file, int line, const char* function) {}
 
 void ast_inspect( cbl_refer_t& input, bool backward, ast_inspect_list_t& inspects ) {
   if( yydebug ) {
-    warnx("%s:%d: INSPECT %zu operations on %s, line %d", __func__, __LINE__,
+    cbl_warning("%s:%d: INSPECT %zu operations on %s, line %d", __func__, __LINE__,
           inspects.size(), input.field->name, yylineno);
   }
   std::for_each(inspects.begin(), inspects.end(), dump_inspect);
@@ -11656,7 +11656,7 @@ cbl_refer_str( char output[], const cbl_refer_t& R ) {
 static void
 dump_inspect_match( const cbl_inspect_match_t& M ) {
 #if 0
-  warnx( "%s:matching field @ %p before %p after %p", __func__,
+  cbl_warning( "%s:matching field @ %p before %p after %p", __func__,
          M.matching.field, M.before.c.field, M.after.c.field );
 #else
   static char fields[3][4 * 64];
@@ -11664,7 +11664,7 @@ dump_inspect_match( const cbl_inspect_match_t& M ) {
   cbl_refer_str(fields[1], M.before.identifier_4);
   cbl_refer_str(fields[2], M.after.identifier_4);
 
-  warnx( "matching %s \n\t\tbefore %s%s \n\t\tafter  %s%s",
+  cbl_warning( "matching %s \n\t\tbefore %s%s \n\t\tafter  %s%s",
          fields[0],
          M.before.initial? "initial " : "", fields[1],
          M.after.initial?  "initial " : "", fields[2] );
@@ -11679,7 +11679,7 @@ dump_inspect_replace( const cbl_inspect_replace_t& R ) {
   cbl_refer_str(fields[2], R.after.identifier_4);
   cbl_refer_str(fields[3], R.replacement);
 
-  warnx( "matching    %s \n\treplacement %s\n\t\tbefore %s%s \n\t\tafter  %s%s",
+  cbl_warning( "matching    %s \n\treplacement %s\n\t\tbefore %s%s \n\t\tafter  %s%s",
          fields[0], fields[3],
          R.before.initial? "initial " : "", fields[1],
          R.after.initial?  "initial " : "", fields[2] );
@@ -11961,7 +11961,7 @@ initialize_one( cbl_num_result_t target, bool with_filler,
       parser_move(tgt, src, current_rounded_mode());
     }
     if( getenv(__func__) ) {
-      warnx("%s:%-5s: %s", __func__, keyword_str(token), field_str(tgt.field));
+      cbl_warning("%s:%-5s: %s", __func__, keyword_str(token), field_str(tgt.field));
     }
     return true;
   }
@@ -11981,7 +11981,7 @@ initialize_one( cbl_num_result_t target, bool with_filler,
     }
 
     if( getenv(__func__) ) {
-      warnx("%s: value: %s", __func__, field_str(tgt.field));
+      cbl_warning("%s: value: %s", __func__, field_str(tgt.field));
     }
   }
 
@@ -11999,7 +11999,7 @@ initialize_one( cbl_num_result_t target, bool with_filler,
       cbl_field_t *from = r->second->field;
       char from_str[128]; // copy static buffer from field_str
       strcpy( from_str, field_str(from) );
-      warnx("%s:  move: %-18s %s \n\t      from %-18s %s", __func__,
+      cbl_warning("%s:  move: %-18s %s \n\t      from %-18s %s", __func__,
             cbl_field_type_str(tgt.field->type) + 3, field_str(tgt.field),
             cbl_field_type_str(from->type) + 3, from_str);
     }
@@ -12026,10 +12026,10 @@ dump_spans( size_t isym,
   assert( nrange == 0 || nrange == spans.size() );
 
   if( isym != field_index(table) ) {
-    warnx("%s:%d: isym %zu is not #%zu %02u %s", __func__, __LINE__,
+    cbl_warning("%s:%d: isym %zu is not #%zu %02u %s", __func__, __LINE__,
 	  isym, field_index(table), table->level, table->name);
   }
-  warnx( "%s: [%zu] #%zu %s has %zu spans and %zu subtables",
+  cbl_warning( "%s: [%zu] #%zu %s has %zu spans and %zu subtables",
 	 __func__, depth, isym, table->name, nrange, subtables.size() );
   for( auto span : spans ) {
     unsigned int last_level = 0;
@@ -12048,7 +12048,7 @@ dump_spans( size_t isym,
     if( p != subtables.end() ) {
       sprintf(at_subtable, "(subtable #%zu)", p->isym);
     }
-    warnx("\t    %02u %-20s to %02u %-20s: %3zu-%zu %s",
+    cbl_warning("\t    %02u %-20s to %02u %-20s: %3zu-%zu %s",
 	  span.first->level, span.first->name,
 	  last_level, last_name,
 	  nrange? ranges[i].first : 1, 
@@ -12057,9 +12057,9 @@ dump_spans( size_t isym,
     i++;
   }
   if( ! subtables.empty() ) {
-    warnx("\ttable #%zu has %zu subtables", isym, subtables.size());
+    cbl_warning("\ttable #%zu has %zu subtables", isym, subtables.size());
     for( auto tbl : subtables ) {
-      warnx("\t    #%zu @ %4zu", tbl.isym, tbl.offset);
+      cbl_warning("\t    #%zu @ %4zu", tbl.isym, tbl.offset);
     }
   }
 }
@@ -12073,7 +12073,7 @@ initialize_table( cbl_num_result_t target,
 		  const std::list<cbl_subtable_t>& subtables )
 {
   if( getenv("initialize_statement") ) {
-    warnx("%s:%d: %s ", __func__, __LINE__, target.refer.str());
+    cbl_warning("%s:%d: %s ", __func__, __LINE__, target.refer.str());
   }
   assert( target.refer.nsubscript == dimensions(target.refer.field) );
   const cbl_refer_t& src( target.refer );
@@ -12126,7 +12126,7 @@ initialize_statement( const cbl_num_result_t& target, bool with_filler,
                       size_t depth = 0 )
 {
   if( getenv(__func__) ) {
-    warnx("%s:%d: %2zu: %s (%s%zuR)",
+    cbl_warning("%s:%d: %2zu: %s (%s%zuR)",
 	  __func__, __LINE__, depth, target.refer.str(),
 	  with_filler? "F" : "",
 	  replacements.size());
@@ -12284,7 +12284,7 @@ initialize_statement( std::list<cbl_num_result_t>& tgts, bool with_filler,
                      data_category_t value_category,
                      const category_map_t& replacements) {
   if( yydebug && getenv(__func__) ) {
-    warnx( "%s: %zu targets, %s filler",
+    cbl_warning( "%s: %zu targets, %s filler",
            __func__, tgts.size(), with_filler? "with" : "no");
     for( auto tgt : tgts ) {
       fprintf( stderr, "%28s: %s\n", __func__, name_of(tgt.refer.field) );
@@ -12314,7 +12314,7 @@ initialize_statement( std::list<cbl_num_result_t>& tgts, bool with_filler,
 
 static void
 dump_inspect_oper( const cbl_inspect_oper_t& op ) {
-  warnx("\t%s: %zu \"matches\", %zu \"replaces\"",
+  cbl_warning("\t%s: %zu \"matches\", %zu \"replaces\"",
         bound_str(op.bound),
         op.matches? op.n_identifier_3 : 0, op.replaces? op.n_identifier_3 : 0);
   if( op.matches )
@@ -12406,7 +12406,7 @@ cbl_field_t *
 new_literal( const literal_t& lit, enum cbl_field_attr_t attr ) {
   bool zstring = lit.prefix[0] == 'Z';
   if( !zstring && lit.data[lit.len] != '\0' ) {
-    warnx("%s:%d: line %d, no NUL terminator '%-*.*s'{%zu/%zu}",
+    cbl_warning("%s:%d: line %d, no NUL terminator '%-*.*s'{%zu/%zu}",
           __func__, __LINE__, yylineno, 
           int(lit.len), int(lit.len),
           lit.data, strlen(lit.data), lit.len);
@@ -12793,7 +12793,7 @@ eval_subject_t::compare( relop_t op, const cbl_refer_t& object, bool deciding )
       }
     }
   if( yydebug ) {
-    warnx("%s:%d: failed for %s %s %s",
+    cbl_warning("%s:%d: failed for %s %s %s",
 	  __func__, __LINE__,
 	  name_of(subject.field), relop_str(op), name_of(object.field));
   }
@@ -12807,7 +12807,7 @@ eval_subject_t::compare( const cbl_refer_t& object,
   
   if( ! compatible( object.field ) ) {
     if( yydebug ) {
-      warnx("%s:%d: failed for %s %s",
+      cbl_warning("%s:%d: failed for %s %s",
 	    __func__, __LINE__,
 	    name_of(subject.field), name_of(object.field));
     }
@@ -12816,7 +12816,7 @@ eval_subject_t::compare( const cbl_refer_t& object,
   if( object2.field ) {
     if( ! compatible( object2.field ) ) {
       if( yydebug ) {
-	warnx("%s:%d: failed for %s %s",
+	cbl_warning("%s:%d: failed for %s %s",
 	      __func__, __LINE__,
 	      name_of(subject.field), name_of(object2.field));
       }
-- 
GitLab