
Grammar extracted by Vadim Zaytsev, see the Grammar Zoo entry for details: cobol/vscobolii/prolog/extracted
Source used for this grammar: Ralf Lämmel, IBM VS COBOL II, ibm-transformed.pl, 4 June 2003 [Explore]
statement_verb, copy_directive_without_period, statements, overflow_phrases, invalid_key_phrases, at_end_phrases, exception_phrases, size_error_phrases, examine_statement, not_at_eop, at_eop, write_before_after, not_at_end, at_end, inspect_replacing_phrase, inspect_tallying_phrase, before_after_phrase, when_other_phrase, when_phrase, e_phrase, invalid_key, not_invalid_key, not_on_exception, on_exception, not_on_overflow, on_overflow, not_on_size_error, on_size_error, use_directive, subtract_statement, set_statement, search_statement, perform_statement, open_statement, multiply_statement, move_statement, inspect_statement, go_to_statement, divide_statement, close_statement, add_statement, accept_statement, call_using_phrase, altered_go_to, occurs_clause, data_clauses, data_description_entry, code_set_clause, recording_mode_clause, linage_area_clause, linage_clause, data_records_clause, value_of_clause, label_records_clause, record_varying_clause, record_clause, block_contains_clause, global_clause, external_clause, file_clauses, file_description_entry, status_clause, relative_key, record_key, password_clause, key_clause, access_mode_clause, record_delimiter_clause, padding_character_clause, organisation_clause, reserve_clause, file_control_clauses, assign_clause, select_clause, file_control_entry, special_names_clauses, currency_clause, class_clause, symbolic_clause, alphabet_clause, environment_clause, computer_paragraphs, sentence, series_of_imperative_statements, procedure_division_content, section, using_phrase, record_description_entry, data_division_content, environment_division_content, identification_division_content, copy_operand, abbreviation_rest, object, relational_operator, operand, simple_condition, combinable_condition, condition, basis, power, times_div, arithmetic_expression, mode, special_register, literal, figurative_constant, assignment_name, environment_name, computer_name, section_name, paragraph_name, text_name, program_name, library_name, symbolic_character, record_name, mnemonic_name, index_name, file_name, data_name, condition_name, class_name, alphabet_name, mod_length, leftmost_character_position, condition_name_reference, subscript, qualified_data_name, identifier, procedure_name, abbreviated_combined_relation_condition, accept_statement_format_i, accept_statement_format_ii, add_statement_format_i, add_statement_format_ii, add_statement_format_iii, after_phrase, alter_statement, blank_when_zero_clause, call_statement_format_i, call_statement_format_ii, cancel_statement, class_condition, close_statement_format_i, close_statement_format_ii, cobol_source_program, combined_condition, compute_statement, condition_name_condition, condition_name_in_data_division, condition_name_in_special_names_paragraph, configuration_section, continue_statement, copy_directive, data_description_entry_format_i, data_description_entry_format_ii, data_description_entry_format_iii, delete_statement, display_statement, divide_statement_format_i, divide_statement_format_ii, divide_statement_format_iii, divide_statement_format_iv, divide_statement_format_v, entry_statement, evaluate_statement, exit_program_statement, exit_statement, file_control_paragraph, go_to_statement_format_i, go_to_statement_format_ii, go_to_statement_format_iv, goback_statement, i_o_control_paragraph, identifier_format_i, identifier_format_ii, idx_entry, if_statement, initialize_statement, input_output_section, inspect_statement_format_i, inspect_statement_format_ii, inspect_statement_format_iii, inspect_statement_format_iv, justified_clause, merge_statement, move_statement_format_i, move_statement_format_ii, multiply_statement_format_i, multiply_statement_format_ii, negated_simple_condition, nested_source_program, object_computer_paragraph, occurs_clause_format_i, occurs_clause_format_ii, ocp_entry, open_statement_format_i, open_statement_format_ii, para, perform_statement_format_i, perform_statement_format_ii, perform_statement_format_iii, perform_statement_format_iv, picture_clause, qsam_or_sam_i_o_control_entries, read_statement_format_i, read_statement_format_ii, redefines_clause, reference_to_procedure_division_name_format_i, reference_to_procedure_division_name_format_ii, relation_condition, release_statement, renames_clause, return_statement, rewrite_statement, search_statement_format_i, search_statement_format_ii, sect, set_statement_format_i, set_statement_format_ii, set_statement_format_iii, set_statement_format_iv, set_statement_format_v, sign_clause, sign_condition, snp_entry, sort_merge_i_o_control_entries, sort_statement, source_computer_paragraph, special_names_paragraph, start_statement, stop_statement, string_statement, subtract_statement_format_i, subtract_statement_format_ii, subtract_statement_format_iii, switch_status_condition, synchronized_clause, test_phrase, unstring_statement, usage_clause, use_directive_format_i, use_directive_format_ii, use_directive_format_iii, value_clause_format_i, value_clause_format_ii, varying_phrase, vsam_i_o_control_entries, w_phrase, write_statement_format_i), 0 root (—), 1 top (cobol_source_program), 13 bottom (integer 29, system_name 4, quoted_pseudo_text, cobol_word, user_defined_word 5, comment_entry 6, dbcs, numeric, character_string, priority_number 3, level_number, alphabetic_user_defined_word 8, nonnumeric).statement_verb ::= "ACCEPT" "ADD" "ALTER" "CALL" "CANCEL" "CLOSE" "COMPUTE" "CONTINUE" "DELETE" "DISPLAY" "DIVIDE" "ENTRY" "EVALUATE" "EXIT" "GOBACK" "GO" "IF" "INITIALIZE" "INSPECT" "MERGE" "MOVE" "MULTIPLY" "OPEN" "PERFORM" "READ" "RELEASE" "RETURN" "REWRITE" "SEARCH" "SET" "SORT" "START" "STOP" "STRING" "SUBTRACT" "UNSTRING" "WRITE" "EXAMINE" "COPY"
copy_directive_without_period ::= "COPY" text_nameliteral "OF""IN" library_nameliteralε "SUPPRESS"ε "REPLACING" copy_operand "BY" copy_operandε
statements ::= accept_statement statement_verb statementsε add_statement statement_verb statements"END-ADD" statement_verb statementsεsize_error_phrases "END-ADD" statement_verb statementsεεε alter_statement statement_verb statementsε call_statement_format_i statement_verb statements"END-CALL" statement_verb statementsεon_overflow "END-CALL" statement_verb statementsεεε call_statement_format_ii statement_verb statements"END-CALL" statement_verb statementsεexception_phrases "END-CALL" statement_verb statementsεεε cancel_statement statement_verb statementsε close_statement statement_verb statementsε compute_statement statement_verb statements"END-COMPUTE" statement_verb statementsεsize_error_phrases "END-COMPUTE" statement_verb statementsεεε continue_statement statement_verb statementsε delete_statement statement_verb statements"END-DELETE" statement_verb statementsεinvalid_key_phrases "END-DELETE" statement_verb statementsεεε display_statement statement_verb statementsε divide_statement statement_verb statements"END-DIVIDE" statement_verb statementsεsize_error_phrases "END-DIVIDE" statement_verb statementsεεε entry_statement statement_verb statementsε evaluate_statement "END-EVALUATE" statement_verb statementsεε exit_statement statement_verb statementsε exit_program_statement statement_verb statementsε goback_statement statement_verb statementsε go_to_statement statement_verb statementsε if_statement "END-IF" statement_verb statementsεε initialize_statement statement_verb statementsε inspect_statement statement_verb statementsε merge_statement statement_verb statementsε move_statement statement_verb statementsε multiply_statement statement_verb statements"END-MULTIPLY" statement_verb statementsεsize_error_phrases "END-MULTIPLY" statement_verb statementsεεε open_statement statement_verb statementsε perform_statement statement_verb statementsε read_statement_format_i statement_verb statements"END-READ" statement_verb statementsεat_end_phrases "END-READ" statement_verb statementsεεε read_statement_format_ii statement_verb statements"END-READ" statement_verb statementsεinvalid_key_phrases "END-READ" statement_verb statementsεεε release_statement statement_verb statementsε return_statement "END-RETURN" statement_verb statementsεε rewrite_statement statement_verb statements"END-REWRITE" statement_verb statementsεinvalid_key_phrases "END-REWRITE" statement_verb statementsεεε search_statement "END-SEARCH" statement_verb statementsεε set_statement statement_verb statementsε sort_statement statement_verb statementsε start_statement statement_verb statements"END-START" statement_verb statementsεinvalid_key_phrases "END-START" statement_verb statementsεεε stop_statement statement_verb statementsε string_statement statement_verb statements"END-STRING" statement_verb statementsεoverflow_phrases "END-STRING" statement_verb statementsεεε subtract_statement statement_verb statements"END-SUBTRACT" statement_verb statementsεsize_error_phrases "END-SUBTRACT" statement_verb statementsεεε unstring_statement statement_verb statements"END-UNSTRING" statement_verb statementsεoverflow_phrases "END-UNSTRING" statement_verb statementsεεε write_statement_format_i statement_verb statements"END-WRITE" statement_verb statementsεwrite_before_after statement_verb statements"END-WRITE" statement_verb statementsεw_phrase "END-WRITE" statement_verb statementsεεεinvalid_key_phrases "END-WRITE" statement_verb statementsεεε examine_statement statement_verb statementsε copy_directive statement_verb statementsε
overflow_phrases ::= on_overflowε not_on_overflowε
invalid_key_phrases ::= invalid_key not_invalid_key invalid_key not_invalid_key
at_end_phrases ::= at_end not_at_end at_end not_at_end
exception_phrases ::= on_exception not_on_exception on_exception not_on_exception
size_error_phrases ::= on_size_error not_on_size_error on_size_error not_on_size_error
examine_statement ::= "EXAMINE" identifier "TALLYING" "ALL""LEADING" literal
not_at_eop ::= "NOT" "AT"ε "END-OF-PAGE""EOP" series_of_imperative_statements
at_eop ::= "AT"ε "END-OF-PAGE""EOP" series_of_imperative_statements
write_before_after ::= "BEFORE""AFTER" "ADVANCING"ε identifierinteger "LINE""LINES"εmnemonic_name"PAGE" ε
not_at_end ::= "NOT" "AT"ε "END" series_of_imperative_statements
at_end ::= "AT"ε "END" series_of_imperative_statements
inspect_replacing_phrase ::= "REPLACING" "CHARACTERS" "BY" identifierliteral before_after_phrase"ALL""LEADING""FIRST" identifierliteral "BY" identifierliteral before_after_phrase
inspect_tallying_phrase ::= "TALLYING" identifier "FOR" "CHARACTERS" before_after_phrase"ALL""LEADING" identifierliteral before_after_phrase
before_after_phrase ::= "BEFORE""AFTER" "INITIAL"ε identifierliteral
when_other_phrase ::= "WHEN" "OTHER" series_of_imperative_statements
when_phrase ::= "WHEN" e_phrase "ALSO" e_phrase series_of_imperative_statements
e_phrase ::= "ANY" condition "TRUE" "FALSE" "NOT"ε identifierliteralarithmetic_expression "THROUGH""THRU" identifierliteralarithmetic_expressionε
invalid_key ::= "INVALID" "KEY"ε series_of_imperative_statements
not_invalid_key ::= "NOT" "INVALID" "KEY"ε series_of_imperative_statements
not_on_exception ::= "NOT" "ON"ε "EXCEPTION" series_of_imperative_statements
on_exception ::= "ON"ε "EXCEPTION" series_of_imperative_statements
not_on_overflow ::= "NOT" "ON"ε "OVERFLOW" series_of_imperative_statements
on_overflow ::= "ON"ε "OVERFLOW" series_of_imperative_statements
not_on_size_error ::= "NOT" "ON"ε "SIZE" "ERROR" series_of_imperative_statements
on_size_error ::= "ON"ε "SIZE" "ERROR" series_of_imperative_statements
use_directive ::= use_directive_format_i use_directive_format_ii use_directive_format_iii
subtract_statement ::= subtract_statement_format_i subtract_statement_format_ii subtract_statement_format_iii
set_statement ::= set_statement_format_i set_statement_format_ii set_statement_format_iii set_statement_format_iv set_statement_format_v
search_statement ::= search_statement_format_i search_statement_format_ii
perform_statement ::= perform_statement_format_i perform_statement_format_ii perform_statement_format_iii perform_statement_format_iv
open_statement ::= open_statement_format_i open_statement_format_ii
multiply_statement ::= multiply_statement_format_i multiply_statement_format_ii
move_statement ::= move_statement_format_i move_statement_format_ii
inspect_statement ::= inspect_statement_format_i inspect_statement_format_ii inspect_statement_format_iii inspect_statement_format_iv
go_to_statement ::= go_to_statement_format_i go_to_statement_format_ii altered_go_to go_to_statement_format_iv
divide_statement ::= divide_statement_format_i divide_statement_format_ii divide_statement_format_iii divide_statement_format_iv divide_statement_format_v
close_statement ::= close_statement_format_i close_statement_format_ii
add_statement ::= add_statement_format_i add_statement_format_ii add_statement_format_iii
accept_statement ::= accept_statement_format_i accept_statement_format_ii
call_using_phrase ::= "USING" "BY"ε "REFERENCE"ε identifier"ADDRESS" "OF" identifierfile_name"BY"ε "CONTENT" "LENGTH" "OF"ε identifier"ADDRESS" "OF" identifierliteral
altered_go_to ::= "GO" "TO"ε
occurs_clause ::= occurs_clause_format_ii occurs_clause_format_i
data_clauses ::= blank_when_zero_clauseexternal_clauseglobal_clausejustified_clauseoccurs_clausepicture_clausesign_clausesynchronized_clauseusage_clausevalue_clause_format_i
data_description_entry ::= data_description_entry_format_i data_description_entry_format_ii data_description_entry_format_iii copy_directive
code_set_clause ::= "CODE-SET" "IS"ε alphabet_name
recording_mode_clause ::= "RECORDING" "MODE"ε "IS"ε mode
linage_area_clause ::= "WITH"ε "FOOTING" "AT"ε data_nameintegerε "LINES"ε "AT"ε "TOP" data_nameintegerε "LINES"ε "AT"ε "BOTTOM" data_nameintegerε
linage_clause ::= "LINAGE" "IS"ε qualified_data_nameinteger "LINES"ε linage_area_clause
data_records_clause ::= "DATA" "RECORD""RECORDS" "IS""ARE"ε qualified_data_name
value_of_clause ::= "VALUE" "OF" system_name "IS"ε qualified_data_nameliteral
label_records_clause ::= "LABEL" "RECORD""RECORDS" "IS""ARE"ε "STANDARD""OMITTED"qualified_data_name
record_varying_clause ::= "IS"ε "VARYING" "IN"ε "SIZE"ε "FROM"ε integerε "TO" integerε "CHARACTERS"ε
record_clause ::= "RECORD" "CONTAINS"ε integer "CHARACTERS"ε"CONTAINS"ε integer "TO" integer "CHARACTERS"εrecord_varying_clause "DEPENDING" "ON"ε qualified_data_nameε
block_contains_clause ::= "BLOCK" "CONTAINS"ε integer "TO"ε integer "CHARACTERS""RECORDS""RECORD"ε
global_clause ::= "IS"ε "GLOBAL"
external_clause ::= "IS"ε "EXTERNAL"
file_clauses ::= external_clauseglobal_clauseblock_contains_clauserecord_clauselabel_records_clausevalue_of_clausedata_records_clauselinage_clauserecording_mode_clausecode_set_clause
file_description_entry ::= "FD""SD" file_name file_clauses ";"
status_clause ::= "FILE"ε "STATUS" "IS"ε qualified_data_name qualified_data_nameε
relative_key ::= "RELATIVE" "KEY"ε "IS"ε qualified_data_name
record_key ::= "RECORD" "KEY"ε "IS"ε qualified_data_name password_clauseε idx_entry
password_clause ::= "PASSWORD" "IS"ε qualified_data_name
key_clause ::= record_key relative_key
access_mode_clause ::= "ACCESS" "MODE"ε "IS"εε "SEQUENTIAL""RANDOM""DYNAMIC"
record_delimiter_clause ::= "RECORD" "DELIMITER" "IS"ε "STANDARD-1"assignment_name
padding_character_clause ::= "PADDING" "CHARACTER"ε "IS"ε qualified_data_nameliteral
organisation_clause ::= "ORGANIZATION" "IS"εε "SEQUENTIAL""INDEXED""RELATIVE"
reserve_clause ::= "RESERVE" integer "AREA""AREAS"ε
file_control_clauses ::= reserve_clauseorganisation_clausepadding_character_clauserecord_delimiter_clauseaccess_mode_clausekey_clausepassword_clausestatus_clause
assign_clause ::= "ASSIGN" "TO"ε assignment_nameliteral
select_clause ::= "SELECT" "OPTIONAL"ε file_name
file_control_entry ::=
select_clause assign_clause file_control_clauses ";"special_names_clauses ::= environment_clausealphabet_clausesymbolic_clauseclass_clausecurrency_clause
currency_clause ::= "CURRENCY" "SIGN"ε "IS"ε literal "DECIMAL-POINT" "IS"ε "COMMA" "CURRENCY" "SIGN"ε "IS"ε literal "DECIMAL-POINT" "IS"ε "COMMA"
class_clause ::= "CLASS" class_name "IS"ε literal "THROUGH""THRU" literalε
symbolic_clause ::= "SYMBOLIC" "CHARACTERS"ε symbolic_character "ARE""IS"ε integer "IN" alphabet_nameε
alphabet_clause ::= "ALPHABET" alphabet_name "IS"ε "STANDARD-1""STANDARD-2""NATIVE""EBCDIC"literal "THROUGH""THRU" literal"ALSO" literalε
environment_clause ::= environment_name "IS"ε mnemonic_name environment_name "IS"ε mnemonic_name snp_entryεsnp_entry
computer_paragraphs ::= source_computer_paragraphobject_computer_paragraph
sentence ::=
statements ";"series_of_imperative_statements ::= statements
procedure_division_content ::= "DECLARATIVES" ";" sect ";" use_directive ";" para "END" "DECLARATIVES" ";"ε paraε section
section ::= section_name "SECTION" priority_numberε ";" para
using_phrase ::= "USING" data_name
record_description_entry ::= data_description_entry
data_division_content ::= "FILE" "SECTION" ";" file_description_entry record_description_entryε "WORKING-STORAGE" "SECTION" ";" data_description_entryε "LINKAGE" "SECTION" ";" data_description_entryε
environment_division_content ::= configuration_sectionε input_output_sectionε
identification_division_content ::= "AUTHOR" ";"ε comment_entry"INSTALLATION" ";"ε comment_entry"DATE-WRITTEN" ";"ε comment_entry"DATE-COMPILED" ";"ε comment_entry"SECURITY" ";"ε comment_entry"REMARKS" ";" comment_entry
copy_operand ::= quoted_pseudo_text identifier literal cobol_word
abbreviation_rest ::= "AND""OR" "NOT"ε relational_operatorε object"(" object abbreviation_rest ")"
object ::= arithmetic_expression
relational_operator ::= "IS""NOT""IS" "NOT""NOT" "IS"ε "GREATER" "THAN"ε">""LESS" "THAN"ε"<""EQUAL" "TO"ε"=""GREATER" "THAN"ε "OR" "EQUAL" "TO"ε">=""LESS" "THAN"ε "OR" "EQUAL" "TO"ε"<="
operand ::= arithmetic_expression
simple_condition ::= class_condition condition_name_condition relation_condition sign_condition switch_status_condition "(" condition ")"
combinable_condition ::= simple_condition negated_simple_condition abbreviated_combined_relation_condition
condition ::= combinable_condition combined_condition
basis ::= identifier literal "(" arithmetic_expression ")"
power ::= "+""-"ε basis "**" basis
times_div ::= power "*""/" power
arithmetic_expression ::= times_div "+""-" times_div
mode ::= "F" "V" "U" "S"
special_register ::= "ADDRESS" "OF" data_name "DEBUG-ITEM" "LENGTH" "OF" identifier "RETURN-CODE" "SHIFT-OUT" "SHIFT-IN" "SORT-CONTROL" "SORT-CORE-SIZE" "SORT-FILE-SIZE" "SORT-MESSAGE" "SORT-MODE-SIZE" "SORT-RETURN" "TALLY" "WHEN-COMPILED"
literal ::= nonnumeric numeric dbcs figurative_constant
figurative_constant ::= "ZERO" "ZEROS" "ZEROES" "SPACE" "SPACES" "HIGH-VALUE" "HIGH-VALUES" "LOW-VALUE" "LOW-VALUES" "QUOTE" "QUOTES" "ALL" literal "NULL" "NULLS"
assignment_name ::= system_name
environment_name ::= system_name
computer_name ::= system_name
section_name ::= user_defined_word
paragraph_name ::= user_defined_word
text_name ::= user_defined_word
program_name ::= user_defined_word
library_name ::= user_defined_word
symbolic_character ::= alphabetic_user_defined_word
record_name ::= qualified_data_name
mnemonic_name ::= alphabetic_user_defined_word
index_name ::= alphabetic_user_defined_word
file_name ::= alphabetic_user_defined_word
data_name ::= alphabetic_user_defined_word
condition_name ::= alphabetic_user_defined_word
class_name ::= alphabetic_user_defined_word
alphabet_name ::= alphabetic_user_defined_word
mod_length ::= arithmetic_expression
leftmost_character_position ::= arithmetic_expression
condition_name_reference ::= condition_name_in_data_division condition_name_in_special_names_paragraph
subscript ::= integer identifier "+""-" integerε index_name "+""-" integerε "+""-" integer
qualified_data_name ::= data_name "IN""OF" data_name "IN""OF" file_nameε
identifier ::= identifier_format_i identifier_format_ii special_register
procedure_name ::= reference_to_procedure_division_name_format_i reference_to_procedure_division_name_format_ii
abbreviated_combined_relation_condition ::= relation_condition abbreviation_rest arithmetic_expression relational_operator "(" "NOT"ε arithmetic_expression abbreviation_rest ")" arithmetic_expression "(" "NOT"ε relational_operatorε arithmetic_expression abbreviation_rest ")"
accept_statement_format_i ::= "ACCEPT" identifier "FROM" mnemonic_nameenvironment_nameε
accept_statement_format_ii ::= "ACCEPT" identifier "FROM" "DATE""DAY""DAY-OF-WEEK""TIME"
add_statement_format_i ::= "ADD" identifierliteral "TO" identifier "ROUNDED"ε
add_statement_format_ii ::= "ADD" identifierliteral "TO"ε identifierliteral "GIVING" identifier "ROUNDED"ε
add_statement_format_iii ::= "ADD" "CORRESPONDING""CORR" identifier "TO" identifier "ROUNDED"ε
after_phrase ::= "AFTER" identifierindex_name "FROM" identifierindex_nameliteral "BY" identifierliteral "UNTIL" condition
alter_statement ::= "ALTER" procedure_name "TO" "PROCEED" "TO"ε procedure_name
blank_when_zero_clause ::= "BLANK" "WHEN"ε "ZERO""ZEROS""ZEROES"
call_statement_format_i ::= "CALL" identifierliteral call_using_phrase copy_directive_without_periodεε
call_statement_format_ii ::= "CALL" identifierliteral call_using_phrase copy_directive_without_periodεε
cancel_statement ::= "CANCEL" identifierliteral
class_condition ::= identifier "IS""NOT""IS" "NOT""NOT" "IS"ε "NUMERIC""ALPHABETIC""ALPHABETIC-LOWER""ALPHABETIC-UPPER"class_name"DBCS""KANJI"
close_statement_format_i ::= "CLOSE" file_name "REEL""UNIT" "FOR"ε "REMOVAL""WITH"ε "NO" "REWIND"ε"WITH"ε "NO" "REWIND""LOCK"ε
close_statement_format_ii ::= "CLOSE" file_name "WITH"ε "LOCK"ε
cobol_source_program ::= "IDENTIFICATION""ID" "DIVISION" ";" "PROGRAM-ID" ";"ε program_name "IS"ε "INITIAL" "PROGRAM"εε ";"ε identification_division_contentε "ENVIRONMENT" "DIVISION" ";" environment_division_contentε "DATA" "DIVISION" ";" data_division_contentε "PROCEDURE" "DIVISION" using_phraseε ";"copy_directive"USING" data_name copy_directive procedure_division_contentε nested_source_program "END" "PROGRAM" program_name ";"ε
combined_condition ::= combinable_condition "AND""OR" combinable_condition
compute_statement ::= "COMPUTE" identifier "ROUNDED"ε "=""EQUAL" arithmetic_expression
condition_name_condition ::= condition_name_reference
condition_name_in_data_division ::= condition_name "IN""OF" data_name "IN""OF" file_nameε "(" subscript ")"
condition_name_in_special_names_paragraph ::= condition_name "IN""OF" mnemonic_name
configuration_section ::= "CONFIGURATION" "SECTION" ";" computer_paragraphs special_names_paragraphε
continue_statement ::=
"CONTINUE"copy_directive ::=
copy_directive_without_period ";"data_description_entry_format_i ::= level_number data_name"FILLER"ε redefines_clauseε data_clauses ";"ε
data_description_entry_format_ii ::= "66" data_name renames_clause ";"ε
data_description_entry_format_iii ::= "88" condition_name value_clause_format_ii ";"ε
delete_statement ::= "DELETE" file_name "RECORD"ε
display_statement ::= "DISPLAY" identifierliteral "UPON" mnemonic_nameenvironment_nameε "WITH"ε "NO" "ADVANCING"ε
divide_statement_format_i ::= "DIVIDE" identifierliteral "INTO" identifier "ROUNDED"ε
divide_statement_format_ii ::= "DIVIDE" identifierliteral "INTO" identifierliteral "GIVING" identifier "ROUNDED"ε
divide_statement_format_iii ::= "DIVIDE" identifierliteral "BY" identifierliteral "GIVING" identifier "ROUNDED"ε
divide_statement_format_iv ::= "DIVIDE" identifierliteral "INTO" identifierliteral "GIVING" identifier "ROUNDED"ε "REMAINDER" identifier
divide_statement_format_v ::= "DIVIDE" identifierliteral "BY" identifierliteral "GIVING" identifier "ROUNDED"ε "REMAINDER" identifier
entry_statement ::= "ENTRY" literal "USING" data_nameε
evaluate_statement ::= "EVALUATE" identifierliteralarithmetic_expressioncondition"TRUE""FALSE" "ALSO" identifierliteralarithmetic_expressioncondition"TRUE""FALSE" when_phrase when_other_phraseε
exit_program_statement ::= "EXIT" "PROGRAM"
exit_statement ::=
"EXIT"file_control_paragraph ::= "FILE-CONTROL" ";" file_control_entry
go_to_statement_format_i ::= "GO" "TO"ε procedure_name
go_to_statement_format_ii ::= "GO" "TO"ε procedure_name "DEPENDING" "ON"ε identifier
go_to_statement_format_iv ::= "GO" "TO"ε "MORE-LABELS"
goback_statement ::=
"GOBACK"i_o_control_paragraph ::= "I-O-CONTROL" ";" qsam_or_sam_i_o_control_entriesvsam_i_o_control_entries ";"ε sort_merge_i_o_control_entries ";"ε
identifier_format_i ::= qualified_data_name "(" subscript ")"ε "(" leftmost_character_position ":" mod_lengthε ")"ε
identifier_format_ii ::= "LINAGE-COUNTER" "IN""OF" file_nameε
idx_entry ::= "ALTERNATE" "RECORD"ε "KEY"ε "IS"ε qualified_data_name "PASSWORD" "IS"ε qualified_data_nameε "WITH"ε "DUPLICATES"ε
if_statement ::= "IF" condition "THEN"ε statement_verb"NEXT" "SENTENCE" statements"NEXT" "SENTENCE" "ELSE" statements"NEXT" "SENTENCE"ε
initialize_statement ::= "INITIALIZE" identifier "REPLACING" "ALPHABETIC""ALPHANUMERIC""NUMERIC""ALPHANUMERIC-EDITED""NUMERIC-EDITED""DBCS""EGCS" "DATA"ε "BY" identifierliteralε
input_output_section ::= "INPUT-OUTPUT" "SECTION" ";" file_control_paragraphε i_o_control_paragraphε
inspect_statement_format_i ::=
"INSPECT" identifier inspect_tallying_phraseinspect_statement_format_ii ::=
"INSPECT" identifier inspect_replacing_phraseinspect_statement_format_iii ::=
"INSPECT" identifier inspect_tallying_phrase inspect_replacing_phraseinspect_statement_format_iv ::= "INSPECT" identifier "CONVERTING" identifierliteral "TO" identifierliteral before_after_phrase
justified_clause ::= "JUSTIFIED""JUST" "RIGHT"ε
merge_statement ::= "MERGE" file_name "ON"ε "ASCENDING""DESCENDING" "KEY"ε qualified_data_name "COLLATING"ε "SEQUENCE" "IS"ε alphabet_nameε "USING" file_name file_name "OUTPUT" "PROCEDURE" "IS"ε procedure_name "THROUGH""THRU" procedure_nameε"GIVING" file_name
move_statement_format_i ::= "MOVE" identifierliteral "TO" identifier
move_statement_format_ii ::= "MOVE" "CORRESPONDING""CORR" identifier "TO" identifier
multiply_statement_format_i ::= "MULTIPLY" identifierliteral "BY" identifier "ROUNDED"ε
multiply_statement_format_ii ::= "MULTIPLY" identifierliteral "BY" identifierliteral "GIVING" identifier "ROUNDED"ε
negated_simple_condition ::=
"NOT" conditionnested_source_program ::= "IDENTIFICATION""ID" "DIVISION" ";" "PROGRAM-ID" ";"ε program_name "IS"ε "COMMON" "INITIAL"ε"INITIAL" "COMMON"ε "PROGRAM"εε ";"ε identification_division_contentε "ENVIRONMENT" "DIVISION" ";" environment_division_contentε "DATA" "DIVISION" ";" data_division_contentε "PROCEDURE" "DIVISION" using_phraseε ";"copy_directive"USING" data_name copy_directive procedure_division_contentε nested_source_program "END" "PROGRAM" program_name ";"
object_computer_paragraph ::= "OBJECT-COMPUTER" ";" computer_name "MEMORY" "SIZE"ε integer "WORDS""CHARACTERS""MODULES"ε ocp_entry ";"ε
occurs_clause_format_i ::= "OCCURS" integer "TIMES"ε "ASCENDING""DESCENDING" "KEY"ε "IS"ε data_name "INDEXED" "BY"ε index_nameε
occurs_clause_format_ii ::= "OCCURS" integer "TO"ε integer "TIMES"ε "DEPENDING" "ON"ε qualified_data_name "ASCENDING""DESCENDING" "KEY"ε "IS"ε data_name "INDEXED" "BY"ε index_nameε
ocp_entry ::= "PROGRAM"ε "COLLATING"ε "SEQUENCE" "IS"ε alphabet_nameε "SEGMENT-LIMIT" "IS"ε priority_numberε
open_statement_format_i ::= "OPEN" "INPUT" file_name "REVERSED""WITH"ε "NO" "REWIND"ε"OUTPUT" file_name "WITH"ε "NO" "REWIND"ε"I-O" file_name"EXTEND" file_name
open_statement_format_ii ::= "OPEN" "INPUT" file_name"OUTPUT" file_name"I-O" file_name"EXTEND" file_name
para ::= sentence paragraph_name ";" sentence ε
perform_statement_format_i ::= "PERFORM" procedure_name "THROUGH""THRU" procedure_nameεseries_of_imperative_statementsε "END-PERFORM"
perform_statement_format_ii ::= "PERFORM" procedure_name "THROUGH""THRU" procedure_nameε identifierinteger "TIMES"identifierinteger "TIMES" series_of_imperative_statementsε "END-PERFORM"
perform_statement_format_iii ::= "PERFORM" procedure_name "THROUGH""THRU" procedure_nameε test_phrasetest_phrase series_of_imperative_statementsε "END-PERFORM"
perform_statement_format_iv ::= "PERFORM" procedure_name "THROUGH""THRU" procedure_nameε varying_phrase after_phrasevarying_phrase series_of_imperative_statementsε "END-PERFORM"
picture_clause ::= "PICTURE""PIC" "IS"ε character_string
qsam_or_sam_i_o_control_entries ::= "RERUN" "ON"ε assignment_namefile_name "EVERY"ε integer "RECORDS""END" "OF"ε "REEL""UNIT" "OF"ε file_name "SAME" "RECORD"ε "AREA"ε "FOR"ε file_name file_name "MULTIPLE" "FILE" "TAPE"ε "CONTAINS"ε file_name "POSITION" integerε "APPLY" "WRITE-ONLY" "ON"ε file_name
read_statement_format_i ::= "READ" file_name "NEXT"ε "RECORD"ε "INTO" identifierε
read_statement_format_ii ::= "READ" file_name "RECORD"ε "INTO" identifierε "KEY" "IS"ε qualified_data_nameε
redefines_clause ::=
"REDEFINES" data_namereference_to_procedure_division_name_format_i ::= paragraph_name "IN""OF" section_nameε
reference_to_procedure_division_name_format_ii ::= section_name
relation_condition ::= operand relational_operator operand
release_statement ::= "RELEASE" record_name "FROM" identifierε
renames_clause ::= "RENAMES" qualified_data_name "THROUGH""THRU" qualified_data_nameε
return_statement ::= "RETURN" file_name "RECORD"ε "INTO" identifierε at_end not_at_endε
rewrite_statement ::= "REWRITE" record_name "FROM" identifierε
search_statement_format_i ::= "SEARCH" identifier "VARYING" identifierindex_nameε at_endε "WHEN" condition series_of_imperative_statements"NEXT" "SENTENCE"
search_statement_format_ii ::= "SEARCH" "ALL" identifier at_endε "WHEN" identifier "IS"ε "EQUAL" "TO"ε"=" identifierliteralarithmetic_expressioncondition_name_reference "AND" identifier "IS"ε "EQUAL" "TO"ε"=" identifierliteralarithmetic_expressioncondition_name_reference series_of_imperative_statements"NEXT" "SENTENCE"ε
sect ::= section_name "SECTION" priority_numberε
set_statement_format_i ::= "SET" index_nameidentifier "TO" index_nameidentifierinteger
set_statement_format_ii ::= "SET" index_name "UP" "BY""DOWN" "BY" identifierinteger
set_statement_format_iii ::= "SET" mnemonic_name "TO" "ON""OFF"
set_statement_format_iv ::= "SET" condition_name_reference "TO" "TRUE"
set_statement_format_v ::= "SET" identifier"ADDRESS" "OF" identifier "TO" identifier"ADDRESS" "OF" identifier"NULL""NULLS"
sign_clause ::= "SIGN" "IS"εε "LEADING""TRAILING" "SEPARATE" "CHARACTER"εε
sign_condition ::= operand "IS""NOT""IS" "NOT""NOT" "IS"ε "POSITIVE""NEGATIVE""ZERO"
snp_entry ::= "ON" "STATUS"ε "IS"ε condition "OFF" "STATUS"ε "IS"ε conditionε "OFF" "STATUS"ε "IS"ε condition "ON" "STATUS"ε "IS"ε conditionε
sort_merge_i_o_control_entries ::= "RERUN" "ON" assignment_nameε "SAME" "RECORD""SORT""SORT-MERGE" "AREA"ε "FOR"ε file_name file_name
sort_statement ::= "SORT" file_name "ON"ε "ASCENDING""DESCENDING" "KEY"ε qualified_data_name "WITH"ε "DUPLICATES" "IN"ε "ORDER"εε "COLLATING"ε "SEQUENCE" "IS"ε alphabet_nameε "USING" file_name"INPUT" "PROCEDURE" "IS"ε procedure_name "THROUGH""THRU" procedure_nameε "GIVING" file_name"OUTPUT" "PROCEDURE" "IS"ε procedure_name "THROUGH""THRU" procedure_nameε
source_computer_paragraph ::= "SOURCE-COMPUTER" ";" computer_name "WITH"ε "DEBUGGING" "MODE"ε ";"ε
special_names_paragraph ::= "SPECIAL-NAMES" ";" special_names_clauses ";"ε
start_statement ::= "START" file_name "KEY" "IS"ε "EQUAL" "TO"ε"=""GREATER" "THAN"ε">""NOT" "LESS" "THAN"ε"NOT" "<""GREATER" "THAN"ε "OR" "EQUAL" "TO"ε">=" qualified_data_nameε
stop_statement ::= "STOP" "RUN"literal
string_statement ::= "STRING" identifierliteral "DELIMITED" "BY"ε identifierliteral"SIZE" "INTO" identifier "WITH"ε "POINTER" identifierε
subtract_statement_format_i ::= "SUBTRACT" identifierliteral "FROM" identifier "ROUNDED"ε
subtract_statement_format_ii ::= "SUBTRACT" identifierliteral "FROM" identifierliteral "GIVING" identifier "ROUNDED"ε
subtract_statement_format_iii ::= "SUBTRACT" "CORRESPONDING""CORR" identifier "FROM" identifier "ROUNDED"ε
switch_status_condition ::= condition_name_reference
synchronized_clause ::= "SYNCHRONIZED""SYNC" "LEFT""RIGHT"ε
test_phrase ::= "WITH"ε "TEST" "BEFORE""AFTER"ε "UNTIL" condition
unstring_statement ::= "UNSTRING" identifier "DELIMITED" "BY"ε "ALL"ε identifierliteral "OR" "ALL"ε identifierliteralε "INTO" identifier "DELIMITER" "IN"ε identifierε "COUNT" "IN"ε identifierε "WITH"ε "POINTER" identifierε "TALLYING" "IN"ε identifierε
usage_clause ::= "USAGE" "IS"εε "BINARY""COMP""COMP-1""COMP-2""COMP-3""COMP-4""COMPUTATIONAL""COMPUTATIONAL-1""COMPUTATIONAL-2""COMPUTATIONAL-3""COMPUTATIONAL-4""DISPLAY""DISPLAY-1""INDEX""PACKED-DECIMAL""POINTER"
use_directive_format_i ::= "USE" "GLOBAL"ε "AFTER" "STANDARD"ε "EXCEPTION""ERROR" "PROCEDURE" "ON"ε file_name"INPUT""OUTPUT""I-O""EXTEND"
use_directive_format_ii ::= "USE" "GLOBAL"ε "AFTER" "STANDARD"ε "BEGINNING""ENDING"ε "FILE""REEL""UNIT"ε "LABEL" "PROCEDURE" "ON"ε file_name"INPUT""OUTPUT""I-O""EXTEND"
use_directive_format_iii ::= "USE" "FOR"ε "DEBUGGING" "ON"ε procedure_name"ALL" "PROCEDURES"
value_clause_format_i ::= "VALUE" "IS"ε literal
value_clause_format_ii ::= "VALUE" "IS"ε"VALUES" "ARE"ε literal "THROUGH""THRU" literalε
varying_phrase ::= "WITH"ε "TEST" "BEFORE""AFTER"ε "VARYING" identifierindex_name "FROM" identifierindex_nameliteral "BY" identifierliteral "UNTIL" condition
vsam_i_o_control_entries ::= "RERUN" "ON"ε assignment_namefile_name "EVERY"ε integer "RECORDS" "OF"ε file_name "SAME" "RECORD"ε "AREA"ε "FOR"ε file_name file_name
w_phrase ::= at_eop not_at_eop at_eop not_at_eop
write_statement_format_i ::= "WRITE" record_name "FROM" identifierε