The Procedure Division contains the routines that process the files and data described in the Environment and Data Divisions.
1 – 1format_declaratives
The Procedure Division contains the routines that process the files and data described in the Environment and Data Divisions. Format 1 - [ PROCEDURE DIVISION [ USING {data-name} ... ] [ GIVING identifier ] . [ DECLARATIVES. { section-name SECTION [ segment-number ] . declarative-sentence [ paragraph-name. [sentence] ... ] ... } ... END DECLARATIVES. ] { section-name SECTION [ segment-number ] . [ paragraph-name. [sentence] ... ] ... } ... ]
2 – 2format
The Procedure Division contains the routines that process the files and data described in the Environment and Data Divisions. Format 2 - [ PROCEDURE DIVISION [ USING {data-name} ... ] [ GIVING identifier ] ] . [ paragraph-name. [sentence] ... ] ... ]
3 – miscellaneous_topics
3.1 – arithmetic-expressions
An arithmetic expression can be one of the following: 1) An identifier (including function-identifier) of a numeric elementary item 2) A numeric literal 3) Two or more of the above choices separated by arithmetic operators (+, -, *, /, **) 4) Two or more arithmetic expressions separated by an arithmetic operator (+, -, *, /, **) 5) An arithmetic expression enclosed in parentheses A unary operator (a sign) can precede any arithmetic expression. The identifiers and literals in an arithmetic expression must represent either: (1) numeric elementary items (including functions), or (2) numeric literals on which arithmetic can be performed.
3.2 – conditional_expressions
A conditional expression specifies a condition the program must evaluate to determine the path of program flow.
3.2.1 – abbreviated
When you combine simple or negated simple conditions in a consecutive sequence, you can abbreviate any of the relation conditions except the first. You can do this by either: 1) Omitting the subject of the relation condition 2) Omitting both the subject and the relational operator of the condition A relation condition in the consecutive sequence must contain a subject (or subject and relational operator) that is common with the preceding relation condition. There must be no parentheses in the consecutive sequence. Format - relation-condition { { AND } [NOT] [relational-operator] object } ... { { OR } }
3.2.2 – class
The class condition tests whether the contents of an operand are numeric or alphabetic. It also determines if an alphabetic operand contains only uppercase or only lowercase characters or if the operand is a class-name. Format - { NUMERIC } identifier-1 IS [ NOT ] { ALPHABETIC } { ALPHABETIC-LOWER } { ALPHABETIC-UPPER } { class-name }
3.2.2.1 – identifier-1
Identifier-1 must reference a data item whose usage is explicitly or implicitly DISPLAY. If identifier-1 is a function-identifier, it must reference an alphanumeric function.
3.2.2.2 – class-name
is the user-defined word for a class. It always possesses the global attribute
3.2.3 – combined_and_negated_combined
A combined condition results from connecting conditions with one of the logical operators AND or OR. Format - condition { { AND } condition } ... { { OR } } condition can be 1) A simple condition 2) A negated simple condition 3) A combined condition 4) A negated combined condition 5) Valid combinations of the preceding conditions
3.2.4 – condition-name
The condition-name condition determines if a data item contains a value assigned to one of that item's condition-names. The term conditional variable refers to the data item. Condition-name refers to a level 88 entry associated with that item. Format - condition-name
3.2.5 – database_key_condition
Database conditions allow alternate paths of control depending on the truth value of a test involving conditions peculiar to the database environment. The database conditions are the tenancy, member, and database key conditions. The database key condition determines whether: (1) two database key values identify the same database record, (2) a database key value is null, or (3) a database key value is identical to any database key value in a keeplist. Format - { ALSO database-key } database-key IS [ NOT ] { NULL } { WITHIN keeplist-name } database-key references a currency indicator or a keeplist entry in the Sub-Schema Section.
3.2.6 – member_database_condition
Database conditions allow alternate paths of control depending on the truth value of a test involving conditions peculiar to the database environment. The database conditions are the tenancy, member, and database key conditions. The member condition determines whether member records are present in one or more sets. Only member record types defined in the Sub-Schema Section are considered in determining the truth value of the condition. Format - [ set-name IS ] [ NOT ] EMPTY set-name is a subschema set name.
3.2.7 – negated_simple
The logical operator NOT negates a simple condition. The truth value of a negated simple condition is the opposite of the simple condition's truth value. Thus, the truth value of a negated simple condition is true only if the simple condition's truth value is false. It is false only if the simple condition's truth value is true. Format - NOT simple-condition
3.2.8 – relation
A relation condition states a relation between two operands. The program compares the operands to determine whether the stated relation is true or false. The first operand is called the condition's subject. The second operand is called its object. Either operand can be: (1) an identifier, (2) a literal, or (3) the value of an arithmetic expression. The set of words that specifies the type of comparison is called the relational operator. Format - {IS [NOT] GREATER THAN } {IS [NOT] > } {IS [NOT] LESS THAN } {identifier-1 } {IS [NOT] < } {identifier-2 } {literal-1 } {IS [NOT] EQUAL TO } {literal-2 } {arith-express-1} {IS [NOT] = } {arith-express-2} {IS GREATER THAN OR EQUAL TO} {IS >= } {IS LESS THAN OR EQUAL TO } {IS <= }
3.2.9 – sign
The sign condition determines if the algebraic value of an arithmetic expression is less than, greater than, or equal to zero. Format - { POSITIVE } arithmetic-expression IS [ NOT ] { NEGATIVE } { ZERO }
3.2.10 – success-failure
This condition tests the return status codes of COBOL and non-COBOL procedures for success or failure conditions. Format - status-code-id IS { SUCCESS } { FAILURE } status-code-id must be a word or longword COMP integer as represented by PIC S9(1 to 9) COMP.
3.2.11 – switch-status
The switch-status condition tests the "on" or "off" setting of an external logical program switch. Format - condition-name
3.2.12 – tenancy_database_condition
Database conditions allow alternate paths of control depending on the truth value of a test involving conditions peculiar to the database environment. The database conditions are the tenancy, member, and database key conditions. The tenancy conditions determine whether a record in the database is an owner, or member, or a tenant in one or more sets. Format - { OWNER } [ NOT ] [ set-name ] { MEMBER } { TENANT } set-name is a subschema set name.
3.3 – database_key_identifiers
Database key identifiers are in Record Selection Expressions. If a database exception condition occurs during the execution of a FETCH or FIND statement, the Database Control System (DBCS) places a database exception condition code in the special register DB-CONDITION. This code identifies the condition. The DBCS also places the record name of database-record in the special register DB-CURRENT-RECORD-NAME and its UID in DB-CURRENT-RECORD-ID. Format 1 - Currency Indicator Access [ { record-name } ] CURRENT [ WITHIN { set-name } ] [ { realm-name } ] Format 2 - Keeplist Access { OFFSET integer-exp } { FIRST } WITHIN keeplist-name { LAST }
3.4 – declaratives
Declaratives specify procedures to be executed only when certain conditions occur. You must write declarative procedures at the beginning of the Procedure Division in consecutive sections. The key word DECLARATIVES begins the declaratives part of the Procedure Division; the pair of key words END DECLARATIVES ends it. Each of these reserved word phrases must: (1) be on a line by itself, starting in Area A; and (2) be followed by a separator period. When you use declarative procedures, you must divide the remainder of the Procedure Division into sections. Format - [ DECLARATIVES. { section-name SECTION [ segment-number ] . declarative-sentence [ paragraph-name. [sentence] ... ] ... } ... END DECLARATIVES. ]
3.5 – I-O status
If a file description entry has a FILE STATUS clause, a value is placed in the two-character FILE STATUS data item during execution of a CLOSE, DELETE, OPEN, READ, REWRITE, START, UNLOCK, or WRITE statement. Two "keys" combine to form this value. Status Key 1 occupies the leftmost character position in the item and Status Key 2 occupies the rightmost position. In combination, the keys indicate the status of the input-output operation.
3.6 – identifiers
In Procedure Division rules, the term identifier means the complete specification of a data item. The term refers to all words required to make your reference to the item unique. To reference a data item that is a function, a function-identifier is used. Format 1 - data-name [qualification] [subscripting] [reference modification] Format 2 - data-name [qualification] [indexing] [reference modification] Format 3 - FUNCTION function-name [ ({argument}...) ] [reference modification]
3.7 – functions
A function (synonymous with intrinsic function) is a temporary data item that represents a value to be determined at the time the function is referenced during the execution of a statement. The value can be alphanumeric, numeric, or integer. A function-identifier is a syntactically correct combination of character strings and separators that uniquely references the data item resulting from the evaluation of a function. Functions are treated as elementary data items, but cannot be receiving operands. A function-identifier that references an alphanumeric function can be specified wherever an identifier is permitted and where a reference to a function is not specifically prohibited by general-format rules. An integer or numeric function can be used anywhere an arithmetic expression can be used, subject to certain restrictions. The general format of a function-identifier is as follows: FUNCTION function-name [({argument}... )] [reference-modifier] A function-name is one of the names listed below. Most function-names are key words but not reserved words (the exceptions are LENGTH, RANDOM, and SUM, which are reserved words, as is FUNCTION), and can be used in a program outside the context of a function. An argument is an identifier (including a function-identifier), a literal an arithmetic expression, or a table that complies with the specific rules governing the number, class, and category of arguments for the function. The arguments in an argument list may be separated by a comma; they are evaluated individually, from left to right. A reference-modifier can be specified only for alphanumeric functions. It specifies the beginning character position and optionally the length of the resulting data item. The functions are listed below. For a complete description of the functions, including their formats, see the chapter on Intrinsic Functions in the COBOL Reference Manual. ACOS LENGTH ORD-MIN* ANNUITY LOG PRESENT-VALUE* ARGCOUNT LOG10 RANDOM ASIN LOWER-CASE RANGE* ATAN MAX* REM CHAR MEAN* REVERSE COS MEDIAN* SIN CURRENT-DATE MIDRANGE* SQRT DATE-OF-INTEGER MIN* STANDARD-DEVIATION* DAY-OF-INTEGER MOD SUM* FACTORIAL NUMVAL TAN INTEGER NUMVAL-C UPPER-CASE INTEGER-OF-DATE ORD VARIANCE* INTEGER-OF-DAY ORD-MAX* WHEN-COMPILED INTEGER-PART *Functions which permit a variable number of arguments which may include occurring items subscripted by "ALL" for one or more of its dimensions. In addition, five new Y2K functions are documented in the release notes: YEAR-TO-YYYY DATE-TO-YYYYMMDD DAY-TO-YYYYDDD TEST-DATE-YYYYMMDD TEST-DAY-YYYYMMDD
3.8 – indexing
Indexing is a special subscripting procedure. In indexing, you use the INDEXED BY phrase of the OCCURS clause to assign an index-name to each table level. You then refer to a table element using the index-name as a subscript. Format - { data-name } ( { , index-name [ { + } literal-2 ] } ) { condition-name } ( { [ { - } ] } ... ) ( { , literal-1 } )
3.9 – phrases
3.9.1 – AT_END
The AT END phrase specifies the action your program takes when the AT END condition occurs. Format - AT END stment
3.9.2 – AT_END-OF-PAGE
The AT END-OF-PAGE phrase specifies the action your program takes when the AT END-OF-PAGE condition occurs. Format - AT END-OF-PAGE stment
3.9.3 – CORRESPONDING
The CORRESPONDING option allows you to specify group items as operands in order to use their corresponding subordinate items in an operation.
3.9.4 – FROM
Format 1 - record-name FROM identifier Format 2 - FROM { keeplist-name } ... Keeplist-name refers to a user-defined keeplist in the Sub-Schema Section. Record-name and identifier must not refer to the same storage area. After statement execution ends, the data in the area referenced by identifier is available to the program. The data is not available in the area referenced by record-name, unless there is an applicable SAME clause.
3.9.5 – INTO
The INTO phrase implicitly moves a current record from the record storage area into an identifier. Format - file-name INTO identifier
3.9.6 – INVALID_KEY
The INVALID KEY phrase specifies the action your program takes when an invalid key condition is detected for the file being processed. Format - INVALID KEY stment
3.9.7 – NOT_AT_END
The NOT AT END phrase specifies the action your program takes when the AT END condition does not occur. Format - NOT AT END stment
3.9.8 – NOT_AT_END-OF-PAGE
The NOT AT END-OF-PAGE phrase specifies the action your program takes when the AT END-OF-PAGE condition does not occur. Format - NOT AT END-OF-PAGE stment
3.9.9 – NOT_INVALID_KEY
The NOT INVALID KEY phrase specifies the action your program takes when an invalid key condition is not detected for the file being processed. Format - NOT INVALID KEY stment
3.9.10 – NOT ON ERROR database
The database on error exception condition occurs when the Database Control System (DBCS) encounters any database exception condition for any Data Manipulation Language (DML) statement. The NOT ON ERROR phrase in a DML statement allows the selection of an imperative statement sequence when any database exception condition does not occur. Format - NOT ON ERROR stment
3.9.11 – NOT_ON_EXCEPTION
The NOT ON EXCEPTION phrase allows execution of an imperative statement when an exception (or error) condition does not occur. Format - NOT ON EXCEPTION stment
3.9.12 – NOT_ON_OVERFLOW
The NOT ON OVERFLOW phrase allows you to specify an action for your program to take when an overflow condition does not exist. Format - NOT ON OVERFLOW stment
3.9.13 – NOT_ON_SIZE_ERROR
The NOT ON SIZE ERROR phrase allows you to specify an action for your program to take when a size error condition does not exist. Format - NOT ON SIZE ERROR stment
3.9.14 – ON ERROR database
The database on error exception condition occurs when the Database Control System (DBCS) encounters any database exception condition for any Data Manipulation Language (DML) statement. The ON ERROR phrase in a DML statement allows the selection of an imperative statement sequence when any database exception condition occurs. Format - ON ERROR stment
3.9.15 – ON_EXCEPTION
The ON EXCEPTION phrase allows execution of an imperative statement when an exception (or error) condition occurs. The ON EXCEPTION option of the CALL statement prevents control transfer of the CALL and triggers the execution of the imperative statement related to the CALL. The ON EXCEPTION option of the ACCEPT statement allows you to handle data entry errors when ACCEPTing into a numeric data field WITH CONVERSION. Format - ON EXCEPTION stment
3.9.16 – ON_OVERFLOW
The ON OVERFLOW phrase allows you to specify an action for your program to take when an overflow condition exists. Format - ON OVERFLOW stment
3.9.17 – ON_SIZE_ERROR
The ON SIZE ERROR phrase allows you to specify an action for your program to take when a size error condition exists. Format - ON SIZE ERROR stment
3.9.18 – RETAINING
The RETAINING clause specifies which currency indicators are not updated during the execution of the CONNECT, FETCH, FIND, MODIFY, RECONNECT, and STORE statements. Format - [ [ {| REALM |} ] ] [ RETAINING [ {| RECORD |} ] CURRENCY ] [ [ {| { SET [ set-name ] ... } |} ] ] [ [ {| { { set-name } ... } |} ] ] set-name is a subschema set name.
3.9.19 – ROUNDED
The rounding operation adds 1 to the absolute value of the low-order digit of the resultant identifier if the absolute value of the next least significant (lower-valued) digit of the intermediate data item is greater than or equal to 5. If you do not use the ROUNDED phrase, any excess low-order digits in the arithmetic result are truncated when the result is moved to the resultant identifier(s).
3.10 – qualification
A reference to a user-defined word is unique if: 1) no other name has the same spelling, including hyphenation, 2) it is a part of a REDEFINES clause (the reference following the word REDEFINES is unique because of clause placement), or 3) scoping rules make it unique. A name in a hierarchy of names can occur in more than one place in your program. Unless you are redefining it, you must refer to this nonunique name using one or more higher-level names in the hierarchy. These higher-level names are called qualifiers. Using them to achieve uniqueness of reference is called qualification. To make your reference unique, you need not specify all available qualifiers for a name, only the one(s) necessary to avoid ambiguity. You cannot use the same data-name as: 1) The name of an external record and as the name of any other external data item in any program contained within or containing the program describing the external data record. 2) The name of an item possessing the global attribute and as the name of any other data item in the program describing the global data item.
3.10.1 – 1format_file
Format 1 - { { { IN } data-name-2 } ... [ { IN } file-name ] } { data-name-1 }{ { { OF } } [ { OF } ] } { condition-name }{ { IN } file-name } { { OF } }
3.10.2 – 2format_paragraph
Format 2 - paragraph-name { IN } section-name { OF }
3.10.3 – 3format_text
Format 3 - text-name { IN } library-name { OF }
3.10.4 – 4format LINAGE
Format 4 - LINAGE-COUNTER { IN } file-name { OF }
3.10.5 – 5format PAGE LINE
Format 5 - { PAGE-COUNTER } { IN } report-name { LINE-COUNTER } { OF }
3.10.6 – 6format_report
Format 6 - { { IN } data-name-4 [ { IN } report-name ] } data-name-3 { { OF } [ { OF } ] } { { IN } report-name } { { OF } }
3.10.7 – 7format_screens
Format 7 - screen-name-1 { { OF } screen-name-2 } ... { { IN } }
3.10.8 – 8format RMS
Format 8 - { RMS-STS } { IN } file-name { RMS-STV } { OF } { RMS-FILENAME }
3.11 – record_selection_expressions
A record selection expression is used to select a record in the database. It can be used in a FETCH or FIND statement. The record thus selected becomes the current record of the run unit upon which subsequent statements may operate when accessing the database.
3.11.1 – 1format_database_key_identifier_access
This format selects a record by a database key value held by the Database Control System (DBCS) in a currency indicator or a keeplist entry. Format 1 - Database Key Identifier Access database-key-identifier
3.11.1.1 – database-key-identifier
identifies a record according to the rules of Database Key Identifiers.
3.11.2 – 2format_set_owner_access
This format selects the record that owns a set. Format 2 - Set Owner Access OWNER WITHIN set-name
3.11.2.1 – set-name
is a subschema set name. The Database Control System (DBCS) uses the currency indicator for set-name to choose the owner record of that set occurrence. A database exception condition occurs if set-name is a singular set (DB-CONDITION is set to DBM$_SINGTYP) or if the currency indicator for the set type is null (DB-CONDITION is set to DBM$_CSTYP_NULL).
3.11.3 – 3format_record_search_access
This format selects a record by its position within a collection of records and optionally by its record type and contents. Format 3 - Record Search Access { FIRST } { LAST } { NEXT } { PRIOR } { ANY } { DUPLICATE } { [ RELATIVE ] int-exp } [record-name] [ WITHIN { realm-name } ] [ USING { rec-key } ... ] [ { set-name } ] [ WHERE { bool-expres } ]
3.11.3.1 – int-exp
is an integer or arithmetic expression resulting in a longword integer value. It cannot be zero.
3.11.3.2 – realm-name
is a subschema realm name.
3.11.3.3 – record-name
is a subschema record name.
3.11.3.4 – set-name
is a subschema set name.
3.11.3.5 – rec-key
is a key data item within the subschema record occurrence. The same rec-key can appear only once in a given USING phrase.
3.11.3.6 – bool-expres
is a conditional expression that involves data items of the object record. It is used to specify additional requirements of a qualifying record. bool-expres: { bool-alt [ OR bool-alt ] ... } bool-alt: { simp-bool-rel [ AND simp-bool-rel ] ... } simp-bool-rel: { bool-condit } { NOT bool-expres } bool-condit: { { {[ NOT ] EQUAL TO } } } { { {[ NOT ] = } } } { { {[ NOT ] LESS THAN } } } { { IS {[ NOT ] < } } } { { {[ NOT ] GREATER THAN } } } { { {[ NOT ] > } } } { { id } { { GREATER THAN OR EQUAL TO } } { id } } { { lit } { { >= } } { lit } } { { { LESS THAN OR EQUAL TO } } } { { { <= } } } { { DOES {[ NOT ] CONTAIN } } } { { {[ NOT ] CONTAINS } } } { { {[ NOT ] MATCH } } } { { {[ NOT ] MATCHES } } }
3.11.3.6.1 – bool-alt
is one or more sub-expressions (simp-bool-rel). Pairs of sub-expressions are joined by the logical operator AND.
3.11.3.6.2 – simp-bool-rel
is a simple-condition (bool-condit), an expression, or the negation of either.
3.11.3.6.3 – bool-condit
a simple-condition is a relation involving two operands joined by a relational operator. At least one operand in each relation must be an item in the record being found or fetched.
3.11.4 – 4format_database_key_access
This format selects the record that is referred to by the database key value contained in the special register DB-KEY. Format 4 - Database Key Access DBKEY
3.12 – reference_modification
Reference modification defines a subset of a data item by specifying its leftmost character and length. Format 1 - data-name ( leftmost-character-position : [ length ] ) Format 2 - FUNCTION function-name [ ({argument}...) ] ( leftmost-character-position : [ length ] )
3.13 – segmentation
VSI COBOL programs execute in a virtual memory environment. Therefore, programs need not manage physical memory by overlaying Procedure Division code. In VSI COBOL, segmentation controls the assignment of Procedure Division sections to fixed or independent segments. The optional segment-number in the section header specifies the type of segment. Format - section-name SECTION [ segment-number ] .
3.13.1 – section-name
names a Procedure Division section.
3.13.2 – segment-number
must be an integer in the range 0 through 99. If there is no segment-number in a section header, the implied segment-number is 0.
3.13.3 – fixed_segments
Fixed segments appear to reside in memory at all times. A fixed segment is in its initial state the first time the program calls it. On later calls, the fixed segment is in its last-used state.
3.13.4 – independent_segments
The state of an independent segment depends on how and when it receives control.
3.14 – subscripting
Subscripts can appear only in references to individual elements in a list, or table, of like elements that do not have individual data-names. Format 1 - { data-name } ( { arithmetic-expression } ... ) { condition-name } Format 2 - { ALL } argument ( { integer-1 } { data-name [ {+|-} integer-2 ] } ... ) { index-name [ {+|-} integer-3 ] } In Format 2, argument is an intrinsic function argument that is allowed to be repeated a variable number of times. Note that Format 1 may also be used for intrinsic function arguments when ALL sub- scripts are not specified. In Format 2, when ALL is specified as a subscript, the effect is as if each table element associated with that subscript position were specified.
4 – ACCEPT
The ACCEPT statement makes low-volume data available to the program. The HP extensions to the ACCEPT statement (formats 3, 4 and 5) are COBOL language additions that facilitate video forms design and data handling.
4.1 – 1format FROM input
The ACCEPT statement makes low-volume data available to the program. The HP extensions to the ACCEPT statement (formats 3, 4 and 5) are COBOL language additions that facilitate video forms design and data handling. Format 1 - ACCEPT dest-item [FROM input-source] [ AT END stment ] [ NOT AT END stment ] [ END-ACCEPT ]
4.1.1 – dest-item
is the identifier of a data item into which data is accepted.
4.1.2 – input-source
is a mnemonic-name defined in the SPECIAL-NAMES paragraph of the Environment Division.
4.1.3 – stment
is an imperative statement executed for an AT END or NOT AT END condition.
4.2 – 2format FROM
The ACCEPT statement makes low-volume data available to the program. The HP extensions to the ACCEPT statement (formats 3, 4 and 5) are COBOL language additions that facilitate video forms design and data handling. Format 2 - { DATE [YYYYMMDD] } ACCEPT dest-item FROM { DAY [YYYYDDD] } { DAY-OF-WEEK } { TIME }
4.2.1 – dest-item
is the identifier of a data item into which data is accepted.
4.3 – 3format_screen_extensions
The ACCEPT statement makes low-volume data available to the program. The HP extensions to the ACCEPT statement (formats 3, 4 and 5) are COBOL language additions that facilitate video forms design and data handling. Format 3 - ACCEPT dest-item {| { line-num } |} {| FROM LINE NUMBER { line-id [ PLUS [ plus-num ] ] } |} {| { PLUS [ plus-num ] } |} {| { column-num } |} {| FROM COLUMN NUMBER { column-id [ PLUS [ plus-num ] ] } |} {| { PLUS [ plus-num ] } |} {| ERASE [TO END OF] { SCREEN } |} {| { LINE } |} {| WITH BELL |} {| UNDERLINED |} {| BOLD |} {| WITH BLINKING |} {| PROTECTED [| SIZE { prot-size-lit } |] |} {| [| { prot-size-item } |] |} {| [| WITH AUTOTERMINATE |] |} {| [| WITH EDITING |] |} {| [| WITH NO BLANK |] |} {| [| WITH FILLER prot-fill-lit |] |} {| WITH CONVERSION |} {| REVERSED |} {| WITH NO ECHO |} {| DEFAULT IS { def-src-lit } |} {| { def-src-item } |} {| { CURRENT VALUE } |} {| CONTROL KEY IN key-dest-item |} { [ ON EXCEPTION stment ] [ NOT ON EXCEPTION stment ] } { [ AT END stment ] [ NOT AT END stment ] } [ END-ACCEPT ]
4.3.1 – dest-item
is the identifier of a data item into which data is accepted.
4.3.2 – line-num
is a numeric literal that specifies a line position on the terminal screen. Line-num must be a positive integer. It cannot be zero.
4.3.3 – line-id
is the identifier of a data item that provides a line position on the terminal screen.
4.3.4 – column-num
is a numeric literal that specifies a column position on the terminal screen. Column-num must be a positive integer. It cannot be zero.
4.3.5 – column-id
is the identifier of a data item that provides a column position on the terminal screen.
4.3.6 – plus-num
is a numeric literal that increments the current value for line or column position, or that increments the value of line-id or column-id. Plus-num can be zero or a positive integer.
4.3.7 – prot-size-lit
is a numeric literal that specifies the maximum length of the video screen field into which data can be typed. Prot-size-lit must be a positive integer. It cannot be zero.
4.3.8 – prot-size-item
is the identifier of a numeric integer data item that specifies the maximum length of the video screen field into which data can be typed. It must be a positive integer; it cannot be zero.
4.3.9 – prot-fill-lit
is a single character alphanumeric literal that is used to initialize each character position of a protected video screen field into which data can be typed.
4.3.10 – def-src-lit
is a nonnumeric literal or a figurative constant. However, it cannot be the figurative constant ALL literal.
4.3.11 – def-src-item
is the identifier of an alphanumeric data item.
4.3.12 – key-dest-item
is the identifier of a data item that defines a control key. Key-dest-item must specify an alphanumeric data item at least four characters in length.
4.3.13 – stment
is an imperative statement executed for an AT END, NOT AT END, ON EXCEPTION or NOT ON EXCEPTION condition.
4.4 – 4format screen extensions CONTROL KEY
The ACCEPT statement makes low-volume data available to the program. The HP extensions to the ACCEPT statement (formats 3, 4 and 5) are COBOL language additions that facilitate video forms design and data handling. Format 4 - ACCEPT CONTROL KEY IN key-dest-item {| { line-num } |} {| FROM LINE NUMBER { line-id [ PLUS [ plus-num ] ] } |} {| { PLUS [ plus-num ] } |} {| { column-num } |} {| FROM COLUMN NUMBER { column-id [ PLUS [ plus-num ] ] } |} {| { PLUS [ plus-num ] } |} {| ERASE [TO END OF] { SCREEN } |} {| { LINE } |} {| WITH BELL |} { [ ON EXCEPTION stment ] [ NOT ON EXCEPTION stment ] } { [ AT END stment ] [ NOT AT END stment ] } [ END-ACCEPT ]
4.4.1 – line-num
is a numeric literal that specifies a line position on the terminal screen. Line-num must be a positive integer. It cannot be zero.
4.4.2 – line-id
is the identifier of a data item that provides a line position on the terminal screen.
4.4.3 – column-num
is a numeric literal that specifies a column position on the terminal screen. Column-num must be a positive integer. It cannot be zero.
4.4.4 – column-id
is the identifier of a data item that provides a column position on the terminal screen.
4.4.5 – plus-num
is a numeric literal that increments the current value for line or column position, or that increments the value of line-id or column-id. Plus-num can be zero or a positive integer.
4.4.6 – key-dest-item
is the identifier of a data item that defines a control key. Key-dest-item must specify an alphanumeric data item at least four characters in length.
4.4.7 – stment
is an imperative statement executed for an AT END, NOT AT END, ON EXCEPTION or NOT ON EXCEPTION condition.
4.5 – 5format_screen_section_extensions
The ACCEPT statement makes low-volume data available to the program. The HP extensions to the ACCEPT statement (formats 3, 4 and 5) are COBOL language additions that facilitate video forms design and data handling. Format 5 - ACCEPT screen-name [ {| LINE NUMBER { line-num } |} ] [ {| { line-id } |} ] [ AT {| |} ] [ {| COLUMN NUMBER { column-num } |} ] [ {| { column-id } |} ] [ ON EXCEPTION stment ] [ NOT ON EXCEPTION stment2 ] [ END-ACCEPT ]
4.5.1 – screen-name
is the name of a screen item defined in the SCREEN SECTION of the program.
4.5.2 – line-num
is a numeric literal that specifies a line position on the terminal screen. Line-num must be a positive integer. It cannot be zero.
4.5.3 – line-id
is the identifier of a data item that provides a line position on the terminal screen.
4.5.4 – column-num
is a numeric literal that specifies a column position on the terminal screen. Column-num must be a positive integer. It cannot be zero.
4.5.5 – column-id
is the identifier of a data item that provides a column position on the terminal screen.
4.5.6 – stment
is an imperative statement executed for an AT END, NOT AT END, ON EXCEPTION or NOT ON EXCEPTION condition.
5 – ADD
The ADD statement adds two or more numeric operands and stores the result.
5.1 – 1format TO
The ADD statement adds two or more numeric operands and stores the result. Format 1 - ADD { num } ... TO { rsult [ ROUNDED ] } ... [ ON SIZE ERROR stment ] [ NOT ON SIZE ERROR stment ] [ END-ADD ]
5.1.1 – num
is a numeric literal or the identifier of an elementary numeric item.
5.1.2 – rsult
is the identifier of an elementary numeric item. It is the resultant identifier.
5.1.3 – stment
is an imperative statement.
5.2 – 2format GIVING
The ADD statement adds two or more numeric operands and stores the result. Format 2 - ADD { num } ... TO { num } GIVING { rsult [ ROUNDED ] } ... [ ON SIZE ERROR stment ] [ NOT ON SIZE ERROR stment ] [ END-ADD ]
5.2.1 – num
is a numeric literal or the identifier of an elementary numeric item.
5.2.2 – rsult
is the identifier of an elementary numeric item or an elementary numeric edited item. It is the resultant identifier.
5.2.3 – stment
is an imperative statement.
5.3 – 3format CORRESPONDING
The ADD statement adds two or more numeric operands and stores the result. Format 3 - ADD { CORRESPONDING } grp-1 TO grp-2 [ ROUNDED ] { CORR } [ ON SIZE ERROR stment ] [ NOT ON SIZE ERROR stment ] [ END-ADD ]
5.3.1 – grp
is the identifier of a numeric group item.
5.3.2 – stment
is an imperative statement.
6 – ALTER
The ALTER statement changes the destination of a GO TO statement. Format - ALTER { proc TO [ PROCEED TO ] new-proc } ...
6.1 – proc
is the name of a paragraph that contains one sentence: a GO TO statement without the DEPENDING phrase.
6.2 – new-proc
is a procedure-name.
7 – CALL
The CALL statement transfers control to another program in the executable image. Format - CALL prog-name [ {{{ [BY REFERENCE] } }} [{{BY REFERENCE } }] ] [ {{{ BY CONTENT } }} [{{BY CONTENT } }] ] [USING{{{ BY DESCRIPTOR }{arg}...}} [{{BY DESCRIPTOR}{arg}...}] ... ] [ {{{ BY VALUE } }} [{{BY VALUE } }] ] [ { OMITTED } [ OMITTED ] ] [ GIVING function-res ] { [ ON EXCEPTION stment ] [ NOT ON EXCEPTION stment ] } { [ ON OVERFLOW stment ] [ NOT ON OVERFLOW stment ] } [ END-CALL ]
7.1 – prog-name
is a nonnumeric literal or the identifier of an alphanumeric data item. It is the name of the program to which control transfers.
7.2 – arg
is the argument. It identifies the data that is available to both the calling and called programs. It is any data item described in the File Section, Working-Storage Section, or Linkage Section, or it is a nonnumeric literal. It must not be a function-identifier.
7.3 – function-res
is the identifier of an elementary integer numeric data item with COMP, COMP-1, or COMP-2 usage and no scaling positions. Function-res can be subscripted, and it can be qualified. When control returns to the calling program, function-res can contain a function result.
7.4 – stment
is an imperative statement.
8 – CANCEL
The CANCEL statement removes the logical relationship to another program. Format - CANCEL { prog-name } ...
8.1 – prog-name
is a nonumeric literal or the identifier of an alphanumeric data item. It contains the program-name of the program to be cancelled.
9 – CLOSE
The CLOSE statement ends processing of reels (or units) and files. It can also perform rewind, lock, and removal operations. Format - { [ { REEL } [ FOR REMOVAL ] ] } CLOSE { file-name [ { UNIT } [ WITH NO REWIND ] ] } ... { [ WITH { NO REWIND } ] } { [ { LOCK } ] }
9.1 – file-name
is the name of a file described in the Data Division. It cannot be a sort or merge file.
10 – COMMIT
The COMMIT statement ends your database transaction, makes permanent all changes made to the database since the last quiet point, and establishes a new quiet point for this run unit. Format - COMMIT [ RETAINING ] [ ON ERROR stment ] [ NOT ON ERROR stment ] [ END-COMMIT ]
10.1 – stment
is an imperative statement.
11 – COMPUTE
The COMPUTE statement evaluates an arithmetic expression and stores the result. Format - COMPUTE { rsult [ ROUNDED ] } ... = arithmetic-expression [ ON SIZE ERROR stment ] [ NOT ON SIZE ERROR stment ] [ END-COMPUTE ]
11.1 – rsult
is the identifier of an elementary numeric item or an elementary numeric edited item. It is the resultant identifier.
11.2 – stment
is an imperative statement.
12 – CONNECT
The CONNECT statement inserts the current record of the run unit as a member record into one or more sets. The set occurrence for each insertion is determined by the currency indicator for the corresponding set type. Format - CONNECT [ record-name ] TO { { set-name } ... } { ALL } [ [{| REALM |}] ] [ RETAINING [{| RECORD |}] CURRENCY ] [ [{| { SET [ set-name ] ... } |}] ] [ [{| { { set-name } ... } |}] ] [ ON ERROR stment ] [ NOT ON ERROR stment ] [ END-CONNECT ]
12.1 – record-name
names a subschema record type.
12.2 – set-name
names a subschema set type.
12.3 – stment
is an imperative statement.
13 – CONTINUE
The CONTINUE statement indicates that no executable statement is present. It causes an implicit control transfer to the next executable statement. Format - CONTINUE
14 – DELETE
The DELETE statement logically removes a record from a mass storage file. Format - DELETE file-name RECORD [ INVALID KEY stment ] [ NOT INVALID KEY stment ] [ END-DELETE ]
14.1 – file-name
is the name of a relative or indexed file described in the Data Division. It cannot be the name of a sequential file or a sort or merge file.
14.2 – stment
is an imperative statement.
15 – DISCONNECT
The DISCONNECT statement logically removes the current record of the run unit from one or more sets. Format - DISCONNECT [record-name] FROM { { set-name } ... } { ALL } [ ON ERROR stment ] [ NOT ON ERROR stment ] [ END-DISCONNECT ]
15.1 – record-name
names a subschema record type.
15.2 – set-name
names a subschema set type.
15.3 – stment
is an imperative statement.
16 – DISPLAY
The DISPLAY statement transfers low-volume data from the program to the default system output device or to the object of a mnemonic-name. The HP extensions to the DISPLAY statement, Formats 2 and 3, are COBOL language additions that facilitate video forms design and data handling. Format 4 sets a program variable to the current command line argument number to read with a Format 7 ACCEPT. Format 5 sets the name of an environment variable or system logical while Format 6 sets the value of an environment variable or system logical.
16.1 – 1format_statement
The DISPLAY statement transfers low-volume data from the program to the default system output device or to the object of a mnemonic-name. The HP extensions to the DISPLAY statement (formats 2 and 3) are COBOL language additions that facilitate video forms design and data handling. Format 1 - DISPLAY { src-item } ... [ UPON output-dest ] [ WITH NO ADVANCING ] [ WITH CONVERSION] [ END-DISPLAY ]
16.1.1 – src-item
is a literal or the identifier of a data item. The literal can be any figurative constant including ALL literal.
16.1.2 – output-dest
is a mnemonic-name defined in the SPECIAL-NAMES paragraph of the Environment Division.
16.2 – 2format_screen_extensions
The DISPLAY statement transfers low-volume data from the program to the default system output device or to the object of a mnemonic-name. The HP extensions to the DISPLAY statement (formats 2 and 3) are COBOL language additions that facilitate video forms design and data handling. Format 2 - DISPLAY { src-item [{| { line-num } |}] } [{| AT LINE NUMBER { line-id [ PLUS [ plus-num ] ] } |}] } [{| { PLUS [ plus-num ] } |}] } [{| { column-num } |}] } [{| AT COLUMN NUMBER { column-id [ PLUS [ plus-num ] ] } |}] } [{| { PLUS [ plus-num ] } |}] } [{| ERASE [TO END OF] { SCREEN } |}] } ... [{| { LINE } |}] } [{| WITH BELL |}] } [{| UNDERLINED |}] } [{| BOLD |}] } [{| WITH BLINKING |}] } [{| REVERSED |}] } [{| WITH CONVERSION |}] } [ WITH NO ADVANCING ] [ END-DISPLAY ]
16.2.1 – src-item
is a literal or the identifier of a data item. The literal can be any figurative constant except ALL literal.
16.2.2 – output-dest
is a mnemonic-name defined in the SPECIAL-NAMES paragraph of the Environment Division.
16.2.3 – line-num
is a numeric literal that specifies a line position on the terminal screen. Line-num must be a positive integer. It cannot be zero.
16.2.4 – line-id
is the identifier of a data item that provides a line position on the terminal screen.
16.2.5 – column-num
is a numeric literal that specifies a column position on the terminal screen. Column-num must be a positive integer. It cannot be zero.
16.2.6 – column-id
is the identifier of a data item that provides a column position on the terminal screen.
16.2.7 – plus-num
is a numeric literal that increments the current value for line or column position, or that increments the value of line-id or column-id. Plus-num can be zero or a positive integer.
16.3 – 3format_screen_section_extensions
The DISPLAY statement transfers low-volume data from the program to the default system output device or to the object of a mnemonic-name. The HP extensions to the DISPLAY statement (formats 2 and 3) are COBOL language additions that facilitate video forms design and data handling. Format 3 - DISPLAY screen-name [ {| LINE NUMBER { line-num } |} ] [ {| { line-id } |} ] [ AT {| |} ] [ {| COLUMN NUMBER { column-num } |} ] [ {| { column-id } |} ] [ END-DISPLAY ]
16.3.1 – screen-name
is the name of a screen item defined in the SCREEN SECTION of the program.
16.3.2 – line-num
is a numeric literal that specifies a line position on the terminal screen. Line-num must be a positive integer. It cannot be zero.
16.3.3 – line-id
is the identifier of a data item that provides a line position on the terminal screen.
16.3.4 – column-num
is a numeric literal that specifies a column position on the terminal screen. Column-num must be a positive integer. It cannot be zero.
16.3.5 – column-id
is the identifier of a data item that provides a column position on the terminal screen.
16.4 – 4format_arg_position_extensions
When a Format 4 DISPLAY statement is specified, the value stored in arg-position is moved to argument-number. This updates the current argument position indicator for the command line. See ARGUMENT-NUMBER in the SPECIAL-NAMES paragraph. This point to to selected argument to be read by a Format 7 ACCEPT statement. Format 4 - DISPLAY arg-position UPON argument-number [ END-DISPLAY ]
16.4.1 – arg-position
is a literal or identifier that specifies the desired argument position on the run command line. It must be an unsigned integer.
16.4.2 – argument-number
is a mnemonic name associated with argument-number in the SPECIAL-NAMES paragraph in the Environment Division, representing the name of an environment variable or system logical.
16.5 – 5format_envlog_name_extensions
When a Format 5 DISPLAY statement is specified, the value stored in envlog-name is moved to environment-name. See ENVIRONMENT-NAME in the SPECIAL-NAMES paragraph. The updated value of environment-name becomes the environment variable or logical to be accessed by subsequent Format 6 DISPLAY and Format 8 ACCEPT statements. Format 5 - DISPLAY envlog-name UPON environment-name [ END-DISPLAY ]
16.5.1 – envlog-name
references an alphanumeric data item, or is a nonnumeric literal.
16.5.2 – environment-name
is a mnemonic name associated with ARGUMENT-NUMBER in the SPECIAL-NAMES paragraph in the Environment Division, representing the name of an environment variable or system logical.
16.5.3 – Example
Example of Formats 5 and 6. IDENTIFICATION DIVISION. PROGRAM-ID. SAMPLE. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. ENVIRONMENT-NAME IS NAME-OF-EVAR ENVIRONMENT-VALUE IS VALUE-OF-EVAR. DATA DIVISION. WORKING-STORAGE SECTION. 01 NAME-1 PIC X(20). 01 VALUE-ACCEPTED PIC X(20). PROCEDURE DIVISION. P1. * The name of the environment variable MOVE "TESTPATH1" TO NAME-1. * Create an environment with the name "TESTPATH1" DISPLAY NAME-1 UPON NAME-OF-EVAR. * Set the value of "TESTPATH1" DISPLAY "/USER/MYNAME" UPON VALUE-OF-EVAR. * Read the value of TESTPATH1 into a variable ACCEPT VALUE-ACCEPTED FROM VALUE-OF-EVAR. * Display the value of TESTPATH1" DISPLAY VALUE-ACCEPTED. STOP RUN.
16.6 – 6format_envlog_value_extensions
When a Format 6 DISPLAY statement is specified, environment-value receives the value stored in envlog-value. The environment variable or logical is the one named by a Format 5 DISPLAY statement. See ENVIRONMENT-VALUE in the SPECIAL-NAMES paragraph. Format 6 - DISPLAY envlog-value UPON environment-value [ ON EXCEPTION stment ] [ NOT ON EXCEPTION stment2 ] [ END-DISPLAY ]
16.6.1 – envlog-value
references an alphanumeric data item, or is a nonnumeric literal.
16.6.2 – environment-value
is a mnemonic name associated with ENVIRONMENT-VALUE in the SPECIAL-NAMES paragraph in the Environment Division, representing the contents of the variable associated with the ENVIRONMENT-NAME.
16.6.3 – Example
Example of Formats 5 and 6. IDENTIFICATION DIVISION. PROGRAM-ID. SAMPLE. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. ENVIRONMENT-NAME IS NAME-OF-EVAR ENVIRONMENT-VALUE IS VALUE-OF-EVAR. DATA DIVISION. WORKING-STORAGE SECTION. 01 NAME-1 PIC X(20). 01 VALUE-ACCEPTED PIC X(20). PROCEDURE DIVISION. P1. * The name of the environment variable MOVE "TESTPATH1" TO NAME-1. * Create an environment with the name "TESTPATH1" DISPLAY NAME-1 UPON NAME-OF-EVAR. * Set the value of "TESTPATH1" DISPLAY "/USER/MYNAME" UPON VALUE-OF-EVAR. * Read the value of TESTPATH1 into a variable ACCEPT VALUE-ACCEPTED FROM VALUE-OF-EVAR. * Display the value of TESTPATH1" DISPLAY VALUE-ACCEPTED. STOP RUN.
17 – DIVIDE
The DIVIDE statement divides one or more numeric data items by another. It stores the quotient and, for Formats 4 and 5, the remainder.
17.1 – 1format INTO
The DIVIDE statement divides one or more numeric data items by another. It stores the quotient. Format 1 - DIVIDE srcnum INTO { rsult [ ROUNDED ] } ... [ ON SIZE ERROR stment ] [ NOT ON SIZE ERROR stment ] [ END-DIVIDE ]
17.1.1 – srcnum
is a numeric literal or the identifier of an elementary numeric item.
17.1.2 – rsult
is the identifier of an elementary numeric item. It is the resultant identifier.
17.1.3 – stment
is an imperative statement.
17.2 – 2format INTO GIVING
The DIVIDE statement divides one or more numeric data items by another. It stores the quotient. Format 2 - DIVIDE srcnum INTO srcnum GIVING { rsult [ ROUNDED ] } ... [ ON SIZE ERROR stment ] [ NOT ON SIZE ERROR stment ] [ END-DIVIDE ]
17.2.1 – srcnum
is a numeric literal or the identifier of an elementary numeric item.
17.2.2 – rsult
is the identifier of an elementary numeric item or an elementary numeric edited item. It is the resultant identifier.
17.2.3 – stment
is an imperative statement.
17.3 – 3format BY GIVING
The DIVIDE statement divides one or more numeric data items by another. It stores the quotient. Format 3 - DIVIDE srcnum BY srcnum GIVING { rsult [ ROUNDED ] } ... [ ON SIZE ERROR stment ] [ NOT ON SIZE ERROR stment ] [ END-DIVIDE ]
17.3.1 – srcnum
is a numeric literal or the identifier of an elementary numeric item.
17.3.2 – rsult
is the identifier of an elementary numeric item or an elementary numeric edited item. It is the resultant identifier.
17.3.3 – stment
is an imperative statement.
17.4 – 4format INTO with REMAINDER
The DIVIDE statement divides one or more numeric data items by another. It stores the quotient and remainder. Format 4 - DIVIDE srcnum INTO srcnum GIVING rsult [ ROUNDED ] REMAINDER remaind [ ON SIZE ERROR stment ] [ NOT ON SIZE ERROR stment ] [ END-DIVIDE ]
17.4.1 – srcnum
is a numeric literal or the identifier of an elementary numeric item.
17.4.2 – rsult
is the identifier of an elementary numeric item or an elementary numeric edited item. It is the resultant identifier.
17.4.3 – remaind
is the identifier of an elementary numeric item or an elementary numeric edited item.
17.4.4 – stment
is an imperative statement.
17.5 – 5format BY with REMAINDER
The DIVIDE statement divides one or more numeric data items by another. It stores the quotient and remainder. Format 5 - DIVIDE srcnum BY srcnum GIVING rsult [ ROUNDED ] REMAINDER remaind [ ON SIZE ERROR stment ] [ NOT ON SIZE ERROR stment ] [ END-DIVIDE ]
17.5.1 – srcnum
is a numeric literal or the identifier of an elementary numeric item.
17.5.2 – rsult
is the identifier of an elementary numeric item or an elementary numeric edited item. It is the resultant identifier.
17.5.3 – remaind
is the identifier of an elementary numeric item or an elementary numeric edited item.
17.5.4 – stment
is an imperative statement.
18 – ERASE
The ERASE statement deletes the current record of the run unit from the database. Additional records owned by the current record may also be deleted and/or disconnected. Format - ERASE [ ALL ] [ record-name ] [ ON ERROR stment ] [ NOT ON ERROR stment ] [ END-ERASE ]
18.1 – record-name
names a subschema record type.
18.2 – stment
is an imperative statement.
19 – EVALUATE
The EVALUATE statement selects a program action based on the evaluation of one or more conditions. Format - { subj-item } [ { subj-item } ] EVALUATE { TRUE } [ ALSO { TRUE } ] ... { FALSE } [ { FALSE } ] { { { ANY } { { { cond } { {WHEN{ TRUE } { { { FALSE } { { { [NOT] {obj-item [{THRU } obj-item]} } { { { { [{THROUGH} ]} } [ { ANY }] } } [ { cond }] } } [ALSO { TRUE }] ... } ... stment} ... [ { FALSE }] } } [ { [NOT] {obj-item [{THRU } obj-item]}}] } } [ { { [{THROUGH} ]}}] } } [ WHEN OTHER stment ] [ END-EVALUATE ]
19.1 – subj-item
is an identifier, an arithmetic or conditional expression, or a literal other than the figurative constant ZERO.
19.2 – cond
is a conditional expression.
19.3 – obj-item
is a literal, an identifier, or an arithmetic expression.
19.4 – stment
is an imperative statement.
20 – EXIT
The EXIT statement provides a common logical end point for a series of procedures. The EXIT PROGRAM statement marks the logical end of a called program.
20.1 – 1statement
The EXIT statement provides a common logical end point for a series of procedures. Format - EXIT
20.2 – 2statement PROGRAM
The EXIT PROGRAM statement marks the logical end of a called program. Format - EXIT PROGRAM
21 – FETCH
The FETCH statement is a combined FIND and GET that establishes a specific record in the database as the current record of the run unit and makes the record available to the run unit in the User Work Area. Format - FETCH database-record [ FOR UPDATE ] [ [{| REALM |}] ] [RETAINING [{| RECORD |}] CURRENCY] [ [{| { SET [ set-name ] ... } |}] ] [ [{| { { set-name } ... } |}] ] [{ [ AT END stment ] [ NOT AT END stment ] } ] [{ [ ON ERROR stment ] [ NOT ON ERROR stment ] } ] [ END-FETCH ]
21.1 – database-record
represents a record selection expression. References are made to a record in the data-base according to the rules for Record Selection Expressions.
21.2 – set-name
names a subschema set type.
21.3 – stment
is an imperative statement.
22 – FIND
The FIND statement locates a specific record in the database and establishes it as the current record of the run unit. The FIND ALL statement locates zero or more records in the database and inserts them into the named keeplist.
22.1 – 1format
The FIND statement locates a specific record in the database and establishes it as the current record of the run unit. Format 1 - FIND database-record [ FOR UPDATE ] [ [{| REALM |}] ] [RETAINING [{| RECORD |}] CURRENCY] [ [{| { SET [ set-name ] ... } |}] ] [ [{| { { set-name } ... } |}] ] [{ [ AT END stment ] [ NOT AT END stment ] } ] [{ [ ON ERROR stment ] [ NOT ON ERROR stment ] } ] [ END-FIND ]
22.1.1 – database-record
represents a record selection expression. References are made to a record in the database according to the rules for Record Selection Expressions.
22.1.2 – set-name
names a subschema set type.
22.1.3 – stment
is an imperative statement.
22.2 – 2format ALL
The FIND ALL statement locates zero or more records in the database and inserts them into the named keeplist. Format 2 - FIND ALL keeplist-name [ record-name ] [ WITHIN { realm-name } ] [ { set-name } ] [ USING { rec-key } ... ] [ FOR UPDATE ] [ WHERE { bool-exp } ] [{ [ AT END stment ] [ NOT AT END stment ] } ] [{ [ ON ERROR stment ] [ NOT ON ERROR stment ] } ] [ END-FIND ]
22.2.1 – keeplist-name
names a keeplist in the Sub-Schema Section.
22.2.2 – record-name
is a subschema record name.
22.2.3 – realm-name
is a subschema realm name.
22.2.4 – set-name
is a subschema set name.
22.2.5 – rec-key
is a key data item within the subschema record occurrence. The same rec-key can appear only once in a given USING phrase.
22.2.6 – bool-exp
is a conditional expression that involves data items of the object record. It is used to specify additional requirements of a qualifying record.
22.2.7 – stment
is an imperative statement.
23 – FREE
The FREE statement empties selected keeplists or removes a database key value from a keeplist or currency indicator. Format - { [ { record-name } ] } { CURRENT [ WITHIN { set-name } ] } { [ { realm-name } ] } FREE { { OFFSET integer-exp } } { { FIRST } WITHIN keeplist-name } { { LAST } } { ALL [ { FROM { keeplist-name } ... } ] } { [ { CURRENT } ] } [ ON ERROR stment ] [ NOT ON ERROR stment ] [ END-FREE ]
23.1 – record-name
is a subschema record name.
23.2 – set-name
is a subschema set name.
23.3 – realm-name
is a subschema realm name.
23.4 – integer-exp
is an arithmetic expression or integer. It refers to a position in keeplist-name. Integer-exp cannot be zero.
23.5 – keeplist-name
names a keeplist in the Sub-Schema Section.
23.6 – stment
is an imperative statement.
24 – GENERATE
The GENERATE statement directs the Report Writer Control System (RWCS) to produce a report according to the Report Description entry (RD) in the Report Section of the Data Division. Format - GENERATE report-item
24.1 – report-item
names either a report-name in a Report Description entry, or the group-data-name of a TYPE IS DETAIL report group.
25 – GET
The GET statement moves the contents of the current database record of the run unit to your User Work Area. Format - GET [ record-name ] [ { record-item } ... ] [ ON ERROR stment ] [ NOT ON ERROR stment ] [ END-GET ]
25.1 – record-name
names a database subschema record type.
25.2 – record-item
is a group or elementary data item in a subschema record type. Record-item may be qualified.
25.3 – stment
is an imperative statement.
26 – GO_TO
The GO TO statement transfers control from one part of the Procedure Division to another.
26.1 – 1format
The GO TO statement transfers control from one part of the Procedure Division to another. Format 1 - GO TO [ proc-name ]
26.1.1 – proc-name
is a procedure-name.
26.2 – 2format DEPENDING
The GO TO statement transfers control from one part of the Procedure Division to another. Format 2 - GO TO { proc-name } ... DEPENDING ON num
26.2.1 – proc-name
is a procedure-name.
26.2.2 – num
is the identifier of an elementary numeric item described with no positions to the right of the assumed decimal point.
27 – IF
The IF statement evaluates a condition. The condition's truth value determines the program action that follows. Format - IF condition THEN { { stment-1 } ... } { NEXT SENTENCE } [ ELSE { stment-2 } ... [ END-IF ] ] [ ELSE NEXT SENTENCE ] [ END-IF ]
27.1 – stment
an imperative or conditional statement. An imperative statement can precede a conditional statement.
28 – INITIALIZE
The INITIALIZE statement sets selected types of data fields to predetermined values. Format - INITIALIZE { fld-name } ... [ { { ALPHABETIC } } ] [ { { ALPHANUMERIC } } ] [ REPLACING { { NUMERIC } DATA BY val } ... ] [ { { ALPHANUMERIC-EDITED } } ] [ { { NUMERIC-EDITED } } ]
28.1 – fld-name
is the identifier of the receiving area data item.
28.2 – val
is the sending area. It can be a literal or the identifier of a data item.
29 – INITIATE
The INITIATE statement causes the Report Writer Control System (RWCS) to begin processing a report. Format - INITIATE { report-name } ...
29.1 – report-name
names a report defined by a Report Description entry (RD) in the Report Section of the Data Division.
30 – INSPECT
The INSPECT statement counts or replaces occurrences of single characters or groups of characters in a data item.
30.1 – 1format TALLYING
The INSPECT statement counts or replaces occurrences of single characters or groups of characters in a data item. Format 1 - INSPECT src-string TALLYING { { tally-ctr FOR { { { [ { BEFORE } ] } } { CHARACTERS [ { AFTER } INITIAL delim-val ] ... } ... } ... { { ALL } { { { LEADING } { compare-val [{ BEFORE } ] } } } [{ AFTER } INITIAL delim-val ] ... } ... } ... } ...
30.1.1 – src-string
is the identifier of a group item or an elementary data item with DISPLAY usage. INSPECT operates on the contents of this data item.
30.1.2 – tally-ctr
is the identifier of an elementary numeric data item.
30.1.3 – compare-val
is the character-string INSPECT uses for comparison. It is a nonnumeric literal (or figurative constant other than ALL literal) or the identifier of an elementary alphabetic, alphanumeric, or numeric data item with DISPLAY usage.
30.1.4 – delim-val
is the character-string that delimits the INSPECT operation. Its content restrictions are the same as those for compare-val.
30.2 – 2format REPLACING
The INSPECT statement counts or replaces occurrences of single characters or groups of characters in a data item. Format 2 - INSPECT src-string REPLACING { CHARACTERS BY replace-char [{ BEFORE } INITIAL delim-val] ... } { [{ AFTER } ] } { { ALL } } ... { { LEADING } { compare-val BY replace-val { { FIRST } [ { BEFORE } INITIAL delim-val ] ... } ... } [ { AFTER } ] } }
30.2.1 – src-string
is the identifier of a group item or an elementary data item with DISPLAY usage. INSPECT operates on the contents of this data item.
30.2.2 – compare-val
is the character-string INSPECT uses for comparison. It is a nonnumeric literal (or figurative constant other than ALL literal) or the identifier of an elementary alphabetic, alphanumeric, or numeric data item with DISPLAY usage.
30.2.3 – delim-val
is the character-string that delimits the INSPECT operation. Its content restrictions are the same as those for compare-val.
30.2.4 – replace-char
is the one-character item that replaces all characters. Its content restrictions are the same as those for compare-val.
30.2.5 – replace-val
is the character-string that replaces occurrences of compare-val. Its content restrictions are the same as those for compare-val.
30.3 – 3format TALLYING REPLACING
The INSPECT statement counts or replaces occurrences of single characters or groups of characters in a data item. Format 3 - INSPECT src-string TALLYING { { tally-ctr FOR { { { [ { BEFORE } ] } } { CHARACTERS [ { AFTER } INITIAL delim-val ] ... } ... } ... { { ALL } { { { LEADING } { compare-val { [{ BEFORE } ] } } } [{ AFTER } INITIAL delim-val ] ... } ... } ... } ... REPLACING { CHARACTERS BY replace-char [{ BEFORE } INITIAL delim-val] ... } { [{ AFTER } ] } { { ALL } } ... { { LEADING } { compare-val BY replace-val { { FIRST } [ { BEFORE } INITIAL delim-val ] ... } ... } [ { AFTER } ] } }
30.3.1 – src-string
is the identifier of a group item or an elementary data item with DISPLAY usage. INSPECT operates on the contents of this data item.
30.3.2 – tally-ctr
is the identifier of an elementary numeric data item.
30.3.3 – compare-val
is the character-string INSPECT uses for comparison. It is a nonnumeric literal (or figurative constant other than ALL literal) or the identifier of an elementary alphabetic, alphanumeric, or numeric data item with DISPLAY usage.
30.3.4 – delim-val
is the character-string that delimits the INSPECT operation. Its content restrictions are the same as those for compare-val.
30.3.5 – replace-char
is the one-character item that replaces all characters. Its content restrictions are the same as those for compare-val.
30.3.6 – replace-val
is the character-string that replaces occurrences of compare-val. Its content restrictions are the same as those for compare-val.
30.4 – 4format CONVERTING
The INSPECT statement counts or replaces occurrences of single characters or groups of characters in a data item. Format 4 - INSPECT src-string CONVERTING compare-chars TO convert-chars [ { BEFORE } INITIAL delim-val ] ... [ { AFTER } ]
30.4.1 – src-string
is the identifier of a group item or an elementary data item with DISPLAY usage. INSPECT operates on the contents of this data item.
30.4.2 – delim-val
is the character-string that delimits the INSPECT operation. Its content restrictions are the same as those for compare-val.
30.4.3 – compare-chars
is the string that contains the individual characters that convert to those in convert-chars. It is the same kind of item as compare-val.
30.4.4 – convert-chars
is the string that contains the individual characters to which the characters in compare-chars convert. It is the same kind of item as compare-val.
31 – KEEP
The KEEP statement inserts a database key value from a currency indicator or keeplist into a keeplist. Format - [ [ { record-name } ] ] [ CURRENT [ WITHIN { set-name } ] ] [ [ { realm-name } ] ] KEEP [ { OFFSET integer-exp } ] [ { FIRST } WITHIN keeplist-name ] [ { LAST } ] USING destination-keeplist [ ON ERROR stment ] [ NOT ON ERROR stment ] [ END-KEEP ]
31.1 – record-name
is a subschema record name.
31.2 – set-name
is a subschema set name.
31.3 – realm-name
is a subschema realm name.
31.4 – integer-exp
is an arithmetic expression or integer. It refers to a position in keeplist-name. Integer-exp cannot be zero.
31.5 – keeplist-name
names a keeplist in the Sub-Schema Section.
31.6 – destination-keeplist
names a keeplist in the Sub-Schema Section to receive the database key value.
31.7 – stment
is an imperative statement.
32 – MERGE
The MERGE statement takes two or more identically sequenced files and combines them according to the key values you specify. During the process, it makes records available, in merged order, to routines in OUTPUT PROCEDURE or to an output file. Format - MERGE mergefile { ON { ASCENDING } KEY { mergekey } ... } ... { { DESCENDING } } [ COLLATING SEQUENCE IS alpha ] USING infile { infile } ... { OUTPUT PROCEDURE IS first-proc [ { THRU } end-proc ] } { [ { THROUGH } ] } { GIVING { outfile } ... }
32.1 – mergefile
is a file-name described in a sort-merge file description (SD) entry in the Data Division.
32.2 – mergekey
is the data-name of a data item in a record associated with mergefile.
32.3 – alpha
is an alphabet-name defined in the SPECIAL-NAMES paragraph of the Environment Division.
32.4 – infile
is the file-name of an input file. It must be described in a file description (FD) entry in the Data Division.
32.5 – first-proc
is the section-name or paragraph-name of the output procedure's first (or only) section or paragraph.
32.6 – end-proc
is the section-name or paragraph-name of the output procedure's last section or paragraph.
32.7 – outfile
is the file-name of an output file. It must be described in a file description (FD) entry in the Data Division.
33 – MODIFY
The MODIFY statement changes the contents of specified data items in a database record. Format - MODIFY [ record-name ] [ { record-item } ... ] [ [{| REALM |}] ] [RETAINING [{| RECORD |}] CURRENCY] [ [{| { SET [ set-name ] ... } |}] ] [ [{| { { set-name } ... } |}] ] [ ON ERROR stment ] [ NOT ON ERROR stment ] [ END-MODIFY ]
33.1 – record-name
names a database subschema record type.
33.2 – record-item
is a group or elementary data item in a subschema record type. Record-item can be qualified.
33.3 – set-name
names a subschema set type.
33.4 – stment
is an imperative statement.
34 – MOVE
The MOVE statement transfers data to one or more data areas. The editing rules control data transfer.
34.1 – 1format
The MOVE statement transfers data to one or more data areas. The editing rules control data transfer. Format 1 - MOVE { src-item } TO { dest-item } ... { lit }
34.1.1 – src-item
is an identifier that represents the sending area.
34.1.2 – lit
is a literal that represents the sending area.
34.1.3 – dest-item
is an identifier that represents the receiving area.
34.2 – 2format CORRESPONDING
The MOVE statement transfers data to one or more data areas. The editing rules control data transfer. Format 2 - MOVE { CORRESPONDING } src-item TO dest-item { CORR }
34.2.1 – src-item
is an identifier that represents the sending area.
34.2.2 – dest-item
is an identifier that represents the receiving area.
35 – MULTIPLY
The MULTIPLY statement multiplies two numeric operands and stores the result.
35.1 – 1format
The MULTIPLY statement multiplies two numeric operands and stores the result. Format 1 - MULTIPLY srcnum BY { rsult [ ROUNDED ] } ... [ ON SIZE ERROR stment ] [ NOT ON SIZE ERROR stment ] [ END-MULTIPLY ]
35.1.1 – srcnum
is a numeric literal or the identifier of an elementary numeric item.
35.1.2 – rsult
is the identifier of an elementary numeric item. It is the resultant identifier.
35.1.3 – stment
is an imperative statement.
35.2 – 2format GIVING
The MULTIPLY statement multiplies two numeric operands and stores the result. Format 2 - MULTIPLY srcnum BY srcnum GIVING { rsult [ ROUNDED ] } ... [ ON SIZE ERROR stment ] [ NOT ON SIZE ERROR stment ] [ END-MULTIPLY ]
35.2.1 – srcnum
is a numeric literal or the identifier of an elementary numeric item.
35.2.2 – rsult
is the identifier of an elementary numeric item or an elementary numeric edited item. It is the resultant identifier.
35.2.3 – stment
is an imperative statement.
36 – OPEN
The OPEN statement creates an access stream to the file, makes the file available to the program, begins the processing of a file, and specifies file sharing.
36.1 – 1format_sequential_relative_indexed
The OPEN statement creates an access stream to the file, makes the file available to the program, begins the processing of a file, and specifies file sharing. Format 1 - Sequential, Relative, Indexed { { [WITH LOCK ]} } { { [ {NO OTHERS }]} } { { [ {{|READERS |}}]} } {{INPUT }{file-name[WITH NO REWIND][ALLOWING {{|WRITERS |}}]}...} {{OUTPUT}{ [ {{|UPDATERS|}}]} } { { [ {ALL }]} } OPEN{ }... { { [WITH LOCK ]} } { { [ { NO OTHERS } ]} } { { [ { {| READERS |}} ]} } {{EXTEND}{ file-name [ALLOWING { {| WRITERS |}} ]}... } {{I-O }{ [ { {| UPDATERS |}} ]} } { { [ { ALL } ]} }
36.1.1 – file-name
is the name of a file described in the Data Division. It cannot be the name of a sort or merge file.
36.2 – 2format_report_writer
The OPEN statement creates an access stream to the file, makes the file available to the program, begins the processing of a file, and specifies file sharing. Format 2 - Report Writer OPEN { OUTPUT { file-name [ WITH NO REWIND ] } ... } ... { EXTEND { file-name } ... }
36.2.1 – file-name
is the name of a file described in the Data Division. It cannot be the name of a sort or merge file.
37 – PERFORM
The PERFORM statement executes one or more procedures. It returns control to the end of the PERFORM statement when procedure execution ends.
37.1 – 1format
The PERFORM statement executes one or more procedures. It returns control to the end of the PERFORM statement when procedure execution ends. Format 1 - PERFORM [first-proc [ { THRU } end-proc ]] [ [ { THROUGH } ]] [ stment END-PERFORM ]
37.1.1 – first-proc
is a procedure-name that identifies a paragraph or section in the Procedure Division. The set of statements in first-proc are the first (or only) set of statements in the PERFORM range.
37.1.2 – end-proc
is a procedure-name that identifies a paragraph or section in the Procedure Division. The set of statements in end-proc are the last set of statements in the PERFORM range.
37.1.3 – stment
is an imperative statement.
37.2 – 2format_repeat-count
The PERFORM statement executes one or more procedures. It returns control to the end of the PERFORM statement when procedure execution ends. Format 2 - PERFORM [first-proc [ { THRU } end-proc ]] repeat-count TIMES [ [ { THROUGH } ]] [ stment END-PERFORM ]
37.2.1 – first-proc
is a procedure-name that identifies a paragraph or section in the Procedure Division. The set of statements in first-proc are the first (or only) set of statements in the PERFORM range.
37.2.2 – end-proc
is a procedure-name that identifies a paragraph or section in the Procedure Division. The set of statements in end-proc are the last set of statements in the PERFORM range.
37.2.3 – stment
is an imperative statement.
37.2.4 – repeat-count
is a numeric integer literal or the identifier of a numeric integer elementary item. It controls how many times the statement set (or sets) executes.
37.3 – 3format UNTIL
The PERFORM statement executes one or more procedures. It returns control to the end of the PERFORM statement when procedure execution ends. Format 3 - PERFORM [first-proc [ { THRU } end-proc ]] [ WITH TEST { BEFORE } ] [ [ { THROUGH } ]] [ { AFTER } ] UNTIL cond [ stment END-PERFORM ]
37.3.1 – first-proc
is a procedure-name that identifies a paragraph or section in the Procedure Division. The set of statements in first-proc are the first (or only) set of statements in the PERFORM range.
37.3.2 – end-proc
is a procedure-name that identifies a paragraph or section in the Procedure Division. The set of statements in end-proc are the last set of statements in the PERFORM range.
37.3.3 – stment
is an imperative statement.
37.3.4 – cond
can be any conditional expression.
37.4 – 4format VARYING
The PERFORM statement executes one or more procedures. It returns control to the end of the PERFORM statement when procedure execution ends. Format 4 - PERFORM [first-proc [ { THRU } end-proc ]] [ WITH TEST { BEFORE } ] [ [ { THROUGH } ]] [ { AFTER } ] VARYING var FROM init BY increm UNTIL cond [ AFTER var FROM init BY increm UNTIL cond ] ... [ stment END-PERFORM ]
37.4.1 – first-proc
is a procedure-name that identifies a paragraph or section in the Procedure Division. The set of statements in first-proc are the first (or only) set of statements in the PERFORM range.
37.4.2 – end-proc
is a procedure-name that identifies a paragraph or section in the Procedure Division. The set of statements in end-proc are the last set of statements in the PERFORM range.
37.4.3 – stment
is an imperative statement.
37.4.4 – cond
can be any conditional expression.
37.4.5 – var
is an index-name or the identifier of a numeric elementary data item. Its value is changed by increm each time all statements in the PERFORM range execute.
37.4.6 – init
is a numeric literal, index-name, or the identifier of a numeric elementary data item. It specifies the value of var before any statement in the PERFORM range executes.
37.4.7 – increm
is a nonzero numeric literal or the identifier of a numeric elementary data item. It systematically changes the value of var each time the program executes all statements in the PERFORM range.
38 – READ
For sequential access files, the READ statement makes the next logical record available. For random access files, READ makes a specified record available.
38.1 – 1format_sequential
For sequentially accessed files, the READ statement makes the next logical record in the sequence available. Format 1 - READ file-name [ NEXT ] RECORD [ INTO dest-item ] [ PREVIOUS ] [ PRIOR ] [ WITH [ NO ] LOCK ] [ REGARDLESS OF LOCK ] [ { UPDATERS } ] [ ALLOWING { READERS } ] [ { NO OTHERS } ] [ AT END stment ] [ NOT AT END stment ] [ END-READ ]
38.1.1 – file-name
is the name of a file described in the Data Division. It cannot be a sort or merge file.
38.1.2 – dest-item
is the identifier of a data item that receives the record accessed by the READ statement.
38.1.3 – stment
is an imperative statement executed for an at end or not at end condition.
38.2 – 2format_random_dynamic
For randomly accessed files, READ makes a specified record available. Format 2 - READ file-name RECORD [ INTO dest-item ] [ WITH [ NO ] LOCK ] [ REGARDLESS OF LOCK ] [ { UPDATERS } ] [ ALLOWING { READERS } ] [ { NO OTHERS } ] [ KEY IS key-data ] [ INVALID KEY stment ] [ NOT INVALID KEY stment ] [ END-READ ]
38.2.1 – file-name
is the name of a file described in the Data Division. It cannot be a sort or merge file.
38.2.2 – dest-item
is the identifier of a data item that receives the record accessed by the READ statement.
38.2.3 – key-data
is the data-name of a data item or the segmented-key name specified as a record key for file-name. It can be qualified. This clause is not used on RELATIVE files.
38.2.4 – stment
is an imperative statement executed for an invalid key or not invalid key condition.
39 – READY
The READY statement begins a database transaction, prepares one or more database realms for processing, and places each specified realm in a ready mode. Format - READY [ realm-name ] ... [ { { CONCURRENT } } ] [ { { EXCLUSIVE } [ { RETRIEVAL } ] } ] [ { { PROTECTED } [ { UPDATE } ] } ] [ USAGE-MODE IS { { BATCH } } ] [ { [ { CONCURRENT } ] } ] [ { { RETRIEVAL } [ { EXCLUSIVE } ] } ] [ { { UPDATE } [ { PROTECTED } ] } ] [ { [ { BATCH } ] } ] [ WITH WAIT ] [ ON ERROR stment ] [ NOT ON ERROR stment ] [ END-READY ]
39.1 – realm-name
names a subschema realm name.
39.2 – stment
is an imperative statement.
40 – RECONNECT
The RECONNECT statement moves the current database record of the run unit from one set to another (possibly the same) set. Format - RECONNECT [ record-name ] WITHIN { { set-name } ... } { ALL } [ [{| REALM |}] ] [ RETAINING [{| RECORD |}] CURRENCY ] [ [{| { SET [ set-name ] ... } |}] ] [ [{| { { set-name } ... } |}] ] [ ON ERROR stment ] [ NOT ON ERROR stment ] [ END-RECONNECT ]
40.1 – record-name
names a subschema record type.
40.2 – set-name
names a subschema set type.
40.3 – stment
is an imperative statement.
41 – RECORD
The RECORD statement creates a Common Data Dictionary/Repository (CDD/Repository) dependency relationship between a COBOL program and a dictionary entity stored in CDD/Repository. For this statement to be meaningful, you must compile your program with the /DEPENDENCY_DATA qualifier. RECORD DEPENDENCY pathname [ TYPE IS rel-type ] [ IN DICTIONARY ].
41.1 – pathname
is a partial or full CDD/Repository pathname. It specifies a CDD/Repository dictionary entity stored in CDO format.
41.2 – rel-type
is a valid CDD/Repository protocol. It specifies the type of relationship to be created between the VSI COBOL program and the CDO dictionary entity specified in the pathname. The default is CDD$COMPILED_DEPENDS_ON.
42 – RELEASE
The RELEASE statement transfers records to the initial phase of a sort operation. Format - RELEASE rec [ FROM src-area ]
42.1 – rec
is the name of a logical record in a sort-merge file description (SD) entry. It can be qualified.
42.2 – src-area
is the identifier of the data item that contains the data. If src-area is a function-identifier, it must reference an alphanumeric function.
43 – RETURN
The RETURN statement gets sorted records from a sort operation. It also returns merged records in a merge operation. Format - RETURN smrg-file RECORD [ INTO dest-area ] AT END stment [ NOT AT END stment ] [ END-RETURN ]
43.1 – smrg-file
is the name of a file described in a sort-merge file description (SD) entry.
43.2 – dest-area
is the identifier of the data item to which the returned smrg-file record is moved.
43.3 – stment
is an imperative statement.
44 – REWRITE
The REWRITE statement logically replaces a mass storage file record.
44.1 – 1format_sequential
Format 1 - REWRITE rec-name [ FROM src-item ] [ ALLOWING NO OTHERS ] [ END-REWRITE ]
44.1.1 – rec-name
is the name of a logical record in the Data Division File Section. It can be qualified.
44.1.2 – src-item
is the identifier of the data item that contains the data. If src-item is a function-identifier, it must reference an alphanumeric function.
44.2 – 2format_relative_indexed
Format 2 - REWRITE rec-name [ FROM src-item ] [ ALLOWING NO OTHERS ] [ INVALID KEY stment ] [ NOT INVALID KEY stment ] [ END-REWRITE ]
44.2.1 – rec-name
is the name of a logical record in the Data Division File Section. It can be qualified.
44.2.2 – src-item
is the identifier of the data item that contains the data. If src-item is a function-identifier, it must reference an alphanumeric function.
44.2.3 – stment
is an imperative statement.
45 – ROLLBACK
The ROLLBACK statement ends your database transaction, nullifies all database changes made by this run unit since its last quiet point, and establishes a new quiet point for this run unit. Format - ROLLBACK [ ON ERROR stment ] [ NOT ON ERROR stment ] [ END-ROLLBACK ]
45.1 – stment
is an imperative statement.
46 – SEARCH
The SEARCH statement searches for a table element that satisfies a condition. It sets the value of the associated index to point to the table element.
46.1 – 1format_serial
The SEARCH statement searches for a table element that satisfies a condition. It sets the value of the associated index to point to the table element. Format 1 - SEARCH src-table [ VARYING pointr ] [ AT END stment ] { {WHEN cond stment} ... END-SEARCH } { } { {WHEN cond { stment } } } { { { NEXT SENTENCE } } ... }
46.1.1 – src-table
is a table identifier.
46.1.2 – pointr
is an index-name or the identifier of a data item described as USAGE INDEX, or an elementary numeric data item with no positions to the right of the assumed decimal point.
46.1.3 – cond
is any conditional expression.
46.1.4 – stment
is an imperative statement.
46.2 – 2format_binary
The SEARCH statement searches for a table element that satisfies a condition. It sets the value of the associated index to point to the table element. Format 2 - SEARCH ALL src-table [ AT END stment ] WHEN { elemnt { IS EQUAL TO } arg } { { IS = } } { cond-name } [ AND { elemnt { IS EQUAL TO } arg } ] ... [ { { IS = } } ] [ { cond-name } ] { stment [ END-SEARCH ] } { NEXT SENTENCE }
46.2.1 – src-table
is a table identifier.
46.2.2 – stment
is an imperative statement.
46.2.3 – elemnt
is an indexed data-name. It refers to the table element against which the argument is compared.
46.2.4 – arg
is the argument tested against each element (elemnt) in the search. It is an identifier, a literal, or an arithmetic expression.
46.2.5 – cond-name
is a condition-name.
47 – SET
The SET statement sets values of indexes associated with table elements. It can also change the value of a conditional variable, change the status of an external switch, and store the address of a COBOL identifier reference at run time.
47.1 – 1format TO
The SET statement sets values of indexes associated with table elements. It can also change the value of a conditional variable, change the status of an external switch, and store the address of a COBOL identifier reference at run time. Format 1 - SET { rsult } ... TO val
47.1.1 – rsult
is an index-name, the identifier of an index data item, or an elementary numeric data item described as an integer.
47.1.2 – val
is a positive integer, which may be signed. It can also be an index-name (or the identifier of an index data item) or an elementary numeric data item described as an integer.
47.2 – 2format UP DOWN
The SET statement sets values of indexes associated with table elements. It can also change the value of a conditional variable, change the status of an external switch, and store the address of a COBOL identifier reference at run time. Format 2 - SET { indx } ... { UP BY } increm { DOWN BY }
47.2.1 – indx
is an index-name.
47.2.2 – increm
is an integer, which may be signed. It can also be the identifier of an elementary numeric data item described as an integer.
47.3 – 3format_cond-name
The SET statement sets values of indexes associated with table elements. It can also change the value of a conditional variable, change the status of an external switch, and store the address of a COBOL identifier reference at run time. Format 3 - SET { cond-name } ... TO TRUE
47.3.1 – cond-name
is a condition-name that must be associated with a conditional variable.
47.4 – 4format_switch-name
The SET statement sets values of indexes associated with table elements. It can also change the value of a conditional variable, change the status of an external switch, and store the address of a COBOL identifier reference at run time. Format 4 - SET { { switch-name } ... TO { ON } } ... { { OFF } }
47.4.1 – switch-name
is the name of an external switch defined in the SPECIAL-NAMES paragraph.
47.5 – 5format REFERENCE
The SET statement sets values of indexes associated with table elements. It can also change the value of a conditional variable, change the status of an external switch, and store the address of a COBOL identifier reference at run time. Format 5 - SET { pointer-id } ... TO REFERENCE OF identifier
47.5.1 – pointer-id
is a data-name whose data description entry must contain the USAGE IS POINTER or POINTER-64 clause.
47.5.2 – identifier
is a data item in the File, Working-Storage, Linkage Section, or Sub-Schema Section.
47.6 – 6format SUCCESS FAILURE
The SET statement sets values of indexes associated with table elements. It can also change the value of a conditional variable, change the status of an external switch, and store the address of a COBOL identifier reference at run time. Format 6 - SET status-code-id TO { SUCCESS } { FAILURE }
47.6.1 – status-code-id
is a word or longword integer data item represented by PIC S9(1) to S9(9) COMP.
48 – SORT
The SORT statement handles both files and tables.
48.1 – 1format_file
The SORT statement creates a sort file by executing input procedures or transferring records from an input file. It sorts the records in the sort file using one or more keys that you specify. Finally, it returns each record from the sort file, in sorted order, to output procedures or an output file. Format - SORT sortfile { ON { ASCENDING } KEY { sortkey } ... } ... { { DESCENDING } } [ WITH DUPLICATES IN ORDER ] [ COLLATING SEQUENCE IS alpha ] { INPUT PROCEDURE IS first-proc [ { THRU } end-proc ] } { [ { THROUGH } ] } { USING { infile } ... } { OUTPUT PROCEDURE IS first-proc [ { THRU } end-proc ] } { [ { THROUGH } ] } { GIVING { outfile } ... }
48.1.1 – sortfile
is a file-name described in a sort-merge file description (SD) entry in the Data Division.
48.1.2 – sortkey
is the data-name of a data item in a record associated with sortfile.
48.1.3 – alpha
is an alphabet-name defined in the SPECIAL-NAMES paragraph of the Environment Division.
48.1.4 – first-proc
is the section-name or paragraph-name of the first (or only) section or paragraph of the INPUT or OUTPUT procedure range.
48.1.5 – infile
is the file-name of the input file. It must be described in a file description (FD) entry in the Data Division.
48.1.6 – end-proc
is the section-name or paragraph-name of the last section or paragraph of the INPUT or OUTPUT procedure range.
48.1.7 – outfile
is the file-name of the output file. It must be described in a file description (FD) entry in the Data Division.
48.2 – 2format_table
The SORT statement orders a table. It sorts the table elements based on the keys as specified in the OCCURS for the table. The table keys as specified in the OCCURS can be overridden with keys as specified in the SORT statement. If no key is specified, the table elements are the SORT keys. Format - SORT table-name [ ON { ASCENDING } KEY { sortkey } ... ] ... [ { DESCENDING } ] [ WITH DUPLICATES IN ORDER ] [ COLLATING SEQUENCE IS alpha ].
48.2.1 – table-name
is a table described with OCCURS in the Data Division.
48.2.2 – sortkey
is the data-name of a data item in the table-name table.
48.2.3 – alpha
is an alphabet-name defined in the SPECIAL-NAMES paragraph of the Environment Division.
49 – START
The START statement establishes the logical position of the Next Record Pointer in an indexed or relative file. The logical position affects subsequent sequential record retrieval. Format - [ { IS EQUAL TO } ] [ { IS = } ] [ { IS GREATER THAN } ] START file-name [ KEY { IS > } key-data ] [ { IS NOT LESS THAN } ] [ { IS NOT < } ] [ { IS GREATER THAN OR EQUAL TO } ] [ { IS >= } ] [ { IS LESS THAN } ] [ { IS < } ] [ { IS LESS THAN OR EQUAL TO } ] [ { IS <= } ] [ { IS NOT GREATER THAN } ] [ { IS NOT > } ] [ REGARDLESS OF LOCK ] [ { UPDATERS } ] [ ALLOWING { READERS } ] [ { NO OTHERS } ] [ INVALID KEY stment ] [ NOT INVALID KEY stment ] [ END-START ]
49.1 – file-name
is the name of an indexed or relative file with sequential or dynamic access. It cannot be the name of a sort or merge file.
49.2 – key-data
is the data-name of a data item or the segmented-key name specified as a record key, or the leftmost part of a record key, or the relative key for file-name. It can be qualified.
49.3 – stment
is an imperative statement.
50 – STOP
The STOP statement permanently terminates or temporarily suspends image execution. Format - STOP { RUN } { disp }
50.1 – disp
is any literal, or any figurative constant except ALL literal.
51 – STORE
The STORE statement stores a new record in the database, establishes the record as an owner of an empty set of each set type for which the record is an owner record type, and connects the record as a member to the current set of each set type for which the record is an AUTOMATIC member record type. Format - STORE record-name [ [ NEXT TO ] DBKEY ] [ WITHIN { realm-name } ... ] [ [{| REALM |}] ] [ RETAINING [{| RECORD |}] CURRENCY ] [ [{| { SET [ set-name ] ... } |}] ] [ [{| { { set-name } ... } |}] ] [ ON ERROR stment ] [ NOT ON ERROR stment ] [ END-STORE ]
51.1 – record-name
names a subschema record type.
51.2 – realm-name
names a subschema realm.
51.3 – set-name
names a subschema set type.
51.4 – stment
is an imperative statement.
52 – STRING
The STRING statement concatenates the partial or complete contents of one or more data items into a single data item. Format - STRING { { src-string } ... DELIMITED BY { delim } } ... { { SIZE } } INTO dest-string [ WITH POINTER pointr ] [ ON OVERFLOW stment ] [ NOT ON OVERFLOW stment ] [ END-STRING ]
52.1 – src-string
is a nonnumeric literal or identifier of a DISPLAY data item. It is the sending area.
52.2 – delim
is a nonnumeric literal or the identifier of a DISPLAY data item. It is the delimiter of src-string.
52.3 – dest-string
is the identifier of a DISPLAY data item. It cannot be reference modified. Dest-string is the receiving area that contains the result of the concatenated src-strings.
52.4 – pointr
is an elementary numeric data item described as an integer. It points to the position in dest-string to contain the next character moved.
52.5 – stment
is an imperative statement.
53 – SUBTRACT
The SUBTRACT statement subtracts one, or the sum of two or more, numeric items from one or more items. It stores the result in one or more items.
53.1 – 1format FROM
The SUBTRACT statement subtracts one, or the sum of two or more, numeric items from one or more items. It stores the result in one or more items. Format 1 - SUBTRACT { num } ... FROM { rsult [ ROUNDED ] } ... [ ON SIZE ERROR stment ] [ NOT ON SIZE ERROR stment ] [ END-SUBTRACT ]
53.1.1 – num
is a numeric literal or the identifier of an elementary numeric item.
53.1.2 – rsult
is the identifier of an elementary numeric item. It is the resultant identifier.
53.1.3 – stment
is an imperative statement.
53.2 – 2format GIVING
The SUBTRACT statement subtracts one, or the sum of two or more, numeric items from one or more items. It stores the result in one or more items. Format 2 - SUBTRACT { num } ... FROM num GIVING { rsult [ ROUNDED ] } ... [ ON SIZE ERROR stment ] [ NOT ON SIZE ERROR stment ] [ END-SUBTRACT ]
53.2.1 – num
is a numeric literal or the identifier of an elementary numeric item.
53.2.2 – rsult
is the identifier of an elementary numeric item or an elementary numeric edited item. It is the resultant identifier.
53.2.3 – stment
is an imperative statement.
53.3 – 3format CORRESPONDING
The SUBTRACT statement subtracts one, or the sum of two or more, numeric items from one or more items. It stores the result in one or more items. Format 3 - SUBTRACT { CORRESPONDING } grp-1 FROM grp-2 [ ROUNDED ] { CORR } [ ON SIZE ERROR stment ] [ NOT ON SIZE ERROR stment ] [ END-SUBTRACT ]
53.3.1 – grp
is the identifier of a group item.
53.3.2 – stment
is an imperative statement.
54 – SUPPRESS
The SUPPRESS statement causes the Report Writer Control System (RWCS) to inhibit the presentation of a report group. Format - SUPPRESS PRINTING
55 – TERMINATE
The TERMINATE statement causes the Report Writer Control System (RWCS) to complete the processing of the specified report. Format - TERMINATE { report-name } ...
55.1 – report-name
names a report defined by a Report Description entry in the Report Section of the Data Division.
56 – UNLOCK
The UNLOCK statement removes record locks from a record or all currently locked records in the file. Format - UNLOCK file-name [ RECORD ] [ ALL RECORDS ]
56.1 – file-name
is the name of a sequential, relative, or indexed file described in the Data Division.
57 – UNSTRING
The UNSTRING statement separates contiguous data in a sending field and stores it in one or more receiving fields. Format - UNSTRING src-string [ DELIMITED BY [ALL] delim [ OR [ALL] delim ] ... ] INTO { dest-string [DELIMITER IN delim-dest] [COUNT IN countr] } ... [ WITH POINTER pointr ] [ TALLYING IN tally-ctr ] [ ON OVERFLOW stment ] [ NOT ON OVERFLOW stment ] [ END-UNSTRING ]
57.1 – src-string
is the identifier of an alphanumeric class data item. It cannot be reference modified. Src-string is the sending field.
57.2 – delim
is a nonumeric literal or the identifier of an alphanumeric data item. It is the delimiter for the UNSTRING operation.
57.3 – dest-string
is the identifier of an alphanumeric, alphabetic, or numeric DISPLAY data item. It is the receiving field for the data from src-string.
57.4 – delim-dest
is the identifier of an alphanumeric data item. It is the receiving field for delimiters.
57.5 – countr
is the identifier of an elementary numeric data item described as an integer. It contains the count of characters moved.
57.6 – pointr
is the identifier of an elementary numeric data item described as an integer. It points to the current character position in src-string.
57.7 – tally-ctr
is the identifier of an elementary numeric data item described as an integer. It counts the number of dest-string fields accessed during the UNSTRING operation.
57.8 – stment
is an imperative statement.
58 – USE
The USE statement specifies Declarative procedures to handle input/output errors and database exception conditions. It can also specify procedures to be executed before the program processes a specific report group. These procedures supplement the standard procedures in the COBOL Run-Time System and OpenVMS RMS.
58.1 – 1format AFTER EXCEPTION
The USE statement specifies Declarative procedures to handle input/output errors and database exception conditions. It can also specify procedures to be executed before the program processes a specific report group. These procedures supplement the standard procedures in the COBOL Run-Time System and OpenVMS RMS. Format 1 - { {file-name} ...} { INPUT } USE [GLOBAL] AFTER STANDARD {EXCEPTION }PROCEDURE ON{ OUTPUT }. {ERROR } { I-O } { EXTEND }
58.1.1 – file-name
is the name of a file connector described in a file description entry in a Data Division. It cannot refer to a sort or merge file.
58.2 – 2format BEFORE REPORTING
The USE statement specifies Declarative procedures to handle input/output errors and database exception conditions. It can also specify procedures to be executed before the program processes a specific report group. These procedures supplement the standard procedures in the COBOL Run-Time System and OpenVMS RMS. Format 2 - USE [GLOBAL] BEFORE REPORTING group-data-name .
58.2.1 – group-data-name
is the name of a report group in a report group description entry in a Data Division. It must not appear in more than one USE statement.
58.3 – 3format DB-EXCEPTION
The USE statement specifies Declarative procedures to handle input/output errors and database exception conditions. It can also specify procedures to be executed before the program processes a specific report group. Format 3 - USE [GLOBAL] FOR DB-EXCEPTION [ON { {DBM$_exception-condition} ... }]. [ { OTHER }]
58.3.1 – DBM$ exception-condition
is a symbolic constant name beginning with the characters "DBM$_". It identifies a DBMS exception condition.
59 – WRITE
The WRITE statement releases a logical record to an output or input-output file. It can also position lines vertically on a logical page.
59.1 – 1format_sequential
The WRITE statement releases a logical record to an output or input-output file. It can also position lines vertically on a logical page. Format 1 - WRITE rec-name [ FROM src-item ] [ ALLOWING NO OTHERS ] [ { advance-num [ LINE ] } ] [ { BEFORE } { [ LINES ] } ] [ { AFTER } ADVANCING { top-name } ] [ { PAGE } ] [ AT { END-OF-PAGE } stment ] [ { EOP } ] [ NOT AT { END-OF-PAGE } stment ] [ { EOP } ] [ END-WRITE ]
59.1.1 – rec-name
is the name of a logical record described in the Data Division File Section. It cannot be qualified. The logical record cannot be in a sort-merge file description entry.
59.1.2 – src-item
is the identifier of the data item that contains the data. If src-item is a function-identifier, it must reference an alphanumeric function.
59.1.3 – advance-num
is an integer or the identifier of an unsigned data item described as an integer. Its value can be zero.
59.1.4 – top-name
is a mnemonic-name equated to "C01" in the SPECIAL-NAMES paragraph of the Environment Division. It represents top-of-page and is equivalent to the PAGE phrase.
59.1.5 – stment
is an imperative statement.
59.2 – 2format_relative_indexed
The WRITE statement releases a logical record to an output or input-output file. It can also position lines vertically on a logical page. Format 2 - WRITE rec-name [ FROM src-item ] [ ALLOWING NO OTHERS ] [ INVALID KEY stment ] [ NOT INVALID KEY stment ] [ END-WRITE ]
59.2.1 – rec-name
is the name of a logical record described in the Data Division File Section. It cannot be qualified. The logical record cannot be in a sort-merge file description entry.
59.2.2 – src-item
is the identifier of the data item that contains the data. If src-item is a function-identifier, it must reference an alphanumeric function.
59.2.3 – stment
is an imperative statement.