diff --git a/gcc/cobol/cdf.y b/gcc/cobol/cdf.y index 057b4553c3c703e0bd12950edf5c337e43e6491c..b6a9418568acb95f44701cf9b7720964dec10408 100644 --- a/gcc/cobol/cdf.y +++ b/gcc/cobol/cdf.y @@ -31,6 +31,8 @@ #include "copybook.h" #include "ec.h" #include "symbols.h" +#include "exceptc.h" +#include "exceptg.h" #include <ctype.h> #include <fcntl.h> diff --git a/gcc/cobol/except.cc b/gcc/cobol/except.cc index ea281a1f0510a400dac7b521bfa79f046eb10e7f..f8c57d18675e788262eb257ab86a01d5c6473486 100644 --- a/gcc/cobol/except.cc +++ b/gcc/cobol/except.cc @@ -47,11 +47,11 @@ static const ec_descr_t * ec_type_descr( ec_type_t type ) { - auto p = std::find( exception_table, exception_table_end, type ); - if( p == exception_table_end ) { + auto p = std::find( __gg__exception_table, __gg__exception_table_end, type ); + if( p == __gg__exception_table_end ) { warnx("no such exception: 0x%04x", type); } - assert( p != exception_table_end ); + assert( p != __gg__exception_table_end ); return p; } @@ -69,11 +69,11 @@ ec_type_disposition( ec_type_t type ) { ec_type_t ec_type_of( const cbl_name_t name ) { - auto p = std::find_if( exception_table, exception_table_end, + auto p = std::find_if( __gg__exception_table, __gg__exception_table_end, [name]( const ec_descr_t& descr ) { return 0 == strcasecmp(name, descr.name); } ); - return p == exception_table_end? ec_none_e : p->type; + return p == __gg__exception_table_end? ec_none_e : p->type; } static size_t diff --git a/gcc/cobol/exceptg.h b/gcc/cobol/exceptg.h index 708d692e5083d238cfd533ed40c54b41efd1c200..c706b2f1d3c75d00818fa35d1d332671493654e3 100644 --- a/gcc/cobol/exceptg.h +++ b/gcc/cobol/exceptg.h @@ -33,4 +33,17 @@ extern void declarative_runtime_match(cbl_field_t *declaratives, cbl_label_t *lave ); +// >>TURN arguments +struct cbl_exception_files_t { + ec_type_t type; + size_t nfile; + size_t *files; + bool operator<( const cbl_exception_files_t& that ) { + return type < that.type; + } +}; + +size_t symbol_declaratives_add( size_t program, + const std::list<cbl_declarative_t>& dcls ); + #endif diff --git a/gcc/cobol/parse_ante.h b/gcc/cobol/parse_ante.h index feaf5a82cf2e88aa6dd10f601e9b592d2d981c5c..1668502430da22dd7c123f439f955b9f65baa786 100644 --- a/gcc/cobol/parse_ante.h +++ b/gcc/cobol/parse_ante.h @@ -46,6 +46,7 @@ #include <stack> #include <string> +#include "exceptc.h" #include "exceptg.h" #define MAXLENGTH_FORMATTED_DATE 10 diff --git a/libgcobol/common-defs.h b/libgcobol/common-defs.h index 088b51342b3ee798f9dd14f54d07ab69c8f48ab7..cfe62f5858deb35855a301fa245f0d794492c77c 100644 --- a/libgcobol/common-defs.h +++ b/libgcobol/common-defs.h @@ -445,108 +445,6 @@ const char * ec_type_str( ec_type_t type ); ec_disposition_t ec_type_disposition( ec_type_t type ); ec_type_t ec_type_of( const cbl_name_t name ); -// >>TURN arguments -struct cbl_exception_files_t { - ec_type_t type; - size_t nfile; - size_t *files; - bool operator<( const cbl_exception_files_t& that ) { - return type < that.type; - } -}; - -// SymException -struct cbl_exception_t { - size_t program, file; - ec_type_t type; - cbl_file_mode_t mode; -}; - -struct cbl_declarative_t { - enum { files_max = 16 }; - size_t section; // implies program - bool global; - ec_type_t type; - uint32_t nfile, files[files_max]; - cbl_file_mode_t mode; - - cbl_declarative_t( cbl_file_mode_t mode = file_mode_none_e ) - : section(0), global(false), type(ec_none_e) - , nfile(0) - , mode(mode) - { - std::fill(files, files + COUNT_OF(files), 0); - } - cbl_declarative_t( ec_type_t type ) - : section(0), global(false), type(type) - , nfile(0) - , mode(file_mode_none_e) - { - std::fill(files, files + COUNT_OF(files), 0); - } - - cbl_declarative_t( size_t section, ec_type_t type, - const std::list<size_t>& files, - cbl_file_mode_t mode, bool global = false ) - : section(section), global(global), type(type) - , nfile(files.size()) - , mode(mode) - { - assert( files.size() <= COUNT_OF(this->files) ); - std::fill(this->files, this->files + COUNT_OF(this->files), 0); - if( nfile > 0 ) { - std::copy( files.begin(), files.end(), this->files ); - } - } - cbl_declarative_t( const cbl_declarative_t& that ) - : section(that.section), global(that.global), type(that.type) - , nfile(that.nfile) - , mode(that.mode) - { - std::fill(files, files + COUNT_OF(files), 0); - if( nfile > 0 ) { - std::copy( that.files, that.files + nfile, this->files ); - } - } - - /* - * Sort file names before file modes, and file modes before non-IO. - */ - bool operator<( const cbl_declarative_t& that ) const { - // file name declaratives first, in section order - if( nfile != 0 ) { - if( that.nfile != 0 ) return section < that.section; - return true; - } - // file mode declaratives between file name declaratives and non-IO - if( mode != file_mode_none_e ) { - if( that.nfile != 0 ) return false; - if( that.mode == file_mode_none_e ) return true; - return section < that.section; - } - // all others by section, after names and modes - if( that.nfile != 0 ) return false; - if( that.mode != file_mode_none_e ) return false; - return section < that.section; - } - - // TRUE if there are no files to match, or the provided file is in the list. - bool match_file( size_t file ) const { - static const auto pend = files + nfile; - - return nfile == 0 || pend != std::find(files, files + nfile, file); - } - - // USE Format 1 names a file mode, or at least one file, and not an EC. - bool is_format_1() const { - assert(type != ec_none_e || nfile > 0 || mode != file_mode_none_e); - return nfile > 0 || mode != file_mode_none_e; - } -}; - -size_t symbol_declaratives_add( size_t program, - const std::list<cbl_declarative_t>& dcls ); - static inline bool ec_cmp( ec_type_t raised, ec_type_t mask ) { diff --git a/libgcobol/exceptc.h b/libgcobol/exceptc.h index 236edaeef2ab96387551c79837a5446f69efa3ec..2f0cb50fd6051c5f236fc837f62088f4fd0e3219 100644 --- a/libgcobol/exceptc.h +++ b/libgcobol/exceptc.h @@ -29,8 +29,8 @@ * OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. */ -#ifndef _CBL_EXCEPT_H_ -#define _CBL_EXCEPT_H_ +#ifndef _CBL_EXCEPTC_H_ +#define _CBL_EXCEPTC_H_ static const ec_type_t simon_says_important[] = { ec_argument_function_e, @@ -48,363 +48,11 @@ static const ec_type_t simon_says_important[] = { ec_program_arg_mismatch_e, }; -ec_descr_t exception_table[] = { - { ec_all_e, ec_category_none_e, - "EC-ALL", "Any exception" }, - - { ec_argument_e, ec_category_none_e, - "EC-ARGUMENT", "Argument error" }, - { ec_argument_function_e, ec_category_fatal_e, - "EC-ARGUMENT-FUNCTION", "Function argument error" }, - { ec_argument_imp_e, uc_category_implementor_e, - "EC-ARGUMENT-IMP", "Implementor-defined argument error" }, - - { ec_argument_imp_command_e, uc_category_implementor_e, - "EC-ARGUMENT-IMP-COMMAND", "COMMAND-LINE Subscript out of bounds" }, - { ec_argument_imp_environment_e, uc_category_implementor_e, - "EC-ARGUMENT-IMP-ENVIRONMENT", "Envrionment Variable is not defined" }, - - { ec_bound_e, ec_category_none_e, - "EC-BOUND", "Boundary violation" }, - { ec_bound_func_ret_value_e, uc_category_nonfatal_e, - "EC-BOUND-FUNC-RET-VALUE", - "Intrinsic function output does not fit in returned value item" }, - { ec_bound_imp_e, uc_category_implementor_e, - "EC-BOUND-IMP", "Implementor-defined boundary violation" }, - { ec_bound_odo_e, ec_category_fatal_e, - "EC-BOUND-ODO", "OCCURS ... DEPENDING ON data item out of bounds" }, - { ec_bound_overflow_e, uc_category_nonfatal_e, - "EC-BOUND-OVERFLOW", - "Current capacity of dynamic-capacity table greater than expected value" }, - { ec_bound_ptr_e, uc_category_fatal_e, - "EC-BOUND-PTR", "Data-pointer contains an address that is out of bounds" }, - { ec_bound_ref_mod_e, ec_category_fatal_e, - "EC-BOUND-REF-MOD", "Reference modifier out of bounds" }, - { ec_bound_set_e, uc_category_nonfatal_e, - "EC-BOUND-SET", "Invalid use of SET to set capacity of " - "dynamic-capacity table above specified maximum" }, - { ec_bound_subscript_e, ec_category_fatal_e, - "EC-BOUND-SUBSCRIPT", "Subscript out of bounds" }, - { ec_bound_table_limit_e, uc_category_fatal_e, - "EC-BOUND-TABLE-LIMIT", - "Capacity of dynamic-capacity table would exceed implementor's maximum" }, - - { ec_data_e, ec_category_none_e, - "EC-DATA", "Data exception" }, - { ec_data_conversion_e, uc_category_nonfatal_e, - "EC-DATA-CONVERSION", - "Conversion failed because of incomplete character correspondence" }, - { ec_data_imp_e, uc_category_implementor_e, - "EC-DATA-IMP", "Implementor-defined data exception" }, - { ec_data_incompatible_e, uc_category_fatal_e, - "EC-DATA-INCOMPATIBLE", "Incompatible data exception" }, - { ec_data_not_finite_e, uc_category_fatal_e, - "EC-DATA-NOT-FINITE", - "Attempt to use a data item described with a standard floating-point usage " - "when its contents are either a NaN or a representation of infinity" }, - { ec_data_overflow_e, uc_category_fatal_e, - "EC-DATA-OVERFLOW", - "Exponent overflow during MOVE to a receiving data item described with a " - "standard floating-point usage" }, - { ec_data_ptr_null_e, uc_category_fatal_e, - "EC-DATA-PTR-NULL", - "Based item data-pointer is set to NULL when referenced" }, - - { ec_external_data_mismatch_e, uc_category_fatal_e, - "EC-EXTERNAL-DATA-MISMATCH", - "File referencing control item conflict because the linage, " - "file status or relative key references are not to the same item " }, - { ec_external_file_mismatch_e, uc_category_fatal_e, - "EC-EXTERNAL-FILE-MISMATCH", - "File control SELECT statements are not compatible" }, - { ec_external_format_conflict_e, uc_category_fatal_e, - "EC-EXTERNAL-FORMAT-CONFLICT", - "Data definitions definitions do not conform" }, - - { ec_flow_e, ec_category_none_e, - "EC-FLOW", "Execution control flow violation" }, - { ec_flow_global_exit_e, uc_category_fatal_e, - "EC-FLOW-GLOBAL-EXIT", "EXIT PROGRAM in a global Declarative" }, - { ec_flow_global_goback_e, uc_category_fatal_e, - "EC-FLOW-GLOBAL-GOBACK", "GOBACK in a global declarative" }, - { ec_flow_imp_e, uc_category_implementor_e, - "EC-FLOW-IMP", "Implementor-defined control flow violation" }, - { ec_flow_release_e, uc_category_fatal_e, - "EC-FLOW-RELEASE", "RELEASE not in range of SORT" }, - { ec_flow_report_e, uc_category_fatal_e, - "EC-FLOW-REPORT", - "GENERATE, INITIATE, or TERMINATE during USE BEFORE REPORTING declarative" }, - { ec_flow_return_e, uc_category_fatal_e, - "EC-FLOW-RETURN", "RETURN not in range of MERGE or SORT" }, - { ec_flow_search_e, uc_category_fatal_e, - "EC-FLOW-SEARCH", - "Invalid use of SET to change capacity of dynamic- capacity table during " - "SEARCH of same table" }, - { ec_flow_use_e, uc_category_fatal_e, - "EC-FLOW-USE", "A USE statement caused another to be executed" }, - - { ec_function_e, ec_category_none_e, - "EC-FUNCTION", "Function exception" }, - { ec_function_not_found_e, uc_category_fatal_e, - "EC-FUNCTION-NOT-FOUND", - "Function not found or function pointer does not point to a function" }, - { ec_function_ptr_invalid_e, uc_category_fatal_e, - "EC-FUNCTION-PTR-INVALID", "Signature mismatch" }, - { ec_function_ptr_null_e, uc_category_fatal_e, - "EC-FUNCTION-PTR-NULL", - "Function pointer used in calling a function is NULL" }, - - { ec_io_e, ec_category_none_e, - "EC-IO", "Input-output exception" }, - { ec_io_at_end_e, uc_category_nonfatal_e, - "EC-I-O-AT-END", "I-O status 1x" }, - { ec_io_eop_e, uc_category_nonfatal_e, - "EC-I-O-EOP", "An end of page condition occurred" }, - { ec_io_eop_overflow_e, uc_category_nonfatal_e, - "EC-I-O-EOP-OVERFLOW", "A page overflow condition occurred" }, - { ec_io_file_sharing_e, uc_category_nonfatal_e, - "EC-I-O-FILE-SHARING", "I-O status 6x" }, - { ec_io_imp_e, uc_category_implementor_e, - "EC-I-O-IMP", "I-O status 9x" }, - { ec_io_invalid_key_e, uc_category_nonfatal_e, - "EC-I-O-INVALID-KEY", "I-O status 2x" }, - { ec_io_linage_e, uc_category_fatal_e, - "EC-I-O-LINAGE", - "The value of a data item referenced in the LINAGE clause is not within " - "the required range" }, - { ec_io_logic_error_e, uc_category_fatal_e, - "EC-I-O-LOGIC-ERROR", "I-O status 4x" }, - { ec_io_permanent_error_e, uc_category_fatal_e, - "EC-I-O-PERMANENT-ERROR", "I-O status 3x" }, - { ec_io_record_operation_e, uc_category_nonfatal_e, - "EC-I-O-RECORD-OPERATION", "I-O status 5x" }, - - { ec_imp_e, ec_category_none_e, - "EC-IMP", "Implementor-defined exception condition" }, - - { ec_imp_suffix_e, ec_category_none_e, - "EC-IMP-SUFFIX", "Imp" }, - - { ec_locale_e, ec_category_none_e, - "EC-LOCALE", "Any locale related exception" }, - { ec_locale_imp_e, uc_category_implementor_e, - "EC-LOCALE-IMP", "Implementor-defined locale related exception" }, - { ec_locale_incompatible_e, uc_category_fatal_e, - "EC-LOCALE-INCOMPATIBLE", - "The referenced locale does not specify the expected characters in " - "LC_COLLATE" }, - { ec_locale_invalid_e, uc_category_fatal_e, - "EC-LOCALE-INVALID", "Locale content is invalid or incomplete" }, - { ec_locale_invalid_ptr_e, uc_category_fatal_e, - "EC-LOCALE-INVALID-PTR", "Pointer does not reference a saved locale" }, - { ec_locale_missing_e, uc_category_fatal_e, - "EC-LOCALE-MISSING", "The specified locale is not available" }, - { ec_locale_size_e, uc_category_fatal_e, - "EC-LOCALE-SIZE", "Digits were truncated in locale editing" }, - - { ec_oo_e, ec_category_none_e, - "EC-OO", "Any predefined OO related exception" }, - { ec_oo_arg_omitted_e, uc_category_fatal_e, - "EC-OO-ARG-OMITTED", "Reference to an omitted argument" }, - { ec_oo_conformance_e, uc_category_fatal_e, - "EC-OO-CONFORMANCE", "Failure for an object-view" }, - { ec_oo_exception_e, uc_category_fatal_e, - "EC-OO-EXCEPTION", "An exception object was not handled" }, - { ec_oo_imp_e, uc_category_implementor_e, - "EC-OO-IMP", "Implementor-defined OO exception" }, - { ec_oo_method_e, uc_category_fatal_e, - "EC-OO-METHOD", "Requested method is not available" }, - { ec_oo_null_e, uc_category_fatal_e, - "EC-OO-NULL", - "Method invocation was attempted with a null object reference" }, - { ec_oo_resource_e, uc_category_fatal_e, - "EC-OO-RESOURCE", "Insufficient system resources to create the object" }, - { ec_oo_universal_e, uc_category_fatal_e, - "EC-OO-UNIVERSAL", "A runtime type check failed" }, - - { ec_order_e, ec_category_none_e, - "EC-ORDER", "Ordering exception" }, - { ec_order_imp_e, uc_category_implementor_e, - "EC-ORDER-IMP", "Implementor-defined ordering exception" }, - { ec_order_not_supported_e, uc_category_fatal_e, - "EC-ORDER-NOT-SUPPORTED", - "Cultural ordering table or ordering level specified for " - "STANDARD-COMPARE function not supported" }, - - { ec_overflow_e, ec_category_none_e, - "EC-OVERFLOW", "Overflow condition" }, - { ec_overflow_imp_e, uc_category_implementor_e, - "EC-OVERFLOW-IMP", "Implementor-defined overflow condition" }, - { ec_overflow_string_e, uc_category_nonfatal_e, - "EC-OVERFLOW-STRING", "STRING overflow condition" }, - { ec_overflow_unstring_e, uc_category_nonfatal_e, - "EC-OVERFLOW-UNSTRING", "UNSTRING overflow condition" }, - - { ec_program_e, ec_category_none_e, - "EC-PROGRAM", "Inter-program communication exception" }, - { ec_program_arg_mismatch_e, uc_category_fatal_e, - "EC-PROGRAM-ARG-MISMATCH", "Parameter mismatch" }, - { ec_program_arg_omitted_e, uc_category_fatal_e, - "EC-PROGRAM-ARG-OMITTED", "A reference to an omitted argument" }, - { ec_program_cancel_active_e, uc_category_fatal_e, - "EC-PROGRAM-CANCEL-ACTIVE", "Canceled program active" }, - { ec_program_imp_e, uc_category_implementor_e, - "EC-PROGRAM-IMP", - "Implementor-defined inter-program communication exception" }, - { ec_program_not_found_e, uc_category_fatal_e, - "EC-PROGRAM-NOT-FOUND", "Called program not found" }, - { ec_program_ptr_null_e, uc_category_fatal_e, - "EC-PROGRAM-PTR-NULL", "Program-pointer used in CALL is set to NULL" }, - { ec_program_recursive_call_e, uc_category_fatal_e, - "EC-PROGRAM-RECURSIVE-CALL", "Called program active" }, - { ec_program_resources_e, uc_category_fatal_e, - "EC-PROGRAM-RESOURCES", "Resources not available for called program" }, - - { ec_raising_e, ec_category_none_e, - "EC-RAISING", "EXIT ... RAISING or GOBACK RAISING exception" }, - { ec_raising_imp_e, uc_category_implementor_e, - "EC-RAISING-IMP", - "Implementor-defined EXIT ... RAISING or GOBACK RAISING exception" }, - { ec_raising_not_specified_e, uc_category_fatal_e, - "EC-RAISING-NOT-SPECIFIED", - "EXIT ... RAISING or GOBACK RAISING an EC-USER exception condition not " - "specified in RAISING phrase of procedure division header" }, - - { ec_range_e, ec_category_none_e, - "EC-RANGE", "Range exception" }, - { ec_range_imp_e, uc_category_implementor_e, - "EC-RANGE-IMP", "Implementor-defined range exception" }, - { ec_range_index_e, uc_category_fatal_e, - "EC-RANGE-INDEX", - "Index set outside the range of values allowed by the implementor" }, - { ec_range_inspect_size_e, uc_category_fatal_e, - "EC-RANGE-INSPECT-SIZE", "Size of replace items in INSPECT differs" }, - { ec_range_invalid_e, uc_category_nonfatal_e, - "EC-RANGE-INVALID", - "Starting value of THROUGH range greater than ending value" }, - { ec_range_perform_varying_e, uc_category_fatal_e, - "EC-RANGE-PERFORM-VARYING", - "Setting of varied item in PERFORM is negative" }, - { ec_range_ptr_e, uc_category_fatal_e, - "EC-RANGE-PTR", "Pointer SET UP or DOWN is outside range" }, - { ec_range_search_index_e, uc_category_nonfatal_e, - "EC-RANGE-SEARCH-INDEX", - "No table element found in SEARCH because initial index out of range" }, - { ec_range_search_no_match_e, uc_category_nonfatal_e, - "EC-RANGE-SEARCH-NO-MATCH", - "No table element found in SEARCH because no element matched criteria" }, - - { ec_report_e, ec_category_none_e, - "EC-REPORT", "Report writer exception" }, - { ec_report_active_e, uc_category_fatal_e, - "EC-REPORT-ACTIVE", "INITIATE on an active report" }, - { ec_report_column_overlap_e, uc_category_nonfatal_e, - "EC-REPORT-COLUMN-OVERLAP", "Overlapping report items" }, - { ec_report_file_mode_e, uc_category_fatal_e, - "EC-REPORT-FILE-MODE", - "An INITIATE statement was executed for a file connector that was not " - "open in the extend or output mode" }, - { ec_report_imp_e, uc_category_implementor_e, - "EC-REPORT-IMP", "Implementor-defined report writer exception" }, - { ec_report_inactive_e, uc_category_fatal_e, - "EC-REPORT-INACTIVE", "GENERATE or TERMINATE on an inactive report" }, - { ec_report_line_overlap_e, uc_category_nonfatal_e, - "EC-REPORT-LINE-OVERLAP", "Overlapping report lines" }, - { ec_report_not_terminated_e, uc_category_nonfatal_e, - "EC-REPORT-NOT-TERMINATED", "Report file closed with active report" }, - { ec_report_page_limit_e, uc_category_nonfatal_e, - "EC-REPORT-PAGE-LIMIT", "Vertical page limit exceeded" }, - { ec_report_page_width_e, uc_category_nonfatal_e, - "EC-REPORT-PAGE-WIDTH", "Page width exceeded" }, - { ec_report_sum_size_e, uc_category_fatal_e, - "EC-REPORT-SUM-SIZE", "Overflow of sum counter" }, - { ec_report_varying_e, uc_category_fatal_e, - "EC-REPORT-VARYING", "VARYING clause expression noninteger" }, - - { ec_screen_e, ec_category_none_e, - "EC-SCREEN", "Screen handling exception" }, - { ec_screen_field_overlap_e, uc_category_nonfatal_e, - "EC-SCREEN-FIELD-OVERLAP", "Screen fields overlap" }, - { ec_screen_imp_e, uc_category_implementor_e, - "EC-SCREEN-IMP", "Implementor-defined screen handling exception" }, - { ec_screen_item_truncated_e, uc_category_nonfatal_e, - "EC-SCREEN-ITEM-TRUNCATED", "Screen field too long for line" }, - { ec_screen_line_number_e, uc_category_nonfatal_e, - "EC-SCREEN-LINE-NUMBER", - "Screen item line number exceeds terminal size" }, - { ec_screen_starting_column_e, uc_category_nonfatal_e, - "EC-SCREEN-STARTING-COLUMN", - "Screen item starting column exceeds line size" }, - - { ec_size_e, ec_category_none_e, - "EC-SIZE", "Size error exception" }, - { ec_size_address_e, uc_category_fatal_e, - "EC-SIZE-ADDRESS", "Invalid pointer arithmetic" }, - { ec_size_exponentiation_e, ec_category_fatal_e, - "EC-SIZE-EXPONENTIATION", "Exponentiation rules violated" }, - { ec_size_imp_e, uc_category_implementor_e, - "EC-SIZE-IMP", "Implementor-defined size error exception" }, - { ec_size_overflow_e, ec_category_fatal_e, - "EC-SIZE-OVERFLOW", "Arithmetic overflow in calculation" }, - { ec_size_truncation_e, ec_category_fatal_e, - "EC-SIZE-TRUNCATION", "Significant digits truncated in store" }, - { ec_size_underflow_e, ec_category_fatal_e, - "EC-SIZE-UNDERFLOW", "Floating-point underflow" }, - { ec_size_zero_divide_e, ec_category_fatal_e, - "EC-SIZE-ZERO-DIVIDE", "Division by zero" }, - - { ec_sort_merge_e, ec_category_none_e, - "EC-SORT-MERGE", "SORT or MERGE exception" }, - { ec_sort_merge_active_e, uc_category_fatal_e, - "EC-SORT-MERGE-ACTIVE", - "File SORT or MERGE executed when one is already active" }, - { ec_sort_merge_file_open_e, ec_category_fatal_e, - "EC-SORT-MERGE-FILE-OPEN", - "A USING or GIVING file is open upon execution of a SORT or MERGE" }, - { ec_sort_merge_imp_e, uc_category_implementor_e, - "EC-SORT-MERGE-IMP", - "Implementor-defined SORT or MERGE exception" }, - { ec_sort_merge_release_e, uc_category_fatal_e, - "EC-SORT-MERGE-RELEASE", "RELEASE record too long or too short" }, - { ec_sort_merge_return_e, uc_category_fatal_e, - "EC-SORT-MERGE-RETURN", "RETURN executed when at end condition exists" }, - { ec_sort_merge_sequence_e, uc_category_fatal_e, - "EC-SORT-MERGE-SEQUENCE", "Sequence error on MERGE USING file" }, - - { ec_storage_e, ec_category_none_e, - "EC-STORAGE", "Storage allocation exception" }, - { ec_storage_imp_e, uc_category_implementor_e, - "EC-STORAGE-IMP", "Implementor-defined storage allocation exception" }, - { ec_storage_not_alloc_e, uc_category_nonfatal_e, - "EC-STORAGE-NOT-ALLOC", - "The data-pointer specified in a FREE statement does not identify " - "currently allocated storage" }, - { ec_storage_not_avail_e, uc_category_nonfatal_e, - "EC-STORAGE-NOT-AVAIL", - "The amount of storage requested by an ALLOCATE statement " - "is not available"}, - { ec_user_e, ec_category_none_e, - "EC-USER", "User-defined exception condition" }, - { ec_user_suffix_e, uc_category_nonfatal_e, - "EC-USER-SUFFIX", "Level-3 user-defined exception condition" }, - - { ec_validate_e, ec_category_none_e, - "EC-VALIDATE", "VALIDATE exception" }, - { ec_validate_content_e, uc_category_nonfatal_e, - "EC-VALIDATE-CONTENT", "VALIDATE content error" }, - { ec_validate_format_e, uc_category_nonfatal_e, - "EC-VALIDATE-FORMAT", "VALIDATE format error" }, - { ec_validate_imp_e, uc_category_implementor_e, - "EC-VALIDATE-IMP", "Implementor-defined VALIDATE exception" }, - { ec_validate_relation_e, uc_category_nonfatal_e, - "EC-VALIDATE-RELATION", "VALIDATE relation error" }, - { ec_validate_varying_e, uc_category_fatal_e, - "EC-VALIDATE-VARYING", "VARYING clause expression noninteger" }, -} ; -static const auto exception_table_end = exception_table + COUNT_OF(exception_table); +extern ec_descr_t *__gg__exception_table; +extern ec_descr_t *__gg__exception_table_end; /* Inventory of exceptions: - In except.hc::exception_table, unimplemented ECs have a uc_ disposition. + In except.hc::__gg__exception_table, unimplemented ECs have a uc_ disposition. ec_function_argument_e ACOS ANNUITY @@ -438,4 +86,95 @@ static const auto exception_table_end = exception_table + COUNT_OF(exception_tab ec_size_exponentiation */ + +// SymException +struct cbl_exception_t { + size_t program, file; + ec_type_t type; + cbl_file_mode_t mode; +}; + + +struct cbl_declarative_t { + enum { files_max = 16 }; + size_t section; // implies program + bool global; + ec_type_t type; + uint32_t nfile, files[files_max]; + cbl_file_mode_t mode; + + cbl_declarative_t( cbl_file_mode_t mode = file_mode_none_e ) + : section(0), global(false), type(ec_none_e) + , nfile(0) + , mode(mode) + { + std::fill(files, files + COUNT_OF(files), 0); + } + cbl_declarative_t( ec_type_t type ) + : section(0), global(false), type(type) + , nfile(0) + , mode(file_mode_none_e) + { + std::fill(files, files + COUNT_OF(files), 0); + } + + cbl_declarative_t( size_t section, ec_type_t type, + const std::list<size_t>& files, + cbl_file_mode_t mode, bool global = false ) + : section(section), global(global), type(type) + , nfile(files.size()) + , mode(mode) + { + assert( files.size() <= COUNT_OF(this->files) ); + std::fill(this->files, this->files + COUNT_OF(this->files), 0); + if( nfile > 0 ) { + std::copy( files.begin(), files.end(), this->files ); + } + } + cbl_declarative_t( const cbl_declarative_t& that ) + : section(that.section), global(that.global), type(that.type) + , nfile(that.nfile) + , mode(that.mode) + { + std::fill(files, files + COUNT_OF(files), 0); + if( nfile > 0 ) { + std::copy( that.files, that.files + nfile, this->files ); + } + } + + /* + * Sort file names before file modes, and file modes before non-IO. + */ + bool operator<( const cbl_declarative_t& that ) const { + // file name declaratives first, in section order + if( nfile != 0 ) { + if( that.nfile != 0 ) return section < that.section; + return true; + } + // file mode declaratives between file name declaratives and non-IO + if( mode != file_mode_none_e ) { + if( that.nfile != 0 ) return false; + if( that.mode == file_mode_none_e ) return true; + return section < that.section; + } + // all others by section, after names and modes + if( that.nfile != 0 ) return false; + if( that.mode != file_mode_none_e ) return false; + return section < that.section; + } + + // TRUE if there are no files to match, or the provided file is in the list. + bool match_file( size_t file ) const { + static const auto pend = files + nfile; + + return nfile == 0 || pend != std::find(files, files + nfile, file); + } + + // USE Format 1 names a file mode, or at least one file, and not an EC. + bool is_format_1() const { + assert(type != ec_none_e || nfile > 0 || mode != file_mode_none_e); + return nfile > 0 || mode != file_mode_none_e; + } +}; + #endif diff --git a/libgcobol/libgcobol.cc b/libgcobol/libgcobol.cc index 85b896ca6166116e2b5cae238d6d6e9638893971..821e3216eea487988c66cd16f89da063a5a5b55f 100644 --- a/libgcobol/libgcobol.cc +++ b/libgcobol/libgcobol.cc @@ -176,8 +176,8 @@ static ec_status_t ec_status; static const ec_descr_t * local_ec_type_descr( ec_type_t type ) { - auto p = std::find( exception_table, exception_table_end, type ); - assert( p != exception_table_end ); + auto p = std::find( __gg__exception_table, __gg__exception_table_end, type ); + assert( p != __gg__exception_table_end ); return p; } @@ -10818,11 +10818,11 @@ static void default_exception_handler( ec_type_t ec) { if( ec != ec_none_e ) { - auto p = std::find_if( exception_table, exception_table_end, + auto p = std::find_if( __gg__exception_table, __gg__exception_table_end, [ec](const ec_descr_t& descr) { return descr.type == ec; } ); - if( p == exception_table_end ) { + if( p == __gg__exception_table_end ) { err(EXIT_FAILURE, "logic error: %s:%zu: %s unknown exception %x", ec_status.source_file, @@ -11217,8 +11217,8 @@ __gg__func_exception_status(cblc_field_t *dest) char ach[128] = "<not in table?>"; if(stashed_exception_code) { - ec_descr_t *p = exception_table; - while(p < exception_table_end ) + ec_descr_t *p = __gg__exception_table; + while(p < __gg__exception_table_end ) { if( p->type == (ec_type_t)stashed_exception_code ) { diff --git a/libgcobol/valconv.cc b/libgcobol/valconv.cc index f987b1f90fcef9c1cdcbd31bc7b84a84086a30cc..58a45823444f3b01ce1c90086cef79073a04bef1 100644 --- a/libgcobol/valconv.cc +++ b/libgcobol/valconv.cc @@ -1369,3 +1369,361 @@ __gg__remove_trailing_zeroes(char *p) } } +// This is just a convenient place to put this, since it is used in both the +// run-time and compile-time code + +ec_descr_t __gg__exception_table[] = { + { ec_all_e, ec_category_none_e, + "EC-ALL", "Any exception" }, + + { ec_argument_e, ec_category_none_e, + "EC-ARGUMENT", "Argument error" }, + { ec_argument_function_e, ec_category_fatal_e, + "EC-ARGUMENT-FUNCTION", "Function argument error" }, + { ec_argument_imp_e, uc_category_implementor_e, + "EC-ARGUMENT-IMP", "Implementor-defined argument error" }, + + { ec_argument_imp_command_e, uc_category_implementor_e, + "EC-ARGUMENT-IMP-COMMAND", "COMMAND-LINE Subscript out of bounds" }, + { ec_argument_imp_environment_e, uc_category_implementor_e, + "EC-ARGUMENT-IMP-ENVIRONMENT", "Envrionment Variable is not defined" }, + + { ec_bound_e, ec_category_none_e, + "EC-BOUND", "Boundary violation" }, + { ec_bound_func_ret_value_e, uc_category_nonfatal_e, + "EC-BOUND-FUNC-RET-VALUE", + "Intrinsic function output does not fit in returned value item" }, + { ec_bound_imp_e, uc_category_implementor_e, + "EC-BOUND-IMP", "Implementor-defined boundary violation" }, + { ec_bound_odo_e, ec_category_fatal_e, + "EC-BOUND-ODO", "OCCURS ... DEPENDING ON data item out of bounds" }, + { ec_bound_overflow_e, uc_category_nonfatal_e, + "EC-BOUND-OVERFLOW", + "Current capacity of dynamic-capacity table greater than expected value" }, + { ec_bound_ptr_e, uc_category_fatal_e, + "EC-BOUND-PTR", "Data-pointer contains an address that is out of bounds" }, + { ec_bound_ref_mod_e, ec_category_fatal_e, + "EC-BOUND-REF-MOD", "Reference modifier out of bounds" }, + { ec_bound_set_e, uc_category_nonfatal_e, + "EC-BOUND-SET", "Invalid use of SET to set capacity of " + "dynamic-capacity table above specified maximum" }, + { ec_bound_subscript_e, ec_category_fatal_e, + "EC-BOUND-SUBSCRIPT", "Subscript out of bounds" }, + { ec_bound_table_limit_e, uc_category_fatal_e, + "EC-BOUND-TABLE-LIMIT", + "Capacity of dynamic-capacity table would exceed implementor's maximum" }, + + { ec_data_e, ec_category_none_e, + "EC-DATA", "Data exception" }, + { ec_data_conversion_e, uc_category_nonfatal_e, + "EC-DATA-CONVERSION", + "Conversion failed because of incomplete character correspondence" }, + { ec_data_imp_e, uc_category_implementor_e, + "EC-DATA-IMP", "Implementor-defined data exception" }, + { ec_data_incompatible_e, uc_category_fatal_e, + "EC-DATA-INCOMPATIBLE", "Incompatible data exception" }, + { ec_data_not_finite_e, uc_category_fatal_e, + "EC-DATA-NOT-FINITE", + "Attempt to use a data item described with a standard floating-point usage " + "when its contents are either a NaN or a representation of infinity" }, + { ec_data_overflow_e, uc_category_fatal_e, + "EC-DATA-OVERFLOW", + "Exponent overflow during MOVE to a receiving data item described with a " + "standard floating-point usage" }, + { ec_data_ptr_null_e, uc_category_fatal_e, + "EC-DATA-PTR-NULL", + "Based item data-pointer is set to NULL when referenced" }, + + { ec_external_data_mismatch_e, uc_category_fatal_e, + "EC-EXTERNAL-DATA-MISMATCH", + "File referencing control item conflict because the linage, " + "file status or relative key references are not to the same item " }, + { ec_external_file_mismatch_e, uc_category_fatal_e, + "EC-EXTERNAL-FILE-MISMATCH", + "File control SELECT statements are not compatible" }, + { ec_external_format_conflict_e, uc_category_fatal_e, + "EC-EXTERNAL-FORMAT-CONFLICT", + "Data definitions definitions do not conform" }, + + { ec_flow_e, ec_category_none_e, + "EC-FLOW", "Execution control flow violation" }, + { ec_flow_global_exit_e, uc_category_fatal_e, + "EC-FLOW-GLOBAL-EXIT", "EXIT PROGRAM in a global Declarative" }, + { ec_flow_global_goback_e, uc_category_fatal_e, + "EC-FLOW-GLOBAL-GOBACK", "GOBACK in a global declarative" }, + { ec_flow_imp_e, uc_category_implementor_e, + "EC-FLOW-IMP", "Implementor-defined control flow violation" }, + { ec_flow_release_e, uc_category_fatal_e, + "EC-FLOW-RELEASE", "RELEASE not in range of SORT" }, + { ec_flow_report_e, uc_category_fatal_e, + "EC-FLOW-REPORT", + "GENERATE, INITIATE, or TERMINATE during USE BEFORE REPORTING declarative" }, + { ec_flow_return_e, uc_category_fatal_e, + "EC-FLOW-RETURN", "RETURN not in range of MERGE or SORT" }, + { ec_flow_search_e, uc_category_fatal_e, + "EC-FLOW-SEARCH", + "Invalid use of SET to change capacity of dynamic- capacity table during " + "SEARCH of same table" }, + { ec_flow_use_e, uc_category_fatal_e, + "EC-FLOW-USE", "A USE statement caused another to be executed" }, + + { ec_function_e, ec_category_none_e, + "EC-FUNCTION", "Function exception" }, + { ec_function_not_found_e, uc_category_fatal_e, + "EC-FUNCTION-NOT-FOUND", + "Function not found or function pointer does not point to a function" }, + { ec_function_ptr_invalid_e, uc_category_fatal_e, + "EC-FUNCTION-PTR-INVALID", "Signature mismatch" }, + { ec_function_ptr_null_e, uc_category_fatal_e, + "EC-FUNCTION-PTR-NULL", + "Function pointer used in calling a function is NULL" }, + + { ec_io_e, ec_category_none_e, + "EC-IO", "Input-output exception" }, + { ec_io_at_end_e, uc_category_nonfatal_e, + "EC-I-O-AT-END", "I-O status 1x" }, + { ec_io_eop_e, uc_category_nonfatal_e, + "EC-I-O-EOP", "An end of page condition occurred" }, + { ec_io_eop_overflow_e, uc_category_nonfatal_e, + "EC-I-O-EOP-OVERFLOW", "A page overflow condition occurred" }, + { ec_io_file_sharing_e, uc_category_nonfatal_e, + "EC-I-O-FILE-SHARING", "I-O status 6x" }, + { ec_io_imp_e, uc_category_implementor_e, + "EC-I-O-IMP", "I-O status 9x" }, + { ec_io_invalid_key_e, uc_category_nonfatal_e, + "EC-I-O-INVALID-KEY", "I-O status 2x" }, + { ec_io_linage_e, uc_category_fatal_e, + "EC-I-O-LINAGE", + "The value of a data item referenced in the LINAGE clause is not within " + "the required range" }, + { ec_io_logic_error_e, uc_category_fatal_e, + "EC-I-O-LOGIC-ERROR", "I-O status 4x" }, + { ec_io_permanent_error_e, uc_category_fatal_e, + "EC-I-O-PERMANENT-ERROR", "I-O status 3x" }, + { ec_io_record_operation_e, uc_category_nonfatal_e, + "EC-I-O-RECORD-OPERATION", "I-O status 5x" }, + + { ec_imp_e, ec_category_none_e, + "EC-IMP", "Implementor-defined exception condition" }, + + { ec_imp_suffix_e, ec_category_none_e, + "EC-IMP-SUFFIX", "Imp" }, + + { ec_locale_e, ec_category_none_e, + "EC-LOCALE", "Any locale related exception" }, + { ec_locale_imp_e, uc_category_implementor_e, + "EC-LOCALE-IMP", "Implementor-defined locale related exception" }, + { ec_locale_incompatible_e, uc_category_fatal_e, + "EC-LOCALE-INCOMPATIBLE", + "The referenced locale does not specify the expected characters in " + "LC_COLLATE" }, + { ec_locale_invalid_e, uc_category_fatal_e, + "EC-LOCALE-INVALID", "Locale content is invalid or incomplete" }, + { ec_locale_invalid_ptr_e, uc_category_fatal_e, + "EC-LOCALE-INVALID-PTR", "Pointer does not reference a saved locale" }, + { ec_locale_missing_e, uc_category_fatal_e, + "EC-LOCALE-MISSING", "The specified locale is not available" }, + { ec_locale_size_e, uc_category_fatal_e, + "EC-LOCALE-SIZE", "Digits were truncated in locale editing" }, + + { ec_oo_e, ec_category_none_e, + "EC-OO", "Any predefined OO related exception" }, + { ec_oo_arg_omitted_e, uc_category_fatal_e, + "EC-OO-ARG-OMITTED", "Reference to an omitted argument" }, + { ec_oo_conformance_e, uc_category_fatal_e, + "EC-OO-CONFORMANCE", "Failure for an object-view" }, + { ec_oo_exception_e, uc_category_fatal_e, + "EC-OO-EXCEPTION", "An exception object was not handled" }, + { ec_oo_imp_e, uc_category_implementor_e, + "EC-OO-IMP", "Implementor-defined OO exception" }, + { ec_oo_method_e, uc_category_fatal_e, + "EC-OO-METHOD", "Requested method is not available" }, + { ec_oo_null_e, uc_category_fatal_e, + "EC-OO-NULL", + "Method invocation was attempted with a null object reference" }, + { ec_oo_resource_e, uc_category_fatal_e, + "EC-OO-RESOURCE", "Insufficient system resources to create the object" }, + { ec_oo_universal_e, uc_category_fatal_e, + "EC-OO-UNIVERSAL", "A runtime type check failed" }, + + { ec_order_e, ec_category_none_e, + "EC-ORDER", "Ordering exception" }, + { ec_order_imp_e, uc_category_implementor_e, + "EC-ORDER-IMP", "Implementor-defined ordering exception" }, + { ec_order_not_supported_e, uc_category_fatal_e, + "EC-ORDER-NOT-SUPPORTED", + "Cultural ordering table or ordering level specified for " + "STANDARD-COMPARE function not supported" }, + + { ec_overflow_e, ec_category_none_e, + "EC-OVERFLOW", "Overflow condition" }, + { ec_overflow_imp_e, uc_category_implementor_e, + "EC-OVERFLOW-IMP", "Implementor-defined overflow condition" }, + { ec_overflow_string_e, uc_category_nonfatal_e, + "EC-OVERFLOW-STRING", "STRING overflow condition" }, + { ec_overflow_unstring_e, uc_category_nonfatal_e, + "EC-OVERFLOW-UNSTRING", "UNSTRING overflow condition" }, + + { ec_program_e, ec_category_none_e, + "EC-PROGRAM", "Inter-program communication exception" }, + { ec_program_arg_mismatch_e, uc_category_fatal_e, + "EC-PROGRAM-ARG-MISMATCH", "Parameter mismatch" }, + { ec_program_arg_omitted_e, uc_category_fatal_e, + "EC-PROGRAM-ARG-OMITTED", "A reference to an omitted argument" }, + { ec_program_cancel_active_e, uc_category_fatal_e, + "EC-PROGRAM-CANCEL-ACTIVE", "Canceled program active" }, + { ec_program_imp_e, uc_category_implementor_e, + "EC-PROGRAM-IMP", + "Implementor-defined inter-program communication exception" }, + { ec_program_not_found_e, uc_category_fatal_e, + "EC-PROGRAM-NOT-FOUND", "Called program not found" }, + { ec_program_ptr_null_e, uc_category_fatal_e, + "EC-PROGRAM-PTR-NULL", "Program-pointer used in CALL is set to NULL" }, + { ec_program_recursive_call_e, uc_category_fatal_e, + "EC-PROGRAM-RECURSIVE-CALL", "Called program active" }, + { ec_program_resources_e, uc_category_fatal_e, + "EC-PROGRAM-RESOURCES", "Resources not available for called program" }, + + { ec_raising_e, ec_category_none_e, + "EC-RAISING", "EXIT ... RAISING or GOBACK RAISING exception" }, + { ec_raising_imp_e, uc_category_implementor_e, + "EC-RAISING-IMP", + "Implementor-defined EXIT ... RAISING or GOBACK RAISING exception" }, + { ec_raising_not_specified_e, uc_category_fatal_e, + "EC-RAISING-NOT-SPECIFIED", + "EXIT ... RAISING or GOBACK RAISING an EC-USER exception condition not " + "specified in RAISING phrase of procedure division header" }, + + { ec_range_e, ec_category_none_e, + "EC-RANGE", "Range exception" }, + { ec_range_imp_e, uc_category_implementor_e, + "EC-RANGE-IMP", "Implementor-defined range exception" }, + { ec_range_index_e, uc_category_fatal_e, + "EC-RANGE-INDEX", + "Index set outside the range of values allowed by the implementor" }, + { ec_range_inspect_size_e, uc_category_fatal_e, + "EC-RANGE-INSPECT-SIZE", "Size of replace items in INSPECT differs" }, + { ec_range_invalid_e, uc_category_nonfatal_e, + "EC-RANGE-INVALID", + "Starting value of THROUGH range greater than ending value" }, + { ec_range_perform_varying_e, uc_category_fatal_e, + "EC-RANGE-PERFORM-VARYING", + "Setting of varied item in PERFORM is negative" }, + { ec_range_ptr_e, uc_category_fatal_e, + "EC-RANGE-PTR", "Pointer SET UP or DOWN is outside range" }, + { ec_range_search_index_e, uc_category_nonfatal_e, + "EC-RANGE-SEARCH-INDEX", + "No table element found in SEARCH because initial index out of range" }, + { ec_range_search_no_match_e, uc_category_nonfatal_e, + "EC-RANGE-SEARCH-NO-MATCH", + "No table element found in SEARCH because no element matched criteria" }, + + { ec_report_e, ec_category_none_e, + "EC-REPORT", "Report writer exception" }, + { ec_report_active_e, uc_category_fatal_e, + "EC-REPORT-ACTIVE", "INITIATE on an active report" }, + { ec_report_column_overlap_e, uc_category_nonfatal_e, + "EC-REPORT-COLUMN-OVERLAP", "Overlapping report items" }, + { ec_report_file_mode_e, uc_category_fatal_e, + "EC-REPORT-FILE-MODE", + "An INITIATE statement was executed for a file connector that was not " + "open in the extend or output mode" }, + { ec_report_imp_e, uc_category_implementor_e, + "EC-REPORT-IMP", "Implementor-defined report writer exception" }, + { ec_report_inactive_e, uc_category_fatal_e, + "EC-REPORT-INACTIVE", "GENERATE or TERMINATE on an inactive report" }, + { ec_report_line_overlap_e, uc_category_nonfatal_e, + "EC-REPORT-LINE-OVERLAP", "Overlapping report lines" }, + { ec_report_not_terminated_e, uc_category_nonfatal_e, + "EC-REPORT-NOT-TERMINATED", "Report file closed with active report" }, + { ec_report_page_limit_e, uc_category_nonfatal_e, + "EC-REPORT-PAGE-LIMIT", "Vertical page limit exceeded" }, + { ec_report_page_width_e, uc_category_nonfatal_e, + "EC-REPORT-PAGE-WIDTH", "Page width exceeded" }, + { ec_report_sum_size_e, uc_category_fatal_e, + "EC-REPORT-SUM-SIZE", "Overflow of sum counter" }, + { ec_report_varying_e, uc_category_fatal_e, + "EC-REPORT-VARYING", "VARYING clause expression noninteger" }, + + { ec_screen_e, ec_category_none_e, + "EC-SCREEN", "Screen handling exception" }, + { ec_screen_field_overlap_e, uc_category_nonfatal_e, + "EC-SCREEN-FIELD-OVERLAP", "Screen fields overlap" }, + { ec_screen_imp_e, uc_category_implementor_e, + "EC-SCREEN-IMP", "Implementor-defined screen handling exception" }, + { ec_screen_item_truncated_e, uc_category_nonfatal_e, + "EC-SCREEN-ITEM-TRUNCATED", "Screen field too long for line" }, + { ec_screen_line_number_e, uc_category_nonfatal_e, + "EC-SCREEN-LINE-NUMBER", + "Screen item line number exceeds terminal size" }, + { ec_screen_starting_column_e, uc_category_nonfatal_e, + "EC-SCREEN-STARTING-COLUMN", + "Screen item starting column exceeds line size" }, + + { ec_size_e, ec_category_none_e, + "EC-SIZE", "Size error exception" }, + { ec_size_address_e, uc_category_fatal_e, + "EC-SIZE-ADDRESS", "Invalid pointer arithmetic" }, + { ec_size_exponentiation_e, ec_category_fatal_e, + "EC-SIZE-EXPONENTIATION", "Exponentiation rules violated" }, + { ec_size_imp_e, uc_category_implementor_e, + "EC-SIZE-IMP", "Implementor-defined size error exception" }, + { ec_size_overflow_e, ec_category_fatal_e, + "EC-SIZE-OVERFLOW", "Arithmetic overflow in calculation" }, + { ec_size_truncation_e, ec_category_fatal_e, + "EC-SIZE-TRUNCATION", "Significant digits truncated in store" }, + { ec_size_underflow_e, ec_category_fatal_e, + "EC-SIZE-UNDERFLOW", "Floating-point underflow" }, + { ec_size_zero_divide_e, ec_category_fatal_e, + "EC-SIZE-ZERO-DIVIDE", "Division by zero" }, + + { ec_sort_merge_e, ec_category_none_e, + "EC-SORT-MERGE", "SORT or MERGE exception" }, + { ec_sort_merge_active_e, uc_category_fatal_e, + "EC-SORT-MERGE-ACTIVE", + "File SORT or MERGE executed when one is already active" }, + { ec_sort_merge_file_open_e, ec_category_fatal_e, + "EC-SORT-MERGE-FILE-OPEN", + "A USING or GIVING file is open upon execution of a SORT or MERGE" }, + { ec_sort_merge_imp_e, uc_category_implementor_e, + "EC-SORT-MERGE-IMP", + "Implementor-defined SORT or MERGE exception" }, + { ec_sort_merge_release_e, uc_category_fatal_e, + "EC-SORT-MERGE-RELEASE", "RELEASE record too long or too short" }, + { ec_sort_merge_return_e, uc_category_fatal_e, + "EC-SORT-MERGE-RETURN", "RETURN executed when at end condition exists" }, + { ec_sort_merge_sequence_e, uc_category_fatal_e, + "EC-SORT-MERGE-SEQUENCE", "Sequence error on MERGE USING file" }, + + { ec_storage_e, ec_category_none_e, + "EC-STORAGE", "Storage allocation exception" }, + { ec_storage_imp_e, uc_category_implementor_e, + "EC-STORAGE-IMP", "Implementor-defined storage allocation exception" }, + { ec_storage_not_alloc_e, uc_category_nonfatal_e, + "EC-STORAGE-NOT-ALLOC", + "The data-pointer specified in a FREE statement does not identify " + "currently allocated storage" }, + { ec_storage_not_avail_e, uc_category_nonfatal_e, + "EC-STORAGE-NOT-AVAIL", + "The amount of storage requested by an ALLOCATE statement " + "is not available"}, + { ec_user_e, ec_category_none_e, + "EC-USER", "User-defined exception condition" }, + { ec_user_suffix_e, uc_category_nonfatal_e, + "EC-USER-SUFFIX", "Level-3 user-defined exception condition" }, + + { ec_validate_e, ec_category_none_e, + "EC-VALIDATE", "VALIDATE exception" }, + { ec_validate_content_e, uc_category_nonfatal_e, + "EC-VALIDATE-CONTENT", "VALIDATE content error" }, + { ec_validate_format_e, uc_category_nonfatal_e, + "EC-VALIDATE-FORMAT", "VALIDATE format error" }, + { ec_validate_imp_e, uc_category_implementor_e, + "EC-VALIDATE-IMP", "Implementor-defined VALIDATE exception" }, + { ec_validate_relation_e, uc_category_nonfatal_e, + "EC-VALIDATE-RELATION", "VALIDATE relation error" }, + { ec_validate_varying_e, uc_category_fatal_e, + "EC-VALIDATE-VARYING", "VARYING clause expression noninteger" }, +} ; + +const ec_descr_t *__gg__exception_table_end = __gg__exception_table + COUNT_OF(__gg__exception_table);