diff --git a/gcc/cobol/cbldiag.h b/gcc/cobol/cbldiag.h index 4fbf51a6274ab9acea3b49fb4decca28f6d38d25..aeef96ebab6624fe7a294d29393e5bc0129d71d0 100644 --- a/gcc/cobol/cbldiag.h +++ b/gcc/cobol/cbldiag.h @@ -33,6 +33,6 @@ const char * cobol_filename(); void yyerror( const char fmt[], ... ); -void yyerrorl( int line, const char *filename, const char fmt[], ... ); +void yyerrorvl( int line, const char *filename, const char fmt[], ... ); bool yywarn( const char fmt[], ... ); diff --git a/gcc/cobol/lexio.cc b/gcc/cobol/lexio.cc index 152f9c65d6b43c99a18648e8e93cc00ea44b53d2..77010e4c43781c45234d6162da67d17b844887ce 100644 --- a/gcc/cobol/lexio.cc +++ b/gcc/cobol/lexio.cc @@ -1361,7 +1361,7 @@ cdftext::lex_open( const char filename[] ) { for( auto name : included_files ) { int input; if( -1 == (input = open(name, O_RDONLY)) ) { - yyerrorl(1, "", "cannot open -include file %s", name); + yyerrorvl(1, "", "cannot open -include file %s", name); continue; } cobol_filename(name, inode_of(input)); @@ -1634,7 +1634,7 @@ cdftext::free_form_reference_format( int input ) { __attribute__ ((fallthrough)); default: // flag other characters in indicator area if( ! ISSPACE(indcol[0]) ) { - yyerrorl( mfile.lineno, cobol_filename(), + yyerrorvl( mfile.lineno, cobol_filename(), "error: stray indicator '%c' (0x%0x): \"%.*s\"", indcol[0], indcol[0], int(mfile.line_length() - 1), mfile.cur ); diff --git a/gcc/cobol/parse_ante.h b/gcc/cobol/parse_ante.h index 1c323ec4a05e660e6e31b1dbf2c4cc1593612381..47a07ec67cc0824edc39fdf319244c75b7ccb3d3 100644 --- a/gcc/cobol/parse_ante.h +++ b/gcc/cobol/parse_ante.h @@ -104,83 +104,11 @@ size_t parse_error_count() { return nparse_error; } #include <syslog.h> -void -yyerror( char const *s, int error_level /* = LOG_ERR */ ) { - if( error_level <= LOG_ERR ) { - ++nparse_error; - } - - fflush(stdout); - if( yychar == 0 ) { // strictly YYEOF, but not defined here - const char *where = yylineno == 1? "" : " detected at end of file"; - fprintf( stderr, "%s:%d: %s%s\n", - cobol_filename(), yylineno, s, where); - return; - } - - if( !yytext || yytext[0] == '.') { - fprintf( stderr, "%s:%d: %s\n", - cobol_filename(), yylineno, s); - return; - } - - auto len = yytext[yyleng-1] == '\n'? yyleng - 1 : yyleng; - - fprintf( stderr, "%s:%d: %s at '%.*s'\n", - cobol_filename(), yylineno, s, len, yytext); -} - - int yylex(void); extern int yydebug; #include <stdarg.h> -void -dnu_yyerror( const char fmt[], ... ) { - char *msg; - va_list ap; - - va_start(ap, fmt); - (void)! vasprintf(&msg, fmt, ap); - assert(msg); - yyerror(msg); - free(msg); - va_end(ap); -} - -void -dnu_yywarn( const char fmt[], ... ) { - char *msg; - va_list ap; - - va_start(ap, fmt); - (void)! vasprintf(&msg, fmt, ap); - assert(msg); - yyerror(msg, LOG_WARNING); - free(msg); - va_end(ap); -} - -void -yyerrorl( int line, const char *filename, const char fmt[], ... ) { - ++nparse_error; - - char *msg; - va_list ap; - - va_start(ap, fmt); - (void)! vasprintf(&msg, fmt, ap); - assert(msg); - - if( !filename ) filename = cobol_filename(); - - fprintf( stderr, "%s:%d: %s\n", filename, line, msg); - - free(msg); - va_end(ap); -} - const char * consistent_encoding_check( const char input[] ) { cbl_field_t faux = { diff --git a/gcc/cobol/symbols.cc b/gcc/cobol/symbols.cc index 1af67d066568500106a58f9883e59a2308b8cdad..cd43ce918cff793f1db6f6d553415c8ebc0a7a22 100644 --- a/gcc/cobol/symbols.cc +++ b/gcc/cobol/symbols.cc @@ -2217,7 +2217,7 @@ symbol_field_parent_set( struct cbl_field_t *field ) if( had_picture(prior) ) { auto efile = symbol_in_file(e); const char *filename = efile? efile->elem.filename : NULL; - yyerrorl(prior->line, filename, + yyerrorvl(prior->line, filename, "error: group %s cannot have PICTURE clause", prior->name); return NULL; } diff --git a/gcc/cobol/util.cc b/gcc/cobol/util.cc index b8723bf487f03988ec83a8c2848f26dd0699bfa2..b888dabd4592402dce84bf5984ae7b9bd72820d5 100644 --- a/gcc/cobol/util.cc +++ b/gcc/cobol/util.cc @@ -2133,6 +2133,28 @@ yywarn( const char gmsgid[], ... ) { return ret; } +/* + * Sometimes during parsing an error is noticed late. This message refers back + * to an arbitrary file and line number. + */ +void +yyerrorvl( int line, const char *filename, const char fmt[], ... ) { + parse_error_inc(); + auto_diagnostic_group d; // not needed unless we can use global_dc + char *msg; + va_list ap; + + va_start(ap, fmt); + msg = xvasprintf(fmt, ap); + + if( !filename ) filename = cobol_filename(); + + fprintf( stderr, "%s:%d: %s\n", filename, line, msg); + + free(msg); + va_end(ap); +} + static inline size_t matched_length( const regmatch_t& rm ) { return rm.rm_eo - rm.rm_so; } @@ -2292,20 +2314,6 @@ cbl_message(int fd, const char *format_string, ...) free(ostring); } -/* Uses the GCC warning() to output the formatted string */ - -void -cbl_warning(const char *format_string, ...) - { - va_list ap; - va_start(ap, format_string); - char *ostring = xvasprintf(format_string, ap); - va_end(ap); - // We call warnging() with a code of zero, which is just a generic warning - warning_at(gcc_location(), 0, "%s", ostring); - free(ostring); - } - /* Uses the GCC internal_error () to output the formatted string. Processing ends with a stack trace */