diff --git a/gcc/cobol/gcobc b/gcc/cobol/gcobc index 74f54a4ef9f18e2d9dc1b522d24bf963d7166ca8..93e1bd302a66fadd3504626beb329042d27e4ca6 100755 --- a/gcc/cobol/gcobc +++ b/gcc/cobol/gcobc @@ -150,9 +150,9 @@ do case $opt in -A | -Q) warn "$opt" ;; - -b) mode="-shared" + -b) mode="-shared" ;; - -c) mode="-c" + -c) mode="-c" ;; --conf=*) warn "$opt" ;; @@ -161,8 +161,8 @@ do -d | --debug) opts="$opts -fcobol-exceptions=EC-ALL" warn "$opt implies -fstack-check:" ;; - # -D - -E) opts="$opts $opt -fsyntax-only" + # -D + -E) opts="$opts $opt -fsyntax-only" ;; -echo) echo="echo" ;; @@ -367,7 +367,7 @@ do opts="$opts -ffree-form" ;; - -h | --help) opts="$opts --help" + -h | --help) opts="$opts --help" ;; -HELP) help && exit @@ -375,7 +375,7 @@ do -i | --info) warn "$opt" ;; - # -I + # -I -fimplicit-init) warn "$opt" ;; -j | -job) warn "$opt" @@ -384,26 +384,26 @@ do ;; -K*) warn "$opt" ;; - # -l - # -L + # -l + # -L --list*) warn "$opt" ;; - -m) mode="-shared" + -m) mode="-shared" ;; # -main # -nomain - # -o + # -o # -O0, -Ox -O | -O2 | -Os) warn "$opt" ;; - -S) mode="$opt" + -S) mode="$opt" ;; -save-temps=*) opt="$(echo "$opt" | sed -E 's/^.+=//')" export GCOBOL_TEMPDIR="$opt" ;; -save-temps) export GCOBOL_TEMPDIR="${PWD:-$(pwd)}" ;; - # -shared is identical + # -shared is identical -std=mvs) opts="$opts -dialect ibm" ;; diff --git a/gcc/cobol/genapi.cc b/gcc/cobol/genapi.cc index 9c2ab8ad207a7fb8b1aa174aec23ed646049f201..ef3fdfd206870c967ee634d258c987fe4675499c 100644 --- a/gcc/cobol/genapi.cc +++ b/gcc/cobol/genapi.cc @@ -233,7 +233,7 @@ create_cblc_string_variable(const char *var_name, const char *var_contents) // This is a way of having the compiler communicate with GDB. I create a // global const char[] string with a known name so that GDB can look for that // variable and pick up its contents. - + // This probably should be in the .debug_info section, but for the moment I // don't know how to do that, but I do know how to do this: @@ -1450,7 +1450,7 @@ get_bytes_needed(cbl_field_t *field) } if( !(field->attr & separate_e) ) { - // This is COMP-3, so there is a sign nybble. + // This is COMP-3, so there is a sign nybble. digits += 1; } retval = (digits+1)/2; @@ -3256,7 +3256,7 @@ parser_first_statement( int lineno ) { // In the event that this routine is the one that main() calls to get the // execution ball rolling, we want the GDB "start" function to be able - // to set a temporary breakpoint at this location. We get that rolling + // to set a temporary breakpoint at this location. We get that rolling // here. char ach[256]; @@ -3269,7 +3269,7 @@ parser_first_statement( int lineno ) SHOW_PARSE_END } - if( strcmp(current_function->our_name, ach_cobol_entry_point) == 0 + if( strcmp(current_function->our_name, ach_cobol_entry_point) == 0 && !suppress_cobol_entry_point ) { sprintf(ach, @@ -3580,7 +3580,7 @@ parser_enter_program( const char *funcname_, if( strcmp(funcname_, "main") == 0 && this_module_has_main ) { - // setting 'retval' to 1 let's the caller know that we are being told + // setting 'retval' to 1 let's the caller know that we are being told // both to synthesize a main() entry point to duplicate GCC's default // behavior, and to create an explicit entry point named "main". This will // eventually result in a link error (because of the duplicated entry @@ -4125,7 +4125,7 @@ parser_accept( struct cbl_refer_t refer, NULL_TREE); } -// TODO: update documentation. +// TODO: update documentation. void parser_accept_exception( cbl_label_t *accept_label ) { @@ -4207,7 +4207,7 @@ parser_accept_command_line( cbl_refer_t tgt, if( !source.field ) { // The whole command-line is wanted - gg_assign(erf, + gg_assign(erf, gg_call_expr( INT, "__gg__get_command_line", gg_get_address_of(tgt.field->var_decl_node), @@ -4217,7 +4217,7 @@ parser_accept_command_line( cbl_refer_t tgt, if( error ) { // There is an ON EXCEPTION phrase: - IF( erf, ne_op, integer_zero_node ) + IF( erf, ne_op, integer_zero_node ) { SHOW_PARSE { @@ -4235,7 +4235,7 @@ parser_accept_command_line( cbl_refer_t tgt, if( not_error ) { // There is an NOT ON EXCEPTION phrase: - IF( erf, eq_op, integer_zero_node ) + IF( erf, eq_op, integer_zero_node ) { SHOW_PARSE { @@ -4254,7 +4254,7 @@ parser_accept_command_line( cbl_refer_t tgt, else { // A particular parameter has been requested: - gg_assign(erf, + gg_assign(erf, gg_call_expr( INT, "__gg__get_argv", gg_get_address_of(tgt.field->var_decl_node), @@ -4267,7 +4267,7 @@ parser_accept_command_line( cbl_refer_t tgt, if( error ) { // There is an ON EXCEPTION phrase: - IF( erf, ne_op, integer_zero_node ) + IF( erf, ne_op, integer_zero_node ) { SHOW_PARSE { @@ -4285,7 +4285,7 @@ parser_accept_command_line( cbl_refer_t tgt, if( not_error ) { // There is an NOT ON EXCEPTION phrase: - IF( erf, eq_op, integer_zero_node ) + IF( erf, eq_op, integer_zero_node ) { SHOW_PARSE { @@ -4388,7 +4388,7 @@ parser_accept_envar(struct cbl_refer_t tgt, if( error ) { // There is an ON EXCEPTION phrase: - IF( erf, ne_op, integer_zero_node ) + IF( erf, ne_op, integer_zero_node ) { gg_append_statement( error->structs.arith_error->into.go_to ); } @@ -4400,7 +4400,7 @@ parser_accept_envar(struct cbl_refer_t tgt, if( not_error ) { // There is an NOT ON EXCEPTION phrase: - IF( erf, eq_op, integer_zero_node ) + IF( erf, eq_op, integer_zero_node ) { gg_append_statement( not_error->structs.arith_error->into.go_to ); } @@ -5834,7 +5834,7 @@ parser_exit_program(void) // exits back to COBOL only, else continue /* * If RETURNING was specified, the field is provided as an argument, no lookup * necessary. refer.field == NULL means exit(0) unless ec != ec_none_e. - * If ec == ec_all_e, that indicates RAISING LAST EXCEPTION was used. + * If ec == ec_all_e, that indicates RAISING LAST EXCEPTION was used. */ static @@ -5843,7 +5843,7 @@ pe_stuff(cbl_refer_t refer, ec_type_t ec) { // This is the moral equivalent of a C "return xyz;". - // There cannot be both a non-zero exit status and an exception condition. + // There cannot be both a non-zero exit status and an exception condition. gcc_assert( !(ec != ec_none_e && refer.field != NULL) ); gg_call(VOID, @@ -5937,7 +5937,7 @@ parser_exit( cbl_refer_t refer, ec_type_t ec ) { SHOW_PARSE_HEADER if( gg_trans_unit.function_stack.size() - && current_function->returning + && current_function->returning && !refer.field) { // ->returning works only if there is no refer.field @@ -5951,7 +5951,7 @@ parser_exit( cbl_refer_t refer, ec_type_t ec ) { SHOW_PARSE_TEXT(" refer.prog_func is non-zero") } - + SHOW_PARSE_END } TRACE1 @@ -6693,8 +6693,8 @@ parser_division(cbl_division_t division, cbl_ffi_crv_t crv = args[i].crv; cbl_field_t *new_var = args[i].refer.field; - - if( crv == by_value_e ) + + if( crv == by_value_e ) { switch(new_var->type) { @@ -6708,7 +6708,7 @@ parser_division(cbl_division_t division, break; } } - + if( crv == by_value_e ) { // 'parameter' is the 64-bit or 128-bit value that was placed on the stack @@ -7524,7 +7524,7 @@ parser_perform(struct cbl_perform_tgt_t *tgt, struct cbl_refer_t how_many) { // There is no N. This is PERFORM proc-1 THROUGH proc-2 // false means nexting in GDB will work - internal_perform_through(tgt->from(), tgt->to(), false); + internal_perform_through(tgt->from(), tgt->to(), false); } else { @@ -8094,7 +8094,7 @@ perform_outofline_before_varying( struct cbl_perform_tgt_t *tgt, // for the generated runtime code to reach this point except by jumpint to // the EXIT: label. // We have, you see, reached the egress: - gg_append_statement( tgt->addresses.exit.label ); + gg_append_statement( tgt->addresses.exit.label ); sprintf(ach, "_procretb.%ld:", our_pseudo_label); @@ -8715,7 +8715,7 @@ parser_perform_inline_times(struct cbl_perform_tgt_t *tgt, } int stash = gg_get_current_line_number(); - gg_set_current_line_number(tgt->addresses.line_number_of_setup_code); + gg_set_current_line_number(tgt->addresses.line_number_of_setup_code); gg_append_statement( tgt->addresses.setup.label ); // Get the count: @@ -8746,7 +8746,7 @@ parser_perform_inline_times(struct cbl_perform_tgt_t *tgt, gg_append_statement( tgt->addresses.exit.go_to ); ENDIF - gg_set_current_line_number(stash); + gg_set_current_line_number(stash); SHOW_PARSE { @@ -12125,7 +12125,7 @@ create_and_call(size_t narg, for( size_t i=0; i<narg; i++ ) { cbl_ffi_crv_t crv = args[i].crv; - + if( args[i].refer.field && args[i].refer.field->type == FldLiteralN ) { crv = by_value_e; @@ -12194,7 +12194,7 @@ create_and_call(size_t narg, && is_valuable(args[i].refer.field->type) ) { cbl_unimplemented("CALL USING BY CONTENT <temporary> would require " - "REPOSITORY PROTOTYPES."); + "REPOSITORY PROTOTYPES."); } // BY CONTENT means that the called program gets a copy of the data. @@ -15551,11 +15551,11 @@ initial_from_float128(cbl_field_t *field, _Float128 value) // For COMP-6 (flagged by separate_e), the number of required digits is // twice the capacity. - + // For COMP-3, the number of digits is 2*capacity minus 1, because the // the final "digit" is a sign nybble. - size_t ndigits = (field->attr & separate_e) + size_t ndigits = (field->attr & separate_e) ? field->data.capacity * 2 : field->data.capacity * 2 - 1; digits_from_float128(ach, field, ndigits, rdigits, value); @@ -15664,7 +15664,7 @@ initial_from_float128(cbl_field_t *field, _Float128 value) memset(ach, 0, sizeof(ach)); memset(retval, 0, field->data.capacity); size_t ndigits = field->data.capacity; - + if( (field->attr & blank_zero_e) && value == 0 ) { memset(retval, internal_space, field->data.capacity); @@ -16313,7 +16313,7 @@ parser_symbol_add(struct cbl_field_t *new_var ) if( new_var->data.memsize < new_var->data.capacity * new_var->occurs.bounds.upper ) { cbl_internal_error("LEVEL 01 (%s) OCCURS " - "has insufficient data.memsize", new_var->name); + "has insufficient data.memsize", new_var->name); } } @@ -16392,9 +16392,9 @@ parser_symbol_add(struct cbl_field_t *new_var ) TRACE1_HEADER if( new_var->level ) { - gg_fprintf( trace_handle, - 1, - "%2.2d ", + gg_fprintf( trace_handle, + 1, + "%2.2d ", build_int_cst_type(INT, new_var->level)); } TRACE1_TEXT(new_var->name) @@ -16403,7 +16403,7 @@ parser_symbol_add(struct cbl_field_t *new_var ) { gg_fprintf( trace_handle, 1, " [%ld]", - build_int_cst_type(LONG, + build_int_cst_type(LONG, *(const long *)new_var->data.initial)); } TRACE1_END @@ -16915,5 +16915,4 @@ parser_symbol_add(struct cbl_field_t *new_var ) } done: return; - } - + } diff --git a/gcc/cobol/genutil.cc b/gcc/cobol/genutil.cc index 54f7a0b91e9c47bab575969ccf967c84c09ca55f..4feadb3a9ae892878894320c5943adf5d272ae1e 100644 --- a/gcc/cobol/genutil.cc +++ b/gcc/cobol/genutil.cc @@ -91,18 +91,18 @@ tree var_decl_arithmetic_rounds; // int* __gg__arithmetic_rounds; tree var_decl_fourplet_flags_size; // size_t __gg__fourplet_flags_size; tree var_decl_fourplet_flags; // int* __gg__fourplet_flags; -tree var_decl_treeplet_1f; // cblc_field_pp_type_node , "__gg__treeplet_1f" -tree var_decl_treeplet_1o; // SIZE_T_P , "__gg__treeplet_1o" -tree var_decl_treeplet_1s; // SIZE_T_P , "__gg__treeplet_1s" -tree var_decl_treeplet_2f; // cblc_field_pp_type_node , "__gg__treeplet_2f" -tree var_decl_treeplet_2o; // SIZE_T_P , "__gg__treeplet_2o" -tree var_decl_treeplet_2s; // SIZE_T_P , "__gg__treeplet_2s" -tree var_decl_treeplet_3f; // cblc_field_pp_type_node , "__gg__treeplet_3f" -tree var_decl_treeplet_3o; // SIZE_T_P , "__gg__treeplet_3o" -tree var_decl_treeplet_3s; // SIZE_T_P , "__gg__treeplet_3s" -tree var_decl_treeplet_4f; // cblc_field_pp_type_node , "__gg__treeplet_4f" -tree var_decl_treeplet_4o; // SIZE_T_P , "__gg__treeplet_4o" -tree var_decl_treeplet_4s; // SIZE_T_P , "__gg__treeplet_4s" +tree var_decl_treeplet_1f; // cblc_field_pp_type_node , "__gg__treeplet_1f" +tree var_decl_treeplet_1o; // SIZE_T_P , "__gg__treeplet_1o" +tree var_decl_treeplet_1s; // SIZE_T_P , "__gg__treeplet_1s" +tree var_decl_treeplet_2f; // cblc_field_pp_type_node , "__gg__treeplet_2f" +tree var_decl_treeplet_2o; // SIZE_T_P , "__gg__treeplet_2o" +tree var_decl_treeplet_2s; // SIZE_T_P , "__gg__treeplet_2s" +tree var_decl_treeplet_3f; // cblc_field_pp_type_node , "__gg__treeplet_3f" +tree var_decl_treeplet_3o; // SIZE_T_P , "__gg__treeplet_3o" +tree var_decl_treeplet_3s; // SIZE_T_P , "__gg__treeplet_3s" +tree var_decl_treeplet_4f; // cblc_field_pp_type_node , "__gg__treeplet_4f" +tree var_decl_treeplet_4o; // SIZE_T_P , "__gg__treeplet_4o" +tree var_decl_treeplet_4s; // SIZE_T_P , "__gg__treeplet_4s" // There are times when I need to insert a NOP into the code, mainly to force // a .loc directive into the assembly language so that the GDB-COBOL debugger @@ -252,7 +252,7 @@ get_integer_value(tree value, gg_assign(rdigits, gg_cast(INT, member(field, "rdigits"))); // Scale by the number of rdigits, which turns 12.34 into 12. - // When check_for_fractional_digits is true, __gg__rdigits will be set + // When check_for_fractional_digits is true, __gg__rdigits will be set // to 1 for 12.34, and will be set to zero 12.00 scale_by_power_of_ten(temp, gg_negate(rdigits), @@ -275,7 +275,7 @@ get_data_offset_dest(cbl_refer_t &refer, Analyze(); // This routine returns a tree which is the size_t offset to the data in the // refer/field - + // Because this is for destination/receiving variables, OCCURS DEPENDING ON // is not checked. @@ -321,7 +321,7 @@ get_data_offset_dest(cbl_refer_t &refer, // we might have an error condition at this point: if( !parent ) { - cbl_internal_error("Too many subscripts"); + cbl_internal_error("Too many subscripts"); } // Pick up the integer value of the subscript: static tree subscript = gg_define_variable(LONG, "..gdod_subscript", vs_file_static); @@ -555,7 +555,7 @@ get_data_offset_source(cbl_refer_t &refer, // This routine returns a tree which is the size_t offset to the data in the // refer/field - // Because this is for source / sending variables, checks are made for + // Because this is for source / sending variables, checks are made for // OCCURS DEPENDING ON violations (when those exceptions are enabled) tree retval = gg_define_variable(SIZE_T); @@ -828,7 +828,7 @@ get_data_offset_source(cbl_refer_t &refer, return retval; } -void +void get_binary_value( tree value, tree rdigits, cbl_field_t *field, @@ -877,7 +877,7 @@ get_binary_value( tree value, tree dest_type = TREE_TYPE(value); tree source_type = tree_type_from_field(field); - gg_assign(value, + gg_assign(value, gg_cast(dest_type, gg_indirect( gg_cast(build_pointer_type(source_type), gg_get_address_of(field->data_decl_node))))); @@ -1368,7 +1368,7 @@ get_binary_value( tree value, case FldAlphanumeric: { - + } @@ -1481,7 +1481,7 @@ scale_by_power_of_ten_N(tree value, bool check_for_fractional) { // This routine is called when we know N at compile time. - + Analyze(); Analyzer.Message("takes int N"); if( N == 0 ) @@ -1856,7 +1856,7 @@ copy_little_endian_into_place(cbl_field_t *dest, // lhs is 99.999. So, lhs.digits is 5, and lhs.rdigits is 3. // 10^(5 - 3 + 2) is 10^4, which is 10000. Because 12345 is >= 10000, the // source can't fit into the destination. - + // Note: I am not trying to avoid the use of stack variables, because I am // not sure how to declare a file-static variable of unknown type. tree abs_value = gg_define_variable(TREE_TYPE(value)); @@ -2020,8 +2020,8 @@ build_array_of_size_t( size_t N, const size_t *values) { // We create and populate an array of size_t values - - // This only works because it is used in but one spot. If this routine is + + // This only works because it is used in but one spot. If this routine is // called twice, be careful about how the first one is used. It's a static // variable, you see. static tree values_p = gg_define_variable(SIZE_T_P, "..baost_values_p", vs_file_static); @@ -2141,13 +2141,13 @@ refer_refmod_length(cbl_refer_t &refer) if( any_length ) { - rt_capacity = + rt_capacity = gg_cast(LONG, member(refer.field->var_decl_node, "capacity")); } else { - rt_capacity = + rt_capacity = build_int_cst_type(LONG, refer.field->data.capacity); } @@ -2179,7 +2179,7 @@ refer_refmod_length(cbl_refer_t &refer) } else { - get_integer_value(value64, + get_integer_value(value64, refer.refmod.from->field, refer_offset_source(*refer.refmod.from) ); @@ -2269,9 +2269,9 @@ refer_refmod_length(cbl_refer_t &refer) if( enabled_exceptions.match(ec_bound_ref_mod_e) ) { SET_EXCEPTION_CODE(ec_bound_ref_mod_e); - + // Our intentions are honorable. But at this point, where - // we notice that start + length is too long, the + // we notice that start + length is too long, the // get_data_offset_source routine has already been run and // it's too late to actually change the refstart. There are // theoretical solutions to this -- mainly, @@ -2554,7 +2554,7 @@ refer_offset_source(cbl_refer_t &refer, tree retval = gg_define_variable(SIZE_T); gg_assign(var_decl_odo_violation, integer_zero_node); - + gg_assign(retval, get_data_offset_source(refer, pflags)); if( process_this_exception(ec_bound_odo_e) ) { @@ -2648,5 +2648,3 @@ qualified_data_dest(cbl_refer_t &refer) return gg_add(member(refer.field->var_decl_node, "data"), refer_offset_dest(refer)); } - - diff --git a/gcc/cobol/lexio.h b/gcc/cobol/lexio.h index 6c0bd0efcedc3ea980959408c8490150af4f074c..75ee22c0130a415f366ab843bac843412063bf91 100644 --- a/gcc/cobol/lexio.h +++ b/gcc/cobol/lexio.h @@ -125,9 +125,6 @@ struct YYLTYPE # define YYLTYPE_IS_TRIVIAL 1 #endif -// void location_dump( const char func[], int line, -// const char tag[], const YYLTYPE& loc); - struct filespan_t : public bytespan_t { char *cur, *eol, *quote; private: diff --git a/gcc/cobol/parse_ante.h b/gcc/cobol/parse_ante.h index e3f125489847ea3108969cef8ec99616468b9b1f..c5099a48f3e2c7145749cc91e36c1a151f68d66c 100644 --- a/gcc/cobol/parse_ante.h +++ b/gcc/cobol/parse_ante.h @@ -78,25 +78,25 @@ static size_t nparse_error = 0; size_t parse_error_inc() { return ++nparse_error; } size_t parse_error_count() { return nparse_error; } void input_file_status_notify(); - -#define YYLLOC_DEFAULT(Current, Rhs, N) \ + +#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 \ - { \ + 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).last_line = YYRHSLOC (Rhs, 0).last_line; \ (Current).first_column = \ - (Current).last_column = YYRHSLOC (Rhs, 0).last_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(); \ @@ -110,7 +110,7 @@ extern int yydebug; const char * consistent_encoding_check( const YYLTYPE& loc, const char input[] ) { cbl_field_t faux = { - .type = FldAlphanumeric, + .type = FldAlphanumeric, .data = { .capacity = capacity_cast(strlen(input)), .initial = input } }; @@ -211,7 +211,7 @@ namcpy(const YYLTYPE& loc, cbl_name_t tgt, const char *src ) { auto len = snprintf(tgt, sizeof(cbl_name_t), "%s", src); if( ! (0 < len && len < int(sizeof(cbl_name_t))) ) { error_msg(loc, "name truncated to '%s' (max %zu characters)", - tgt, sizeof(cbl_name_t)-1); + tgt, sizeof(cbl_name_t)-1); return false; } return true; @@ -322,9 +322,9 @@ struct evaluate_elem_t { label = protolabel; label.line = yylineno; if( -1 == snprintf(label.name, sizeof(label.name), - "%.*s_%d", (int)sizeof(label.name)-6, skel, yylineno) ) { + "%.*s_%d", (int)sizeof(label.name)-6, skel, yylineno) ) { yyerror("could not create unique label '%s_%d' because it is too long", - skel, yylineno); + skel, yylineno); } } @@ -608,17 +608,17 @@ class eval_subject_t { } size_t subject_count() const { return columns.size(); } size_t object_count() { return std::distance(columns.begin(), pcol); } - + void object_relop( relop_t op ) { abbr_relop = op; } relop_t object_relop() const { return abbr_relop; } void rewind() { pcol = columns.begin(); } - + bool compatible( const cbl_field_t *object ) const; - // compare sets result - cbl_field_t * compare( int token ); - cbl_field_t * compare( relop_t op, + // compare sets result + cbl_field_t * compare( int token ); + cbl_field_t * compare( relop_t op, const cbl_refer_t& object, bool deciding = false); cbl_field_t * compare( const cbl_refer_t& object, const cbl_refer_t& object2 = nullptr); @@ -633,7 +633,7 @@ class eval_subject_t { } // decide() calls codegen with the result and increments the subject column. - // On FALSE, skip past <statements> and fall into next WHEN. + // On FALSE, skip past <statements> and fall into next WHEN. bool decided( cbl_field_t *result ) { this->result = result; parser_if( result ); @@ -683,7 +683,7 @@ class eval_subject_t { } pcol++; return true; - } + } bool decide( const cbl_refer_t& object, const cbl_refer_t& object2, bool invert ) { if( pcol == columns.end() ) return false; if( compare(object, object2) ) { @@ -738,9 +738,9 @@ struct perform_t { *fini, // Format 3, code that reverts handlers *top, // Format 3, above imperative-statement-1 *from, // Format 3, imperative-statement-1 - *finally, + *finally, *other, *common; - ec_labels_t() + ec_labels_t() : init(NULL), fini(NULL), top(NULL), from(NULL), finally(NULL), other(NULL), common(NULL) @@ -757,7 +757,7 @@ struct perform_t { static cbl_label_t * new_label( cbl_label_type_t type, const cbl_name_t role ); } ec_labels; - + struct { cbl_label_t *start, *end; cbl_field_t *unsatisfied, *size; @@ -828,7 +828,7 @@ perform_ec_cleanup() { /* ... empty init block ... */ parser_label_goto(perf->ec_labels.top); parser_label_label(perf->ec_labels.fini); -#endif +#endif } static list<cbl_label_t*> searches; @@ -882,13 +882,13 @@ typedef list<cbl_domain_t>::iterator domain_iter; * returned as a NAME or NAME88 token. NAME88 is returned only if a correctly, * uniquely specified Level 88 data item is found in the symbol table (because * else we can't know). - * + * * When the parser gets a NAME or NAME88 token, it retrieves the pending list * of qualifiers, if any, from the name queue. It adds the returned name to * the list and calls symbol_find() to search the name map. For correctly * specified names, the lexer has already done that work, which is now * unfortunately repeated. For incorrect names, the parser emits a most useful - * diagnostic. + * diagnostic. */ static name_queue_t name_queue; @@ -901,7 +901,7 @@ tee_up_name( const YYLTYPE& loc, const char name[] ) { name_queue.push(loc, name); } cbl_namelist_t -teed_up_names() { +teed_up_names() { return name_queue_t::namelist_of( name_queue.peek() ); } @@ -916,11 +916,11 @@ class tokenset_t { std::transform(name, name + strlen(name) + 1, lname, ftolower); return lname; } - + 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 ) { auto lname( lowercase(name) ); auto cw = cobol_words.insert(lname); @@ -988,7 +988,7 @@ class current_tokens_t { public: current_tokens_t() {} int find( const cbl_name_t name, bool include_intrinsics ) { - return tokens.find(name, 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); @@ -1304,9 +1304,9 @@ struct ffi_args_t { int i=0; for( const auto& arg : elems ) { dbgmsg( "%8d) %-10s %-16s %s", i++, - cbl_ffi_crv_str(arg.crv), - 3 + cbl_field_type_str(arg.refer.field->type), - arg.refer.field->pretty_name() ); + cbl_ffi_crv_str(arg.crv), + 3 + cbl_field_type_str(arg.refer.field->type), + arg.refer.field->pretty_name() ); } } @@ -1421,8 +1421,8 @@ class prog_descr_t { locale_t(const cbl_name_t name = NULL, const char *os_name = NULL) : name(""), os_name(os_name) { if( name ) { - bool ok = namcpy(YYLTYPE(), this->name, name); - gcc_assert(ok); + bool ok = namcpy(YYLTYPE(), this->name, name); + gcc_assert(ok); } } } locale; @@ -1481,7 +1481,7 @@ struct cbl_typedef_less { if( result > 0 ) return false; // Names that match are different if they're in different programs - // and neither is external. + // and neither is external. auto lhs = field_index(a); auto rhs = field_index(b); if( lhs != rhs ) { @@ -1540,7 +1540,7 @@ class program_stack_t : protected std::stack<prog_descr_t> { return pending.call_convention = convention; } 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; @@ -1570,8 +1570,8 @@ class program_stack_t : protected std::stack<prog_descr_t> { } void apply_pending() { - if( size() == 1 && 0 != pending.call_convention ) { - top().call_convention = pending.call_convention; + if( size() == 1 && 0 != pending.call_convention ) { + top().call_convention = pending.call_convention; } if( pending.initial ) { auto e = symbol_at(top().program_index); @@ -1613,7 +1613,7 @@ struct rel_part_t { return *this; } - bool is_value() const { return operand && is_elementary(operand->field->type); } + bool is_value() const { return operand && is_elementary(operand->field->type); } }; /* @@ -1641,13 +1641,13 @@ class log_expr_t { __func__, __LINE__, name_of(init)); } } - + cbl_field_t * and_term() { return andable; } log_expr_t * and_term( cbl_field_t *rhs ) { if( ! is_conditional(rhs) ) { - dbgmsg("%s:%d: logic error: %s is not a truth value", + dbgmsg("%s:%d: logic error: %s is not a truth value", __func__, __LINE__, name_of(rhs)); } else { parser_logop( andable, andable, and_op, rhs ); @@ -1656,10 +1656,10 @@ class log_expr_t { } log_expr_t * or_term( cbl_field_t *rhs ) { if( ! is_conditional(rhs) ) { - dbgmsg("%s:%d: logic error: %s is not a truth value", + dbgmsg("%s:%d: logic error: %s is not a truth value", __func__, __LINE__, name_of(rhs)); return this; - } + } if( ! orable ) { orable = andable; } else { @@ -1714,7 +1714,7 @@ static class current_t { parser_entry_activate( iprog, eval ); auto name = cbl_label_of(symbol_at(iprog))->name; cbl_unimplemented("Global declarative %s for %s", - eval->name, name); + eval->name, name); parser_call( new_literal(strlen(name), name, quoted_e), cbl_refer_t(), 0, NULL, NULL, NULL, false ); } @@ -2001,7 +2001,7 @@ static class current_t { options_paragraph = cbl_options_t(); first_statement = 0; - + return fOK; } @@ -2029,18 +2029,18 @@ 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"); - } + 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; } return false; } - + /* * At the end of each program, ensure there are no uses of an ambiguous * procedure (SECTION or PARAGRAPH) name. At the end of a top-level program, @@ -2143,8 +2143,8 @@ static class current_t { return lave_label; } - cbl_label_t * new_section( cbl_label_t * section ) { - std::swap( programs.top().section, section ); + cbl_label_t * new_section( cbl_label_t * section ) { + std::swap( programs.top().section, section ); return section; } @@ -2215,7 +2215,7 @@ static class current_t { */ void declaratives_evaluate( ec_type_t handled = ec_none_e ) { - // The exception file number is assumed to be zero unless it has been + // 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); @@ -2234,7 +2234,7 @@ static class current_t { } void antecedent_dump() const { - if( ! yydebug ) return; + if( ! yydebug ) return; if( ! antecedent_cache.operand ) { yywarn( "Antecedent: none" ); } else { @@ -2254,7 +2254,7 @@ static class current_t { return antecedent_cache; } rel_part_t& antecedent_invert( bool invert=true ) { - antecedent_cache.invert = invert; + antecedent_cache.invert = invert; antecedent_dump(); return antecedent_cache; } @@ -2462,7 +2462,7 @@ is_callable( const cbl_field_t *field ) { struct cbl_fieldloc_t { YYLTYPE loc; cbl_field_t *field; - + cbl_fieldloc_t() : loc{ 1,1, 1,1 }, field(NULL) {} cbl_fieldloc_t( const YYLTYPE& loc, cbl_field_t *field ) : loc(loc), field(field) @@ -2485,7 +2485,7 @@ intrinsic_call_0( cbl_field_t *output, int token ) { static bool intrinsic_call_1( cbl_field_t *output, int token, - cbl_refer_t *r1, const YYLTYPE& loc ) { + cbl_refer_t *r1, const YYLTYPE& loc ) { std::vector<cbl_refer_t> args { *r1 }; if( 0 == intrinsic_invalid_parameter(token, args) ) { error_msg(loc, "invalid parameter '%s'", r1->field->name); @@ -2629,7 +2629,7 @@ symbol_find( const YYLTYPE& loc, const char *name ) { auto names = name_queue.pop_as_names(); } names.push_front(name); - auto found = symbol_find( PROGRAM, names ); + auto found = symbol_find( PROGRAM, names ); if( found.first && !found.second ) { auto field = cbl_field_of(found.first); error_msg(loc, "'%s' is not unique, first defined on line %d", @@ -2646,13 +2646,13 @@ register_find( const char *name ) { static bool valid_redefine( const YYLTYPE& loc, - const cbl_field_t *field, const cbl_field_t *orig ) { + const cbl_field_t *field, const cbl_field_t *orig ) { // Must have same level. if( field->level != orig->level ) { error_msg(loc, "cannot redefine %s %s as %s %s " - "because they have different levels", - orig->level_str(), orig->name, - field->level_str(), field->name); + "because they have different levels", + orig->level_str(), orig->name, + field->level_str(), field->name); return false; } @@ -2675,34 +2675,34 @@ valid_redefine( const YYLTYPE& loc, if( e != sym.field ) { auto wrong = cbl_field_of(e); error_msg(loc, "%s %s on line %d lies between %s and %s", - wrong->level_str(), wrong->name, wrong->line, - orig->name, field->name); + wrong->level_str(), wrong->name, wrong->line, + orig->name, field->name); return false; } // cannot redefine a table if( orig->occurs.ntimes() ) { error_msg(loc, "cannot redefine table %s %s", - orig->level_str(), orig->name); + orig->level_str(), orig->name); return false; } // redefined field cannot be ODO if( orig->occurs.depending_on ) { error_msg(loc, "redefined data item %s %s has OCCURS DEPENDING ON", - orig->level_str(), orig->name); + orig->level_str(), orig->name); return false; } // redefiner cannot have ODO if( field->occurs.depending_on ) { error_msg(loc, "data item %s %s cannot use REDEFINES and OCCURS DEPENDING ON", - field->level_str(), field->name); + field->level_str(), field->name); return false; } if( is_variable_length(orig) ) { error_msg(loc, "redefined data item %s %s has OCCURS DEPENDING ON", - orig->level_str(), orig->name); + orig->level_str(), orig->name); return false; } // We don't know about the redefining group until it's completely defined. @@ -2717,8 +2717,8 @@ valid_redefine( const YYLTYPE& loc, if( field->type != FldGroup && orig->type != FldGroup ) { if( orig->size() < field->size() ) { if( orig->level > 1 || orig->has_attr(external_e) ) { - dbgmsg( "size error orig: %s", field_str(orig) ); - dbgmsg( "size error redef: %s", field_str(field) ); + dbgmsg( "size error orig: %s", field_str(orig) ); + dbgmsg( "size error redef: %s", field_str(field) ); error_msg(loc, "%s (%s size %u) larger than REDEFINES %s (%s size %u)", field->name, 3 + cbl_field_type_str(field->type), field->size(), @@ -2745,8 +2745,8 @@ valid_redefine( const YYLTYPE& loc, if( ! same_group ) { error_msg(loc, "cannot redefine %s %s as %s %s " "because they belong to different groups", - orig->level_str(), orig->name, - field->level_str(), field->name); + orig->level_str(), orig->name, + field->level_str(), field->name); return false; } @@ -2816,7 +2816,7 @@ field_add( const YYLTYPE& loc, cbl_field_t *field ) { break; } - // Use isym 0 to indicate the location of the field under construction. + // Use isym 0 to indicate the location of the field under construction. symbol_field_location(0, loc); struct symbol_elem_t *e = symbol_field_add(PROGRAM, field); @@ -2831,7 +2831,7 @@ field_add( const YYLTYPE& loc, cbl_field_t *field ) { break; default: error_msg(loc, "%s %s is not part of an 01 record", - field->level_str(), field->name ); + field->level_str(), field->name ); return NULL; break; } @@ -2862,8 +2862,8 @@ uniform_picture( const char *picture, char model ) { [model]( char ch ) { return model == TOLOWER(ch); } ); -} - +} + static enum cbl_field_attr_t uniform_picture( const char *picture ) { static char ch[] = { 'A', 'X' }; @@ -2876,11 +2876,11 @@ uniform_picture( const char *picture ) { } } return none_e; -} +} static bool field_type_update( cbl_field_t *field, cbl_field_type_t type, - YYLTYPE loc, + YYLTYPE loc, bool is_usage = false) { // preserve NumericEdited if already established @@ -2912,7 +2912,7 @@ field_type_update( cbl_field_t *field, cbl_field_type_t type, } dbgmsg( "%s:%d: %s became %s based on %s", __func__, __LINE__, field->name, - cbl_field_type_str(field->type), cbl_field_type_str(type) ); + cbl_field_type_str(field->type), cbl_field_type_str(type) ); return true; } @@ -2937,7 +2937,7 @@ field_capacity_error( const YYLTYPE& loc, const cbl_field_t *field ) { } return false; } -#define ERROR_IF_CAPACITY(L, F) \ +#define ERROR_IF_CAPACITY(L, F) \ do { if( field_capacity_error(L, F) ) YYERROR; } while(0) static const char * @@ -2959,7 +2959,7 @@ static bool value_encoding_check( const YYLTYPE& loc, cbl_field_t *field ) { if( ! field->internalize() ) { error_msg(loc, "inconsistent string literal encoding for '%s'", - field->data.initial); + field->data.initial); return false; } return true; @@ -3029,7 +3029,7 @@ alphabet_add( const YYLTYPE& loc, cbl_encoding_t encoding ) { return cbl_alphabet_of(e); } -// The current field always exists in the symbol table, even if it's incomplete. +// The current field always exists in the symbol table, even if it's incomplete. static cbl_field_t * current_field(cbl_field_t * field = NULL) { static cbl_field_t *local; @@ -3075,8 +3075,8 @@ parser_move_carefully( const char */*F*/, int /*L*/, if( is_index ) { if( tgt.field->type != FldIndex && src.field->type != FldIndex) { error_msg(src.loc, "invalid SET %s (%s) TO %s (%s): not a field index", - tgt.field->name, cbl_field_type_str(tgt.field->type), - src.field->name, cbl_field_type_str(src.field->type)); + tgt.field->name, cbl_field_type_str(tgt.field->type), + src.field->name, cbl_field_type_str(src.field->type)); delete tgt_list; return false; } @@ -3479,7 +3479,7 @@ file_section_parent_set( cbl_field_t *field ) { } void ast_call(const YYLTYPE& loc, cbl_refer_t name, - cbl_refer_t returning, + cbl_refer_t returning, size_t narg, cbl_ffi_arg_t args[], cbl_label_t *except, cbl_label_t *not_except, @@ -3499,13 +3499,13 @@ ast_end_program(const char name[] ) { auto& L( *cbl_label_of(&elem) ); if( L.used ) { if( ! L.lain ) { - YYLTYPE loc { L.line, 1, L.line, 1 }; + YYLTYPE loc { L.line, 1, L.line, 1 }; error_msg(loc, "line %d: %s " "is used on line %d and never defined", L.line, L.name, L.used ); } - dbgmsg("label: %.20s: %d/%d/%d", - L.name, L.line, L.lain, L.used); + dbgmsg("label: %.20s: %d/%d/%d", + L.name, L.line, L.lain, L.used); } } } ); @@ -3524,7 +3524,7 @@ goodnight_gracie() { assert(prog); std::set<std::string> externals = current.end_program(); - + if( !externals.empty() ) { for( const auto& name : externals ) { yywarn("%s calls external symbol '%s'", @@ -3558,5 +3558,3 @@ static void ast_first_statement( const YYLTYPE& loc ) { parser_first_statement(loc.first_line); } } - - diff --git a/gcc/cobol/posix/udf/Makefile b/gcc/cobol/posix/udf/Makefile index a6990fbdc3274aebfd800d4ff421b03c1268c4e7..8321f2dde90f8cd9865b021e2cdc9fe31bedd22f 100644 --- a/gcc/cobol/posix/udf/Makefile +++ b/gcc/cobol/posix/udf/Makefile @@ -9,7 +9,7 @@ t/errno: t/errno.cbl posix-mkdir.cbl | libposix-errno.so ../../built-gcobol $(FLAGS) -o $@ -I$$(pwd) \ $(firstword $^) $(LDFLAGS) -lposix-errno -libposix-errno.so: ../c/posix_errno.c posix-errno.o +libposix-errno.so: ../c/posix_errno.c posix-errno.o gcc $(CFLAGS) -shared -o $@ $^ posix-errno.o: posix-errno.cbl diff --git a/gcc/cobol/symbols.cc b/gcc/cobol/symbols.cc index 557b7c3fb7d9679d9f905be6c03b117e801dda29..1a5405259afbaa6491d9000e3d2e2f742490a588 100644 --- a/gcc/cobol/symbols.cc +++ b/gcc/cobol/symbols.cc @@ -84,7 +84,7 @@ static struct symbol_table_t { size_t capacity, nelem; size_t first_program, procedures; struct { - size_t file_status, linage_counter, return_code, + size_t file_status, linage_counter, return_code, exception_condition, very_true, very_false; } registers; @@ -136,7 +136,7 @@ symbol_table_extend() { } else { if( 0 != msync(symbols.elems, symbols.size(), MS_SYNC | MS_INVALIDATE) ) { cbl_err( "%s:%d: could not synchronize symbol table with mapped file", - __func__, __LINE__ ); + __func__, __LINE__ ); } } @@ -261,8 +261,8 @@ symbol_valid_udf_args( size_t function, std::list<cbl_refer_t> args ) { e++; // skip over linkage_sect_e, which appears after the function if( e->type != SymField ) { ERROR_FIELD(arg.field, - "FUNCTION %s has no defined parameter matching arg %zu, '%s'", - L->name, iarg, arg.field->name ); + "FUNCTION %s has no defined parameter matching arg %zu, '%s'", + L->name, iarg, arg.field->name ); return NULL; } @@ -284,7 +284,7 @@ static const struct cbl_field_t empty_float = { 0, FldFloat, FldInvalid, intermediate_e, 0, 0, 0, nonarray, 0, "", - 0, cbl_field_t::linkage_t(), + 0, cbl_field_t::linkage_t(), {16, 16, 32, 0, NULL, NULL, {NULL}, {NULL}}, NULL }; static const struct cbl_field_t empty_comp5 = { @@ -299,7 +299,7 @@ static const struct cbl_field_t empty_comp5 = { #else # define CONSTANT_E intermediate_e #endif - + static struct cbl_field_t empty_literal = { 0, FldInvalid, FldInvalid, CONSTANT_E, 0, 0, 0, nonarray, 0, "", @@ -489,7 +489,7 @@ static bool label_cmp( const cbl_label_t& key, if( ! names_matched ) { if( 0 != strcasecmp(key.name, elem.name) ) return false; } - + switch( key.type ) { case LblNone: @@ -868,49 +868,49 @@ field_size( const struct cbl_field_t *field ) { const char * cbl_field_attr_str( cbl_field_attr_t attr ) { switch(attr) { - case none_e: return "none"; - case figconst_1_e: return "figconst_1"; - case figconst_2_e: return "figconst_2"; - case figconst_4_e: return "figconst_4"; - case rjust_e: return "rjust"; - case ljust_e: return "ljust"; - case zeros_e: return "zeros"; - case signable_e: return "signable"; - case constant_e: return "constant"; - case function_e: return "function"; - case quoted_e: return "quoted"; - case filler_e: return "filler"; - case _spare_e: return "temporary"; - case intermediate_e: return "intermediate"; - case embiggened_e: return "embiggened"; - case all_alpha_e: return "all_alpha"; - case all_x_e: return "all_x"; - case all_ax_e: return "all_ax"; - case prog_ptr_e: return "prog_ptr"; - case scaled_e: return "scaled"; - case refmod_e: return "refmod"; - case based_e: return "based"; - case any_length_e: return "any_length"; - case global_e: return "global"; - case external_e: return "external"; - case blank_zero_e: return "blank_zero"; - case linkage_e: return "linkage"; - case local_e: return "local"; - case leading_e: return "leading"; - case separate_e: return "separate"; - case envar_e: return "envar"; - case dnu_1_e: return "dnu_1"; - case bool_encoded_e: return "bool"; - case hex_encoded_e: return "hex"; - case depends_on_e: return "depends_on"; - case initialized_e: return "initialized"; - case has_value_e: return "has_value"; - case ieeedec_e: return "ieeedec"; - case big_endian_e: return "big"; - case same_as_e: return "same_as"; - case record_key_e: return "record_key"; - case typedef_e: return "typedef"; - case strongdef_e: return "strongdef"; + case none_e: return "none"; + case figconst_1_e: return "figconst_1"; + case figconst_2_e: return "figconst_2"; + case figconst_4_e: return "figconst_4"; + case rjust_e: return "rjust"; + case ljust_e: return "ljust"; + case zeros_e: return "zeros"; + case signable_e: return "signable"; + case constant_e: return "constant"; + case function_e: return "function"; + case quoted_e: return "quoted"; + case filler_e: return "filler"; + case _spare_e: return "temporary"; + case intermediate_e: return "intermediate"; + case embiggened_e: return "embiggened"; + case all_alpha_e: return "all_alpha"; + case all_x_e: return "all_x"; + case all_ax_e: return "all_ax"; + case prog_ptr_e: return "prog_ptr"; + case scaled_e: return "scaled"; + case refmod_e: return "refmod"; + case based_e: return "based"; + case any_length_e: return "any_length"; + case global_e: return "global"; + case external_e: return "external"; + case blank_zero_e: return "blank_zero"; + case linkage_e: return "linkage"; + case local_e: return "local"; + case leading_e: return "leading"; + case separate_e: return "separate"; + case envar_e: return "envar"; + case dnu_1_e: return "dnu_1"; + case bool_encoded_e: return "bool"; + case hex_encoded_e: return "hex"; + case depends_on_e: return "depends_on"; + case initialized_e: return "initialized"; + case has_value_e: return "has_value"; + case ieeedec_e: return "ieeedec"; + case big_endian_e: return "big"; + case same_as_e: return "same_as"; + case record_key_e: return "record_key"; + case typedef_e: return "typedef"; + case strongdef_e: return "strongdef"; } return "???"; } @@ -1197,7 +1197,7 @@ symbols_dump( size_t first, bool header ) { asprintf(&s, "%4zu %-18s %s (%s)", e->program, cbl_field_type_str(cbl_field_of(e)->type) + 3, field_str(cbl_field_of(e)), - odo_str? odo_str : + odo_str? odo_str : cbl_field_type_str(cbl_field_of(e)->usage) + 3); } break; @@ -1416,7 +1416,7 @@ static struct symbol_elem_t * group->data.capacity += field_size(field); group->data.memsize += field_memsize(field); - // If group has a parent that is a record area, expand it, too. + // If group has a parent that is a record area, expand it, too. if( 0 < group->parent ) { auto redefined = symbol_redefines(group); if( redefined && is_record_area(redefined) ) { @@ -1602,12 +1602,12 @@ value_or_figconst_name( const char *value ) { return normal_value_e == fig? value : cbl_figconst_str(fig); } -const char * -cbl_field_t::attr_str( const std::vector<cbl_field_attr_t>& attrs ) const +const char * +cbl_field_t::attr_str( const std::vector<cbl_field_attr_t>& attrs ) const { const char *sep = ""; char *out = NULL; - + for( auto attr : attrs ) { char *part = out; if( has_attr(attr) ) { @@ -1838,7 +1838,7 @@ size_t parse_error_count(); /* * This function produces a zero-filled level number, so 1 becomes "01". It's * needed because the diagnostic format string doesn't support zero-filled - * integer conversion or width. + * integer conversion or width. */ const char * cbl_field_t::level_str( uint32_t level ) { @@ -1918,7 +1918,7 @@ symbols_update( size_t first, bool parsed_ok ) { } } } - + bool size_invalid = field->data.memsize > 0 && symbol_redefines(field); if( size_invalid ) { // redefine of record area is ok auto redefined = symbol_redefines(field); @@ -1945,7 +1945,7 @@ symbols_update( size_t first, bool parsed_ok ) { // no field redefines the file's default record auto file = cbl_file_of(symbol_at(field->parent)); ERROR_FIELD(field, "line %d: %s lacks a file description", - file->line, file->name); + file->line, file->name); return 0; } } @@ -1953,7 +1953,7 @@ symbols_update( size_t first, bool parsed_ok ) { if( yydebug || parse_error_count() == 0 ) { if( field->type == FldInvalid ) { ERROR_FIELD(field, "line %d: %s %s requires PICTURE", - field->line, field->level_str(), field->name); + field->line, field->level_str(), field->name); } else { dbgmsg("%s: error: data item %s #%zu '%s' capacity %u rejected", @@ -1997,7 +1997,7 @@ symbols_update( size_t first, bool parsed_ok ) { p = symbol_at(--isym); continue; } - + // Verify REDEFINing field has no ODO components auto parent = symbol_redefines(field); if( parent && !is_record_area(parent) && is_variable_length(field) ) { @@ -2009,18 +2009,18 @@ symbols_update( size_t first, bool parsed_ok ) { if( field->type == FldInvalid ) { dbgmsg("%s:%d: %s", __func__, __LINE__, field_str(field)); ERROR_FIELD(field, "line %d: %s %s requires PICTURE", - field->line, field->level_str(), field->name); + field->line, field->level_str(), field->name); continue; } assert( ! field->is_typedef() ); - + if( parsed_ok ) parser_symbol_add(field); } finalize_symbol_map2(); if( yydebug ) dump_symbol_map2(); - + build_symbol_map(); int ninvalid = 0; @@ -2130,7 +2130,7 @@ symbol_find_forward_field( size_t program, const char name[] ) { &nelem, sizeof(key), symbol_elem_cmp ) ); if( !e ) dbgmsg("%s:%d: no forward reference for program %zu '%s'", - __func__, __LINE__, program, name); + __func__, __LINE__, program, name); return e; @@ -2159,7 +2159,7 @@ had_picture( const cbl_field_t *field ) { if( is_elementary(field->type) ) { switch(field->type) { case FldAlphanumeric: - // VALUE string for alphanumeric might mean no PICTURE. + // VALUE string for alphanumeric might mean no PICTURE. return field->data.initial == NULL; case FldNumericDisplay: case FldNumericEdited: @@ -2208,7 +2208,7 @@ symbol_in_file( symbol_elem_t *e ) { auto end = std::reverse_iterator<symbol_elem_t *>(symbols_begin()); auto p = std::find_if( beg, end, []( const symbol_elem_t& elem ) { - return elem.type == SymFilename; + return elem.type == SymFilename; } ); return p != end? &*p : NULL; @@ -2240,14 +2240,14 @@ symbol_field_parent_set( struct cbl_field_t *field ) return NULL; // 77/78 cannot be a parent } } - + if( prior->level == field->level ) { auto redefined = symbol_redefines(prior); if( redefined ) prior = redefined; field->parent = prior->parent; return cbl_field_of(symbol_at(field->parent)); } - + if( prior->level < field->level ) { if( prior->has_attr(same_as_e) ) { ERROR_FIELD(prior, "%s created with SAME AS or TYPE TO, cannot have new member %s", @@ -2285,9 +2285,9 @@ symbol_field_parent_set( struct cbl_field_t *field ) return false; } ); if( ! all_numeric ) { - auto loc = symbol_field_location(0); + auto loc = symbol_field_location(0); error_msg(loc, "%s %s invalid VALUE for numeric type %s", - field->level_str(), field->name, prior->name); + field->level_str(), field->name, prior->name); } } return prior; @@ -2360,7 +2360,7 @@ symbol_table_init(void) { // 01 ARGI is the current index into the argv array { 0, FldNumericBin5, FldInvalid, signable_e, 0, 0, 0, nonarray, 0, "_ARGI", 0, {}, {16, 16, MAX_FIXED_POINT_DIGITS, 0, NULL, NULL, {NULL}, {NULL}}, NULL }, - + // These last two don't require actual storage; they get BOOL var_decl_node // in parser_symbol_add() { 0, FldConditional, FldInvalid, constant_e , 0, 0, 0, nonarray, 0, @@ -2511,7 +2511,7 @@ symbol_append( const symbol_elem_t& elem ) { return e; } -cbl_label_t * +cbl_label_t * cbl_perform_tgt_t::finally( size_t program ) { assert(0 < ito); static const char fini[] = "_fini"; @@ -2521,7 +2521,7 @@ cbl_perform_tgt_t::finally( size_t program ) { assert(n < int(sizeof(fini))); symbol_elem_t elem = { .type = SymLabel, - .program = program, + .program = program, .elem = { .label = proto } }, *e; e = symbol_add(&elem); ifrom = symbol_index(e); @@ -2590,10 +2590,10 @@ struct symbol_elem_t * symbol_typedef_add( size_t program, struct cbl_field_t *field ) { assert(field); assert(field->is_typedef()); - + if( field->is_strongdef() && field->level != 1 ) { ERROR_FIELD(field, "%s %s STRONG TYPEDEF must be level 01", - field->level_str(), field->name); + field->level_str(), field->name); return NULL; } @@ -2734,14 +2734,14 @@ symbol_field_add( size_t program, struct cbl_field_t *field ) } /* - * TYPEDEF is relevant only in Data Division. + * TYPEDEF is relevant only in Data Division. */ struct symbol_elem_t * symbol_typedef( size_t program, const char name[] ) { auto beg = std::reverse_iterator<symbol_elem_t *>(symbols_end()); auto end = std::reverse_iterator<symbol_elem_t *>(symbols_begin(program)); - + auto p = std::find_if( beg, end, [name]( const symbol_elem_t& sym ) { if( sym.type == SymField ) { @@ -2794,7 +2794,7 @@ symbol_field( size_t program, size_t parent, const char name[] ) symbol_elem_t * symbol_register( const char name[] ) { - auto p = std::find_if(symbols_begin(), symbol_at(symbols.first_program), + auto p = std::find_if(symbols_begin(), symbol_at(symbols.first_program), [len = strlen(name), name]( auto e ) { if( e.type == SymField ) { if( strlen(cbl_field_of(&e)->name) == len ) { @@ -2803,7 +2803,7 @@ symbol_register( const char name[] ) } return false; } ); - + return p; } @@ -2968,7 +2968,7 @@ static size_t seek_parent( const symbol_elem_t *e, size_t level ) { size_t program = e->program; const cbl_field_t *field = cbl_field_of(e); - while( program == e->program && level <= field->level ) { + while( program == e->program && level <= field->level ) { if( e->type != SymField ) break; auto f = cbl_field_of(e); if( f->parent == 0 ) break; @@ -2982,7 +2982,7 @@ seek_parent( const symbol_elem_t *e, size_t level ) { * For a group, create new fields and copy members recursively. * Precondition: both fields exist in the symbol table. * Postcondition: return final element copied. - * + * * "The condition-name entries for a particular conditional variable * shall immediately follow the entry describing the item...." */ @@ -2990,12 +2990,12 @@ struct symbol_elem_t * symbol_field_same_as( cbl_field_t *tgt, const cbl_field_t *src ) { if( target_in_src(tgt, src) ) { ERROR_FIELD(tgt, "%s %s may not reference itself as part of %s %s", - tgt->level_str(), tgt->name, src->level_str(), src->name); + tgt->level_str(), tgt->name, src->level_str(), src->name); return NULL; } if( tgt->level == 77 && src->type == FldGroup ) { ERROR_FIELD(tgt, "%s %s TYPE TO %s must be an elementary item", - tgt->level_str(), tgt->name, src->name); + tgt->level_str(), tgt->name, src->name); return NULL; } auto last_elem = symbol_at(field_index(tgt)); @@ -3007,8 +3007,8 @@ symbol_field_same_as( cbl_field_t *tgt, const cbl_field_t *src ) { symbol_elem_t *eog = symbol_at_impl(end_of_group(isrc), true); if( src->type != FldGroup ) { - // For scalar, check for Level 88, which if extant must follow immediately. - eog = std::find_if( bog + 1, + // For scalar, check for Level 88, which if extant must follow immediately. + eog = std::find_if( bog + 1, symbols_end(), []( const auto& elem ) { if( elem.type == SymField ) { @@ -3017,7 +3017,7 @@ symbol_field_same_as( cbl_field_t *tgt, const cbl_field_t *src ) { } return true; } ); - } + } cbl_field_t dup = { .parent = field_index(tgt), .line = tgt->line }; @@ -3108,7 +3108,7 @@ is_numeric_constant( const char name[] ) { } #if 0 - auto isym = + auto isym = auto e = symbol_field( current_program_index(), 0, name ); if( !e ) return NULL; auto field = cbl_field_of(e); @@ -3326,7 +3326,7 @@ static cbl_field_t * new_temporary_impl( enum cbl_field_type_t type ) { extern int yylineno; - static int nstack, nliteral; + static int nstack, nliteral; static const struct cbl_field_t empty_alpha = { 0, FldAlphanumeric, FldInvalid, intermediate_e, 0, 0, 0, nonarray, 0, "", @@ -3375,12 +3375,12 @@ new_temporary_impl( enum cbl_field_type_t type ) snprintf(f->name, sizeof(f->name), "_literal%d",++nliteral); } else { snprintf(f->name, sizeof(f->name), "_stack%d",++nstack); - + if( getenv("symbol_temporaries_free") ) { dbgmsg("%s: %s, %s", __func__, f->name, 3 + cbl_field_type_str(f->type)); } } - + return f; } @@ -3421,7 +3421,7 @@ new_literal_add( const char initial[], uint32_t len, enum cbl_field_attr_t attr } static size_t literal_count = 1; - sprintf(field->name, + sprintf(field->name, "%s%c_%zd", "_literal", field->type == FldLiteralA ? 'a' : 'n', @@ -3460,14 +3460,14 @@ void temporaries_t::dump() const { char *output; extern int yylineno; - + asprintf(&output, "%4d: %zu Literals", yylineno, literals.size()); for( const auto& elem : used ) { if( ! elem.second.empty() ) { char *so_far = output; asprintf(&output, "%s, %zu %s", - so_far, - elem.second.size(), + so_far, + elem.second.size(), 3 + cbl_field_type_str(elem.first)); free(so_far); } @@ -3499,11 +3499,11 @@ cbl_field_t * temporaries_t::reuse( cbl_field_type_t type ) { //// DUBNER is defeating reuse as part of investigating problems with recursion return NULL; -//// - +//// + auto& fields = freed[type]; cbl_field_t *field; - + if( fields.empty() ) { return NULL; } else { @@ -3511,7 +3511,7 @@ temporaries_t::reuse( cbl_field_type_t type ) { field = *p; fields.erase(p); } - + return add(field); } @@ -3523,7 +3523,7 @@ temporaries_t::acquire( cbl_field_type_t type ) { field = new_temporary_impl(type); add(field); } - return parser_symbol_add2(field); // notify of reuse + return parser_symbol_add2(field); // notify of reuse } void @@ -3628,14 +3628,14 @@ cbl_field_t::is_ascii() const { /* * Convert an input source-code string literal (or VALUE) to internal encoding. - * - * Input encoding initially defaults to UTF-8, regardless of locale(7), + * + * Input encoding initially defaults to UTF-8, regardless of locale(7), * for two reasons: * 1) The source code might not match the locale - * 2) The assumption is easily disproved with most input. That is, - * input values above 0x7F will rarely look like UFT-8 unless + * 2) The assumption is easily disproved with most input. That is, + * input values above 0x7F will rarely look like UFT-8 unless * they actually are UTF-8. - * + * * If conversion from UTF-8 fails, the compiler's locale is examined * next. If it is C, it is ignored, else it is tried. If that fails, * the input is assumed to be encoded as CP1252. @@ -3651,7 +3651,7 @@ static const char * guess_encoding() { static const char *fromcode; - if( ! fromcode ) { + if( ! fromcode ) { return fromcode = os_locale.assumed; } @@ -3672,9 +3672,9 @@ cbl_field_t::internalize() { static iconv_t cd = iconv_open(tocode, fromcode); static const size_t noconv = size_t(-1); - // Sat Mar 16 11:45:08 2024: require temporary environment for testing + // Sat Mar 16 11:45:08 2024: require temporary environment for testing if( getenv( "INTERNALIZE_NO") ) return data.initial; - + bool using_assumed = fromcode == os_locale.assumed; if( fromcode == tocode || has_attr(hex_encoded_e) ) { @@ -3683,14 +3683,14 @@ cbl_field_t::internalize() { if( is_ascii() ) return data.initial; assert(data.capacity > 0); - + char output[data.capacity + 2], *out = output; char *in = const_cast<char*>(data.initial); size_t n, inbytesleft = data.capacity, outbytesleft = sizeof(output); if( !is_literal(this) && inbytesleft < strlen(data.initial) ) { inbytesleft = strlen(data.initial); } - + assert(fromcode != tocode); while( (n = iconv( cd, &in, &inbytesleft, &out, &outbytesleft)) == noconv ) { @@ -3711,13 +3711,13 @@ cbl_field_t::internalize() { if( 0 < inbytesleft ) { // data.capacity + inbytesleft is not correct if the remaining portion has - // multibyte characters. But the fact reamins that the VALUE is too big. + // multibyte characters. But the fact reamins that the VALUE is too big. ERROR_FIELD(this, "%s %s VALUE '%s' requires %zu bytes for size %u", - cbl_field_t::level_str(level), name, data.initial, - data.capacity + inbytesleft, data.capacity ); + cbl_field_t::level_str(level), name, data.initial, + data.capacity + inbytesleft, data.capacity ); } - // Replace data.initial only if iconv output differs. + // Replace data.initial only if iconv output differs. if( 0 != memcmp(data.initial, output, out - output) ) { assert(out <= output + data.capacity); @@ -3737,14 +3737,14 @@ cbl_field_t::internalize() { int len = int(out - output); char *mem = static_cast<char*>( xcalloc(1, sizeof(output)) ); - // Set the new memory to all blanks, tacking a '!' on the end. + // Set the new memory to all blanks, tacking a '!' on the end. memset(mem, 0x20, sizeof(output) - 1); mem[ sizeof(output) - 2] = '!'; if( is_literal(this) ) { - data.capacity = len; // trailing '!' will be overwritten + data.capacity = len; // trailing '!' will be overwritten } - + memcpy(mem, output, len); // copy only as much as iconv converted free(const_cast<char*>(data.initial)); @@ -3762,7 +3762,7 @@ cbl_field_t::internalize() { } } - + return data.initial; } @@ -3963,32 +3963,32 @@ symbol_label_add( size_t program, cbl_label_t *input ) bool symbol_label_section_exists( size_t program ) { auto pblob = std::find_if( symbols_begin(program), symbols_end(), - []( const auto& sym ) { - if( sym.type == SymField ) { - auto& f( sym.elem.field ); - return f.type == FldBlob; - } - return false; - } ); + []( const auto& sym ) { + if( sym.type == SymField ) { + auto& f( sym.elem.field ); + return f.type == FldBlob; + } + return false; + } ); if( pblob == symbols_end() ) return true; // Section name not required bool has_section = std::any_of( ++pblob, symbols_end(), - []( const auto& sym ) { - if( sym.type == SymLabel ) { - auto& L(sym.elem.label); - if( L.type == LblSection ) { - if( L.name[0] != '_' ) { // not implicit - return true; // Section name exists - } - } - } - return false; - } ); + []( const auto& sym ) { + if( sym.type == SymLabel ) { + auto& L(sym.elem.label); + if( L.type == LblSection ) { + if( L.name[0] != '_' ) { // not implicit + return true; // Section name exists + } + } + } + return false; + } ); if( yydebug && ! has_section ) { symbols_dump(program, true); } // Return true if no Declaratives, because the (non-)requirement is met. - // Return false if Declaratives exist, because no Section name was found. + // Return false if Declaratives exist, because no Section name was found. return has_section; } @@ -4545,7 +4545,7 @@ cbl_key_t( const cbl_occurs_key_t& that ) void cbl_occurs_t::key_alloc( bool ascending ) { - auto nbytes = sizeof(keys[0]) * (nkey + 1); + auto nbytes = sizeof(keys[0]) * (nkey + 1); cbl_occurs_key_t key = { ascending, cbl_field_list_t() }; keys = static_cast<cbl_occurs_key_t *>(xrealloc(keys, nbytes)); @@ -4602,9 +4602,9 @@ cbl_occurs_t::subscript_ok( const cbl_field_t *subscript ) const { if( !is_literal(subscript) ) { return true; // Cannot check non-literals, so, OK. } - // It must be a number. - if( subscript->type != FldLiteralN ) return false; - + // It must be a number. + if( subscript->type != FldLiteralN ) return false; + auto sub = subscript->data.value; if( sub < 1 || sub != size_t(sub) ) { @@ -4775,8 +4775,8 @@ cbl_file_key_t::deforward( size_t ifile ) { } if( ! (is_numeric(field) && 0 == field->data.rdigits) ) { ERROR_FIELD(field, "line %d: RELATIVE file %s key %s " - "must be integer type", - file->line, file->name, field->name); + "must be integer type", + file->line, file->name, field->name); return ifield; } return ifield; diff --git a/gcc/cobol/symfind.cc b/gcc/cobol/symfind.cc index 0665b9253dfbc9146e0c49c65f13e9a1fff1f6fc..f9dc78731a30bfdfd3d273d010eb43a131b12c86 100644 --- a/gcc/cobol/symfind.cc +++ b/gcc/cobol/symfind.cc @@ -97,7 +97,7 @@ static field_keymap_t symbol_map2; void update_symbol_map2( const symbol_elem_t *e ) { auto field = cbl_field_of(e); - + if( ! field->is_typedef() ) { switch( field->type ) { case FldForward: @@ -151,7 +151,7 @@ dump_symbol_map2( const field_key_t& key, const std::list<size_t>& candidates ) } dbgmsg( "%s:%d: %3zu %s {%s}", __func__, __LINE__, - key.program, key.name, fields ); + key.program, key.name, fields ); free(fields); } @@ -506,7 +506,7 @@ symbol_match2( size_t program, } free(ancestry); } - + return fields; } @@ -533,7 +533,7 @@ symbol_match( size_t program, std::list<const char *> names ) { auto inserted = output.insert(*p); if( ! inserted.second ) { yyerror("%s is not a unique reference", key.name); - } + } } return output; } @@ -553,11 +553,11 @@ symbol_typedef( size_t program, std::list<const char *> names ) { static const symbol_elem_t * symbol_field_alias_01; -const symbol_elem_t * +const symbol_elem_t * symbol_field_alias_begin() { return symbol_field_alias_01 = symbol_field_current_record(); } -void +void symbol_field_alias_end() { symbol_field_alias_01 = NULL; } diff --git a/gcc/cobol/util.cc b/gcc/cobol/util.cc index 52d78c98f39f336a3a1d24e6e4c3036838d1bebd..7b1328107d750b164676a6fcbb9967bfa50c7219 100644 --- a/gcc/cobol/util.cc +++ b/gcc/cobol/util.cc @@ -301,13 +301,13 @@ is_numeric_edited( const char picture[] ) { break; default: numed_message = xasprintf("invalid PICTURE character " - "'%c' at offset %zu in '%s'", - *p, p - picture, picture); + "'%c' at offset %zu in '%s'", + *p, p - picture, picture); break; } dbgmsg( "%s: no, because '%c' at %.*s<-- in '%s'", - __func__, *p, int(p - picture) + 1, picture, picture ); + __func__, *p, int(p - picture) + 1, picture, picture ); return false; } @@ -622,7 +622,7 @@ symbol_field_type_update( cbl_field_t *field, // type matches itself if( field->type == candidate ) { - if( is_usage ) field->usage = candidate; + if( is_usage ) field->usage = candidate; return true; } if( is_usage && field->usage == candidate ) return true; @@ -645,7 +645,7 @@ symbol_field_type_update( cbl_field_t *field, assert(field->type != candidate && is_elementary(candidate)); /* - * Concrete usage candidate. Update usage first (if USAGE clause), then type. + * Concrete usage candidate. Update usage first (if USAGE clause), then type. */ if( is_usage ) { switch(field->type) { @@ -682,7 +682,7 @@ symbol_field_type_update( cbl_field_t *field, if( ! (dialect_mf() && field->has_attr(all_x_e)) ) { return false; } - __attribute__((fallthrough)); + __attribute__((fallthrough)); case FldFloat: case FldNumericBin5: case FldNumericBinary: @@ -1072,7 +1072,7 @@ valid_move( const struct cbl_field_t *tgt, const struct cbl_field_t *src ) /* Needs C++11 */ static_assert(sizeof(matrix[0]) == COUNT_OF(matrix[0]), "matrix should be square"); - + for( const cbl_field_t *args[] = {tgt, src}, **p=args; p < args + COUNT_OF(args); p++ ) { auto& f(**p); @@ -1090,12 +1090,12 @@ valid_move( const struct cbl_field_t *tgt, const struct cbl_field_t *src ) default: if( sizeof(matrix[0]) < f.type ) { cbl_internal_error("logic error: MOVE %s %s invalid type:", - cbl_field_type_str(f.type), f.name); + cbl_field_type_str(f.type), f.name); } break; } } - + assert(tgt->type < sizeof(matrix[0])); assert(src->type < sizeof(matrix[0])); @@ -1115,7 +1115,7 @@ valid_move( const struct cbl_field_t *tgt, const struct cbl_field_t *src ) { case 0: if( src->type == FldLiteralA && is_numericish(tgt) && !is_literal(tgt) ) { - // Allow if input string is an integer. + // Allow if input string is an integer. const char *p = src->data.initial, *pend = p + src->data.capacity; if( p[0] == '+' || p[0] == '-' ) p++; retval = std::all_of( p, pend, isdigit ); @@ -1143,7 +1143,7 @@ valid_move( const struct cbl_field_t *tgt, const struct cbl_field_t *src ) retval = !src_alpha; break; default: - dbgmsg("%s:%d: matrix at %s, %s is %d", __func__, __LINE__, + dbgmsg("%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); @@ -1157,11 +1157,11 @@ valid_move( const struct cbl_field_t *tgt, const struct cbl_field_t *src ) } if( yydebug && getenv(__func__) ) { - dbgmsg("%s:%d: ok to move %s to %s (0x%02x)", __func__, __LINE__, + dbgmsg("%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); } - + return retval; } @@ -1741,7 +1741,7 @@ date_time_fmt( const char input[] ) { regex_t reg; char type; char pattern[256]; } fmts[] = { { regex_t(), 'D', "^((" DATE_FMT_B "T" TIME_FMT_B ")|(" - DATE_FMT_E "T" TIME_FMT_E "))$" }, + DATE_FMT_E "T" TIME_FMT_E "))$" }, { regex_t(), 'd', "^(" DATE_FMT_B "|" DATE_FMT_E ")$" }, { regex_t(), 't', "^(" TIME_FMT_B "|" TIME_FMT_E ")$" }, }; @@ -1784,9 +1784,9 @@ struct input_file_t { int lineno; const char *name; const line_map *lines; - + input_file_t( const char *name, ino_t inode, - int lineno=1, const line_map *lines = NULL ) + int lineno=1, const line_map *lines = NULL ) : inode(inode), lineno(lineno), name(name), lines(lines) { if( inode == 0 ) inode_set(); @@ -1820,14 +1820,14 @@ class unique_stack : public std::stack<input_file_t> if( n > 1 ) { char *wd = get_current_dir_name(); if( wd ) { - dbgmsg( "depth line copybook filename\n" - "----- ---- --------" - "----------------------------------------"); - for( const auto& v : c ) { - dbgmsg( " %4zu %4d %s", c.size() - --n, v.lineno, no_wd(wd, v.name) ); - } + dbgmsg( "depth line copybook filename\n" + "----- ---- --------" + "----------------------------------------"); + for( const auto& v : c ) { + dbgmsg( " %4zu %4d %s", c.size() - --n, v.lineno, no_wd(wd, v.name) ); + } } else { - dbgmsg("unable to get current working directory: %m"); + dbgmsg("unable to get current working directory: %m"); } free(wd); } @@ -1851,7 +1851,7 @@ static const unsigned int sysp = 0; // not a C header file, cf. line-map.h * Maintain a stack of input filenames. Ensure the files are unique (by * inode), to prevent copybook cycles. Before pushing a new name, Record the * line number that was is current for the current name, so that it can be - * restored when the usurper is popped. + * restored when the usurper is popped. * * Both the file-reader (lexio) and the scanner use this stack. Lexio uses it * to enforce uniqueness, and the scanner to maintain line numbers. @@ -1869,7 +1869,7 @@ bool cobol_filename( const char *name, ino_t inode ) { inode = p->second; assert(inode != 0); } - linemap_add(line_table, LC_ENTER, sysp, name, 1); + linemap_add(line_table, LC_ENTER, sysp, name, 1); input_filename_vestige = name; bool pushed = input_filenames.push( input_file_t(name, inode, 1, lines) ); input_filenames.top().lineno = yylineno = 1; @@ -1902,7 +1902,7 @@ cobol_filename_restore() { const input_file_t& top( input_filenames.top() ); old_filenames[top.name] = top.inode; input_filename_vestige = top.name; - + input_filenames.pop(); if( input_filenames.empty() ) return NULL; @@ -1948,7 +1948,7 @@ verify_format( const char gmsgid[] ) { static int status = regcomp( &re, pattern, cflags ); static char errbuf[80]; - + if( status != 0 ) { int n = regerror(status, &re, errbuf, sizeof(errbuf)); @@ -1959,7 +1959,7 @@ verify_format( const char gmsgid[] ) { gcc_assert(status == 0); regmatch_t rm[30]; - + if( REG_NOMATCH != regexec(&re, gmsgid, COUNT_OF(rm), rm, 0) ){ fprintf(stderr, "bad diagnositic format: '%s'\n", gmsgid); } @@ -1978,7 +1978,7 @@ ydferror( const char gmsgid[], ... ) { va_start (ap, gmsgid); rich_location richloc (line_table, token_location); bool ret = global_dc->diagnostic_impl (&richloc, nullptr, option_id, - gmsgid, &ap, DK_ERROR); + gmsgid, &ap, DK_ERROR); va_end (ap); } @@ -1996,7 +1996,7 @@ class temp_loc_t : protected YYLTYPE { public: temp_loc_t() : orig(token_location) { if( yychar < 3 ) return; - + gcc_location_set(yylloc); // use lookahead location } temp_loc_t( const YYLTYPE& loc) : orig(token_location) { @@ -2004,8 +2004,8 @@ class temp_loc_t : protected YYLTYPE { } temp_loc_t( const YDFLTYPE& loc) : orig(token_location) { YYLTYPE lloc = { - loc.first_line, loc.first_column, - loc.last_line, loc.last_column }; + loc.first_line, loc.first_column, + loc.last_line, loc.last_column }; gcc_location_set(lloc); } ~temp_loc_t() { @@ -2069,7 +2069,7 @@ yyerror( const char gmsgid[], ... ) { va_start (ap, gmsgid); rich_location richloc (line_table, token_location); bool ret = global_dc->diagnostic_impl (&richloc, nullptr, option_id, - gmsgid, &ap, DK_ERROR); + gmsgid, &ap, DK_ERROR); va_end (ap); global_dc->end_group(); } @@ -2081,7 +2081,7 @@ yywarn( const char gmsgid[], ... ) { va_list ap; va_start (ap, gmsgid); auto ret = emit_diagnostic_valist( DK_WARNING, token_location, - option_id, gmsgid, &ap ); + option_id, gmsgid, &ap ); va_end (ap); return ret; } @@ -2118,7 +2118,7 @@ cobol_fileline_set( const char line[] ) { static const int cflags = REG_EXTENDED | REG_ICASE; static regex_t re, *preg = NULL; - int erc; + int erc; regmatch_t pmatch[4]; if( !preg ) { @@ -2138,19 +2138,19 @@ cobol_fileline_set( const char line[] ) { error_msg(yylloc, "invalid #line directive: %s", line ); return line; } - + const char *line_str = xstrndup(line + pmatch[1].rm_so, matched_length(pmatch[1])), *filename = xstrndup(line + pmatch[2].rm_so, matched_length(pmatch[2])); int fileline; - + if( 1 != sscanf(line_str, "%d", &fileline) ) yywarn("could not parse line number %s from #line directive", line_str); - + input_file_t input_file( filename, ino_t(0), fileline ); // constructor sets inode - if( getenv(__func__) ) return filename; // ignore #line directive - + if( getenv(__func__) ) return filename; // ignore #line directive + if( input_filenames.empty() ) { input_file.lines = linemap_add(line_table, LC_ENTER, sysp, filename, 1); input_filenames.push(input_file); @@ -2159,7 +2159,7 @@ cobol_fileline_set( const char line[] ) { input_file_t& file = input_filenames.top(); file = input_file; yylineno = file.lineno; - + return file.name; } @@ -2190,7 +2190,7 @@ parse_file( const char filename[] ) parser_enter_file(filename); timespec_t start; - + int erc = yyparse(); timespec_t finish;