diff --git a/gcc/cobol/ChangeLog b/gcc/cobol/ChangeLog index 5f4dd264a6d7cb0bd9633850d20a8efecc17e46a..669a9c6f2d40193e2156ab3d5440ea885500bb98 100644 --- a/gcc/cobol/ChangeLog +++ b/gcc/cobol/ChangeLog @@ -35,6 +35,13 @@ convert inspect.h to cbl_warning convert lexio.cc to cbl_warning convert parse.y cbl_warning + convert symfind.cc to cbl_warning + convert util.cc to cbl_warning + convert symbols.h to cbl_warning + + + + diff --git a/gcc/cobol/symbols.h b/gcc/cobol/symbols.h index a8bca49204b2fcd2420fa096a2891248a6e9e26a..e24b808d3942dc15b39257c3f8f8dfee987c6200 100644 --- a/gcc/cobol/symbols.h +++ b/gcc/cobol/symbols.h @@ -47,6 +47,7 @@ #include <vector> #include "common-defs.h" +#include "util.h" #define PICTURE_MAX 64 @@ -151,7 +152,7 @@ is_numeric( cbl_field_type_t type ) { case FldIndex: 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; } @@ -1341,7 +1342,7 @@ struct cbl_alphabet_t { } void dump() const { - warnx("'%s': %s, '%c' to '%c' (low 0x%02x, high 0x%02x)", + cbl_warning("'%s': %s, '%c' to '%c' (low 0x%02x, high 0x%02x)", name, encoding_str(encoding), low_index, last_index, low_index, high_index); if( encoding == custom_encoding_e ) { @@ -1862,10 +1863,10 @@ struct cbl_perform_tgt_t { void dump() const { assert(ifrom); if( !ito ) { - warnx( "%s:%d: #%3zu %s", __PRETTY_FUNCTION__, __LINE__, + cbl_warning( "%s:%d: #%3zu %s", __PRETTY_FUNCTION__, __LINE__, ifrom, from()->str() ); } else { - warnx( "%s:%d: #%3zu %s THRU #%3zu %s", __PRETTY_FUNCTION__, __LINE__, + cbl_warning( "%s:%d: #%3zu %s THRU #%3zu %s", __PRETTY_FUNCTION__, __LINE__, ifrom, from()->str(), ito, to()->str() ); } } diff --git a/gcc/cobol/symfind.cc b/gcc/cobol/symfind.cc index 4c6ea7e2f484c91da72b463d00ac9a46446bae01..50d07019f9edd6b12bcf0f1c8240911b656816c5 100644 --- a/gcc/cobol/symfind.cc +++ b/gcc/cobol/symfind.cc @@ -159,7 +159,7 @@ dump_symbol_map2( const field_key_t& key, const std::list<size_t>& candidates ) free(tmp); } - warnx( "%s:%d: %3zu %s {%s}", __func__, __LINE__, + cbl_warning( "%s:%d: %3zu %s {%s}", __func__, __LINE__, key.program, key.name, fields ); free(fields); } @@ -175,7 +175,7 @@ dump_symbol_map2() { n++; } } - warnx("symbol_map2 has %d program elements", n); + cbl_warning("symbol_map2 has %d program elements", n); } static void @@ -192,7 +192,7 @@ dump_symbol_map_value( const char name[], const symbol_map_t::value_type& value free(tmp); } - warnx( "%s:%d: %s -> %-24s {%s }", __func__, __LINE__, + cbl_warning( "%s:%d: %s -> %-24s {%s }", __func__, __LINE__, name, value.first.c_str(), ancestry ); free(ancestry); } @@ -210,7 +210,7 @@ field_structure( symbol_elem_t& sym ) { if( getenv(__func__) && sym.type == SymField ) { const auto& field = *cbl_field_of(&sym); - warnx("%s: #%zu %s: '%s' is_data_field: %s", __func__, + cbl_warning("%s: #%zu %s: '%s' is_data_field: %s", __func__, symbol_index(&sym), cbl_field_type_str(field.type), field.name, is_data_field(sym)? "yes" : "no" ); } @@ -242,7 +242,7 @@ field_structure( symbol_elem_t& sym ) { } if( getenv(__func__) && yydebug ) { - warnx( "%s:%d: '%s' has %zu ancestors", __func__, __LINE__, + cbl_warning( "%s:%d: '%s' has %zu ancestors", __func__, __LINE__, elem.first.c_str(), elem.second.size() ); dump_symbol_map_value(__func__, elem); } @@ -276,7 +276,7 @@ build_symbol_map() { symbol_map.erase(sym_name_t("")); if( yydebug ) { - warnx( "%s:%d: %zu of %zu symbols inserted into %zu in symbol_map", + cbl_warning( "%s:%d: %zu of %zu symbols inserted into %zu in symbol_map", __func__, __LINE__, nsym, end, symbol_map.size() ); if( getenv(__func__) ) { @@ -306,7 +306,7 @@ public: } protected: void dump_key( const char tag[], const symbol_map_t::key_type& key ) const { - warnx( "symbol_map key: %s { %3zu %3zu %s }", + cbl_warning( "symbol_map key: %s { %3zu %3zu %s }", tag, key.program, key.parent, key.name ); } }; @@ -339,7 +339,7 @@ public: ancestors->front() ); if( p != item.second.end() ) { if( false && yydebug ) { - warnx( "reduce_ancestry:%d: reduce %s to %zu parents [%zu ...]", __LINE__, + cbl_warning( "reduce_ancestry:%d: reduce %s to %zu parents [%zu ...]", __LINE__, item.first.c_str(), ancestors->size(), ancestors->at(0) ); } // Preserve symbol's index at front of ancestor list. @@ -450,7 +450,7 @@ name_has_names( const symbol_elem_t *e, for( auto name : names ) { p += snprintf( p, (buffer + sizeof(buffer)) - p, "%s ", name ); } - warnx("%s: #%zu (%s) matches '%s'", __func__, + cbl_warning("%s: #%zu (%s) matches '%s'", __func__, symbol_index(orig), cbl_field_of(orig)->name, buffer); } @@ -496,7 +496,7 @@ symbol_match2( size_t program, } if( fields.empty() ) { - warnx("%s: '%s' matches no fields", __func__, ancestry); + cbl_warning("%s: '%s' matches no fields", __func__, ancestry); dump_symbol_map2(); } else { char *fieldstr = NULL; @@ -509,7 +509,7 @@ symbol_match2( size_t program, free(partial); } - warnx("%s: '%s' matches %zu fields: {%s}", __func__, ancestry, fields.size(), fieldstr); + cbl_warning("%s: '%s' matches %zu fields: {%s}", __func__, ancestry, fields.size(), fieldstr); free(fieldstr); } free(ancestry); @@ -593,7 +593,7 @@ symbol_find( size_t program, std::list<const char *> names ) { return std::pair<symbol_elem_t *, bool>(NULL, false); } if( yydebug ) { - warnx( "%s:%d: '%s' has %zu possible matches", + cbl_warning( "%s:%d: '%s' has %zu possible matches", __func__, __LINE__, names.back(), items.size() ); std::for_each( items.begin(), items.end(), dump_symbol_map_value1 ); } @@ -656,7 +656,7 @@ symbol_find_of( size_t program, std::list<const char *> names, size_t group ) { symbol_map_t input = symbol_match(program, names); if( getenv(__func__) && input.size() != 1 ) { - warnx( "%s:%d: '%s' has %zu candidates for group %zu", + cbl_warning( "%s:%d: '%s' has %zu candidates for group %zu", __func__, __LINE__, names.back(), input.size(), group ); std::for_each( input.begin(), input.end(), dump_symbol_map_value1 ); } @@ -672,7 +672,7 @@ symbol_find_of( size_t program, std::list<const char *> names, size_t group ) { } if( yydebug ) { - warnx( "%s:%d: '%s' has %zu possible matches", + cbl_warning( "%s:%d: '%s' has %zu possible matches", __func__, __LINE__, names.back(), input.size() ); std::for_each( input.begin(), input.end(), dump_symbol_map_value1 ); } diff --git a/gcc/cobol/util.cc b/gcc/cobol/util.cc index 415936b6fae0647266f8cff5397a7b6cd6dac82d..d2890456efb295857c43989ee12b35cf5583013f 100644 --- a/gcc/cobol/util.cc +++ b/gcc/cobol/util.cc @@ -99,7 +99,7 @@ symbol_type_str( enum symbol_type_t type ) case SymDataSection: return "SymDataSection"; } - warnx("%s:%d: invalid symbol_type_t %d", __func__, __LINE__, type); + cbl_warning("%s:%d: invalid symbol_type_t %d", __func__, __LINE__, type); return "???"; } @@ -148,7 +148,7 @@ cbl_field_type_str( enum cbl_field_type_t type ) case FldBlob: return "FldBlob"; } - warnx("%s:%d: invalid symbol_type_t %d", __func__, __LINE__, type); + cbl_warning("%s:%d: invalid symbol_type_t %d", __func__, __LINE__, type); return "???"; } @@ -171,7 +171,7 @@ cbl_logop_str( enum logop_t op ) case false_op: return "false_op"; } - warnx("%s:%d: invalid logop_t %d", __func__, __LINE__, op); + cbl_warning("%s:%d: invalid logop_t %d", __func__, __LINE__, op); return "???"; } @@ -242,7 +242,7 @@ is_alpha_edited( const char picture[] ) { if( symbol_currency(*p) ) continue; if( yydebug ) { - warnx( "%s: bad character '%c' at %.*s<-- in '%s'", + cbl_warning( "%s: bad character '%c' at %.*s<-- in '%s'", __func__, *p, int(p - picture) + 1, picture, picture ); } return false; @@ -319,7 +319,7 @@ is_numeric_edited( const char picture[] ) { } if( yydebug ) { - warnx( "%s: no, because '%c' at %.*s<-- in '%s'", + cbl_warning( "%s: no, because '%c' at %.*s<-- in '%s'", __func__, *p, int(p - picture) + 1, picture, picture ); } return false; @@ -340,7 +340,7 @@ normalize_picture( char picture[] ) if( (erc = regcomp(preg, regex, cflags)) != 0 ) { regerror(erc, preg, regexmsg, sizeof(regexmsg)); - warnx( "%s:%d: could not compile regex: %s", __func__, __LINE__, regexmsg ); + cbl_warning( "%s:%d: could not compile regex: %s", __func__, __LINE__, regexmsg ); return picture; } @@ -361,11 +361,11 @@ normalize_picture( char picture[] ) p = picture + pmatch[2].rm_so; len = 0; if( 1 != sscanf(p, "%zu", &len) ) { - warnx("%s:%d: no number found in '%s'", __func__, __LINE__, p); + cbl_warning("%s:%d: no number found in '%s'", __func__, __LINE__, p); goto irregular; } if( len == 0 ) { - warnx("%s:%d: ZERO length found in '%s'", __func__, __LINE__, p); + cbl_warning("%s:%d: ZERO length found in '%s'", __func__, __LINE__, p); goto irregular; } @@ -418,7 +418,7 @@ match( const char picture[], const char pattern[] ) if( (erc = regcomp(preg, pattern, cflags)) != 0 ) { regerror(erc, preg, regexmsg, sizeof(regexmsg)); - warnx( "%s:%d: could not compile regex: %s", __func__, __LINE__, regexmsg ); + cbl_warning( "%s:%d: could not compile regex: %s", __func__, __LINE__, regexmsg ); return picture; } @@ -457,7 +457,7 @@ is_elementary( enum cbl_field_type_t type ) case FldFloat: return true; // takes up space } - 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; } @@ -478,12 +478,12 @@ integer_move_ok( const cbl_field_t *src, const cbl_field_t *tgt ) { if( is_numericish(src) && ! (tgt->type == FldInvalid || is_literal(tgt)) ) { if( src->data.rdigits > 0 ) { - warnx("%s has %d rdigits", src->name, src->data.rdigits); + cbl_warning("%s has %d rdigits", src->name, src->data.rdigits); } - ////warnx("%s:%d has %d rdigits", src->name, __LINE__, src->data.rdigits); + ////cbl_warning("%s:%d has %d rdigits", src->name, __LINE__, src->data.rdigits); return src->data.rdigits == 0; } - ////warnx("%s:%d has %d rdigits", src->name, __LINE__, src->data.rdigits); + ////cbl_warning("%s:%d has %d rdigits", src->name, __LINE__, src->data.rdigits); return integer_move_ok( tgt, src ); } @@ -1036,9 +1036,9 @@ struct move_corresponding_field { tgt.field = cbl_field_of(symbol_at(elem.second)); if( yydebug ) { - warnx("move_corresponding:%d: SRC: %3zu %s", __LINE__, + cbl_warning("move_corresponding:%d: SRC: %3zu %s", __LINE__, elem.first, src.str()); - warnx("move_corresponding:%d: to %3zu %s", __LINE__, + cbl_warning("move_corresponding:%d: to %3zu %s", __LINE__, elem.second, tgt.str()); } @@ -1143,7 +1143,7 @@ valid_move( const struct cbl_field_t *tgt, const struct cbl_field_t *src ) if( yydebug && ! retval ) { auto bad = std::find_if( p, pend, []( char ch ) { return ! ISDIGIT(ch); } ); - warnx("%s:%d: offending character '%c' at position %zu", + cbl_warning("%s:%d: offending character '%c' at position %zu", __func__, __LINE__, *bad, bad - p); } } @@ -1164,7 +1164,7 @@ valid_move( const struct cbl_field_t *tgt, const struct cbl_field_t *src ) retval = !src_alpha; break; default: - warnx("%s:%d: matrix at %s, %s is %d", __func__, __LINE__, + cbl_warning("%s:%d: matrix at %s, %s is %d", __func__, __LINE__, cbl_field_type_str(src->type), cbl_field_type_str(tgt->type), matrix[src->type][tgt->type]); assert(false); @@ -1173,14 +1173,14 @@ valid_move( const struct cbl_field_t *tgt, const struct cbl_field_t *src ) if( retval && src->has_attr(embiggened_e) ) { if( is_numeric(tgt) && tgt->data.capacity < src->data.capacity ) { if( yydebug ) { - warnx("error: source no longer fits in target"); + cbl_warning("error: source no longer fits in target"); } return false; } } if( yydebug && getenv(__func__) ) { - warnx("%s:%d: ok to move %s to %s (0x%02x)", __func__, __LINE__, + cbl_warning("%s:%d: ok to move %s to %s (0x%02x)", __func__, __LINE__, cbl_field_type_str(src->type), cbl_field_type_str(tgt->type), retval); } @@ -1206,7 +1206,7 @@ valid_picture( enum cbl_field_type_t type, const char picture[] ) case FldDisplay: case FldPointer: // These types don't take pictures; the grammar shouldn't call the function. - warnx("%s:%d: no polaroid: %s", __func__, __LINE__, cbl_field_type_str(type)); + cbl_warning("%s:%d: no polaroid: %s", __func__, __LINE__, cbl_field_type_str(type)); return false; case FldNumericBinary: case FldFloat: @@ -1274,7 +1274,7 @@ type_capacity( enum cbl_field_type_t type, uint32_t digits ) return 16; } - warnx( "%s:%d: invalid size %u for type %s", __func__, __LINE__, + cbl_warning( "%s:%d: invalid size %u for type %s", __func__, __LINE__, digits, cbl_field_type_str(type) ); return digits; @@ -1425,7 +1425,7 @@ public: (!key.has_paragraph() && 0 == strcasecmp(key.section(), ref.paragraph())) || 0 == strcasecmp(key.paragraph(), ref.paragraph()); if( false && hit ) { - warnx("%s: key {%s of %s} matches ref {%s of %s} ", __func__, + cbl_warning("%s: key {%s of %s} matches ref {%s of %s} ", __func__, key.paragraph(), key.section(), ref.paragraph(), ref.section()); } @@ -1438,7 +1438,7 @@ globally_unique( size_t program, const procref_t& ref ) { const procedures_t& procedures = programs[program]; assert(!procedures.empty()); #if 0 - warnx("%s: %zu matches for %s of '%s'", __func__, + cbl_warning("%s: %zu matches for %s of '%s'", __func__, count_if(procedures.begin(), procedures.end(), procedure_match(ref)), ref.paragraph(), ref.section()); #endif @@ -1453,7 +1453,7 @@ locally_unique( size_t program, const procdef_t& key, const procref_t& ref ) { procref_base_t full_ref(section_name, ref.paragraph()); if( getenv(__func__) ) { - warnx("%s: %zu for ref %s of '%s' (line %d) " + cbl_warning("%s: %zu for ref %s of '%s' (line %d) " "in %s of '%s' (as %s of '%s')", __func__, procedures.count(full_ref), ref.paragraph(), ref.section(), ref.line_number(), @@ -1483,7 +1483,7 @@ procedure_definition_add( size_t program, const cbl_label_t *procedure ) { procdef_t key( section_name, paragraph_name, isym ); if( getenv(__func__) ) { - warnx("%s: #%3zu %s of %s", __func__, isym, paragraph_name, section_name); + cbl_warning("%s: #%3zu %s of %s", __func__, isym, paragraph_name, section_name); } current_procedure = programs[program].insert( make_pair(key, procedures_t::mapped_type()) ); @@ -1495,7 +1495,7 @@ procedure_reference_add( const char *section, const char *paragraph, int line, size_t context ) { if( getenv(__func__) ) { - warnx("%s: line %3d %s of %s", __func__, line, paragraph, section); + cbl_warning("%s: line %3d %s of %s", __func__, line, paragraph, section); } current_procedure->second.push_back( procref_t(section, paragraph, line, context) ); @@ -1513,10 +1513,10 @@ public: bool operator()( procedures_t::mapped_type::const_reference ref ) { #if 0 - warnx("%s: %s of '%s' is %s locally unique", __func__, + cbl_warning("%s: %s of '%s' is %s locally unique", __func__, ref.paragraph(), ref.section(), locally_unique( program, key, ref )? "" : "not"); - warnx("%s: %s of '%s' is %s globally unique", __func__, + cbl_warning("%s: %s of '%s' is %s globally unique", __func__, ref.paragraph(), ref.section(), globally_unique( program, ref )? "" : "not"); #endif @@ -1529,12 +1529,12 @@ public: #if 0 static void dump( procedures_t::const_reference elem ) { - warnx( "%s: %s OF '%s' has %zu references:", __func__, + cbl_warning( "%s: %s OF '%s' has %zu references:", __func__, elem.first.paragraph(), elem.first.section(), elem.second.size() ); int i=0; for( auto p = elem.second.begin(); p != elem.second.end(); p++ ) { - warnx("%s:\t%2d: %s OF '%s' at %d", __func__, ++i, + cbl_warning("%s:\t%2d: %s OF '%s' at %d", __func__, ++i, p->paragraph(), p->section(), p->line_number() ); } } @@ -1550,7 +1550,7 @@ ambiguous_reference( size_t program ) { is_unique(program, proc.first) ); if( proc.second.end() != ambiguous ) { if( yydebug || getenv("symbol_label_add")) { - warnx("%s: %s of '%s' has %zu potential matches", __func__, + cbl_warning("%s: %s of '%s' has %zu potential matches", __func__, ambiguous->paragraph(), ambiguous->section(), procedures.count(*ambiguous)); } @@ -1616,7 +1616,7 @@ parent_names( const symbol_elem_t *elem, if( is_filler(cbl_field_of(elem)) ) return; - // warnx("%s: asked about %s of %s (%zu away)", __func__, + // cbl_warning("%s: asked about %s of %s (%zu away)", __func__, // cbl_field_of(elem)->name, // cbl_field_of(group)->name, elem - group); @@ -1640,7 +1640,7 @@ public: : lgroup(lgroup), rgroup(rgroup), type(type) { if( yydebug ) { - warnx( "%s:%d: for #%zu %s and #%zu %s on line %d", __func__, __LINE__, + cbl_warning( "%s:%d: for #%zu %s and #%zu %s on line %d", __func__, __LINE__, symbol_index(lgroup), cbl_field_of(lgroup)->name, symbol_index(rgroup), cbl_field_of(rgroup)->name, yylineno ); } @@ -1658,7 +1658,7 @@ public: corresponding_fields_t::value_type operator()( const symbol_elem_t& that ) { - // warnx( "find_corresponding:%d: trying %s ", __LINE__, + // cbl_warning( "find_corresponding:%d: trying %s ", __LINE__, // cbl_field_of(&that)->name ); if( &that == lgroup ) return std::make_pair(0,0); @@ -1707,7 +1707,7 @@ public: break; } - // warnx( "find_corresponding:%d: %zu => %zu ", __LINE__, + // cbl_warning( "find_corresponding:%d: %zu => %zu ", __LINE__, // symbol_index(&that), symbol_index(e) ); return std::make_pair( symbol_index(&that), symbol_index(e)); @@ -1727,7 +1727,7 @@ corresponding_fields( cbl_field_t *lhs, cbl_field_t *rhs, lhsg.z = std::find_if( lhsg.a, symbols_end(), next_group(lhsg.a) ); if( yydebug ) { - warnx("%s:%d: examining %zu symbols after %s", __func__, __LINE__, + cbl_warning("%s:%d: examining %zu symbols after %s", __func__, __LINE__, lhsg.z - lhsg.a, lhs->name); } @@ -1738,7 +1738,7 @@ corresponding_fields( cbl_field_t *lhs, cbl_field_t *rhs, output.erase(0); if( yydebug ) { - warnx( "%s:%d: %s and %s have %zu corresponding fields", + cbl_warning( "%s:%d: %s and %s have %zu corresponding fields", __func__, __LINE__, lhs->name, rhs->name, output.size() ); } @@ -1764,12 +1764,12 @@ corresponding_arith_fields( cbl_field_t *lhs, cbl_field_t *rhs ) { static int file_of( cbl_file_t *file ) { // return fileno from var_decl_node - warnx("not implemented for %s", file->name); + cbl_warning("not implemented for %s", file->name); return open("/dev/null", 0); // <-- not this } static size_t record_size( cbl_file_t *file ) { // return record size of file - warnx("not implemented for %s", file->name); + cbl_warning("not implemented for %s", file->name); return 7; // <-- not this } static size_t record_count( cbl_file_t *file ) { @@ -1783,7 +1783,7 @@ static size_t record_count( cbl_file_t *file ) { } if( 0 != sb.st_size % size ) { - warnx("file %s is %zu bytes, not a multiple of record size %zu", + cbl_warning("file %s is %zu bytes, not a multiple of record size %zu", file->name, sb.st_size, size); } return sb.st_size / size; @@ -1930,7 +1930,7 @@ date_time_fmt( const char input[] ) { if( ! compiled ) { for( auto& fmt : fmts ) { - ////warnx( "%s: %c, %s", __func__, fmt.type, fmt.pattern ); + ////cbl_warning( "%s: %c, %s", __func__, fmt.type, fmt.pattern ); if( (erc = regcomp(&fmt.reg, fmt.pattern, cflags)) != 0 ) { char msg[80]; regerror(erc, &fmt.reg, msg, sizeof(msg)); @@ -1940,7 +1940,7 @@ date_time_fmt( const char input[] ) { compiled = true; } - ////warnx("%s: input '%s'", __func__, input); + ////cbl_warning("%s: input '%s'", __func__, input); for( auto& fmt : fmts ) { if( 0 == regexec(&fmt.reg, input, COUNT_OF(m), m, eflags) ) { result = fmt.type; @@ -1987,12 +1987,12 @@ class unique_stack : public std::stack<input_file_t> if( n > 1 || yydebug ) { static char wd[PATH_MAX]; getcwd(wd, sizeof(wd)); - warnx( "depth line copybook filename\n" + cbl_warning( "depth line copybook filename\n" " " "----- ---- --------" "----------------------------------------"); for( const auto& v : c ) { - warnx( " %4zu %4d %s", c.size() - --n, v.lineno, no_wd(wd, v.name) ); + cbl_warning( " %4zu %4d %s", c.size() - --n, v.lineno, no_wd(wd, v.name) ); } } return false; @@ -2014,7 +2014,7 @@ bool cobol_filename( const char *name, ino_t inode ) { auto p = old_filenames.find(name); if( p == old_filenames.end() ) { for( auto& elem : old_filenames ) { - warnx("%6zu %-30s", elem.second, elem.first.c_str()); + cbl_warning("%6zu %-30s", elem.second, elem.first.c_str()); } errx(EXIT_FAILURE, "logic error: missing inode for %s", name); } @@ -2024,7 +2024,7 @@ bool cobol_filename( const char *name, ino_t inode ) { bool pushed = input_filenames.push( input_file_t(name, inode) ); input_filenames.top().lineno = yylineno = 1; if( getenv(__func__) ) { - warnx(" saving %s with lineno as %d", + cbl_warning(" saving %s with lineno as %d", input_filenames.top().name, input_filenames.top().lineno); } symbol_cobol_filename_begin(name); @@ -2037,7 +2037,7 @@ cobol_lineno_save() { auto& input( input_filenames.top() ); input.lineno = yylineno; if( getenv(__func__) ) { - warnx(" setting %s with lineno as %d", input.name, input.lineno); + cbl_warning(" setting %s with lineno as %d", input.name, input.lineno); } return input.name; } @@ -2059,7 +2059,7 @@ cobol_filename_restore() { auto input = input_filenames.top(); yylineno = input.lineno; if( getenv("cobol_filename") ) { - warnx("restoring %s with lineno to %d", + cbl_warning("restoring %s with lineno to %d", input_filenames.top().name, input.lineno); } symbol_cobol_filename_begin(input.name); @@ -2081,7 +2081,7 @@ cobol_fileline_set( const char line[] ) { if( !preg ) { if( (erc = regcomp(&re, pattern, cflags)) != 0 ) { regerror(erc, &re, regexmsg, sizeof(regexmsg)); - warnx( "%s:%d: could not compile regex: %s", __func__, __LINE__, regexmsg ); + cbl_warning( "%s:%d: could not compile regex: %s", __func__, __LINE__, regexmsg ); return line; } preg = &re; @@ -2089,7 +2089,7 @@ cobol_fileline_set( const char line[] ) { if( (erc = regexec(preg, line, COUNT_OF(pmatch), pmatch, 0)) != 0 ) { if( erc != REG_NOMATCH ) { regerror(erc, preg, regexmsg, sizeof(regexmsg)); - warnx( "%s:%d: could not compile regex: %s", __func__, __LINE__, regexmsg ); + cbl_warning( "%s:%d: could not compile regex: %s", __func__, __LINE__, regexmsg ); return line; } yyerrorv( "error: invalid #line directive: %s", line ); @@ -2181,7 +2181,7 @@ cobol_set_debugging( bool flex, bool yacc, bool parser ) if( ind ) { int col; if( 1 != sscanf(ind, "%d", &col) ) { - warnx("ignored non-integer value for INDICATOR_COLUMN=%s", ind); + cbl_warning("ignored non-integer value for INDICATOR_COLUMN=%s", ind); } cobol_set_indicator_column(col); } @@ -2196,11 +2196,11 @@ cobol_parse_files (int nfile, const char **files) { char * opaque = setlocale(LC_CTYPE, ""); if( ! opaque ) { - warnx("warning: setlocale: unable to initialize LOCALE"); + cbl_warning("warning: setlocale: unable to initialize LOCALE"); } else { char *codeset = nl_langinfo(CODESET); if( ! codeset ) { - warnx("nl_langinfo failed after setlocale succeeded"); + cbl_warning("nl_langinfo failed after setlocale succeeded"); } else { os_locale.codeset = codeset; }