From 04a78c95035f004342bc85e3bdeb7b0b7bec1ab9 Mon Sep 17 00:00:00 2001
From: Bob Dubner <rdubner@symas.com>
Date: Tue, 24 Dec 2024 15:49:29 -0500
Subject: [PATCH] Convert show_parse.h and symbols.cc to cbl_warning

---
 gcc/cobol/ChangeLog    |  2 ++
 gcc/cobol/show_parse.h |  6 ++--
 gcc/cobol/symbols.cc   | 80 +++++++++++++++++++++---------------------
 3 files changed, 45 insertions(+), 43 deletions(-)

diff --git a/gcc/cobol/ChangeLog b/gcc/cobol/ChangeLog
index 669a9c6f2d40..ac41c8e25ec4 100644
--- a/gcc/cobol/ChangeLog
+++ b/gcc/cobol/ChangeLog
@@ -37,7 +37,9 @@
 	convert parse.y cbl_warning
 	convert symfind.cc to cbl_warning
 	convert util.cc to cbl_warning
+	convert show-parse.h to cbl_warning
 	convert symbols.h to cbl_warning
+	convert symbols.cc to cbl_warning
     
     
     
diff --git a/gcc/cobol/show_parse.h b/gcc/cobol/show_parse.h
index ef6c15a1e8b3..68fd92a2106a 100644
--- a/gcc/cobol/show_parse.h
+++ b/gcc/cobol/show_parse.h
@@ -410,12 +410,12 @@ extern bool cursor_at_sol;
         do{                     \
         if(!a)                  \
             {                   \
-            warnx("%s(): parameter " #a " is NULL", __func__); \
+            cbl_warning("%s(): parameter " #a " is NULL", __func__); \
             gcc_assert(false);  \
             }                   \
         if( !a->var_decl_node && a->type != FldConditional && a->type != FldLiteralA)  \
             {                   \
-            warnx("%s() parameter " #a " is variable %s<%s> with NULL var_decl_node", \
+            cbl_warning("%s() parameter " #a " is variable %s<%s> with NULL var_decl_node", \
                 __func__,       \
                 a->name,        \
                 cbl_field_type_str(a->type) ); \
@@ -427,7 +427,7 @@ extern bool cursor_at_sol;
         do{                     \
         if(!a)                  \
             {                   \
-            warnx("%s(): parameter " #a " is NULL", __func__); \
+            cbl_warning("%s(): parameter " #a " is NULL", __func__); \
             gcc_assert(false);  \
             }                   \
         }while(0);
diff --git a/gcc/cobol/symbols.cc b/gcc/cobol/symbols.cc
index 572b831bd99e..236547c226fb 100644
--- a/gcc/cobol/symbols.cc
+++ b/gcc/cobol/symbols.cc
@@ -427,8 +427,8 @@ special_pair_cmp( const cbl_special_name_t& key,
   const bool matched = key.id == elem.id || 0 == strcasecmp(key.name, elem.name);
 
   if( getenv(__func__) ) {
-    warnx("%s:%d: key:  id=%2d, %s", __func__, __LINE__, key.id, key.name);
-    warnx("%s:%d: elem: id=%2d, %s => %s", __func__, __LINE__,
+    cbl_warning("%s:%d: key:  id=%2d, %s", __func__, __LINE__, key.id, key.name);
+    cbl_warning("%s:%d: elem: id=%2d, %s => %s", __func__, __LINE__,
           elem.id, elem.name, matched? "match" : "no match");
   }
 
@@ -979,7 +979,7 @@ update_block_offsets( struct symbol_elem_t *block)
 
   if( getenv(__func__) ) {
     cbl_field_t *field = cbl_field_of(block);
-    warnx( "%s: offset is %3zu for %2u %-30s #%3zu P%zu",
+    cbl_warning( "%s: offset is %3zu for %2u %-30s #%3zu P%zu",
            __func__, field->offset, field->level, field->name,
            symbol_index(block), field->parent );
   }
@@ -1014,7 +1014,7 @@ update_block_offsets( struct symbol_elem_t *block)
     }
 
     if( getenv(__func__) ) {
-      warnx( "%s: offset is %3zu for %2u %-30s #%3zu P%zu",
+      cbl_warning( "%s: offset is %3zu for %2u %-30s #%3zu P%zu",
              __func__, field->offset, field->level, field->name,
              symbol_index(e), field->parent );
     }
@@ -1104,7 +1104,7 @@ symbol_field_capacity( const cbl_field_t *field ) {
   size_t size = std::accumulate( symbol_at(bog), symbol_at_impl(eog),
                                  0, sym_field_size::capacity );
 
-  if(true) warnx("%s: %02u %s.data.capacity computed as %zu", __func__,
+  if(true) cbl_warning("%s: %02u %s.data.capacity computed as %zu", __func__,
                   field->level, field->name, size);
 
   return size;
@@ -1119,13 +1119,13 @@ has_odo( const symbol_elem_t& e ) {
 struct cbl_field_t *
 symbol_find_odo_debug( cbl_field_t * field ) {
   size_t bog = field_index(field), eog = end_of_group(bog);
-  warnx("%s: %s is #%zu - #%zu of %zu, ends at %s", __func__,
+  cbl_warning("%s: %s is #%zu - #%zu of %zu, ends at %s", __func__,
         field->name, bog, eog, symbols.nelem,
         eog == symbols.nelem? "[end]" : cbl_field_of(symbol_at(eog))->name );
 
   auto e = std::find_if( symbol_at(bog), symbol_at_impl(eog, true), has_odo );
   if( e != symbol_at_impl(eog, true) ) {
-    warnx("%s: %s has ODO at #%zu (return '%s')", __func__,
+    cbl_warning("%s: %s has ODO at #%zu (return '%s')", __func__,
           field->name, symbol_index(e),
           cbl_field_of(e)->name );
   }
@@ -1228,7 +1228,7 @@ symbols_dump( size_t first, bool header ) {
       }
       break;
     default:
-      warnx("%s: cannot dump symbol type %d", __func__, e->type);
+      cbl_warning("%s: cannot dump symbol type %d", __func__, e->type);
       continue;
     }
     fprintf(stderr, "%4zu: %s\n", e - symbols_begin(), s);
@@ -1343,7 +1343,7 @@ static struct symbol_elem_t *
   }
 
   if(yydebug && group->type != FldGroup) {
-    warnx("Field #%zu '%s' is not a group", symbol_index(e), group->name);
+    cbl_warning("Field #%zu '%s' is not a group", symbol_index(e), group->name);
     symbols_dump(symbols.first_program, true);
   }
   if( group->type == FldInvalid ) return e;
@@ -1411,8 +1411,8 @@ static struct symbol_elem_t *
     }
 
     if( details ) {
-      warnx("%s:%d: %s", __func__, __LINE__, field_str(field) );
-      warnx("%s:%d: %s", __func__, __LINE__, field_str(group) );
+      cbl_warning("%s:%d: %s", __func__, __LINE__, field_str(field) );
+      cbl_warning("%s:%d: %s", __func__, __LINE__, field_str(group) );
     }
   }
 
@@ -1421,13 +1421,13 @@ static struct symbol_elem_t *
 
   if( 0 < group->data.memsize && group->data.memsize < group->data.capacity ) {
     if( yydebug ) {
-      warnx( "%s:%d: small capacity?\n\t%s", __func__, __LINE__, field_str(group) );
+      cbl_warning( "%s:%d: small capacity?\n\t%s", __func__, __LINE__, field_str(group) );
     }
     group->data.memsize = group->data.capacity;
   }
 
   if( group->data.capacity == 0 ) {
-    warnx( "%s:%d: zero capacity?\n\t%s", __func__, __LINE__, field_str(group) );
+    cbl_warning( "%s:%d: zero capacity?\n\t%s", __func__, __LINE__, field_str(group) );
   }
 
   switch( group->level ) {
@@ -1453,12 +1453,12 @@ verify_block( const struct symbol_elem_t *block,
     if( getenv(__func__) ) {
       if( e == block ) {
         static const char ds[] = "--------------------------------";
-        warnx( "%17s %-3s %-3s %-18s %-3s %3s %-16s  C/D/R = init\n"
+        cbl_warning( "%17s %-3s %-3s %-18s %-3s %3s %-16s  C/D/R = init\n"
                "%.25s %-.3s %-.3s %-.18s %-.3s %.3s %-.16s %-.7s  %-.16s",
                "", "ndx", "off", "type", "par", "lvl", "name",
                ds, ds, ds, ds, ds, ds, ds, ds, ds );
       }
-      warnx( "%s:%d: %3zu %3zu %-18s %3zu  %02d %-16s %2u/%u/%d = '%s'",
+      cbl_warning( "%s:%d: %3zu %3zu %-18s %3zu  %02d %-16s %2u/%u/%d = '%s'",
              __func__, __LINE__, e - symbols.elems, field->offset,
              cbl_field_type_str(field->type),
              field->parent, field->level, field->name,
@@ -1940,7 +1940,7 @@ symbols_update( size_t first, bool parsed_ok ) {
     }
 
     if(! (field->data.memsize == 0 || field_size(field) <= field->data.memsize) ) {
-      if( yydebug ) warnx( "%s:%d: #%zu: invalid: %s", __func__, __LINE__,
+      if( yydebug ) cbl_warning( "%s:%d: #%zu: invalid: %s", __func__, __LINE__,
                            symbol_index(p), field_str(cbl_field_of(p)) );
     }
     assert(field->data.memsize == 0 || field_size(field) <= field_memsize(field));
@@ -2064,7 +2064,7 @@ symbol_field_forward( size_t index ) {
   assert( index < symbols.nelem );
   symbol_elem_t *e = symbol_at(index);
   if( (e->type != SymField) ) {
-    warnx("%s: logic error: #%zu is %s", __func__, index, symbol_type_str(e->type));
+    cbl_warning("%s: logic error: #%zu is %s", __func__, index, symbol_type_str(e->type));
   }
   assert(e->type == SymField);
 
@@ -2103,7 +2103,7 @@ symbol_find_forward_field( size_t program, const char name[] ) {
     e = static_cast<struct symbol_elem_t *>(lfind( &key, start,
                                                    &nelem, sizeof(key),
                                                    symbol_elem_cmp ) );
-    if( !e && yydebug ) warnx("%s:%d: no forward reference for program %zu '%s'",
+    if( !e && yydebug ) cbl_warning("%s:%d: no forward reference for program %zu '%s'",
                               __func__, __LINE__, program, name);
 
 
@@ -2164,10 +2164,10 @@ name_queue_t::dump( const char tag[] ) const {
         p += snprintf( p, line + sizeof(line) - p, "%s%s", sep, name );
         sep = "::";
       }
-      warnx("name_queue: %s: %2d: %s", tag, ++i, line);
+      cbl_warning("name_queue: %s: %2d: %s", tag, ++i, line);
     }
     if( empty() ) {
-      warnx("name_queue: %s: is empty", tag);
+      cbl_warning("name_queue: %s: is empty", tag);
     }
   }
 
@@ -2698,7 +2698,7 @@ symbol_field_add( size_t program, struct cbl_field_t *field )
       }
     }
 
-    warnx( "%s:%d: %3zu %-18s %02d %-16s %u/%u/%d = '%s'", __func__, __LINE__,
+    cbl_warning( "%s:%d: %3zu %-18s %02d %-16s %u/%u/%d = '%s'", __func__, __LINE__,
            field->offset,
            cbl_field_type_str(field->type), field->level, field->name,
            field->data.capacity, field->data.digits, field->data.rdigits,
@@ -2869,7 +2869,7 @@ symbol_field_forward_add( size_t program, size_t parent,
                                0, cbl_field_t::linkage_t(),
                                {0,0,0,0, " ", NULL, {NULL}, {NULL}}, NULL };
   if( sizeof(field.name) < strlen(name) ) {
-    warnx("%s:%d: logic error: name %s too long", __func__, __LINE__, name);
+    cbl_warning("%s:%d: logic error: name %s too long", __func__, __LINE__, name);
     return NULL;
   }
   strcpy( field.name, name);
@@ -2923,12 +2923,12 @@ symbol_file( size_t program, const char name[] ) {
       return e;
     }
     if( e->type != SymField ) {
-      warnx("%s:%d: '%s' is not a file and has parent of type %s",
+      cbl_warning("%s:%d: '%s' is not a file and has parent of type %s",
             __func__, __LINE__, name, symbol_type_str(e->type));
       return NULL;
     }
     if( symbol_index(e) == 0 ) {
-      warnx("%s:%d: '%s' is not a file and has no parent",
+      cbl_warning("%s:%d: '%s' is not a file and has no parent",
             __func__, __LINE__, name);
       return NULL;
     }
@@ -3227,7 +3227,7 @@ symbol_file_record_sizes( struct cbl_file_t *file ) {
   output.max = cbl_field_of(&*p.second)->data.capacity;
 
   if( yydebug && getenv(__func__) ) {
-    warnx("%s: %s: min '%s' %zu, max '%s' %zu", __func__, file->name,
+    cbl_warning("%s: %s: min '%s' %zu, max '%s' %zu", __func__, file->name,
           cbl_field_of(&*p.first)->name, output.min,
           cbl_field_of(&*p.second)->name, output.max);
   }
@@ -3408,7 +3408,7 @@ new_temporary_impl( enum cbl_field_type_t type )
     snprintf(f->name, sizeof(f->name), "_stack%d",++nstack);
     
     if( getenv("symbol_temporaries_free") ) {
-      warnx("%s: %s, %s", __func__, f->name, 3 + cbl_field_type_str(f->type));
+      cbl_warning("%s: %s, %s", __func__, f->name, 3 + cbl_field_type_str(f->type));
     }
   }
   
@@ -3472,7 +3472,7 @@ temporaries_t::literal( const char value[], uint32_t len, cbl_field_attr_t attr
     if( p != literals.end() ) {
       cbl_field_t *field = p->second;
       if( false && attr != none_e && field->attr != attr ) {
-        warnx("temporaries_t::%s:%d: '%s' logic: using prior attr %08lx, not %08lx",
+        cbl_warning("temporaries_t::%s:%d: '%s' logic: using prior attr %08lx, not %08lx",
               __func__, __LINE__,
               field->data.initial, field->attr, attr);
       }
@@ -3503,13 +3503,13 @@ temporaries_t::dump() const {
       free(so_far);
     }
   }
-  warnx("status: %s", output);
+  cbl_warning("status: %s", output);
   free(output);
 }
 
 temporaries_t::~temporaries_t() {
   if( getenv( "symbol_temporaries_free" ) ) {
-    warnx("%s: %zu literals", __func__, literals.size());
+    cbl_warning("%s: %zu literals", __func__, literals.size());
     for( const auto& elem : literals ) {
       const literal_an& key(elem.first);
       fprintf(stderr, "%c '%s'\n", key.is_quoted? 'Q' : ' ', key.value.c_str());
@@ -3759,11 +3759,11 @@ cbl_field_t::internalize() {
       if( (p = std::find(data.initial, eoi, '\0')) != eoi ) {
         sprintf(nullitude, "NUL @ %zu", p - data.initial);
       }
-      warnx("%s:%d: before: %-15s %-20s: '%.*s'{%u}, %s", __func__, __LINE__,
+      cbl_warning("%s:%d: before: %-15s %-20s: '%.*s'{%u}, %s", __func__, __LINE__,
             3 + cbl_field_type_str(type), name,
             data.capacity, data.initial, data.capacity, nullitude);
     }
-    if( yydebug ) warnx("%s: converted '%.*s' to %s",
+    if( yydebug ) cbl_warning("%s: converted '%.*s' to %s",
                         __func__, data.capacity, data.initial, tocode);
 
     int len = int(out - output);
@@ -3793,7 +3793,7 @@ cbl_field_t::internalize() {
       if( (p = std::find(data.initial, eoi, '\0')) != eoi ) {
         sprintf(nullitude, "NUL @ %zu", p - data.initial);
       }
-      warnx("%s:%d: after:  %-15s %-20s: '%.*s'{%u}, %s", __func__, __LINE__,
+      cbl_warning("%s:%d: after:  %-15s %-20s: '%.*s'{%u}, %s", __func__, __LINE__,
             "", name,
             data.capacity, data.initial, data.capacity, nullitude);
     }
@@ -3919,7 +3919,7 @@ symbol_label_add( size_t program, cbl_label_t *input )
 {
   if( getenv(__func__) ) {
     const cbl_label_t *L = input;
-    warnx( "%s:%d: %-5s #%3zu %-9s '%s' of '%s' at line %d", __func__, __LINE__,
+    cbl_warning( "%s:%d: %-5s #%3zu %-9s '%s' of '%s' at line %d", __func__, __LINE__,
            "input",
            size_t(0),
            L->type_str()+3,
@@ -3939,7 +3939,7 @@ symbol_label_add( size_t program, cbl_label_t *input )
 
     if( getenv(__func__) ) {
       const cbl_label_t *L = label;
-      warnx( "%s:%d: %-5s #%3zu %-9s '%s' of '%s' at line %d",
+      cbl_warning( "%s:%d: %-5s #%3zu %-9s '%s' of '%s' at line %d",
              __func__, __LINE__,
              verb,
              symbol_elem_of(L) - symbols_begin(),
@@ -3982,7 +3982,7 @@ symbol_label_add( size_t program, cbl_label_t *input )
 
   if( getenv(__func__) ) {
     const cbl_label_t *L = cbl_label_of(e);
-    warnx( "%s:%d: added #%3zu %-9s '%s' of '%s' at line %d", __func__, __LINE__,
+    cbl_warning( "%s:%d: added #%3zu %-9s '%s' of '%s' at line %d", __func__, __LINE__,
            e - symbols_begin(),
            L->type_str()+3,
            L->name,
@@ -4091,7 +4091,7 @@ symbol_special_add( size_t program, struct cbl_special_name_t *special )
   if( e ) {
     cbl_special_name_t *s = cbl_special_name_of(e);
     if( getenv(__func__) ) {
-      warnx("%s:%d matches %s %d (%s)", __func__, __LINE__,
+      cbl_warning("%s:%d matches %s %d (%s)", __func__, __LINE__,
             special->name, int(s->id), s->name);
     }
     return e;
@@ -4106,7 +4106,7 @@ symbol_special_add( size_t program, struct cbl_special_name_t *special )
   }
 
   if( getenv(__func__) ) {
-    warnx( "%s:%d: added special '%s'", __func__, __LINE__,
+    cbl_warning( "%s:%d: added special '%s'", __func__, __LINE__,
            e->elem.special.name);
   }
 
@@ -4747,7 +4747,7 @@ symbol_forward_names( size_t ifield ) {
   for( auto sym = symbols_begin(ifield); sym && sym->type == SymField; ) {
     const cbl_field_t *field = cbl_field_of(sym);
     if( !(field->type == FldForward) ) {
-      warnx("%s:%d: logic error, not FldForward: #%zu %s",
+      cbl_warning("%s:%d: logic error, not FldForward: #%zu %s",
             __func__, __LINE__, symbol_index(sym), field_str(field));
     }
     assert(field->type == FldForward);
@@ -4793,7 +4793,7 @@ cbl_file_key_t::deforward( size_t ifile ) {
                     const auto field = cbl_field_of(symbol_at(ifield));
 
                     if( is_forward(field) && yydebug ) {
-                      warnx("%s:%d: key %d: #%zu %s of %s is %s", "deforward", __LINE__,
+                      cbl_warning("%s:%d: key %d: #%zu %s of %s is %s", "deforward", __LINE__,
                             keys[ifile]++, ifield, field->name, file->name,
                             cbl_field_type_str(field->type) + 3);
                     }
@@ -5034,6 +5034,6 @@ has_value( cbl_field_type_t type ) {
   case FldLiteralN:
     return true;
   }
-  warnx( "%s:%d: invalid symbol_type_t %d", __func__, __LINE__, type );
+  cbl_warning( "%s:%d: invalid symbol_type_t %d", __func__, __LINE__, type );
   return false;
 }
-- 
GitLab