diff options
Diffstat (limited to 'gcc/cobol/parse_ante.h')
-rw-r--r-- | gcc/cobol/parse_ante.h | 693 |
1 files changed, 428 insertions, 265 deletions
diff --git a/gcc/cobol/parse_ante.h b/gcc/cobol/parse_ante.h index aa36628..105afe9 100644 --- a/gcc/cobol/parse_ante.h +++ b/gcc/cobol/parse_ante.h @@ -28,9 +28,9 @@ * OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. */ -#include <assert.h> -#include <string.h> -#include <stdio.h> +#include <cassert> +#include <cstring> +#include <cstdio> #include <algorithm> #include <list> @@ -47,9 +47,6 @@ #pragma GCC diagnostic push #pragma GCC diagnostic ignored "-Wmissing-field-initializers" -extern void declarative_runtime_match(cbl_field_t *declaratives, - cbl_label_t *lave ); - extern YYLTYPE yylloc; extern int yylineno, yyleng, yychar; @@ -73,42 +70,46 @@ void apply_declaratives(); const char * keyword_str( int token ); void labels_dump(); -cbl_dialect_t cbl_dialect; +unsigned int cbl_dialects; size_t cbl_gcobol_features; +static enum cbl_division_t current_division; static size_t nparse_error = 0; -size_t parse_error_inc() { return ++nparse_error; } +size_t parse_error_inc() { + mode_syntax_only(current_division); + return ++nparse_error; +} size_t parse_error_count() { return nparse_error; } void input_file_status_notify(); -#define YYLLOC_DEFAULT(Current, Rhs, N) \ - do { \ - if (N) \ - { \ - (Current).first_line = YYRHSLOC (Rhs, 1).first_line; \ - (Current).first_column = YYRHSLOC (Rhs, 1).first_column; \ - (Current).last_line = YYRHSLOC (Rhs, N).last_line; \ - (Current).last_column = YYRHSLOC (Rhs, N).last_column; \ - location_dump("parse.c", N, \ - "rhs N ", YYRHSLOC (Rhs, N)); \ - } \ - else \ - { \ - (Current).first_line = \ - (Current).last_line = YYRHSLOC (Rhs, 0).last_line; \ - (Current).first_column = \ - (Current).last_column = YYRHSLOC (Rhs, 0).last_column; \ - } \ - location_dump("parse.c", __LINE__, "current", (Current)); \ - gcc_location_set( location_set(Current) ); \ - input_file_status_notify(); \ +#define YYLLOC_DEFAULT(Current, Rhs, N) \ + do { \ + if (N) \ + { \ + (Current).first_line = YYRHSLOC (Rhs, 1).first_line; \ + (Current).first_column = YYRHSLOC (Rhs, 1).first_column; \ + (Current).last_line = YYRHSLOC (Rhs, N).last_line; \ + (Current).last_column = YYRHSLOC (Rhs, N).last_column; \ + location_dump("parse.c", N, \ + "rhs N ", YYRHSLOC (Rhs, N)); \ + } \ + else \ + { \ + (Current).first_line = \ + (Current).last_line = YYRHSLOC (Rhs, 0).last_line; \ + (Current).first_column = \ + (Current).last_column = YYRHSLOC (Rhs, 0).last_column; \ + } \ + location_dump("parse.c", __LINE__, "current", (Current)); \ + input_file_status_notify(); \ + gcc_location_set( location_set(Current) ); \ } while (0) int yylex(void); extern int yydebug; -#include <stdarg.h> +#include <cstdarg> const char * consistent_encoding_check( const YYLTYPE& loc, const char input[] ) { @@ -131,8 +132,6 @@ const char * original_picture(); static const relop_t invalid_relop = static_cast<relop_t>(-1); -static enum cbl_division_t current_division; - static cbl_refer_t null_reference; static cbl_field_t *literally_one, *literally_zero; @@ -142,7 +141,8 @@ literal_of( size_t value ) { case 0: return literally_zero; case 1: return literally_one; } - cbl_err("logic error: %s: %zu not supported", __func__, value); + cbl_err("logic error: %s: " HOST_SIZE_T_PRINT_UNSIGNED " not supported", + __func__, (fmt_size_t)value); return NULL; } @@ -180,21 +180,23 @@ has_clause( int data_clauses, data_clause_t clause ) { return clause == (data_clauses & clause); } + static bool -is_cobol_word( const char name[] ) { +is_cobol_charset( const char name[] ) { auto eoname = name + strlen(name); - auto p = std::find_if( name, eoname, + auto ok = std::all_of( name, eoname, []( char ch ) { switch(ch) { case '-': case '_': - return false; + return true; case '$': // maybe one day (IBM allows) + return false; break; } - return !ISALNUM(ch); + return 0 != ISALNUM(ch); } ); - return p == eoname; + return ok; } bool @@ -208,6 +210,9 @@ in_file_section(void) { return current_data_section == file_datasect_e; } static cbl_refer_t * intrinsic_inconsistent_parameter( size_t n, cbl_refer_t *args ); +static int +intrinsic_token_of( const char name[] ); + static inline bool namcpy(const YYLTYPE& loc, cbl_name_t tgt, const char *src ) { // snprintf(3): writes at most size bytes (including the terminating NUL byte) @@ -221,7 +226,13 @@ namcpy(const YYLTYPE& loc, cbl_name_t tgt, const char *src ) { } cbl_field_t * -new_alphanumeric( size_t capacity = MAXIMUM_ALPHA_LENGTH ); +new_alphanumeric( size_t capacity = MAXIMUM_ALPHA_LENGTH, + const cbl_name_t name = nullptr ); + +static inline cbl_field_t * +new_alphanumeric( const cbl_name_t name ) { + return new_alphanumeric(MAXIMUM_ALPHA_LENGTH, name); +} static inline cbl_refer_t * new_reference( enum cbl_field_type_t type, const char *initial ) { @@ -236,9 +247,9 @@ new_reference_like( const cbl_field_t& skel ) { return new cbl_refer_t( new_temporary_like(skel) ); } -static void reject_refmod( YYLTYPE loc, cbl_refer_t ); -static bool require_pointer( YYLTYPE loc, cbl_refer_t ); -static bool require_numeric( YYLTYPE loc, cbl_refer_t ); +static void reject_refmod( YYLTYPE loc, const cbl_refer_t& ); +static bool require_pointer( YYLTYPE loc, const cbl_refer_t& ); +static bool require_integer( YYLTYPE loc, const cbl_refer_t& ); struct cbl_field_t * constant_of( size_t isym ); @@ -281,7 +292,7 @@ struct evaluate_elem_t { relop_t oper; public: cbl_field_t *subject, *object, *cond; - case_t( cbl_field_t * subject ) + explicit case_t( cbl_field_t * subject ) : oper(eq_op) , subject(subject) , object(NULL) @@ -312,21 +323,22 @@ struct evaluate_elem_t { case_iter pcase; void dump() const { - dbgmsg( "nother=%zu label '%s', %zu cases", nother, label.name, cases.size() ); + dbgmsg( "nother=" HOST_SIZE_T_PRINT_UNSIGNED " label '%s', " + HOST_SIZE_T_PRINT_UNSIGNED " cases", + (fmt_size_t)nother, label.name, (fmt_size_t)cases.size() ); std::for_each( cases.begin(), cases.end(), case_t::Dump ); } explicit evaluate_elem_t( const char skel[] ) : nother(0) + , label{LblEvaluate} , result( keep_temporary(FldConditional) ) , pcase( cases.end() ) { - static const cbl_label_t protolabel = { LblEvaluate }; - label = protolabel; label.line = yylineno; if( -1 == snprintf(label.name, sizeof(label.name), "%.*s_%d", (int)sizeof(label.name)-6, skel, yylineno) ) { - yyerror("could not create unique label '%s_%d' because it is too long", + yyerror("could not create unique label %<%s_%d%> because it is too long", skel, yylineno); } } @@ -357,13 +369,14 @@ struct evaluate_elem_t { static class file_delete_args_t { cbl_file_t *file; public: + file_delete_args_t() : file(nullptr) {} void init( cbl_file_t *file ) { this->file = file; } - bool ready() const { return file != NULL; } + bool ready() const { return file != nullptr; } void call_parser_file_delete( bool sequentially ) { parser_file_delete(file, sequentially); - file = NULL; + file = nullptr; } } file_delete_args; @@ -379,7 +392,7 @@ static struct file_read_args_t { void init( struct cbl_file_t *file, - cbl_refer_t record, + const cbl_refer_t& record, cbl_refer_t *read_into, int where ) { this->file = file; @@ -428,7 +441,7 @@ public: this->file = file; } bool ready() const { return file != NULL; } - void call_parser_return_start(cbl_refer_t into = cbl_refer_t() ) { + void call_parser_return_start(const cbl_refer_t& into = cbl_refer_t() ) { parser_return_start(file, into); file = NULL; } @@ -438,17 +451,18 @@ static class file_rewrite_args_t { cbl_file_t *file; cbl_field_t *record; public: + file_rewrite_args_t() : file(nullptr), record(nullptr) {} void init( cbl_file_t *file, cbl_field_t *record ) { this->file = file; this->record = record; } - bool ready() const { return file != NULL; } + bool ready() const { return file != nullptr; } void call_parser_file_rewrite( bool sequentially ) { sequentially = sequentially || file->access == file_access_seq_e; if( file->access == file_access_rnd_e ) sequentially = false; parser_file_rewrite(file, record, sequentially); - file = NULL; - record = NULL; + file = nullptr; + record = nullptr; } } file_rewrite_args; @@ -456,11 +470,12 @@ static class file_start_args_t { cbl_file_t *file; public: file_start_args_t() : file(NULL) {} - void init( YYLTYPE loc, cbl_file_t *file ) { + cbl_file_t * init( YYLTYPE loc, cbl_file_t *file ) { this->file = file; if( is_sequential(file) ) { error_msg(loc, "START invalid with sequential file %s", file->name); } + return file; } bool ready() const { return file != NULL; } void call_parser_file_start() { @@ -476,21 +491,22 @@ static class file_write_args_t { cbl_refer_t *advance; public: file_write_args_t() - : file(NULL) + : file(nullptr) + , data_source(nullptr) , after(false) - , advance(NULL) + , advance(nullptr) {} cbl_file_t * init( cbl_file_t *file, cbl_field_t *data_source, bool after, - cbl_refer_t *advance ) { + const cbl_refer_t *advance ) { this->file = file; this->data_source = data_source; this->after = after; this->advance = new cbl_refer_t(*advance); return this->file; } - bool ready() const { return file != NULL; } + bool ready() const { return file != nullptr; } void call_parser_file_write( bool sequentially ) { sequentially = sequentially || file->access == file_access_seq_e; parser_file_write(file, data_source, after, *advance, sequentially); @@ -524,7 +540,7 @@ struct arith_t { cbl_refer_t remainder; cbl_label_t *on_error, *not_error; - arith_t( cbl_arith_format_t format ) + explicit arith_t( cbl_arith_format_t format ) : format(format), on_error(NULL), not_error(NULL) {} arith_t( cbl_arith_format_t format, refer_list_t * refers ); @@ -542,8 +558,10 @@ struct arith_t { res.refer.field = cbl_field_of(symbol_at(tgt)); tgts.push_back( res ); - dbgmsg("%s:%d: SRC: %3zu %s", __func__, __LINE__, src, a.str()); - dbgmsg("%s:%d: to %3zu %s", __func__, __LINE__, tgt, res.refer.str()); + dbgmsg("%s:%d: SRC: %3" GCC_PRISZ "u %s", + __func__, __LINE__, (fmt_size_t)src, a.str()); + dbgmsg("%s:%d: to %3" GCC_PRISZ "u %s", + __func__, __LINE__, (fmt_size_t)tgt, res.refer.str()); } void operator()( const corresponding_fields_t::const_reference elem ) { another_pair( elem.first, elem.second ); @@ -606,7 +624,7 @@ class eval_subject_t { void new_object_labels(); public: eval_subject_t(); - void append( cbl_refer_t field ) { + void append( const cbl_refer_t& field ) { columns.push_back(field); pcol = columns.begin(); } @@ -737,6 +755,7 @@ public: static void dump_inspect( const cbl_inspect_t& i ); +void dump_inspect_match( const cbl_inspect_match_t& M ); struct perform_t { struct cbl_perform_tgt_t tgt; @@ -776,11 +795,10 @@ struct perform_t { cbl_refer_t table; } search; - perform_t( cbl_label_t *from, cbl_label_t *to = NULL ) + explicit perform_t( cbl_label_t *from, cbl_label_t *to = NULL ) : tgt( from, to ), before(true) - { - search = {}; - } + , search() + {} ~perform_t() { varys.clear(); } cbl_field_t * until() { assert(!varys.empty()); @@ -879,7 +897,7 @@ static struct cbl_label_t * paragraph_reference( const char name[], size_t section ); static inline void -list_add( list<cbl_num_result_t>& list, cbl_refer_t refer, int round ) { +list_add( list<cbl_num_result_t>& list, const cbl_refer_t& refer, int round ) { struct cbl_num_result_t arg = { static_cast<cbl_round_t>(round), refer }; list.push_back(arg); } @@ -918,55 +936,78 @@ teed_up_names() { } class tokenset_t { - std::vector<const char *>token_names; - std::map <std::string, int> tokens; - std::set<std::string> cobol_words; - + // token_names is initialized from a generated header file. + std::vector<const char *>token_names; // position indicates token value + std::map <std::string, int> tokens; // aliases + std::set<std::string> cobol_words; // Anything in COBOL-WORDS may appear only once. + public: static std::string lowercase( const cbl_name_t name ) { cbl_name_t lname; std::transform(name, name + strlen(name) + 1, lname, ftolower); return lname; } + static std::string + uppercase( const cbl_name_t name ) { + cbl_name_t uname; + std::transform(name, name + strlen(name) + 1, uname, ftoupper); + return uname; + } public: tokenset_t(); int find( const cbl_name_t name, bool include_intrinsics ); - bool equate( const YYLTYPE& loc, int token, const cbl_name_t name ) { + bool equate( const YYLTYPE& loc, int token, + const cbl_name_t name, const cbl_name_t verb = "EQUATE") { auto lname( lowercase(name) ); auto cw = cobol_words.insert(lname); if( ! cw.second ) { - error_msg(loc, "COBOL-WORDS EQUATE: %s may appear but once", name); + error_msg(loc, "COBOL-WORDS %s: %s may appear but once", verb, name); return false; } auto p = tokens.find(lowercase(name)); bool fOK = p == tokens.end(); if( fOK ) { // name not already in use tokens[lname] = token; + dbgmsg("%s:%d: %d has alias %s", __func__, __LINE__, token, name); } else { - error_msg(loc, "EQUATE: %s already defined as a token", name); + error_msg(loc, "%s: %s already defined as a token", verb, name); } return fOK; } - bool undefine( const YYLTYPE& loc, const cbl_name_t name ) { + bool undefine( const YYLTYPE& loc, + const cbl_name_t name, const cbl_name_t verb = "UNDEFINE" ) { auto lname( lowercase(name) ); auto cw = cobol_words.insert(lname); if( ! cw.second ) { - error_msg(loc, "COBOL-WORDS UNDEFINE: %s may appear but once", name); + error_msg(loc, "COBOL-WORDS %s: %s may appear but once", verb, name); return false; } + + // Do not erase generic, multi-type tokens COMPUTATIONAL and BINARY_INTEGER. + if( binary_integer_usage_of(name) ) { + dbgmsg("%s:%d: generic %s remains valid as a token", __func__, __LINE__, name); + return true; + } + auto p = tokens.find(lname); bool fOK = p != tokens.end(); if( fOK ) { // name in use tokens.erase(p); } else { - error_msg(loc, "UNDEFINE: %s not defined as a token", name); + error_msg(loc, "%s: %s not defined as a token", verb, name); } + dbgmsg("%s:%d: %s removed as a valid token name", __func__, __LINE__, name); return fOK; } - bool substitute( const YYLTYPE& loc, const cbl_name_t extant, int token, const cbl_name_t name ) { - return equate( loc, token, name ) && undefine( loc, extant ); + + bool substitute( const YYLTYPE& loc, + const cbl_name_t extant, int token, const cbl_name_t name ) { + return + equate( loc, token, name, "SUBSTITUTE" ) + && + undefine( loc, extant, "SUBSTITUTE" ); } bool reserve( const YYLTYPE& loc, const cbl_name_t name ) { auto lname( lowercase(name) ); @@ -991,7 +1032,7 @@ class tokenset_t { const char * name_of( int tok ) const { tok -= (255 + 3); gcc_assert(0 <= tok && size_t(tok) < token_names.size()); - return token_names[tok]; + return tok < 0? "???" : token_names[tok]; } }; @@ -1002,24 +1043,42 @@ class current_tokens_t { int find( const cbl_name_t name, bool include_intrinsics ) { return tokens.find(name, include_intrinsics); } - bool equate( const YYLTYPE& loc, cbl_name_t keyword, const cbl_name_t name ) { - int token = keyword_tok(keyword); - if( 0 == token ) { - error_msg(loc, "EQUATE %s: not a valid token", keyword); - return false; + bool equate( const YYLTYPE& loc, const cbl_name_t keyword, const cbl_name_t alias ) { + int token; + if( 0 == (token = binary_integer_usage_of(keyword)) ) { + if( 0 == (token = keyword_tok(keyword)) ) { + error_msg(loc, "EQUATE %s: not a valid token", keyword); + return false; + } } - return tokens.equate(loc, token, name); + auto name = keyword_alias_add(tokens.uppercase(keyword), + tokens.uppercase(alias)); + if( name != keyword ) { + error_msg(loc, "EQUATE: %s is already an alias for %s", alias, name.c_str()); + return false; + } + return tokens.equate(loc, token, alias); } bool undefine( const YYLTYPE& loc, cbl_name_t keyword ) { return tokens.undefine(loc, keyword); } - bool substitute( const YYLTYPE& loc, cbl_name_t keyword, const cbl_name_t name ) { - int token = keyword_tok(keyword); - if( 0 == token ) { - error_msg(loc, "SUBSTITUTE %s: not a valid token", keyword); - return false; + bool substitute( const YYLTYPE& loc, const cbl_name_t keyword, const cbl_name_t alias ) { + int token; + if( 0 == (token = binary_integer_usage_of(keyword)) ) { + if( 0 == (token = keyword_tok(keyword)) ) { + error_msg(loc, "SUBSTITUTE %s: not a valid token", keyword); + return false; + } } - return tokens.substitute(loc, keyword, token, name); + auto name = keyword_alias_add(tokens.uppercase(keyword), + tokens.uppercase(alias)); + if( name != keyword ) { + error_msg(loc, "SUBSTITUTE: %s is already an alias for %s", alias, name.c_str()); + return false; + } + + dbgmsg("%s:%d: %s (%d) will have alias %s", __func__, __LINE__, keyword, token, alias); + return tokens.substitute(loc, keyword, token, alias); } bool reserve( const YYLTYPE& loc, const cbl_name_t name ) { return tokens.reserve(loc, name); @@ -1040,7 +1099,7 @@ redefined_token( const cbl_name_t name ) { struct file_list_t { list<cbl_file_t*> files; file_list_t() {} - file_list_t( cbl_file_t* file ) { + explicit file_list_t( cbl_file_t* file ) { files.push_back(file); } file_list_t( file_list_t& that ) : files(that.files.size()) { @@ -1054,10 +1113,15 @@ struct file_list_t { struct field_list_t { list<cbl_field_t*> fields; - field_list_t( cbl_field_t *field ) { + field_list_t() {} + explicit field_list_t( cbl_field_t *field ) { fields.push_back(field); } - explicit field_list_t() {} + std::vector<const cbl_field_t*> + as_vector() const { + std::vector<const cbl_field_t*> output( fields.begin(), fields.end() ); + return output; + } }; cbl_field_t ** @@ -1084,7 +1148,7 @@ cbl_file_t ** struct refer_list_t { list<cbl_refer_t> refers; - refer_list_t( cbl_refer_t *refer ) { + explicit refer_list_t( cbl_refer_t *refer ) { if( refer ) { refers.push_back(*refer); delete refer; @@ -1106,13 +1170,20 @@ struct refer_list_t { refers.clear(); return tgt; } + std::vector<cbl_refer_t> + vectorize() { + std::vector<cbl_refer_t> tgt(refers.size()); + std::copy(refers.begin(), refers.end(), tgt.begin()); + refers.clear(); + return tgt; + } }; struct refer_marked_list_t : public refer_list_t { cbl_refer_t *marker; refer_marked_list_t() : refer_list_t(NULL), marker(NULL) {} - refer_marked_list_t( cbl_refer_t *marker, refer_list_t *refers ) + refer_marked_list_t( cbl_refer_t *marker, const refer_list_t *refers ) : refer_list_t(*refers), marker(marker) {} refer_marked_list_t( cbl_refer_t *marker, cbl_refer_t *input ) : refer_list_t(input) @@ -1132,7 +1203,7 @@ struct refer_marked_list_t : public refer_list_t { struct refer_collection_t { list<refer_marked_list_t> lists; - refer_collection_t( const refer_marked_list_t& marked_list ) + explicit refer_collection_t( const refer_marked_list_t& marked_list ) { lists.push_back( marked_list ); } @@ -1158,48 +1229,13 @@ struct refer_collection_t { } }; -struct ast_inspect_oper_t { - cbl_inspect_bound_t bound; // CHARACTERS/ALL/LEADING/FIRST - std::list<cbl_inspect_match_t> matches; - std::list<cbl_inspect_replace_t> replaces; - -ast_inspect_oper_t( const cbl_inspect_match_t& match, - cbl_inspect_bound_t bound = bound_characters_e ) - : bound(bound) - { - matches.push_back(match); - } - ast_inspect_oper_t( const cbl_inspect_replace_t& replace, - cbl_inspect_bound_t bound = bound_characters_e ) - : bound(bound) - { - replaces.push_back(replace); - } -}; - -struct ast_inspect_t : public std::list<cbl_inspect_oper_t> { - cbl_refer_t tally; // field is NULL for REPLACING - const std::list<cbl_inspect_oper_t>& opers() const { return *this; } -}; - -struct ast_inspect_list_t : public std::list<cbl_inspect_t> { - ast_inspect_list_t( const cbl_inspect_t& insp ) { - push_back(insp); - } - - cbl_inspect_t * as_array() { - cbl_inspect_t *output = new cbl_inspect_t[ size() ]; - std::copy( begin(), end(), output ); - return output; - } -}; - -void ast_inspect( cbl_refer_t& input, bool backward, ast_inspect_list_t& inspects ); +void ast_inspect( YYLTYPE loc, cbl_refer_t& input, bool backward, + cbl_inspect_opers_t& inspects ); template <typename E> struct elem_list_t { list<E*> elems; - elem_list_t( E *elem ) { + explicit elem_list_t( E *elem ) { elems.push_back(elem); } void clear() { @@ -1224,7 +1260,7 @@ template <typename L, typename E> struct unstring_tgt_t { cbl_refer_t *tgt, *delimiter, *count; - unstring_tgt_t( cbl_refer_t *tgt, + explicit unstring_tgt_t( cbl_refer_t *tgt, cbl_refer_t *delimiter = NULL, cbl_refer_t *count = NULL ) : tgt(tgt), delimiter(delimiter), count(count) @@ -1248,7 +1284,7 @@ private: struct unstring_tgt_list_t { list<unstring_tgt_t> unstring_tgts; - unstring_tgt_list_t( unstring_tgt_t *unstring_tgt ) { + explicit unstring_tgt_list_t( unstring_tgt_t *unstring_tgt ) { unstring_tgts.push_back(*unstring_tgt); delete unstring_tgt; } @@ -1270,7 +1306,7 @@ struct unstring_tgt_list_t { struct unstring_into_t : public unstring_tgt_list_t { cbl_refer_t pointer, tally; - unstring_into_t( unstring_tgt_list_t *tgt_list, + explicit unstring_into_t( unstring_tgt_list_t *tgt_list, cbl_refer_t *pointer = NULL, cbl_refer_t *tally = NULL ) : unstring_tgt_list_t(*tgt_list) @@ -1286,7 +1322,7 @@ struct unstring_into_t : public unstring_tgt_list_t { struct ffi_args_t { list<cbl_ffi_arg_t> elems; - ffi_args_t( cbl_ffi_arg_t *arg ) { + explicit ffi_args_t( cbl_ffi_arg_t *arg ) { this->push_back(arg); } @@ -1362,8 +1398,8 @@ struct file_sort_io_t { file_list_t file_list; cbl_perform_tgt_t tgt; - file_sort_io_t( file_list_t& files ) : file_list(files) {} - file_sort_io_t( cbl_perform_tgt_t& tgt ) : tgt(tgt.from(), tgt.to()) {} + explicit file_sort_io_t( file_list_t& files ) : file_list(files) {} + explicit file_sort_io_t( cbl_perform_tgt_t& tgt ) : tgt(tgt.from(), tgt.to()) {} size_t nfile() const { return file_list.files.size(); } }; @@ -1378,14 +1414,14 @@ struct merge_t { cbl_perform_tgt_t tgt; list<cbl_file_t*> outputs; - merge_t( cbl_file_t *input ) : master(input), type(output_unknown_e) {} + explicit merge_t( cbl_file_t *input ) : master(input), type(output_unknown_e) {} }; static list<merge_t> merges; static inline merge_t& merge_alloc( cbl_file_t *file ) { - merges.push_back(file); + merges.push_back(merge_t(file)); return merges.back(); } @@ -1406,7 +1442,7 @@ static list<cbl_refer_t> lhs; struct vargs_t { std::list<cbl_refer_t> args; vargs_t() {} - vargs_t( struct cbl_refer_t *p ) { args.push_back(*p); delete p; } + explicit vargs_t( struct cbl_refer_t *p ) { args.push_back(*p); delete p; } void push_back( cbl_refer_t *p ) { args.push_back(*p); delete p; } }; @@ -1425,12 +1461,13 @@ class prog_descr_t { std::set<std::string> call_targets, subprograms; public: std::set<function_descr_t> function_repository; - size_t program_index, declaratives_index; + size_t program_index; cbl_label_t *declaratives_eval, *paragraph, *section; const char *collating_sequence; struct locale_t { cbl_name_t name; const char *os_name; - locale_t(const cbl_name_t name = NULL, const char *os_name = NULL) + locale_t() : name(""), os_name(nullptr) {} + locale_t(const cbl_name_t name, const char *os_name) : name(""), os_name(os_name) { if( name ) { bool ok = namcpy(YYLTYPE(), this->name, name); @@ -1441,9 +1478,8 @@ class prog_descr_t { cbl_call_convention_t call_convention; cbl_options_t options; - prog_descr_t( size_t isymbol ) + explicit prog_descr_t( size_t isymbol ) : program_index(isymbol) - , declaratives_index(0) , declaratives_eval(NULL) , paragraph(NULL) , section(NULL) @@ -1554,9 +1590,9 @@ class program_stack_t : protected std::stack<prog_descr_t> { bool pending_initial() { return pending.initial = true; } void push( prog_descr_t descr ) { - cbl_call_convention_t current_call_convention = cbl_call_cobol_e; - if( !empty() ) current_call_convention = top().call_convention; - descr.call_convention = current_call_convention; + cbl_call_convention_t call_convention = cbl_call_cobol_e; + if( !empty() ) call_convention = top().call_convention; + descr.call_convention = call_convention; std::stack<prog_descr_t>& me(*this); me.push(descr); } @@ -1592,11 +1628,12 @@ class program_stack_t : protected std::stack<prog_descr_t> { } } + // cppcheck-suppress-begin useStlAlgorithm cbl_label_t *first_declarative() { auto eval = top().declaratives_eval; if( eval ) return eval; // scan stack container for declaratives - for( auto& prog : c ) { + for( const auto& prog : c ) { if( prog.declaratives_eval ) { eval = prog.declaratives_eval; break; @@ -1604,6 +1641,7 @@ class program_stack_t : protected std::stack<prog_descr_t> { } return eval; } + // cppcheck-suppress-end useStlAlgorithm }; struct rel_part_t { @@ -1611,9 +1649,13 @@ struct rel_part_t { bool has_relop, invert; relop_t relop; - rel_part_t( cbl_refer_t *operand = NULL, - relop_t relop = relop_t(-1), - bool invert = false ) + rel_part_t() + : operand(nullptr), + has_relop(false), + invert(false), + relop(relop_t(-1)) + {} + rel_part_t( cbl_refer_t *operand, relop_t relop, bool invert ) : operand(operand), has_relop(relop != -1), invert(invert), @@ -1647,7 +1689,7 @@ struct rel_part_t { class log_expr_t { cbl_field_t *orable, *andable; public: - log_expr_t( cbl_field_t *init ) : orable(NULL), andable(init) { + explicit log_expr_t( cbl_field_t *init ) : orable(NULL), andable(init) { if( ! is_conditional(init) ) { dbgmsg("%s:%d: logic error: %s is not a truth value", __func__, __LINE__, name_of(init)); @@ -1706,18 +1748,11 @@ static class current_t { int first_statement; bool in_declaratives; // from command line or early TURN - std::list<cbl_exception_files_t> cobol_exceptions; + std::list<exception_turn_t> exception_turns; error_labels_t error_labels; static void declarative_execute( cbl_label_t *eval ) { - if( !eval ) { - if( !enabled_exceptions.empty() ) { - auto index = new_temporary(FldNumericBin5); - parser_match_exception(index, NULL); - } - return; - } assert(eval); auto iprog = symbol_elem_of(eval)->program; if( iprog == current_program_index() ) { @@ -1813,6 +1848,10 @@ static class current_t { class declaratives_t : protected declaratives_list_t { struct file_exception_t { ec_type_t type; uint32_t file; + file_exception_t() : type(ec_none_e), file(0) {} + file_exception_t(ec_type_t type, uint32_t file) + : type(type), file(file) + {} bool operator<( const file_exception_t& that ) const { if( type == that.type ) return file < that.file; return type < that.type; @@ -1820,6 +1859,13 @@ static class current_t { }; std::set<file_exception_t> file_exceptions; public: + declaratives_t() {} + // current compiled data for enabled ECs and Declaratives, used by library. + struct runtime_t { + tree ena, dcl; + runtime_t() : ena(nullptr), dcl(nullptr) {} + } runtime; + bool empty() const { return declaratives_list_t::empty(); } @@ -1837,7 +1883,7 @@ static class current_t { } for( auto f = declarative.files; f && f < declarative.files + declarative.nfile; f++ ) { - file_exception_t ex = { declarative.type, *f }; + file_exception_t ex( declarative.type, *f ); auto result = file_exceptions.insert(ex); if( ! result.second ) { yyerror("%s defined twice for %s", @@ -1849,14 +1895,46 @@ static class current_t { declaratives_list_t::push_back(declarative); return true; } + + // cppcheck-suppress-begin useStlAlgorithm + uint32_t status() const { + uint32_t status_word = 0; + for( auto dcl : *this ) { + status_word |= (EC_ALL_E & dcl.type ); + } + return status_word; + } + // cppcheck-suppress-end useStlAlgorithm + + bool has_format_1() const { + return std::any_of( begin(), end(), + []( const cbl_declarative_t& dcl ) { + return dcl.is_format_1(); + } ); + } + + std::vector<uint64_t> + encode() const { + std::vector<uint64_t> encoded; + auto p = std::back_inserter(encoded); + for( const auto& dcl : *this ) { + *p++ = dcl.section; + *p++ = dcl.global; + *p++ = dcl.type; + *p++ = dcl.nfile; + p = std::copy(dcl.files, std::end(dcl.files), p); + *p++ = dcl.mode; + } + return encoded; + } + } declaratives; void exception_add( ec_type_t ec, bool enabled = true) { - std::set<size_t> files; - enabled_exceptions.turn_on_off(enabled, - false, // for now - ec, files); - if( yydebug) enabled_exceptions.dump(); + exception_turns.push_back(exception_turn_t(ec, enabled)); + } + std::list<exception_turn_t>& pending_exceptions() { + return exception_turns; } bool typedef_add( const cbl_field_t *field ) { @@ -1866,7 +1944,6 @@ static class current_t { const cbl_field_t * has_typedef( const cbl_field_t *field ) { auto found = typedefs.find(field); return found == typedefs.end()? NULL : *found; - return found == typedefs.end()? NULL : *found; } void udf_add( size_t isym ) { @@ -1922,12 +1999,12 @@ static class current_t { std::list<std::string>& debugging_declaratives(bool all) const { const char *para = programs.top().paragraph->name; - auto declaratives = debugging_clients.find(all? ":all:" : para); - if( declaratives == debugging_clients.end() ) { + auto client = debugging_clients.find(all? ":all:" : para); + if( client == debugging_clients.end() ) { static std::list<std::string> empty; return empty; } - return declaratives->second; + return client->second; } bool @@ -1998,7 +2075,7 @@ static class current_t { const cbl_label_t *L; if( (L = symbol_program_add(parent, &label)) == NULL ) return false; - programs.push( symbol_index(symbol_elem_of(L))); + programs.push( prog_descr_t(symbol_index(symbol_elem_of(L))) ); programs.apply_pending(); bool fOK = symbol_at(programs.top().program_index) + 1 == symbols_end(); @@ -2022,10 +2099,6 @@ static class current_t { assert(!programs.empty()); return programs.top().program_index; } - size_t program_declaratives(void) const { - if( programs.empty() ) return 0; - return programs.top().declaratives_index; - } const cbl_label_t * program(void) { return programs.empty()? NULL : cbl_label_of(symbol_at(programs.top().program_index)); @@ -2039,12 +2112,16 @@ static class current_t { bool is_first_statement( const YYLTYPE& loc ) { if( ! in_declaratives && first_statement == 0 ) { - if( ! symbol_label_section_exists(program_index()) ) { - if( ! dialect_ibm() ) { - error_msg(loc, - "Per ISO a program with DECLARATIVES must begin with a SECTION, " - "requires -dialect ibm"); - } + auto eval = programs.top().declaratives_eval; + if( eval ) { + size_t ilabel = symbol_index(symbol_elem_of(eval)); + if( ! symbol_label_section_exists(ilabel) ) { + if( ! dialect_ibm() ) { + error_msg(loc, + "Per ISO a program with DECLARATIVES must begin with a SECTION, " + "requires %<-dialect ibm%>"); + } + } } first_statement = loc.first_line; return true; @@ -2061,12 +2138,12 @@ static class current_t { */ std::set<std::string> end_program() { if( enabled_exceptions.size() ) { - declaratives_evaluate(ec_none_e); + declaratives_evaluate(); } assert(!programs.empty()); - procref_t *ref = ambiguous_reference(program_index()); + const procref_t *ref = ambiguous_reference(program_index()); std::set<std::string> externals = programs.top().external_targets(); /* @@ -2077,9 +2154,19 @@ static class current_t { * subprograms, and whether or not they are COMMON. PROGRAM may be * the caller, or a subprogram could call COMMON sibling. */ + + static std::unordered_set<size_t> callers_we_have_seen; if( programs.size() == 1 ) { if( yydebug ) parser_call_targets_dump(); for( size_t caller : symbol_program_programs() ) { + // We are running through the entire growing list of called programs + // at the point of each END PROGRAM. This confuses the name changing + // routines, so we use a std::set to avoid doing callers more than + // once. + if( callers_we_have_seen.find(caller) != callers_we_have_seen.end() ) + { + continue; + } const char *caller_name = cbl_label_of(symbol_at(caller))->name; for( auto callable : symbol_program_callables(caller) ) { auto called = cbl_label_of(symbol_at(callable)); @@ -2087,11 +2174,16 @@ static class current_t { called->mangled_name? called->mangled_name : called->name; size_t n = - parser_call_target_update(caller, called->name, mangled_name); + parser_call_target_update(caller, + called->name, + mangled_name); // Zero is not an error - dbgmsg("updated %zu calls from #%-3zu (%s) s/%s/%s/", - n, caller, caller_name, called->name, mangled_name); + dbgmsg("updated " HOST_SIZE_T_PRINT_UNSIGNED + " calls from #%-3" GCC_PRISZ "u (%s) s/%s/%s/", + (fmt_size_t)n, (fmt_size_t)caller, caller_name, + called->name, mangled_name); } + callers_we_have_seen.insert(caller); } if( yydebug ) parser_call_targets_dump(); } @@ -2121,7 +2213,7 @@ static class current_t { return symbol_index(symbol_elem_of(section)); } - cbl_label_t *doing_declaratives( bool begin ) { + cbl_label_t * doing_declaratives( bool begin ) { if( begin ) { in_declaratives = true; return NULL; @@ -2131,24 +2223,27 @@ static class current_t { if( declaratives.empty() ) return NULL; assert(!declaratives.empty()); - size_t idcl = symbol_declaratives_add(program_index(), declaratives.as_list()); - programs.top().declaratives_index = idcl; + declaratives.runtime.dcl = parser_compile_dcls(declaratives.encode()); // Create section to evaluate declaratives. Given them unique names so // that we can figure out what is going on in a trace or looking at the // assembly language. - static int eval_count=1; - char eval[32]; - char lave[32]; + static int eval_count = 1; + char eval[32], lave[32]; + sprintf(eval, "_DECLARATIVES_EVAL%d", eval_count); - sprintf(lave, "_DECLARATIVES_LAVE%d", eval_count); - eval_count +=1 ; + sprintf(lave, "_DECLARATIVES_LAVE%d", eval_count++); struct cbl_label_t*& eval_label = programs.top().declaratives_eval; eval_label = label_add(LblSection, eval, yylineno); struct cbl_label_t * lave_label = label_add(LblSection, lave, yylineno); + ast_enter_section(eval_label); - declarative_runtime_match(cbl_field_of(symbol_at(idcl)), lave_label); + + declarative_runtime_match(declaratives.as_list(), lave_label); + + parser_label_label(lave_label); + return lave_label; } @@ -2156,14 +2251,32 @@ static class current_t { std::swap( programs.top().section, section ); return section; } + + ec_type_t ec_type_of( file_status_t status ) { + static std::vector<ec_type_t> ec_by_status { + /* 0 */ ec_none_e, // ec_io_warning_e if low byte is nonzero + /* 1 */ ec_io_at_end_e, + /* 2 */ ec_io_invalid_key_e, + /* 3 */ ec_io_permanent_error_e, + /* 4 */ ec_io_logic_error_e, + /* 5 */ ec_io_record_operation_e, + /* 6 */ ec_io_file_sharing_e, + /* 7 */ ec_io_record_content_e, + /* 8 */ ec_io_imp_e, // unused, not defined by ISO + /* 9 */ ec_io_imp_e, + }; + int status10 = static_cast<unsigned int>(status) / 10; + gcc_assert(ec_by_status.size() == 10); + gcc_assert(0 <= status10 && status10 < 10 && status10 != 8); + return ec_by_status[status10]; + } /* * END DECLARATIVES causes: - * 1. Add DECLARATIVES symbol, containing criteria blob. - * 2. Create section _DECLARATIVES_EVAL + * 1. Create section _DECLARATIVES_EVAL * and exit label _DECLARATIVES_LAVE - * 3. declarative_runtime_match generates runtime evaluation "ladder". - * 4. After a declarative is executed, control branches to the exit label. + * 2. declarative_runtime_match generates runtime evaluation "ladder". + * 3. After a declarative is executed, control branches to the exit label. * * After each verb, we call declaratives_evaluate, * which PERFORMs _DECLARATIVES_EVAL. @@ -2173,18 +2286,8 @@ static class current_t { * alternative entry point (TODO). */ void - declaratives_evaluate( cbl_file_t *file, - file_status_t status = FsSuccess ) { - // The exception file number is assumed to be zero at all times unless - // it has been set to non-zero, at which point whoever picks it up and takes - // action on it is charged with setting it back to zero. - if( file ) - { - parser_set_file_number((int)symbol_index(symbol_elem_of(file))); - } - // parser_set_file_number(file ? (int)symbol_index(symbol_elem_of(file)) : 0); - parser_set_handled((ec_type_t)status); - + declaratives_evaluate( cbl_file_t *file ) { + gcc_assert(file); parser_file_stash(file); cbl_label_t *eval = programs.first_declarative(); @@ -2212,7 +2315,7 @@ static class current_t { * To indicate to the runtime-match function that we want to evaluate * only the exception condition, unrelated to a file, we set the * file register to 0 and the handled-exception register to the - * handled exception condition (not file status). + * handled exception condition. * * declaratives_execute performs the "declarative ladder" produced * by declaratives_runtime_match. That section CALLs the @@ -2223,16 +2326,9 @@ static class current_t { * index, per usual. */ void - declaratives_evaluate( ec_type_t handled = ec_none_e ) { - // The exception file number is assumed to be zero unless it has been - // changed to a non-zero value. The program picking it up and referencing - // it is charged with setting it back to zero. - // parser_set_file_number(0); - - parser_set_handled(handled); - + declaratives_evaluate() { cbl_label_t *eval = programs.first_declarative(); - declarative_execute(eval); + if( eval ) declarative_execute(eval); } cbl_label_t * new_paragraph( cbl_label_t *para ) { @@ -2276,15 +2372,20 @@ static class current_t { cbl_label_t * compute_label() { return error_labels.compute_error; } } current; +void current_enabled_ecs( tree ena ) { + current.declaratives.runtime.ena = ena; +} + #define PROGRAM current.program_index() static void add_debugging_declarative( const cbl_label_t * label ) { + // cppcheck-suppress [unreadVariable] obviously not true const char *section = current.declarative_section_name(); if( section ) { debugging_clients[label->name].push_back(section); } -}; +} cbl_options_t current_options() { return current.options_paragraph; @@ -2354,10 +2455,14 @@ char * normalize_picture( char picture[] ); static inline cbl_field_t * -new_tempnumeric(void) { return new_temporary(FldNumericBin5); } +new_tempnumeric(const cbl_name_t name = nullptr) { + return new_temporary(FldNumericBin5, name); +} static inline cbl_field_t * -new_tempnumeric_float(void) { return new_temporary(FldFloat); } +new_tempnumeric_float(const cbl_name_t name = nullptr) { + return new_temporary(FldFloat, name); +} uint32_t type_capacity( enum cbl_field_type_t type, uint32_t digits ); @@ -2375,11 +2480,27 @@ literal_refmod_valid( YYLTYPE loc, const cbl_refer_t& r ); static bool is_integer_literal( const cbl_field_t *field ) { - if( is_literal(field) ) { - int v, n; + if( field->type == FldLiteralN ) { const char *initial = field->data.initial; - return 1 == sscanf(initial, "%d%n", &v, &n) && n == (int)strlen(initial); + switch( *initial ) { + case '-': case '+': ++initial; + } + + const char *eos = initial + strlen(initial); + auto p = std::find_if_not( initial, eos, fisdigit ); + if( p == eos ) return true; + + if( *p++ == symbol_decimal_point() ) { + switch( *p++ ) { + case 'E': case 'e': + switch( *p++ ) { + case '+': case '-': + return std::all_of(p, eos, []( char ch ) { return ch == '0'; } ); + break; + } + } + } } return false; } @@ -2453,7 +2574,8 @@ is_callable( const cbl_field_t *field ) { case FldPointer: return true; } - cbl_internal_error( "%s:%d: invalid symbol_type_t %d", __func__, __LINE__, field->type ); + cbl_internal_error( "%s:%d: invalid %<symbol_type_t%> %d", + __func__, __LINE__, field->type ); return false; } @@ -2500,8 +2622,8 @@ intrinsic_call_1( cbl_field_t *output, int token, } static bool -intrinsic_call_2( cbl_field_t *tgt, int token, cbl_refer_t *r1, cbl_refer_t *r2 ) { - std::vector<cbl_refer_t> args { *r1, *r2 }; +intrinsic_call_2( cbl_field_t *tgt, int token, const cbl_refer_t *r1, cbl_refer_t *r2 ) { + std::vector<cbl_refer_t> args { *r1, r2? *r2 : cbl_refer_t() }; size_t n = intrinsic_invalid_parameter(token, args); if( n < args.size() ) { error_msg(args[n].loc, "invalid parameter '%s'", args[n].field->name); @@ -2578,18 +2700,14 @@ table_primary_index( cbl_field_t *table ) { NULL : cbl_field_of(symbol_at(table->occurs.indexes.fields[0])); } -static inline const cbl_refer_t // & // Removed the '&' to stop a weird compiler error +static inline const cbl_refer_t // return copy, not element reference invalid_key( const cbl_refer_t& ref ) { assert(ref.field); - - if( ref.nsubscript == 0 ) return ref; - - for( size_t i=0; i < ref.nsubscript; i++ ) { - if( ref.subscripts[i].field->parent != ref.field->parent ) { - return ref.subscripts[i]; - } - } - return NULL; + auto p = std::find_if( ref.subscripts.begin(), ref.subscripts.end(), + [parent = ref.field->parent]( const auto &sub ) { + return sub.field->parent == parent; + } ); + return p != ref.subscripts.end() ? *p : nullptr; } static inline symbol_elem_t * @@ -3006,8 +3124,8 @@ file_add( YYLTYPE loc, cbl_file_t *file ) { } file = cbl_file_of(e); snprintf(field->name, sizeof(field->name), - "%s%zu_%s", - record_area_name_stem, symbol_index(e), file->name); + "%s" HOST_SIZE_T_PRINT_UNSIGNED "_%s", + record_area_name_stem, (fmt_size_t)symbol_index(e), file->name); if( file->attr & external_e ) { snprintf(field->name, sizeof(field->name), "%s%s", record_area_name_stem, file->name); @@ -3037,6 +3155,17 @@ current_field(cbl_field_t * field = NULL) { return local; } +static void +set_real_from_capacity( const YYLTYPE& loc, + cbl_field_t *field, + REAL_VALUE_TYPE *r ) { + if( field == current_field() ) { + error_msg(loc, "cannot define %s via self-reference", field->name); + return; + } + field->data.set_real_from_capacity(r); +} + static struct cbl_special_name_t * special_of( const char F[], int L, const char name[] ) { struct symbol_elem_t *e = symbol_special(PROGRAM, name); @@ -3048,15 +3177,30 @@ special_of( const char F[], int L, const char name[] ) { } #define special_of( F ) special_of(__func__, __LINE__, (F)) +static const special_name_t * +cmd_or_env_special_of( std::string name ) { + static const std::map< std::string, special_name_t > fujitsus + { // Fujitsu calls these "function names", not device names + { "ARGUMENT-NUMBER", ARG_NUM_e }, + { "ARGUMENT-VALUE", ARG_VALUE_e } , + { "ENVIRONMENT-NAME", ENV_NAME_e }, + { "ENVIRONMENT-VALUE", ENV_VALUE_e }, + }; + + std::transform(name.begin(), name.end(), name.begin(), ::toupper); + auto p = fujitsus.find(name.c_str()); + return p != fujitsus.end()? &p->second : nullptr; +} + static inline void -parser_add2( struct cbl_num_result_t& to, - struct cbl_refer_t from ) { +parser_add2( const cbl_num_result_t& to, + const cbl_refer_t& from ) { parser_add(to.refer, to.refer, from, to.rounded); } static inline void -parser_subtract2( struct cbl_num_result_t to, - struct cbl_refer_t from ) { +parser_subtract2( const cbl_num_result_t& to, + const cbl_refer_t& from ) { parser_subtract(to.refer, to.refer, from, to.rounded); } @@ -3079,6 +3223,11 @@ parser_move_carefully( const char */*F*/, int /*L*/, } } else { if( ! valid_move( tgt.field, src.field ) ) { + if( src.field->type == FldPointer && + tgt.field->type == FldPointer ) { + if( dialect_mf() || dialect_gnu() ) return true; + dialect_error(src.loc, "MOVE POINTER", "mf"); + } if( ! is_index ) { char ach[16]; char stype[32]; @@ -3104,7 +3253,6 @@ parser_move_carefully( const char */*F*/, int /*L*/, sprintf(ach, ".%d", tgt.field->data.rdigits); strcat(dtype, ach); } - error_msg(src.loc, "cannot MOVE '%s' (%s) to '%s' (%s)", name_of(src.field), stype, name_of(tgt.field), dtype); @@ -3140,11 +3288,11 @@ ast_set_pointers( const list<cbl_num_result_t>& tgts, cbl_refer_t src ) { void stringify( refer_collection_t *inputs, - cbl_refer_t into, cbl_refer_t pointer, + const cbl_refer_t& into, const cbl_refer_t& pointer, cbl_label_t *on_error = NULL, cbl_label_t *not_error = NULL); -void unstringify( cbl_refer_t& src, refer_list_t *delimited, +void unstringify( const cbl_refer_t& src, refer_list_t *delimited, unstring_into_t * into, cbl_label_t *on_error = NULL, cbl_label_t *not_error = NULL ); @@ -3153,7 +3301,8 @@ static cbl_label_t * implicit_paragraph() { cbl_name_t name; - sprintf(name, "_implicit_paragraph_%zu", symbol_index()); + sprintf(name, "_implicit_paragraph_" HOST_SIZE_T_PRINT_UNSIGNED, + (fmt_size_t)symbol_index()); // Programs have to start with an implicit paragraph return label_add(LblParagraph, name, yylineno); } @@ -3161,12 +3310,14 @@ static cbl_label_t * implicit_section() { cbl_name_t name; - sprintf(name, "_implicit_section_%zu", symbol_index()); + sprintf(name, "_implicit_section_" HOST_SIZE_T_PRINT_UNSIGNED, + (fmt_size_t)symbol_index()); // Programs have to start with an implicit section return label_add(LblSection, name, yylineno); } static void +// cppcheck-suppress constParameterPointer ast_enter_exit_section( cbl_label_t * section ) { auto implicit = section? implicit_paragraph() : NULL; @@ -3236,7 +3387,8 @@ data_division_ready() { } if( nsymbol == 0 || nparse_error > 0 ) { - dbgmsg( "%d errors in DATA DIVISION, compilation ceases", nparse_error ); + dbgmsg( HOST_SIZE_T_PRINT_DEC " errors in DATA DIVISION, compilation ceases", + (fmt_size_t)nparse_error ); return false; } @@ -3245,7 +3397,7 @@ data_division_ready() { static bool -anybody_redefines(cbl_field_t *tree) +anybody_redefines( const cbl_field_t *tree ) { bool retval = false; while(tree) @@ -3255,7 +3407,8 @@ anybody_redefines(cbl_field_t *tree) retval = true; break; } - tree = parent_of(tree); + // cppcheck-suppress [unreadVariable] obviously not true + tree = parent_of(tree); } return retval; } @@ -3302,6 +3455,13 @@ procedure_division_ready( YYLTYPE loc, cbl_field_t *returning, ffi_args_t *ffi_a } } + // Apply ECs from the command line + std::list<exception_turn_t>& exception_turns = current.pending_exceptions(); + for( const auto& exception_turn : exception_turns) { + apply_cdf_turn(exception_turn); + } + exception_turns.clear(); + // Start the Procedure Division. size_t narg = ffi_args? ffi_args->elems.size() : 0; std::vector <cbl_ffi_arg_t> args(narg); @@ -3468,14 +3628,14 @@ file_section_parent_set( cbl_field_t *field ) { field->data.capacity); field->file = file_section_fd; - auto redefined = symbol_redefines(record_area); + const auto redefined = symbol_redefines(record_area); field->parent = redefined? record_area->parent : file->default_record; } return file_section_fd > 0; } void ast_call(const YYLTYPE& loc, cbl_refer_t name, - cbl_refer_t returning, + const cbl_refer_t& returning, size_t narg, cbl_ffi_arg_t args[], cbl_label_t *except, cbl_label_t *not_except, @@ -3534,6 +3694,11 @@ goodnight_gracie() { return true; } +// false after USE statement, to enter Declarative with EC intact. +static bool statement_cleanup = true; + +static void statement_epilog( int token ); + const char * keyword_str( int token ); static YYLTYPE current_location; @@ -3545,9 +3710,7 @@ location_set( const YYLTYPE& loc ) { return current_location = loc; } -static int prior_statement; - -static size_t statement_begin( const YYLTYPE& loc, int token ); +static void statement_begin( const YYLTYPE& loc, int token ); static void ast_first_statement( const YYLTYPE& loc ) { if( current.is_first_statement( loc ) ) { |