Age | Commit message (Collapse) | Author | Files | Lines |
|
constification per cppcheck. Use STRICT_WARN and fix reported
diagnostics. Ignore [shadowVariable] in general. Use std::vector to
avoid exposing arrays as raw pointers.
PR cobol/120621
gcc/cobol/ChangeLog:
* Make-lang.in: Use STRICT_WARN.
* cbldiag.h (location_dump): suppress shadowVariable.
* cdf-copy.cc (esc): Fix shadowVariable.
(copybook_elem_t::open_file): Do not use %m.
* cdf.y: suppress invalidPrintfArgType for target format.
* cdfval.h (struct cdfval_t): Suppress noExplicitConstructor.
* cobol1.cc (cobol_name_mangler): Use C++ cast.
* copybook.h (class copybook_elem_t): Same.
* dts.h: Fixes and suppressions due to cppcheck.
* except.cc (cbl_enabled_exceptions_t::status): Suppress useStlAlgorithm.
(cbl_enabled_exceptions_t::turn_on_off): Const parameter.
(class choose_declarative): Removed.
* genapi.cc (struct called_tree_t): Explicit constructor.
(parser_compile_ecs): Cast to void * for %p.
(parser_compile_dcls): Same.
(parser_statement_begin): Same.
(initialize_variable_internal): Use std::vector for subscripts.
(parser_initialize): Constification.
(get_string_from): Same.
(combined_name): Same.
(parser_perform): Same.
(psa_FldLiteralN): Same.
(is_figconst): Const parameter.
(is_figconst_t): Same.
(parser_exit): Same.
(parser_division): Const pointer.
(parser_perform_conditional): Whitespace.
(parser_set_conditional88): Const parameter.
(inspect_tally): Use std::vector.
(inspect_replacing): Same.
(parser_inspect): Same.
(parser_intrinsic_subst): Use std::vector (constuct elements).
(parser_intrinsic_call_1): Use std::vector for subscripts.
(is_ascending_key): Const pointer.
(parser_sort): Use std::vector.
(parser_file_sort): Same.
(parser_file_merge): Same.
(parser_unstring): Same.
(parser_string): Same.
(parser_call): Const pointer.
(parser_program_hierarchy): Use std::vector.
(conditional_abs): Const paraemeter.
(float_type_of): Same.
(initial_from_initial): Set value, quoted or not.
(parser_symbol_add): Remove redundant nested test.
* genapi.h (parser_add): Const parameters.
(parser_subtract): Same.
(parser_multiply): Same.
(parser_divide): Same.
(parser_perform): Same.
(parser_exit): Same.
(parser_initialize): Same.
(parser_set_conditional88): Same.
(parser_sort): Same.
(parser_file_sort): Same.
(parser_file_merge): Same.
(parser_string): Same.
(is_ascending_key): Same.
* genmath.cc (arithmetic_operation): Use std::vector.
(is_somebody_float): Const parameter.
(all_results_binary): Const parameter.
(fast_multiply): Remove redundant nested test.
(parser_add): Const parameter.
(parser_multiply): Remove redundant nested test.
(parser_divide): Const parameter.
(parser_subtract): Same.
* genutil.cc (get_depending_on_value): Use std::vector.
(get_data_offset): Same.
(tree_type_from_field): Const parameter.
(refer_has_depends): Const pointers.
(get_literal_string): RAII.
(refer_is_clean): Use std::vector.
(get_time_nanoseconds): Newline at EOF.
* genutil.h (tree_type_from_field): Remove declaration.
* inspect.h (struct cbx_inspect_qual_t): Use std::vector.
(struct cbl_inspect_qual_t): Same.
(struct cbx_inspect_match_t): Same.
(class cbl_inspect_match_t): Same.
(struct cbx_inspect_replace_t): Same.
(struct cbl_inspect_replace_t): Same.
(struct cbx_inspect_oper_t): Same.
(struct cbl_inspect_oper_t): Same.
(struct cbx_inspect_t): Same.
(struct cbl_inspect_t): Same.
(parser_inspect): Same.
* lexio.cc (indicated): Const pointer.
(remove_inline_comment): Scope reduction.
(maybe_add_space): Const pointer.
(recognize_replacements): C++ cast.
(check_source_format_directive): Same.
(struct replacing_term_t): Explicit constructor.
(parse_replace_pairs): Const reference.
(location_in): Const reference.
(parse_copy_directive): C++ cast.
(parse_replace_last_off): Const parameter.
(parse_replace_text): Const reference.
(parse_replace_directive): C++ cast.
(cdftext::lex_open): Const reference.
(cdftext::open_output): Scope reduction.
(cdftext::free_form_reference_format): Remove unused variable.
(cdftext::process_file): Simplify.
* lexio.h (struct bytespan_t): Use nullptr.
(struct filespan_t): Initialize icol in constructor.
(struct span_t): Suppress confused operatorEqRetRefThis.
(struct replace_t): Eliminate single-value constructor.
* parse.y: Many const cppcheck reports, and portable bit-shift.
* parse_ante.h (reject_refmod): Const parameter.
(require_pointer): Same.
(require_integer): Same.
(struct evaluate_elem_t): Explicit constructor.
(struct arith_t): Use std::vector.
(class eval_subject_t): Const parameter.
(dump_inspect_match): Declare.
(struct perform_t): Explicit constructor.
(list_add): Const parameter.
(class tokenset_t): Avoid negative array index.
(struct file_list_t): Explicit constructor.
(struct field_list_t): Same.
(struct refer_list_t): Same.
(struct refer_marked_list_t): Const parameter.
(struct refer_collection_t): Explicit constructor.
(struct ast_inspect_oper_t): Remove class.
(ast_inspect_oper_t): Same.
(struct ast_inspect_t): Same.
(struct ast_inspect_list_t): Same.
(ast_inspect): Add location.
(struct elem_list_t): Explicit constructor.
(struct unstring_tgt_t): Same.
(struct unstring_tgt_list_t): Same.
(struct unstring_into_t): Same.
(struct ffi_args_t): Same.
(struct file_sort_io_t): Same.
(merge_t): Same.
(struct vargs_t): Same.
(class prog_descr_t): Eliminate single-value constructor.
(class program_stack_t): Suppress useStlAlgorithm.
(struct rel_part_t): Eliminate single-value constructor.
(class log_expr_t): Explicit constructor.
(add_debugging_declarative): Rename local variable.
(intrinsic_call_2): Const parameter.
(invalid_key): Use std::find_if.
(parser_add2): Const parameter.
(parser_subtract2): Same.
(stringify): Same.
(unstringify): Same.
(anybody_redefines): Same.
(ast_call): Same.
* parse_util.h (class cname_cmp): Explicit constructor.
(intrinsic_inconsistent_parameter): Same.
* scan_ante.h (struct cdf_status_t): Eliminate single-value constructor.
(class enter_leave_t): Explicit constructor.
(update_location): Const pointer, explicit constructor.
(symbol_function_token): Const pointer.
(typed_name): Same.
* scan_post.h (datetime_format_of): Scope reduction.
* show_parse.h (class ANALYZE): Use std::vector, explicit consstructor.
* symbols.cc (symbol_table_extend): Scope reduction.
(cbl_ffi_arg_t::cbl_ffi_arg_t): Define default constructor.
(end_of_group): Const pointer.
(symbol_find_odo): Const parameter.
(rename_not_ok): Same.
(field_str): Use %u instead of %d.
(struct capacity_of): Const pointer.
(symbols_update): Same.
(symbol_field_parent_set): Same.
(symbol_file_add): Same.
(symbol_typedef_add): Same.
(symbol_field_add): Use new operator=().
(symbol_field): Suppress CastIntegerToAddressAtReturn.
(symbol_register): Same.
(symbol_file): Suppress knownConditionTrueFalse.
(next_program): Const parameter.
(symbol_file_record): Same.
(class is_section): Explicit constructor.
(cbl_file_t::no_key): Remove.
(cbl_prog_hier_t::cbl_prog_hier_t): Use std::vector.
(symbol_label_add): Assert pointer is not NULL.
(symbol_label_section_exists): Const reference in lambda.
(expand_picture): Use C++ cast.
(symbol_program_callables): Const pointer.
(symbol_currency_add): Suppress nullPointerRedundantCheck.
(cbl_key_t): Use std::vector.
(cbl_occurs_t::field_add): Const parameter.
(cbl_occurs_t::index_add): Explicit constructor.
(class is_field_at): Same.
(cbl_file_key_t::deforward): Scope reduction.
(cbl_file_t::keys_str): Use allocated memory only.
(file_status_status_of): Const pointer.
(is_register_field): Const parameter.
* symbols.h (struct cbl_field_data_t): Eliminate single-value constructor.
(struct cbl_occurs_bounds_t): Same.
(struct cbl_refer_t): Use std::vector.
(valid_move): Const parameter.
(is_register_field): Same.
(struct cbl_key_t): Use std::vector.
(struct cbl_substitute_t): Eliminate single-value constructor.
(refer_of): Return const reference
(struct cbl_ffi_arg_t): Eliminate single-value constructor.
(class temporaries_t): Same.
(struct cbl_file_key_t): Define default constructor.
(struct cbl_file_lock_t): Define copy constructor and operator=().
(struct cbl_file_t): Complete default constructor.
(struct symbol_elem_t): Explicit constructor.
(symbol_elem_of): Suppress cstyleCast.
(symbol_redefines): Const parameter.
(struct cbl_field_t): Same.
(cbl_section_of): Test for NULL pointer.
(cbl_field_of): Same.
(cbl_label_of): Same.
(cbl_special_name_of): Same.
(cbl_alphabet_of): Same.
(cbl_file_of): Same.
(is_figconst): Delete extra "struct" keyword.
(is_figconst_low): Same.
(is_figconst_zero): Same.
(is_figconst_space): Same.
(is_figconst_quote): Same.
(is_figconst_high): Same.
(is_space_value): Same.
(is_quoted): Same.
(symbol_index): Const parameter.
(struct cbl_prog_hier_t): Suppress noExplicitConstructor.
(struct cbl_perform_vary_t): Eliminate single-value constructor.
(is_signable): Const parameter.
(is_temporary): Same.
(rename_not_ok): Same.
(field_at): Test for NULL pointer.
(class procref_base_t): Eliminate single-value constructor.
* symfind.cc (is_data_field): Const pointer.
(finalize_symbol_map2): Same.
(class in_scope): Same.
(symbol_match2): Same.
* token_names.h: Suppress useInitializationList.
* util.cc (normalize_picture): Whitespace and remove extra "continue".
(redefine_field): Const pointer.
(cbl_field_t::report_invalid_initial_value): Same.
(literal_subscript_oob): Rename shadow variable.
(cbl_refer_t::subscripts_set): Use std::vector.
(cbl_refer_t::str): Same.
(cbl_refer_t::deref_str): Same.
(locally_unique): Use explicit constructor.
(ambiguous_reference): Same.
(class unique_stack): Use const reference.
(cobol_filename): Const pointer.
(verify_format): Scope reduction.
(class temp_loc_t): Do not derive from YYLTYPE.
(cobol_parse_files): Const pointer.
* util.h (as_voidp): Define convenient converter.
libgcobol/ChangeLog:
* common-defs.h (class cbl_enabled_exceptions_t): Const parameter.
|
|
This attempts to eliminate "'clock_gettime' not declared..." when
building on x86_64-apple-darwin15.6.0. Calls to clock_gettime have been
reduced to two locations. Both have been guarded with
gcc/cobol/ChangeLog:
PR cobol/119975
* genapi.cc (parser_intrinsic_call_0): Use get_time_nanoseconds().
* genutil.cc (get_time_64): Rename to get_time_nanoseconds().
(get_time_nanoseconds): Likewise.
* genutil.h (get_time_64): Likewise.
(get_time_nanoseconds): Likewise.
* util.cc (class cbl_timespec): Timing routine uses
get_time_nanoseconds().
(operator-): Likewise.
(parse_file): Likewise.
libgcobol/ChangeLog:
PR cobol/119975
* configure.ac: AC_CHECK_LIB(rt, clock_gettime).
* config.h.in: Likewise.
* configure: Likewise.
* gfileio.cc: Remove in-line cppcheck-suppress.
* intrinsic.cc (timespec_to_string): Use guarded clock_gettime().
(__gg__current_date): Likewise.
(__gg__seconds_past_midnight): Likewise.
(__gg__formatted_current_date): Likewise.
(__gg__random): Likewise.
(__gg__random_next): Likewise.
(__gg__when_compiled): Likewise.
* libgcobol.cc (cobol_time): Likewise.
(get_time_nanoseconds): Likewise.
(__gg__clock_gettime): Likewise.
(__gg__get_date_hhmmssff): Likewise.
* libgcobol.h (__gg__clock_gettime): Likewise.
(struct cbl_timespec): Likewise.
|
|
These changes cause genapi.cc to use whichever of clock_gettime() or
gettimeofday() are available. This prevents compilation errors on
systems where clock_gettime() is not available.
gcc/cobol/ChangeLog:
PR cobol/119975
* genapi.cc (parser_intrinsic_call_0): Use get_time_64() function.
* genutil.cc (get_time_64): Definition created.
* genutil.h (get_time_64): Declaration created.
|
|
This eliminates some of the last vestiges of creating a structure at host-time
that is intended for use at target-time.
It removes some unnecessary processing when exceptions are not enabled.
It improves the creation of code that handles table subscripts and refmod
parameters.
gcc/cobol/ChangeLog:
* cobol1.cc (cobol_langhook_handle_option): Eliminate OPT_M.
* except.cc (cbl_enabled_exception_t::dump): Formatting.
(symbol_declaratives_add): Remove.
(declarative_runtime_match): Change to no-blob processing.
* exceptg.h (declarative_runtime_match): Change declaration.
(symbol_declaratives_add): Remove declaration.
* gcobc: Dialect handling.
* genapi.cc (parser_compile_ecs): Formatting; add SHOW_IF_PARSE.
(parser_compile_dcls): Likewise.
(parser_statement_begin): Avoid unnecessary store_location_stuff() call.
(gg_get_depending_on_value): Streamline get_depending_on_value_from_odo().
(depending_on_value): Likewise.
(parser_display_field): Formatting.
(parser_display): Handle case ENV_NAME_e.
(parser_file_open): Avoid unnecessary store_location_stuff.
(parser_file_close): Likewise.
(parser_file_read): Likewise.
(parser_file_write): Likewise.
(parser_file_delete): Likewise.
(parser_file_rewrite): Likewise.
(parser_file_start): Likewise.
(parser_intrinsic_subst): Streamline get_depending_on_value_from_odo().
(parser_intrinsic_call_1): Likewise.
(parser_lsearch_start): Likewise.
(parser_bsearch_start): Likewise.
(parser_sort): Likewise.
(store_location_stuff): Avoid unnecessary assignments.
(parser_pop_exception): Formatting.
* genmath.cc (parser_add): Avoid var_decl_default_compute_error assignment
when doing fast_add().
(parser_subtract): Likewise.
* genutil.cc (REFER): Macro for analyzing code generation.
(get_integer_value): Use data_decl_node for integer value from FldLiteralN.
(get_data_offset): Streamline exception code processing.
(get_and_check_refstart_and_reflen): Likewise.
(get_depending_on_value_from_odo): Likewise.
(get_depending_on_value): Likewise.
(refer_is_clean): Formatting.
(refer_refmod_length): Streamline exception code processing.
(refer_fill_depends): Likewise.
(refer_offset): Likewise.
(refer_size_dest): Likewise.
(refer_size_source): Likewise.
* genutil.h (get_depending_on_value_from_odo): Likewise.
* lang-specs.h: Options definition.
* lang.opt: -M as in c.opt.
* lexio.h: Formatting.
* parse.y: Expand -dialect suggestions; SECTION SEGMENT messages.
* parse_ante.h (declarative_runtime_match): Dialect handling.
(labels_dump): Likewise.
(class current_tokens_t): Likewise.
(class prog_descr_t): Make program_index size_t to prevent padding bytes.
* scan.l: POP_FILE directive.
* scan_ante.h (class enter_leave_t): Better handle line number when
processing COPY statements.
* symbols.cc (symbol_elem_cmp): Eliminate SymFunction.
(symbols_dump): Likewise.
(symbol_label_section_exists): Likewise.
* symbols.h (NAME_MAX): Eliminate. (Was part of SymFunction).
(dialect_is): Improve dialect handling.
(dialect_gcc): Likewise.
(dialect_ibm): Likewise.
(dialect_gnu): Likewise.
(enum symbol_type_t): Eliminate SymFunction.
* util.cc (symbol_type_str): Likewise.
(class unique_stack): Option -M handling.
(cobol_set_pp_option): Likewise.
(parse_file): Likewise.
* util.h (cobol_set_pp_option): Likewise.
libgcobol/ChangeLog:
* common-defs.h (struct cbl_declarative_t): Eliminate blobl.
* libgcobol.cc (__gg__set_env_name): Code for ENVIRONMENT-NAME/VALUE.
(__gg__set_env_value): Likewise.
gcc/testsuite/ChangeLog:
* cobol.dg/group1/declarative_1.cob: Handle modified exception handling.
|
|
This commit includes changes to the parser's auto-detection heuristic for source
code formatting. The heuristic now examines the line containing "program-id" to
determine whether the code is in ISO "fixed-form reference format", or ISO
"free-form reference format", or the IBM "extended source format".
Changes to the parser also changes to token processing.
On the code generation side, there are some changes that begin to process
numeric literals in order generate more efficient code using information known
at compilation time.
gcc/cobol/ChangeLog:
PR cobol/119337
* Make-lang.in: Change how $(FLEX) is invoked.
* cdf.y: Change parser tokens.
* gcobc: Changed how name is inferred for PR119337
* gcobol.1: Documentation for SOURCE format heuristic
* genapi.cc: Eliminate __gg__odo_violation.
(parser_display_field): Change comment.
* genutil.cc:Eliminate __gg__odo_violation.
(REFER): New macro for analyzing subscript/refmod calculations.
(get_integer_value): Likewise.
(get_data_offset): Eliminate __gg__odo_violation.
(scale_by_power_of_ten_N): Eliminate unnecessary var_decl_rdigits operation.
(refer_is_clean): Check for FldLiteralN.
(REFER_CHECK): Eliminate.
(refer_refmod_length): Streamline var_decl_rdigits processing.
(refer_fill_depends): Likewise.
(refer_offset): Streamline processing when FldLiteralN.
(refer_size): Tag with REFER macro.
(refer_size_dest): Likewise.
(refer_size_source): Likewise.
* genutil.h (get_integer_value): Delete declaration for odo_violation;
change comment for get_integer_value
(REFER_CHECK): Delete declaration.
(refer_check): Delete #define.
* lexio.cc (is_fixed_format): Changes for source format auto-detect.
(is_reference_format): Likewise.
(check_source_format_directive): Likewise.
(valid_sequence_area): Likewise.
(is_p): Likewise.
(is_program_id): Likewise.
(likely_nist_file): Likewise.
(infer_reference_format): Likewise.
(cdftext::free_form_reference_format): Likewise.
* parse.y: Token changes.
* parse_ante.h (class tokenset_t): Likewise.
(class current_tokens_t): Likewise.
(cmd_or_env_special_of): Likewise.
* scan.l: Likewise.
* scan_ante.h (bcomputable): Likewise.
(keyword_alias_add): Likewise.
(struct bint_t): Likewise.
(binary_integer_usage): Likewise.
(binary_integer_usage_of): Likewise.
* scan_post.h (start_condition_str): Likewise.
* symbols.cc (symbol_table_init): Formatting.
* symbols.h (struct cbl_field_data_t): Add "input" method to field_data_t.
(keyword_alias_add): Add forward declaration.
(binary_integer_usage_of): Likewise.
* token_names.h: Change list of tokens.
* util.cc (iso_cobol_word): Change list of COBOL reserved words.
libgcobol/ChangeLog:
* common-defs.h (ec_cmp): Delete "getenv("match_declarative")" calls.
(enabled_exception_match): Delete "getenv("match_declarative")" calls.
* libgcobol.cc: Eliminate __gg__odo_violation.
gcc/testsuite/ChangeLog:
* cobol.dg/group1/simple-if.cob: Make explicitly >>SOURCE FREE
|
|
calculations.
This commit includes changes to exception handling, and changes to the
calculations for offsets and lengths when processing subscripted table entries
and variables with (from:length) reference modifications.
Exception handling in COBOL requires significant amounts of information to be
built at compile time and sent to libgcobol.so at run time. The changes here
reduce some problems caused by creating structures by the host that are
processed by the target, mainly by creating arrays of simple integers rather
than by turning a structure into a stream of bytes.
Significant changes to the logic of exception handling brings the run-time
performance more in line with the ISO specification.
The handling of COBOL variables that include tables defined with DEPENDING ON
clauses is subtly different when used as sending variables versus when they are
receiving variables. This commit folds the very similar refer_offset_source
and refer_offset_dest routines into a single refer_offset routine. It also
streamlines the refer_length_source and refer_length_dest routines by moving
common code into a static refer_length() routine, and having
refer_length_source() and refer_length_dest() each call refer_length() with a
a type flag.
Co-Authored by: James K. Lowden <jklowden@cobolworx.com>
Co-Authored by: Robert Dubner <rdubner@symas.com>
gcc/cobol/ChangeLog:
* cdf.y: Exceptions.
* except.cc (cbl_enabled_exception_t::dump): Likewise.
(cbl_enabled_exceptions_t::dump): Likewise.
(cbl_enabled_exceptions_t::status): Likewise.
(cbl_enabled_exceptions_t::encode): Likewise.
(cbl_enabled_exceptions_t::turn_on_off): Likewise.
(cbl_enabled_exceptions_t::match): Likewise.
(declarative_runtime_match): Likewise. Likewise.
* exceptg.h (struct cbl_exception_files_t): Likewise.
(class exception_turn_t): Likewise.
(apply_cdf_turn): Likewise.
* genapi.cc (treeplet_fill_source): Use refer_offset().
(function_handle_from_name): Likewise.
(parser_initialize_programs): Likewise.
(parser_statement_begin): Likewise.
(array_of_long_long): Exceptions.
(parser_compile_ecs): Exceptions.
(parser_compile_dcls): Exceptions.
(store_location_stuff): Exceptions.
(initialize_variable_internal): Use refer_offset().
(compare_binary_binary): Use refer_offset().
(cobol_compare): Use refer_offset().
(paragraph_label): Formatting.
(parser_goto): Use refer_offset().
(parser_perform_times): Likewise.
(internal_perform_through_times): Likewise.
(parser_enter_file): Exceptions.
(psa_FldLiteralN): Add comment.
(parser_accept): Use refer_offset().
(parser_accept_command_line): Likewise.
(parser_accept_command_line_count): Likewise.
(parser_accept_envar): Likewise.
(parser_set_envar): Likewise.
(parser_display_internal): Likewise.
(parser_initialize_table): Likewise.
(parser_sleep): Likewise.
(parser_allocate): Likewise.
(parser_free): Likewise.
(parser_division): Likewise.
(parser_relop_long): Likewise.
(parser_see_stop_run): Likewise.
(parser_classify): Likewise.
(parser_file_add): Include symbol_table_index in __gg__file_init().
(parser_file_open): Use refer_offset().
(parser_file_write): Move forward declaration of store_location_stuff().
(parser_file_start): Use refer_offset().
(parser_inspect_conv): Likewise:
(parser_intrinsic_numval_c): Likewise:
(parser_intrinsic_subst): Likewise:
(parser_intrinsic_call_1): Likewise:
(parser_intrinsic_call_2): Likewise:
(parser_intrinsic_call_3): Likewise:
(parser_intrinsic_call_4): Likewise:
(parser_sort): Likewise:
(parser_return_start): Exceptions.
(parser_unstring): Use refer_offset().
(create_and_call): Likewise.
(parser_set_pointers): Use refer_offset().
(parser_program_hierarchy): Comment.
(parser_set_handled): Exceptions; removed.
(parser_set_file_number): Exceptions; removed.
(stash_exceptions): Exceptions; removed.
(parser_exception_prepare): Exceptions; removed.
(parser_match_exception): Exceptions; eliminate blob.
(parser_check_fatal_exception): Exceptions.
(parser_push_exception): Create.
(parser_pop_exception): Create.
(mh_identical): Use refer_offset().
(mh_source_is_literalN): Likewise.
(mh_dest_is_float): Likewise.
(mh_numeric_display): Likewise.
(mh_little_endian): Likewise.
(mh_source_is_group): Likewise.
(move_helper): Likewise.
(binary_initial_from_float128): Formatting; change error message.
(initial_from_float128): Change name to "initial_from_initial"
(initial_from_initial): Add one byte to allocation for figconsts.
(parser_symbol_add): Use initial_from_initial().
(parser_symbol_add): Eliminate unneeded logic around actually_create...
* genapi.h: Exceptions.
* genmath.cc (fast_add): Use refer_offset().
(fast_subtract): Likewise.
(fast_multiply): Likewise.
(fast_divide): Likewise.
* genutil.cc: Exceptions; various global definitions.
(get_integer_value): Comment.
(get_data_offset_dest): Eliminate.
(get_data_offset_source): Rename to get_data_offset().
(get_data_offset): Use refer_offset().
(get_binary_value): Likewise; eliminate use of literal_decl_node.
(build_array_of_treeplets): Likewise.
(build_array_of_fourplets): Likewise.
(REFER_CHECK): Comment:
(refer_refmod_length): Use get_any_capacity(); use refer_offset;
set reflen to integer_one_node.
(refer_offset_dest): Change name to refer_offset.
(refer_offset): Use get_data_offset().
(refer_size_dest): Change name to refer_size().
(refer_size): Use get_any_capacity().
(refer_offset_source): Use refer_offset().
(refer_size_source): Likewise.
(qualified_data_source): Likewise.
(qualified_data_dest): Likewise.
(qualified_data_location): Likewise.
* genutil.h: Exceptions; changes to global declarations.
* lexio.cc (likely_nist_file): Added to detect NIST file format.
(cdftext::free_form_reference_format): Handle NIST file format.
* parse.y: (strip_trailing_zeroes): Added.
Changes for exceptions.
* parse_ante.h (parse_error_inc): Likewise.
(YYLLOC_DEFAULT): Likewise.
(static_cast): Likewise.
(is_cobol_word): Change to is_cobol_charset.
(is_cobol_charset): Refine allowed characters.
(require_numeric): Change to require integer.
(require_integer): Likewise.
(current_enabled_ecs): Exceptions.
(is_integer_literal): Change interpretation.
(procedure_division_ready): Exceptions.
(statement_epilog): Likewise.
(statement_begin): Likewise.
* show_parse.h: Changes to GCOBOL_SHOW handling.
* structs.cc: Add symbol_index to cblc_file_t structure.
* symbols.cc (field_str): Repair .initial handling in FldLiteralN.
* symbols.h (struct cbl_field_t): Eliminate literal_decl_node.
(current_enabled_ecs): Exceptions.
* util.cc (cbl_message): Add final newline to error message.
(ftoupper): Added.
(iso_cobol_word): Add list of ISO reserved words.
* util.h (ftoupper): Added.
libgcobol/ChangeLog:
* charmaps.cc: Add #include <vector>.
* common-defs.h (COMMON_DEFS_H_): Add #include <stdio.h>.
(enum cbl_file_mode_t): Add file_mode_any_e.
(enum file_stmt_t): Created.
(cbl_file_mode_str): Add case for file_mode_any_e.
(ec_cmp): Exceptions.
(struct cbl_enabled_exception_t): Likewise.
(struct cbl_declarative_t): Likewise.
(class cbl_enabled_exceptions_array_t): Likewise.
(class cbl_enabled_exceptions_t): Likewise.
(struct cbl_enabled_exceptions_array_t): Likewise.
(enabled_exception_match): Likewise.
* constants.cc: Add #include <vector>.
* exceptl.h (struct cbl_exception_t): Removed.
(struct cbl_declarative_t): Removed.
(class ec_status_t): Removed.
* gcobolio.h: Add symbol_table_index to cblc_file_t.
* gfileio.cc: Add #include <vector>
(establish_status): Comment.
(__io__file_init): Handle symbol_table_index.
(__io__file_delete): Set file->prior_op.
(__io__file_rewrite): Likewise.
(__io__file_read): Likewise.
(__io__file_open): Likewise.
(__io__file_close): Likewise.
* gmath.cc: Include #include <vector>.
* intrinsic.cc: Include #include <vector>.
* libgcobol.cc: Multiple modifications for exceptions.
* valconv.cc: #include <vector>.
|
|
The following patch changes some remaining __int128 uses in the FE
into FIXED_WIDE_INT(128), i.e. emulated 128-bit integral type.
The use of wide_int_to_tree directly from that rather than going through
build_int_cst_type means we don't throw away the upper 64 bits of the
values, so the emitting of constants needing full 128 bits can be greatly
simplied.
Plus all the #pragma GCC diagnostic ignored "-Wpedantic" spots aren't
needed, we don't use the _Float128/__int128 types directly in the FE
anymore.
Note, PR119241/PR119242 bugs are still not fully fixed, I think the
remaining problem is that several FE sources include
../../libgcobol/libgcobol.h and that header declares various APIs with
__int128 and _Float128 types, so trying to build a cross-compiler on a host
without __int128 and _Float128 will still fail miserably.
I believe none of those APIs are actually used by the FE, so the question is
what the FE needs from libgcobol.h and whether the rest could be wrapped
with #ifndef IN_GCC or #ifndef IN_GCC_FRONTEND or something similar
(those 2 macros are predefined when compiling the FE files).
2025-03-26 Jakub Jelinek <jakub@redhat.com>
PR cobol/119242
* genutil.h (get_power_of_ten): Remove #pragma GCC diagnostic
around declaration.
* genapi.cc (psa_FldLiteralN): Change type of value from
__int128 to FIXED_WIDE_INT(128). Remove #pragma GCC diagnostic
around the declaration. Use wi::min_precision to determine
minimum unsigned precision of the value. Use wi::neg_p instead
of value < 0 tests and wi::set_bit_in_zero<FIXED_WIDE_INT(128)>
to build sign bit. Handle field->data.capacity == 16 like
1, 2, 4 and 8, use wide_int_to_tree instead of build_int_cst.
(mh_source_is_literalN): Remove #pragma GCC diagnostic around
the definition.
(binary_initial_from_float128): Likewise.
* genutil.cc (get_power_of_ten): Remove #pragma GCC diagnostic
before the definition.
|
|
These changes switch _Float128 types to REAL_VALUE_TYPE in the front end.
Some __int128 variables and function return values are changed to
FIXED_WIDE_INT(128)
gcc/cobol
PR cobol/119241
* cdf.y: (cdfval_base_t::operator()): Return const.
* cdfval.h: (struct cdfval_base_t): Add const cdfval_base_t&
operator().
(struct cdfval_t): Add cdfval_t constructor. Change cdf_value
definitions.
* gcobolspec.cc (lang_specific_driver): Formatting fix.
* genapi.cc: Include fold-const.h and realmpfr.h.
(initialize_variable_internal): Use real_to_decimal instead of
strfromf128.
(get_binary_value_from_float): Use wide_int_to_tree instead of
build_int_cst_type.
(psa_FldLiteralN): Use fold_convert instead of strfromf128,
real_from_string and build_real.
(parser_display_internal): Rewritten to work on REAL_VALUE_TYPE
rather than _Float128.
(mh_source_is_literalN): Use FIXED_WIDE_INT(128) rather than
__int128, wide_int_to_tree rather than build_int_cst_type,
fold_convert rather than build_string_literal.
(real_powi10): New function.
(binary_initial_from_float128): Change type of last argument from
_Float128 to REAL_VALUE_TYPE, process it using real.cc and mpfr
APIs.
(digits_from_float128): Likewise.
(initial_from_float128): Make static. Remove value argument, add
local REAL_VALUE_TYPE value variable instead, process it using
real.cc and native_encode_expr APIs.
(parser_symbol_add): Adjust initial_from_float128 caller.
* genapi.h (initial_from_float128): Remove declaration.
* genutil.cc (get_power_of_ten): Change return type from __int128
to FIXED_WIDE_INT(128), ditto for retval type, change type of pos
from __int128 to unsigned long long.
(scale_by_power_of_ten_N): Use wide_int_to_tree instead of
build_int_cst_type. Use FIXED_WIDE_INT(128) instead of __int128
as power_of_ten variable type.
(copy_little_endian_into_place): Likewise.
* genutil.h (get_power_of_ten): Change return type from __int128
to FIXED_WIDE_INT(128).
* parse.y (%union): Change type of float128 from _Float128 to
REAL_VALUE_TYPE.
(string_of): Change argument type from _Float128 to
const REAL_VALUE_TYPE &, use real_to_decimal rather than
strfromf128. Add another overload with tree argument type.
(field: cdf): Use real_zerop rather than comparison against 0.0.
(occurs_clause, const_value): Use real_to_integer.
(value78): Use build_real and real_to_integer.
(data_descr1): Use real_to_integer.
(count): Use real_to_integer, real_from_integer and real_identical
instead of direct comparison.
(value_clause): Use real_from_string3 instead of num_str2i. Use
real_identical instead of direct comparison. Use build_real.
(allocate): Use real_isneg and real_iszero instead of <= 0 comparison.
(move_tgt): Use real_to_integer, real_value_truncate,
real_from_integer and real_identical instead of comparison of casts.
(cce_expr): Use real_arithmetic and real_convert or real_value_negate
instead of direct arithmetics on _Float128.
(cce_factor): Use real_from_string3 instead of numstr2i.
(literal_refmod_valid): Use real_to_integer.
* symbols.cc (symbol_table_t::registers_t::registers_t): Formatting
fix.
(ERROR_FIELD): Likewise.
(extend_66_capacity): Likewise.
(cbl_occurs_t::subscript_ok): Use real_to_integer, real_from_integer
and real_identical.
* symbols.h (cbl_field_data_t::etc_t::value): Change type from
_Float128 to tree.
(cbl_field_data_t::etc_t::etc_t): Adjust defaulted argument value.
(cbl_field_data_t::cbl_field_data_t): Formatting fix. Use etc()
rather than etc(0).
(cbl_field_data_t::value_of): Change return type from _Float128 to
tree.
(cbl_field_data_t::operator=): Change return and argument type from
_Float128 to tree.
(cbl_field_data_t::valify): Use real_from_string, real_value_truncate
and build_real.
(cbl_field_t::same_as): Use build_zero_cst instead of _Float128(0.0).
gcc/testsuite
* cobol.dg/literal1.cob: New testcase.
* cobol.dg/output1.cob: Likewise
Co-authored-by: Richard Biener <rguenth@suse.de>
Co-authored-by: Jakub Jelinek <jakub@redhat.com>
Co-authored-by: James K. Lowden <jklowden@cobolworx.com>
Co-authored-by: Robert Dubner <rdubher@symas.com>
|
|
gcc/cobol
* cdf.y: Make compatible with C++14.
* copybook.h: Likewise.
* dts.h: Likewise.
* except.cc: Likewise.
* genapi.cc: Likewise.
* genutil.cc: Likewise.
* genutil.h: Likewise.
* lexio.cc: Likewise.
* parse.y: Likewise.
* parse_ante.h: Likewise.
* show_parse.h: Likewise.
* symbols.cc: Likewise.
* symbols.h: Likewise.
* util.cc: Likewise.
|
|
gcc/cobol/
* LICENSE: New file.
* Make-lang.in: New file.
* config-lang.in: New file.
* lang.opt: New file.
* lang.opt.urls: New file.
* cbldiag.h: New file.
* cdfval.h: New file.
* cobol-system.h: New file.
* copybook.h: New file.
* dts.h: New file.
* exceptg.h: New file.
* gengen.h: New file.
* genmath.h: New file.
* genutil.h: New file.
* inspect.h: New file.
* lang-specs.h: New file.
* lexio.h: New file.
* parse_ante.h: New file.
* parse_util.h: New file.
* scan_ante.h: New file.
* scan_post.h: New file.
* show_parse.h: New file.
* structs.h: New file.
* symbols.h: New file.
* token_names.h: New file.
* util.h: New file.
* cdf-copy.cc: New file.
* lexio.cc: New file.
* scan.l: New file.
* parse.y: New file.
* genapi.cc: New file.
* genapi.h: New file.
* gengen.cc: New file.
* genmath.cc: New file.
* genutil.cc: New file.
* cdf.y: New file.
* cobol1.cc: New file.
* convert.cc: New file.
* except.cc: New file.
* gcobolspec.cc: New file.
* structs.cc: New file.
* symbols.cc: New file.
* symfind.cc: New file.
* util.cc: New file.
* gcobc: New file.
* gcobol.1: New file.
* gcobol.3: New file.
* help.gen: New file.
* udf/stored-char-length.cbl: New file.
|