diff --git a/gcc/cobol/cbldiag.h b/gcc/cobol/cbldiag.h new file mode 100644 index 0000000000000000000000000000000000000000..1eba92d856f7fd287c6f913cd9f3405aeb50e71b --- /dev/null +++ b/gcc/cobol/cbldiag.h @@ -0,0 +1,40 @@ +/* + * Copyright (c) 2021-2023 Symas Corporation + * + * Redistribution and use in source and binary forms, with or without + * modification, are permitted provided that the following conditions are + * met: + * + * * Redistributions of source code must retain the above copyright + * notice, this list of conditions and the following disclaimer. + * * Redistributions in binary form must reproduce the above + * copyright notice, this list of conditions and the following disclaimer + * in the documentation and/or other materials provided with the + * distribution. + * * Neither the name of the Symas Corporation nor the names of its + * contributors may be used to endorse or promote products derived from + * this software without specific prior written permission. + * + * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS + * "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT + * LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR + * A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT + * OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, + * SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT + * LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, + * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY + * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT + * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE + * OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. + */ + +#include <syslog.h> + +void yyerror( char const *s, int error_level = LOG_ERR); +void yyerrorv( const char fmt[], ... ); +void yyerrorvl( int line, const char fmt[], ... ); + +static inline void yywarn( char const *msg ) { yyerror( msg, LOG_WARNING ); } + +void yywarnv( const char fmt[], ... ); + diff --git a/gcc/cobol/cdf.y b/gcc/cobol/cdf.y index e1e0a31f3d31733aae6d985597deb9ca4f439d51..e85053b90766941246134481f1e7dc48fad8fd4d 100644 --- a/gcc/cobol/cdf.y +++ b/gcc/cobol/cdf.y @@ -72,10 +72,7 @@ const char * cdf_token_str( int token ); extern int yylineno, yyleng; extern char *yytext; -#include <syslog.h> -void yyerror( const char *s, int error_level = LOG_ERR); -void yyerrorv( const char fmt[], ... ); -inline void yywarn( const char *msg ) { yyerror( msg, LOG_WARNING ); } +#include "cbldiag.h" int ydflex(void); void ydferror( char const *s, int ); @@ -337,7 +334,13 @@ strings: LITERAL { (void)asprintf(&display_msg, "%s", $1); } ; partials: partial + { + if( ! scanner_lexing() ) YYACCEPT; + } | partials partial + { + if( ! scanner_lexing() ) YYACCEPT; + } ; partial: cdf_if /* text */ | CDF_ELSE { scanner_lexing_toggle(); } @@ -838,11 +841,13 @@ cdfval_t operator==( const cdfval_base_t& lhs, const cdfval_base_t& rhs ) { return cdfval_t(lhs.number == rhs.number); } if( lhs.string ) { - yyerrorv("warning: '%s' is not an integer", lhs.string); + yyerrorv("warning: incommensurate comparison is FALSE: '%s' = %ld", + lhs.string, rhs.number); return false; } if( rhs.string ) { - yyerrorv("warning: '%s' is not an integer", rhs.string); + yyerrorv("warning: incommensurate comparison is FALSE: %ld = '%s'", + lhs.number, rhs.string); return false; } yyerrorv("logic error: '%s' is not an integer", rhs.string); diff --git a/gcc/cobol/except.h b/gcc/cobol/except.h index d276591d8aba20f170c30be529981c8d49f08897..b681beb4637b40a6c5c3338af8bf6b3da10a5d02 100644 --- a/gcc/cobol/except.h +++ b/gcc/cobol/except.h @@ -32,6 +32,22 @@ #ifndef _CBL_EXCEPT_H_ #define _CBL_EXCEPT_H_ +static const ec_type_t simon_says_important[] = { + ec_argument_function_e, + ec_bound_odo_e, + ec_bound_ref_mod_e, + ec_bound_subscript_e, + ec_data_incompatible_e, + ec_data_ptr_null_e, + ec_size_overflow_e, + ec_size_exponentiation_e, + ec_size_truncation_e, + ec_size_zero_divide_e, + ec_program_not_found_e, + ec_program_recursive_call_e, + ec_program_arg_mismatch_e, +}; + ec_descr_t exception_table[] = { { ec_all_e, ec_category_none_e, "EC-ALL", "Any exception" }, diff --git a/gcc/cobol/parse_ante.h b/gcc/cobol/parse_ante.h index 09bbf36cb708dfda2e82d3de78cd5206fd9d13ca..84788c6907abaa42527c5ed911f0dfd01d0a0e0e 100644 --- a/gcc/cobol/parse_ante.h +++ b/gcc/cobol/parse_ante.h @@ -1,7 +1,38 @@ +/* + * Copyright (c) 2021-2023 Symas Corporation + * + * Redistribution and use in source and binary forms, with or without + * modification, are permitted provided that the following conditions are + * met: + * + * * Redistributions of source code must retain the above copyright + * notice, this list of conditions and the following disclaimer. + * * Redistributions in binary form must reproduce the above + * copyright notice, this list of conditions and the following disclaimer + * in the documentation and/or other materials provided with the + * distribution. + * * Neither the name of the Symas Corporation nor the names of its + * contributors may be used to endorse or promote products derived from + * this software without specific prior written permission. + * + * THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS + * "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT + * LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR + * A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT + * OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, + * SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT + * LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, + * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY + * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT + * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE + * OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. + */ + #include "genapi.h" #include "copybook.h" #include "io.h" #include "ec.h" +#include "cbldiag.h" #include <assert.h> #include <err.h> @@ -51,7 +82,7 @@ size_t parse_error_count() { return nparse_error; } #include <syslog.h> void -yyerror( char const *s, int error_level = LOG_ERR) { +yyerror( char const *s, int error_level /* = LOG_ERR */ ) { if( error_level <= LOG_ERR ) { ++nparse_error; } @@ -76,7 +107,6 @@ yyerror( char const *s, int error_level = LOG_ERR) { cobol_filename(), yylineno, s, len, yytext); } -inline void yywarn( char const *msg ) { yyerror( msg, LOG_WARNING ); } int yylex(void); extern int yydebug; diff --git a/gcc/cobol/scan_ante.h b/gcc/cobol/scan_ante.h index ba618ee95795458149460257304277ac854973ca..ac15ec9a2e1b0de339cdb9c3f80bb1e89dd69c81 100644 --- a/gcc/cobol/scan_ante.h +++ b/gcc/cobol/scan_ante.h @@ -42,6 +42,7 @@ #include "cdf.h" #include "symbols.h" #include "copybook.h" +#include "cbldiag.h" /* * Flex override @@ -60,9 +61,6 @@ die_fatal_error( const char msg[] ) { * External functions */ -void yyerror( char const *s, int error_level = LOG_ERR ); -void yyerrorv( const char fmt[], ... ); - void parser_enter_file(const char *filename); void parser_leave_file(); @@ -280,8 +278,8 @@ bool scanner_lexing() { return lexing.on(); } void scanner_lexing( int token, bool tf ) { lexing.push( cdf_status_t(token, tf) ); if( yydebug ) - warnx("%s @ %d: %s: scanning now %s, depth %zu", __func__, yylineno, - keyword_str(token), boolalpha(lexing.on()), lexing.size()); + yywarnv("%s @ %d: %s: scanning now %s, depth %zu", __func__, yylineno, + keyword_str(token), boolalpha(lexing.on()), lexing.size()); } void scanner_lexing_toggle() { if( lexing.empty() ) { @@ -289,8 +287,8 @@ void scanner_lexing_toggle() { return; } lexing.top().toggle(); - if( yydebug ) warnx("%s @ %d: scanning now %s", __func__, yylineno, - boolalpha(lexing.on())); + if( yydebug ) yywarnv("%s @ %d: scanning now %s", __func__, yylineno, + boolalpha(lexing.on())); } void scanner_lexing_pop() { if( lexing.empty() ) { @@ -298,8 +296,8 @@ void scanner_lexing_pop() { return; } lexing.pop(); - if( yydebug ) warnx("%s @ %d: scanning now %s, depth %zu", __func__, yylineno, - boolalpha(lexing.on()), lexing.size()); + if( yydebug ) yywarnv("%s @ %d: scanning now %s, depth %zu", __func__, yylineno, + boolalpha(lexing.on()), lexing.size()); } diff --git a/gcc/cobol/scan_post.h b/gcc/cobol/scan_post.h index 6b94045e956af39fde9c9edf5576a12d1c9f90e4..47e221daf1ee8eb9b6b00f67331a0047c00025d0 100644 --- a/gcc/cobol/scan_post.h +++ b/gcc/cobol/scan_post.h @@ -28,7 +28,6 @@ * OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. */ - /* * Match datetime constants. * @@ -280,8 +279,8 @@ yylex(void) { warnx( "%s:%d: routing %s to CDF parser", __func__, __LINE__, keyword_str(token) ); } else if( !lexing.on() ) { - warnx( "%s:%d: eating %s because conditional compilatiion is FALSE", - __func__, __LINE__, keyword_str(token) ); + yywarnv( "eating %s because conditional compilatiion is FALSE", + keyword_str(token) ); } }