diff options
Diffstat (limited to 'gcc/cobol/lexio.cc')
-rw-r--r-- | gcc/cobol/lexio.cc | 81 |
1 files changed, 49 insertions, 32 deletions
diff --git a/gcc/cobol/lexio.cc b/gcc/cobol/lexio.cc index afe3725..99824b6 100644 --- a/gcc/cobol/lexio.cc +++ b/gcc/cobol/lexio.cc @@ -28,6 +28,7 @@ * OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. */ +#include "config.h" #include <ext/stdio_filebuf.h> #include "cobol-system.h" #include "cbldiag.h" @@ -260,9 +261,10 @@ recognize_replacements( filespan_t mfile, std::list<replace_t>& pending_replacem found = span_t( cm[1].first, cm[1].second ); if( yy_flex_debug ) { size_t n = count_newlines(mfile.data, found.p); - dbgmsg("%s:%d first '%.*s' is on line %zu (offset %zu)", __func__, __LINE__, + dbgmsg("%s:%d first '%.*s' is on line " HOST_SIZE_T_PRINT_UNSIGNED + " (offset " HOST_SIZE_T_PRINT_UNSIGNED ")", __func__, __LINE__, directive.before.size(), directive.before.p, - ++n, found.p - mfile.data); + (fmt_size_t)++n, (fmt_size_t)(found.p - mfile.data)); } } else { dbgmsg("%s:%d not found: '%s' in \n'%.*s'", __func__, __LINE__, @@ -290,8 +292,10 @@ recognize_replacements( filespan_t mfile, std::list<replace_t>& pending_replacem if( yy_flex_debug ) { size_t n = std::count((const char *)mfile.data, recognized.before.p, '\n'); - dbgmsg( "%s:%d: line %zu @ %zu: '%s'\n/%.*s/%.*s/", __func__, __LINE__, - ++n, next.found.p - mfile.data, + dbgmsg( "%s:%d: line " HOST_SIZE_T_PRINT_UNSIGNED + " @ " HOST_SIZE_T_PRINT_UNSIGNED ": '%s'\n/%.*s/%.*s/", + __func__, __LINE__, + (fmt_size_t)++n, (fmt_size_t)(next.found.p - mfile.data), next.directive.before.p, int(recognized.before.size()), recognized.before.p, int(recognized.after.size()), recognized.after.p ); @@ -308,9 +312,10 @@ recognize_replacements( filespan_t mfile, std::list<replace_t>& pending_replacem next.found = span_t( cm[1].first, cm[1].second ); size_t n = std::count((const char *)mfile.data, next.found.p, '\n'); if( false ) - dbgmsg("%s:%d next '%.*s' will be on line %zu (offset %zu)", __func__, __LINE__, + dbgmsg("%s:%d next '%.*s' will be on line " HOST_SIZE_T_PRINT_UNSIGNED + " (offset " HOST_SIZE_T_PRINT_UNSIGNED ")", __func__, __LINE__, next.directive.before.size(), next.directive.before.p, - ++n, next.found.p - mfile.data); + (fmt_size_t)++n, (fmt_size_t)(next.found.p - mfile.data)); } pnext = std::min_element(futures.begin(), futures.end()); } @@ -344,8 +349,10 @@ check_source_format_directive( filespan_t& mfile ) { break; } mfile.cur = const_cast<char*>(cm[0].second); - dbgmsg( "%s:%d: %s format set, on line %zu", __func__, __LINE__, - indicator.column == 7? "FIXED" : "FREE", mfile.lineno() ); + dbgmsg( "%s:%d: %s format set, on line " HOST_SIZE_T_PRINT_UNSIGNED, + __func__, __LINE__, + indicator.column == 7? "FIXED" : "FREE", + (fmt_size_t)mfile.lineno() ); erase_line(const_cast<char*>(cm[0].first), const_cast<char*>(cm[0].second)); } @@ -724,7 +731,7 @@ parse_replacing_pair( const char *stmt, const char *estmt ) { // This eliminated a compiler warning about "format-overflow" yywarn("CDF syntax error"); } - pair.stmt = span_t(0UL, stmt); + pair.stmt = span_t(size_t(0), stmt); pair.replace = replace_t(); } return pair; @@ -764,9 +771,9 @@ parse_replace_pairs( const char *stmt, const char *estmt, bool is_copy_stmt ) { // Report findings. if( false && yy_flex_debug ) { for( size_t i=0; i < cm.size(); i++ ) { - dbgmsg("%s: %s %zu: '%.*s'", __func__, + dbgmsg("%s: %s " HOST_SIZE_T_PRINT_UNSIGNED ": '%.*s'", __func__, cm[i].matched? "Pair" : "pair", - i, + (fmt_size_t)i, cm[i].matched? int(cm[i].length()) : 0, cm[i].matched? cm[i].first : ""); } @@ -825,9 +832,10 @@ parse_replace_pairs( const char *stmt, const char *estmt, bool is_copy_stmt ) { } if( yy_flex_debug ) { - dbgmsg( "%s:%d: %s: %zu pairs parsed from '%.*s'", __func__, __LINE__, - parsed.done()? "done" : "not done", - pairs.size(), parsed.stmt.size(), parsed.stmt.p ); + dbgmsg( "%s:%d: %s: " HOST_SIZE_T_PRINT_UNSIGNED " pairs parsed from '%.*s'", + __func__, __LINE__, + parsed.done() ? "done" : "not done", + (fmt_size_t)pairs.size(), parsed.stmt.size(), parsed.stmt.p ); int i = 0; for( const auto& replace : pairs ) { dbgmsg("%s:%d:%4d: '%s' => '%s'", __func__, __LINE__, @@ -909,9 +917,10 @@ parse_copy_directive( filespan_t& mfile ) { if( yy_flex_debug ) { size_t nnl = 1 + count_newlines(mfile.data, copy_stmt.p); size_t nst = 1 + count_newlines(copy_stmt.p, copy_stmt.pend); - dbgmsg("%s:%d: line %zu: COPY directive is %zu lines '%.*s'", + dbgmsg("%s:%d: line " HOST_SIZE_T_PRINT_UNSIGNED + ": COPY directive is " HOST_SIZE_T_PRINT_UNSIGNED " lines '%.*s'", __func__, __LINE__, - nnl, nst, copy_stmt.size(), copy_stmt.p); + (fmt_size_t)nnl, (fmt_size_t)nst, copy_stmt.size(), copy_stmt.p); } } } @@ -924,7 +933,8 @@ parse_copy_directive( filespan_t& mfile ) { outcome.partial_line = span_t(mfile.cur, copy_stmt.p); if( yy_flex_debug ) { - dbgmsg("%zu expressions", std::count(pattern, pattern + sizeof(pattern), '(')); + dbgmsg(HOST_SIZE_T_PRINT_UNSIGNED " expressions", + (fmt_size_t)std::count(pattern, pattern + sizeof(pattern), '(')); int i = 0; for( const auto& m : cm ) { if( m.matched ) @@ -1008,8 +1018,9 @@ parse_replace_last_off( filespan_t& mfile ) { } } - dbgmsg( "%s:%d: line %zu: parsed '%.*s', ", __func__, __LINE__, - mfile.lineno(), int(cm[0].length()), cm[0].first ); + dbgmsg( "%s:%d: line " HOST_SIZE_T_PRINT_UNSIGNED ": parsed '%.*s', ", + __func__, __LINE__, + (fmt_size_t)mfile.lineno(), int(cm[0].length()), cm[0].first ); // Remove statement from input erase_line(const_cast<char*>(cm[0].first), @@ -1041,20 +1052,23 @@ parse_replace_text( filespan_t& mfile ) { gcc_assert(mfile.line_length() > 2); if( pend[-1] == '\n' ) pend -= 2; auto len = int(pend - mfile.cur); - dbgmsg("%s:%d: line %zu: parsing '%.*s", __func__, __LINE__, - current_lineno, len, mfile.cur); + dbgmsg("%s:%d: line " HOST_SIZE_T_PRINT_UNSIGNED ": parsing '%.*s", + __func__, __LINE__, + (fmt_size_t)current_lineno, len, mfile.cur); } if( ! regex_search(mfile.ccur(), (const char *)mfile.eodata, cm, re) ) { - dbgmsg( "%s:%d: line %zu: not a REPLACE statement:\n'%.*s'", - __func__, __LINE__, current_lineno, + dbgmsg( "%s:%d: line " HOST_SIZE_T_PRINT_UNSIGNED + ": not a REPLACE statement:\n'%.*s'", + __func__, __LINE__, (fmt_size_t)current_lineno, int(mfile.line_length()), mfile.cur ); return span_t(); } // Report findings. if( yy_flex_debug ) { - dbgmsg("%zu expressions", std::count(pattern, pattern + sizeof(pattern), '(')); + dbgmsg(HOST_SIZE_T_PRINT_UNSIGNED " expressions", + (fmt_size_t)std::count(pattern, pattern + sizeof(pattern), '(')); int i = 0; for( const auto& m : cm ) { if( m.matched ) @@ -1083,8 +1097,10 @@ parse_replace_text( filespan_t& mfile ) { replace_directives.push( replacements ); if( yy_flex_debug ) { - dbgmsg( "%s:%d: line %zu: %zu pairs parsed from '%.*s'", __func__, __LINE__, - current_lineno, replacements.size(), int(replace_stmt.size()), replace_stmt.p ); + dbgmsg( "%s:%d: line " HOST_SIZE_T_PRINT_UNSIGNED ": " HOST_SIZE_T_PRINT_UNSIGNED + " pairs parsed from '%.*s'", __func__, __LINE__, + (fmt_size_t)current_lineno, (fmt_size_t)replacements.size(), + int(replace_stmt.size()), replace_stmt.p ); for( const auto& replace : replacements ) { int i = 0; dbgmsg("%s:%d:%4d: '%s' => '%s'", __func__, __LINE__, @@ -1164,8 +1180,9 @@ bytespan_t::append( const char *input, const char *eoinput ) { #if LEXIO auto nq = std::count_if(data, eodata, isquote); dbgmsg("%s:%3d: input ------ '%.*s'", __func__, __LINE__, int(eoinput - input), input); - dbgmsg("%s:%3d: precondition '%.*s' (%zu: %s)", __func__, __LINE__, - int(size()), data, nq, in_string()? "in string" : "not in string"); + dbgmsg("%s:%3d: precondition '%.*s' (" HOST_SIZE_T_PRINT_UNSIGNED ": %s)", + __func__, __LINE__, + int(size()), data, (fmt_size_t)nq, in_string()? "in string" : "not in string"); #endif if( !in_string() ) { // Remove trailing space unless it's part of a literal. while(data < eodata && ISSPACE(eodata[-1])) eodata--; @@ -1563,8 +1580,8 @@ cdftext::map_file( int fd ) { cbl_err( "%s: could not prepare map file from FIFO %d", __func__, input); } - if( false ) dbgmsg("%s: copied %ld bytes from FIFO", - __func__, nout); + if( false ) dbgmsg("%s: copied " HOST_SIZE_T_PRINT_DEC " bytes from FIFO", + __func__, (fmt_size_t)nout); } } } while( S_ISFIFO(sb.st_mode) ); @@ -1774,8 +1791,8 @@ cdftext::process_file( filespan_t mfile, int output, bool second_pass ) { std::copy_if(copied.erased_lines.p, copied.erased_lines.pend, ofs, []( char ch ) { return ch == '\n'; } ); struct { int in, out; filespan_t mfile; } copy; - dbgmsg("%s:%d: line %zu, opening %s on fd %d", __func__, __LINE__, - mfile.lineno(), + dbgmsg("%s:%d: line " HOST_SIZE_T_PRINT_UNSIGNED ", opening %s on fd %d", + __func__, __LINE__,mfile.lineno(), copybook.source(), copybook.current()->fd); copy.in = copybook.current()->fd; copy.mfile = free_form_reference_format( copy.in ); |