7 PROCEDURE DIVISION

PROCEDURE DIVISION Syntax

  PROCEDURE DIVISION [ { USING Subprogram-Argument...     } ]
  ~~~~~~~~~ ~~~~~~~~   { ~~~~~                            }
                       { CHAINING Main-Program-Argument...}
                         ~~~~~~~~
                     [ RETURNING identifier-1 ] .
[ DECLARATIVES. ]      ~~~~~~~~~
  ~~~~~~~~~~~~
[ Event-Handler-Routine... . ]

[ END DECLARATIVES. ]
  ~~~ ~~~~~~~~~~~~
  General-Program-Logic

[ Nested-Subprogram... ]

[ END PROGRAM|FUNCTION name-1 ]
  ~~~ ~~~~~~~ ~~~~~~~~

The PROCEDURE DIVISION of any GnuCOBOL program marks the point where all executable code is written.

7.1 PROCEDURE DIVISION USING

PROCEDURE DIVISION Subprogram-Argument Syntax

[ BY { REFERENCE [ OPTIONAL ]                       } ] identifier-1
     { ~~~~~~~~~   ~~~~~~~~                         }
     { VALUE [ [ UNSIGNED ] SIZE IS { AUTO      } ] }
       ~~~~~     ~~~~~~~~   ~~~~    { ~~~~      }
                                    { DEFAULT   }
                                    { ~~~~~~~   }
                                    { integer-1 }

The USING clause defines the arguments that will be passed to a GnuCOBOL program which is serving as a subprogram.

  1. The reserved words BY and IS are optional and may be omitted. The presence or absence of these words have no effect upon the program.

  2. The USING clause should only be used on the procedure division header of subprograms (subroutines or user-defined functions).

  3. The calling program will pass zero or more data items, known as arguments, to this subprogram — there must be exactly as many <identifier-1> data items specified on the USING clause as the maximum number of arguments the subprogram will ever be passed.

  4. If a subprogram does not expect any arguments, it should not have a USING clause specified on its procedure division header.

  5. The order in which arguments are defined on the USING clause must correspond to the order in which those arguments will be passed to the subprogram by the calling program.

  6. The identifiers specified on the USING clause must be defined in the linkage section of the subprogram. No storage is actually allocated for those identifiers in the subprogram as the actual storage for them will exist in the calling program.

  7. A GnuCOBOL subprogram expects that all arguments to it will be one of two things:

    • The memory address of the actual data item (allocated in the calling program) that is being passed to the subprogram.

    • A numeric, full-word, binary value (i.e. USAGE BINARY-LONG ( 6.9.61 USAGE)) which is the actual argument being passed to the subprogram.

    In the case of the former, the USING clause on the procedure division header should describe the argument via the BY REFERENCE clause — in the latter case, a BY VALUE specification should be coded. This allows the code generated by the compiler to properly reference the subprogram arguments at run-time.

  8. BY REFERENCE is the assumed default for the first USING argument should no BY clause be specified for it. Subsequent arguments will assume the BY specification of the argument prior to them should they lack a BY clause of their own.

  9. Changes made by a subprogram to the value of an argument specified on the USING clause will “be visible” to the calling program only if BY REFERENCE was explicitly specified or implicitly assumed for the argument on the subprogram’s procedure division header and the argument was passed to the subprogram BY REFERENCE by the calling program. 11.6.1 Subprogram Arguments, for additional information on the mechanics of how arguments are passed to subprograms.

  10. The optional SIZE clause allows you to specify the number of bytes a BY VALUE argument will occupy, with SIZE DEFAULT specifying 4 bytes (this is the default if no SIZE clause is used), SIZE AUTO specifying the size of the argument in the calling program and SIZE <integer-1> specifying a specific byte count.

  11. The optional UNSIGNED keyword, legal only if SIZE AUTO or SIZE <integer-1> are coded, will add the unsigned attribute to the argument’s specification in the C-language function header code generated for the subprogram. While not of any benefit when the calling program is a GnuCOBOL program, this can improve compatibility with a C-language calling program.

  12. The OPTIONAL keyword, legal only on BY REFERENCE arguments, allows calling programs to code OMITTED for that corresponding argument when they call this subprogram. 7.8.5 CALL. for additional information on this feature.

7.2 PROCEDURE DIVISION CHAINING

PROCEDURE DIVISION Main-Program-Argument Syntax

[ BY REFERENCE ] [ OPTIONAL ] identifier-1
     ~~~~~~~~~     ~~~~~~~~

The CHAINING term provides one mechanism a programmer may use to retrieve command-line arguments passed to a program at execution time.

  1. PROCEDURE DIVISION CHAINING may only be coded in a main program (that is, the first program executed when a compiled GnuCOBOL compilation unit is executed). It cannot be used in any form of subprogram.

  2. The CHAINING clause defines arguments that will be passed to a main program from the operating system. The argument identifiers specified on the CHAINING clause will be populated by character strings comprised of the parameters specified to the program on the command line that executed it, as follows:

    1. When a GnuCOBOL program is executed from a command-line, the complete command line text will be broken into a series of tokens, where each token is identified as being a word separated from the others in the command text by at least one space. For example, if the command line was /usr/local/myprog THIS IS A TEST, there will be five tokens identified by the operating system — ‘/usr/local/myprog‘, ‘THIS‘, ‘IS‘, ‘A‘ and ‘TEST‘.

    2. Multiple space-delimited tokens may be treated as a single token by enclosing them in quotes. For example, there are only three tokens generated from the command line C:Pgmsmyprog.exe ':code:`THIS IS A‘ TEST` — ‘C:Pgmsmyprog.exe‘, ‘THIS IS A‘ and ‘TEST‘. When quote characters are used to create multi-word tokens, the quote characters themselves are stripped from the token’s value.

    3. Once tokens have been identified, the first one (the command) will be discarded; the rest will be stored into the CHAINING arguments when the program begins execution, with the 2nd token going to the 1st argument, the 3rd token going to the 2nd argument and so forth.

    4. If there are more tokens than there are arguments, the excess tokens will be discarded.

    5. If there are fewer tokens than there are arguments, the excess arguments will be initialized as if the INITIALIZE <identifier-1> ( 7.8.24 INITIALIZE) statement were executed.

    6. All identifiers specified on the CHAINING clause should be defined as PIC X, PIC A, group items (which are treated implicitly as PIC X) or as PIC 9 USAGE DISPLAY. The use of USAGE BINARY (or the like) data items as CHAINING arguments is not recommended as all command-line tokens will be retained in their original character form as they are moved into the argument data items.

    7. If an argument identifier is smaller in storage size than the token value to be stored in it, the right-most excess characters of the token value will be truncated as the value is moved in. Any JUSTIFIED RIGHT clause on such an argument identifier will be ignored.

    8. If an argument is larger in storage size than the token value to be stored in it, the token value will be moved into the argument identifier in a left-justified manner. unmodified-modified byte positions in the identifier will be space filled, unless the argument identifier is defined as PIC 9 USAGE DISPLAY, in which case unmodified bytes will be filled with ‘0‘ characters from the systems native character set.

      This behaviour when the argument is defined as PIC 9 may be unacceptable, as an argument defined as PIC 9(3) but passed in a value of ‘1‘ from the command line will receive a value of ‘100‘, not ‘001‘. Consider defining “numeric” command line arguments as PIC X and then using the NUMVAL intrinsic function ( 8.1.70 NUMVAL) function to determine the proper numeric value.

7.3 PROCEDURE DIVISION RETURNING

PROCEDURE DIVISION RETURNING Syntax

RETURNING identifier-1
~~~~~~~~~

The RETURNING clause on the PROCEDURE DIVISION header documents that the subprogram in which the clause appears will be returning a numeric value back to the program that called it. This is only available for functions as it does not work for programs and has issues depending on the platform (operating system) in use - You must test for this for the specific platform.

  1. The RETURNING clause is optional within a subroutine, as not all subroutines return a value to their caller.

  2. The RETURNING clause is mandatory within a user-defined function, as all such must return a numeric result.

  3. The <identifier-1> data item should be defined as a USAGE BINARY-LONG data item.

  4. Main programs that wish to “pass back” a return code value to the operating system when they exit do not use RETURNING - they do so simply by MOVEing a value to the RETURN-CODE special register.

  5. This is not the only mechanism that a subprogram may use to pass a value back to its caller. Other possibilities are:

    1. The subprogram may modify any argument that is specified as BY REFERENCE on its PROCEDURE DIVISION header. Whether the calling program can actually “see” any modifications depends upon how the calling program passed the argument to the subprogram. 7.8.5 CALL, for more information.

    2. A data item with the GLOBAL ( 6.9.23 GLOBAL) attribute specified in its description in the calling program is automatically visible to and updatable by a subprogram nested with the calling program. 11.2 Independent vs Contained vs Nested Subprograms, for more information on subprogram nesting.

    3. A data item defined with the EXTERNAL ( 6.9.18 EXTERNAL) attribute in a subprogram and the calling program (same name in both programs) is automatically visible to and updatable by both programs, even if those programs are compiled separately from one another.

7.4 PROCEDURE DIVISION Sections and Paragraphs

The procedure division is the only one of the COBOL divisions that allows you to create your own sections and paragraphs. These are collectively referred to as Procedures, and the names you create for those sections and paragraphs are called Procedure Names.

Procedure names are optional in the procedure division and — when used — are named entirely according to the needs and whims of the programmer.

Procedure names may be up to thirty one (31) characters long and may consist of letters, numbers, dashes and underscores. A procedure name may neither begin nor end with a dash (’-‘) or underscore (’_‘) character. This means that Main, 0100-Read-Transaction and 17 are all perfectly valid procedure names.

There are three circumstances under which the use of certain GnuCOBOL statements or options will require the specification of procedures. These situations are:

  1. When DECLARATIVES ( 7.5 DECLARATIVES) are specified.

  2. When the ENTRY statement ( 7.8.14 ENTRY) is being used.

  3. When any procedure division statement that references procedures is used. These statements are:

    • ALTER <procedure-name>

    • GO TO <procedure-name>

    • MERGE ... OUTPUT PROCEDURE <procedure-name>

    • PERFORM <procedure-name>

    • SORT ... INPUT PROCEDURE <procedure-name> and/or SORT ... INPUT PROCEDURE <procedure-name>

7.5 DECLARATIVES

DECLARATIVES Syntax

section-name-1 SECTION.

 USE { [ GLOBAL ] AFTER STANDARD { EXCEPTION } PROCEDURE ON { INPUT       } }
 ~~~ {   ~~~~~~                  { ~~~~~~~~~ }              { ~~~~~       } }
     {                           { ERROR     }              { OUTPUT      } }
     {                             ~~~~~                    { ~~~~~~      } }
     {                                                      { I-O         } }
     { FOR DEBUGGING ON { procedure-name-1           }      { ~~~         } }
     {     ~~~~~~~~~    { ALL PROCEDURES             }      { EXTEND      } }
     {                  { ~~~ ~~~~~~~~~~             }      { ~~~~~~      } }
     {                  { REFERENCES OF identifier-1 }      { file-name-1 } }
     {                                                                      }
     { [ GLOBAL ] BEFORE REPORTING identifier-2                             }
     {   ~~~~~~   ~~~~~~ ~~~~~~~~~                                          }
     {                                                                      }
     { AFTER EC|{EXCEPTION CONDITION}                                       }
             ~~  ~~~~~~~~~ ~~~~~~~~~

The AFTER EXCEPTION CONDITION and AFTER EC clauses are syntactically recognized but are otherwise non-functional. The DECLARATIVES area of the procedure division allows the programmer to define a series of “trap” procedures (referred to as declarative procedures) capable of intercepting certain events that may occur at program execution time. The syntax diagram above shows the format of a single such procedure.

  1. The reserved words AFTER, FOR, ON, PROCEDURE and STANDARD are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. EC and EXCEPTION CONDITION are interchangeable.

  3. The declaratives area may contain any number of declarative procedures, but no two declarative procedures should be coded to trap the same event.

  4. The following points apply to the USE BEFORE REPORTING clause:

    1. <identifier-2> must be a report group.

    2. At run-time, the declaratives procedure will be executed prior to the processing of the specified report group’s presentation; within the procedure you may take either of the following actions:

      • You may adjust the value(s) of any items referenced in SUM ( 8.1.92 SUM) or SOURCE ( 6.9.51 SOURCE) clauses in the report group.

      • You may execute the SUPPRESS ( 7.8.47 SUPPRESS) statement to squelch the presentation of the specified report group altogether. Note that you will be suppressing this one specific instance of that group’s presentation and not all of them.

  5. The following points apply to the USE FOR DEBUGGING clause:

    1. This clause allows you to define a declarative procedure that will be invoked whenever…

      • …<identifier-1> is referenced on any statement.

      • …<procedure-name-1> is executed.

      • …any procedure is executed (ALL PROCEDURES).

    2. A USE FOR DEBUGGING declarative procedure will be ignored at compilation time unless WITH DEBUGGING MODE is specified in the SOURCE-COMPUTER ( 5.1.1 SOURCE-COMPUTER) paragraph. Neither the compiler’s -fdebugging-line switch nor -debug switch will activate this feature.

    3. Any USE FOR DEBUGGING declarative procedures will be ignored at execution time unless the run-time environment variable ( 10.2.3 Run Time Environment Variables) has been set to a value of ‘Y‘, ‘y‘ or ‘1‘.

    4. The typical use of a USE FOR DEBUGGING declarative procedure is to display the DEBUG-ITEM special register, which will be implicitly and automatically created in your program for you if WITH DEBUGGING MODE is active.

      The structure of DEBUG-ITEM will be as follows:

      01  DEBUG-ITEM.
          05 DEBUG-LINE      PIC X(6).
          05 FILLER          PIC X(1) VALUE SPACE.
          05 DEBUG-NAME      PIC X(31).
          05 FILLER          PIC X(1) VALUE SPACE.
          05 DEBUG-SUB-1     PIC S9(4) SIGN LEADING SEPARATE.
          05 FILLER          PIC X(1) VALUE SPACE.
          05 DEBUG-SUB-2     PIC S9(4) SIGN LEADING SEPARATE.
          05 FILLER          PIC X(1) VALUE SPACE.
          05 DEBUG-SUB-3     PIC S9(4) SIGN LEADING SEPARATE.
          05 FILLER          PIC X(1) VALUE SPACE.
          05 DEBUG-CONTENTS  PIC X(31).
      

      where…

      • DEBUG-LINE

        … is the program line number of the statement that triggered the declaratives procedure.

      • DEBUG-NAME

        … is the procedure name or identifier name that triggered the declaratives procedure.

      • DEBUG-SUB-1

        … is the first subscript value (if any) for the reference of the identifier that triggered the declaratives procedure.

      • DEBUG-SUB-2

        … is the second subscript value (if any) for the reference of the identifier that triggered the declaratives procedure.

      • DEBUG-SUB-3

        … is the third subscript value (if any) for the reference of the identifier that triggered the declaratives procedure.

      • DEBUG-CONTENTS

        … is a (brief) statement of the manner in which the procedure that triggered the declaratives procedure was executed or the first 31 characters of the value of the identifier whose reference triggered the declaratives procedure (the value after the statement was executed).

  6. The USE AFTER STANDARD ERROR PROCEDURE clause defines a declarative procedure invoked any time a failure is encountered with the specified I/O type (or against the specified file(s)).

  7. The GLOBAL ( 6.9.23 GLOBAL) option, if used, allows a declarative procedure to be used across the program containing the USE statement and any subprograms nested within that program.

  8. Declarative procedures may not reference any other procedures defined outside the scope of DECLARATIVES.

7.6 Common Clauses on Executable Statements

7.6.1 AT END + NOT AT END

AT END Syntax

[ AT END imperative-statement-1 ]
     ~~~
[ NOT AT END imperative-statement-2 ]
  ~~~    ~~~

AT END clauses may be specified on READ ( 7.8.32 READ), RETURN ( 7.8.36 RETURN), SEARCH ( 7.8.39 SEARCH) and SEARCH ALL ( 7.8.40 SEARCH ALL) statements.

  1. The following points pertain to the use of these clauses on READ ( 7.8.32 READ) and RETURN ( 7.8.36 RETURN) statements:

    1. The AT END clause will — if present — cause <imperative-statement-1> ( Imperative Statement) to be executed if the statement fails due to a file status of 10 (end-of-file). File Status Codes, for a list of possible File Status codes.

      An AT END clause will not detect other non-zero file-status values.

      Use a DECLARATIVES ( 7.5 DECLARATIVES) routine or an explicitly-declared file status field tested after the READ or RETURN to detect error conditions other than end-of-file.

    2. A NOT AT END clause will cause <imperative-statement-2> to be executed if the READ or RETURN attempt is successful.

  2. The following points pertain to the use of these clauses on SEARCH ( 7.8.39 SEARCH) and SEARCH ALL ( 7.8.40 SEARCH ALL) statements:

    1. An AT END clause detects and handles the case where either form of table search has failed to locate an entry that satisfies the search conditions being used.

    2. The NOT AT END clause is not allowed on either form of table search.

7.6.2 CORRESPONDING

Three GnuCOBOL statements — ADD ( 7.8.2.3 ADD CORRESPONDING), MOVE ( 7.8.28.2 MOVE CORRESPONDING) and SUBTRACT ( 7.8.46.3 SUBTRACT CORRESPONDING) support the use of a CORRESPONDING option:

ADD CORRESPONDING group-item-1 TO group-item-2
MOVE CORRESPONDING group-item-1 TO group-item-2
SUBTRACT CORRESPONDING group-item-1 FROM group-item-2

This option allows one or more data items within one group item (<group-item-1> — the first named on the statement) to be paired with correspondingly-named (hence the name) in a second group item (<group-item-2> — the second named on the statement). The contents of <group-item-1> will remain unaffected by the statement while one or more data items within <group-item-2> will be changed.

In order for <data-item-1>, defined subordinate to group item <group-item-1> to be a corresponding match to <data-item-2> which is subordinate to <group-item-2>, each of the following must be true:

  1. Both <data-item-1> and <data-item-2> must have the same name, and that name may not explicitly or implicitly be FILLER.

  2. Both <data-item-1> and <data-item-2>…

    1. …must exist at the same relative structural “depth” of definition within <group-item-1> and <group-item-2>, respectively

    2. …and all “parent” data items defined within each group item must have identical (but non-FILLER) names.

  3. When used with a MOVE verb…

    1. …one of <data-item-1> or <data-item-2> (but not both) is allowed to be a group item

    2. …and it must be valid to move <data-item-1> TO <data-item-2>.

  4. When used with ADD or SUBTRACT verbs, both <data-item-1> and <data-item-2> must be numeric, elementary, unedited items.

  5. Neither <data-item-1> nor <data-item-2> may be a REDEFINES ( 6.9.41 REDEFINES) or RENAMES ( 6.9.42 RENAMES) of another data item.

  6. Neither <data-item-1> nor <data-item-2> may have an OCCURS ( 6.9.35 OCCURS) clause, although either may contain subordinate data items that do have an OCCURS clause (assuming rule 3a applies)

Observe the definitions of data items ‘Q‘ and ‘Y‘…

01  Q.                           01  Y.
    03 X.                            02 A         PIC X(1).
       05 A         PIC 9(1).        02 G1.
       05 G1.                           03 G2.
          10 G2.                           04 B   PIC X(1).
             15 B   PIC X(1).        02 C         PIC X(1).
       05 C.                         02 G3.
          10 FILLER PIC X(1).           03 G5.
       05 G3.                              04 D   PIC X(1).
          10 G4.                        03 G6     PIC X(1).
             15 D   PIC X(1).        02 E         PIC 9(1).
       05 E         PIC X(1).        02 F         PIC X(1).
       05 F         REDEFINES V1     02 G         PIC X(4).
                    PIC X(1).        02 H         OCCURS 4 TIMES
       05 G.                                      PIC X(1).
          10 G6     OCCURS 4 TIMES   66 I         RENAMES E.
                    PIC X(1).        02 J.
       05 H         PIC X(4).           03 K.
       05 I         PIC 9(1).              04 L.
       05 J.                                  05 M.
          10 K.
             15 M   PIC X(1).

The following are the valid CORRESPONDING matches, assuming the statement MOVE CORRESPONDING X TO Y is being executed (there are no valid corresponding matches for ADD CORRESPONDING or SUBTRACT CORRESPONDING because every potential match up violates rule #4):

A, B, C, G

The following are the CORRESPONDING match ups that passed rule #1 (but failed on another rule), and the reasons why they failed.

  • Data Item Failure Reason

  • D Fails due to rule #2b

  • E Fails due to rule #3b

  • F Fails due to rule #5

  • G1 Fails due to rule #3a

  • G2 Fails due to rule #3a

  • G3 Fails due to rule #3a

  • G4 Fails due to rule #1

  • G5 Fails due to rule #1

  • G6 Fails due to rule #6

  • H Fails due to rule #6

  • I Fails due to rule #5

  • J Fails due to rule #3a

  • K Fails due to rule #3a

  • L Fails due to rule #1

  • M Fails due to rule #2a

7.6.3 INVALID KEY + NOT INVALID KEY

INVALID KEY Syntax

[ INVALID KEY imperative-statement-1 ]
  ~~~~~~~
[ NOT INVALID KEY imperative-statement-2 ]
  ~~~ ~~~~~~~

INVALID KEY clauses may be specified on DELETE ( 7.8.11 DELETE), READ ( 7.8.32.2 Random READ), REWRITE ( 7.8.37 REWRITE), START ( 7.8.43 START) and WRITE ( 7.8.52 WRITE) statements.

Specification of an INVALID KEY clause will allow your program to trap an I/O failure condition (with an I/O error code in the file’s FILE-STATUS ( 5.2.1 SELECT) field) that has occurred due to a record-not-found condition and handle it gracefully by executing <imperative-statement-1> ( Imperative Statement).

An optional NOT INVALID KEY clause will cause <imperative-statement-2> to be executed if the statement’s execution was successful.

7.6.4 ON EXCEPTION + NOT ON EXCEPTION

ON EXCEPTION Syntax

[ ON EXCEPTION imperative-statement-1 ]
     ~~~~~~~~~
[ NOT ON EXCEPTION imperative-statement-2 ]
  ~~~    ~~~~~~~~~

EXCEPTION clauses may be specified on ACCEPT ( 7.8.1 ACCEPT), CALL ( 7.8.5 CALL) and DISPLAY ( 7.8.12 DISPLAY) statements.

Specification of an exception clause will allow your program to trap a failure condition that has occurred and handle it gracefully by executing <imperative-statement-1> ( Imperative Statement). If such a condition occurs at runtime without having one of these clauses specified, an error message will be generated (by the GnuCOBOL runtime library) to the SYSERR device (pipe 2). The program may also be terminated, depending upon the type and severity of the error.

An optional NOT ON EXCEPTION clause will cause <imperative-statement-2> to be executed if the statement’s execution was successful.

7.6.5 ON OVERFLOW + NOT ON OVERFLOW

ON OVERFLOW Syntax

[ ON OVERFLOW imperative-statement-1 ]
     ~~~~~~~~
[ NOT ON OVERFLOW imperative-statement-2 ]
  ~~~    ~~~~~~~~

OVERFLOW clauses may be specified on CALL ( 7.8.5 CALL), STRING ( 7.8.45 STRING) and UNSTRING ( 7.8.51 UNSTRING) statements.

An ON OVERFLOW clause will allow your program to trap a failure condition that has occurred and handle it gracefully by executing <imperative-statement-1> ( Imperative Statement). If such a condition occurs at runtime without having one of these clauses specified, an error message will be generated (by the GnuCOBOL runtime library) to the SYSERR device (pipe 2). The program may also be terminated, depending upon the type and severity of the error.

An optional NOT ON OVERFLOW clause will cause <imperative-statement-2> to be executed if the statement’s execution was successful.

7.6.6 ON SIZE ERROR + NOT ON SIZE ERROR

ON SIZE ERROR Syntax

[ ON SIZE ERROR imperative-statement-1 ]
     ~~~~ ~~~~~
[ NOT ON SIZE ERROR imperative-statement-2 ]
  ~~~    ~~~~ ~~~~~

SIZE ERROR clauses may be included on ADD ( 7.8.2 ADD), COMPUTE ( 7.8.9 COMPUTE), DIVIDE ( 7.8.13 DIVIDE), MULTIPLY ( 7.8.29 MULTIPLY) and SUBTRACT ( 7.8.46 SUBTRACT) statements.

Including an ON SIZE ERROR clause on an arithmetic statement will allow your program to trap a failure of an arithmetic statement (either generating a result too large for the receiving field, or attempting to divide by zero) and handle it gracefully by executing <imperative-statement-1> ( Imperative Statement). Field size overflow conditions occur silently, usually without any runtime messages being generated, even though such events rarely lend themselves to generating correct results. Division by zero errors, when no ON SIZE ERROR clause exists, will produce an error message (by the GnuCOBOL runtime library) to the SYSERR device (pipe 2) and will also abort the program.

An optional NOT ON SIZE ERROR clause will cause <imperative-statement-2> to be executed if the arithmetic statement’s execution was successful.

7.6.7 ROUNDED

ROUNDED Syntax

ROUNDED [ MODE IS { AWAY-FROM-ZERO         }
~~~~~~~   ~~~~    { ~~~~~~~~~~~~~~         }
                  { NEAREST-AWAY-FROM-ZERO }
                  { ~~~~~~~~~~~~~~~~~~~~~~ }
                  { NEAREST-EVEN           }
                  { ~~~~~~~~~~~~           }
                  { NEAREST-TOWARD-ZERO    }
                  { ~~~~~~~~~~~~~~~~~~~    }
                  { PROHIBITED             }
                  { ~~~~~~~~~~             }
                  { TOWARD-GREATER         }
                  { ~~~~~~~~~~~~~~         }
                  { TOWARD-LESSER          }
                  { ~~~~~~~~~~~~~          }
                  { TRUNCATION             }
                    ~~~~~~~~~~

GnuCOBOL provides for control over the final rounding process applied to the receiving fields on all arithmetic verbs. Each of the arithmetic statements (ADD ( 7.8.2 ADD), COMPUTE ( 7.8.9 COMPUTE), DIVIDE ( 7.8.13 DIVIDE), MULTIPLY ( 7.8.29 MULTIPLY) and SUBTRACT ( 7.8.46 SUBTRACT)) statements allow an optional ROUNDED clause to be applied to each receiving data item.

The following rules apply to the rounding behaviour induced by this clause.

  1. Rounding only applies when the result being saved to a receiving field with a ROUNDED clause is a non-integer value.

  2. Absence of a ROUNDED clause is the same as specifying ROUNDED MODE IS TRUNCATION.

  3. Use of a ROUNDED clause without a MODE specification is the same as specifying ROUNDED MODE IS NEAREST-AWAY-FROM-ZERO.

The behaviour of the eight different rounding modes is defined in the following table. Note that a ‘...‘ indicates the last digit repeats. The examples assume an integer receiving field.

  • AWAY-FROM-ZERO

    Rounding is to the nearest value of larger magnitude.

    • -3.510 -4 +3.510 +4

    • -3.500 -4 +3.500 +4

    • -3.499… -4 +3.499… +4

    • -2.500 -3 +2.500 +3

    • -2.499… -3 +2.499… +3

  • NEAREST-AWAY-FROM-ZERO

    Rounding is to the nearest value (larger or smaller). If two values are equally near, the value with the larger absolute value is selected.

    • -3.510 -4 +3.510 +4

    • -3.500 -4 +3.500 +4

    • -3.499… -3 +3.499… +3

    • -2.500 -3 +2.500 +3

    • -2.499… -2 +2.499… +2

  • NEAREST-EVEN

    Rounding is to the nearest value (larger or smaller). If two values are equally near, the value whose rightmost digit is even is selected. This mode is sometimes called “Banker’s rounding”.

    • -3.510 -4 +3.510 +4

    • -3.500 -4 +3.500 +4

    • -3.499… -3 +3.499… +3

    • -2.500 -2 +2.500 +2

    • -2.499… -2 +2.499… +2

  • NEAREST-TOWARD-ZERO

    Rounding is to the nearest value (larger or smaller). If two values are equally near, the value with the smaller absolute value is selected.

    • -3.510 -4 +3.510 +4

    • -3.500 -3 +3.500 +3

    • -3.499… -3 +3.499… +3

    • -2.500 -2 +2.500 +2

    • -2.499… -2 +2.499… +2

  • PROHIBITED

    No rounding is performed. If the value cannot be represented exactly in the desired format, the EC-SIZE-TRUNCATION condition (exception code 1005) is set (and may be retrieved via the ACCEPT ( 7.8.1.7 ACCEPT FROM Runtime-Info) statement) and the results of the operation are undefined.

    • -3.510 Undefined +3.510 Undefined

    • -3.500 Undefined +3.500 Undefined

    • -3.499… Undefined +3.499… Undefined

    • -2.500 Undefined +2.500 Undefined

    • -2.499… Undefined +2.499… Undefined

  • TOWARD-GREATER

    Rounding is toward the nearest value whose algebraic value is larger.

    • -3.510 -3 +3.510 +4

    • -3.500 -3 +3.500 +4

    • -3.499… -3 +3.499… +4

    • -2.500 -2 +2.500 +3

    • -2.499… -2 +2.499… +3

  • TOWARD-LESSER

    Rounding is toward the nearest value whose algebraic value is smaller.

    • -3.510 -4 +3.510 +3

    • -3.500 -4 +3.500 +3

    • -3.499… -4 +3.499… +3

    • -2.500 -3 +2.500 +2

    • -2.499… -3 +2.499… +2

  • TRUNCATION

    Rounding is to the nearest value whose magnitude is smaller.

    • -3.510 -3 +3.510 +3

    • -3.500 -3 +3.500 +3

    • -3.499… -3 +3.499… +3

    • -2.500 -2 +2.500 +2

    • -2.499… -2 +2.499… +2

7.7 Special Registers

GnuCOBOL, like other COBOL dialects, includes a number of data items that are automatically available to a programmer without the need to actually define them in the data division. COBOL refers to such items as registers or special registers. The special registers available to a GnuCOBOL program are as follows:

  • COB-CRT-STATUS

    PIC 9(4) — This is the default data item allocated for use by the ACCEPT <data-item> statement ( 7.8.1.4 ACCEPT data-item), if no CRT STATUS ( 5.1.3 SPECIAL-NAMES) clause was specified..

  • DEBUG-ITEM

    Group Item — A group item in which debugging information generated by a USE FOR DEBUGGING section in the declaratives area of the procedure division will place information documenting why the USE FOR DEBUGGING procedure was invoked. Consult the DECLARATIVES ( 7.5 DECLARATIVES) documentation for information on the structure of this register.

  • LINAGE-COUNTER

    BINARY-LONG SIGNED — An occurrence of this register exists for each selected file having a LINAGE ( 6.2.1 File/Sort-Description) clause. If there are multiple files whose file descriptions have LINAGE clauses, any explicit references to this register will require qualification (using OF file-name). The value of this register will be the current logical line number within the page body. The value of this register cannot be modified.

  • LINE-COUNTER

    BINARY-LONG SIGNED — An occurrence of this register exists for each report defined in the program (via an RD ( 6.6 REPORT SECTION)). If there are multiple reports, any explicit references to this register not made in the report section will require qualification (OF report-name). The value of this register will be the current logical line number on the current page. The value of this register cannot be modified.

  • NUMBER-OF-CALL-PARAMETERS

    BINARY-LONG SIGNED — This register contains the number of arguments passed to a subroutine — the same value that would be returned by the C$NARG built-in system subroutine ( 8.2.9 C$NARG). Its value will be zero when referenced in a main program. This register, when referenced from within a user-defined function, returns a value of one (’1‘) if the function has any number of arguments and a zero if it has no arguments.

  • PAGE-COUNTER

    BINARY-LONG SIGNED — An occurrence of this register exists for each report having an RD ( 6.6 REPORT SECTION). If there are multiple such reports, any explicit references to this register not made in the report section will require qualification ( OF report-name). The value of this register will be the current report page number. The value of this register cannot be modified.

  • RETURN-CODE

    BINARY-LONG SIGNED — This register provides a numeric data item into which a subroutine may MOVE ( 7.8.28 MOVE) a value (which will then be available to the calling program) prior to transferring control back to the program that called it, or into which a main program may MOVE a value before returning control to the operating system. Many built-in subroutines will return a value using this register. These values are — by convention — used to signify success (usually with a value of 0) or failure (usually with a non-zero value) of the process the program was attempting to perform. This register may also be modified by a subprogram as a result of that subprogram’s use of the RETURNING ( 7.3 PROCEDURE DIVISION RETURNING) clause.

  • SORT-RETURN

    BINARY-LONG SIGNED — This register is used to report the success/fail status of a RELEASE ( 7.8.34 RELEASE) or RETURN ( 7.8.36 RETURN) statement. A value of 0 is reported on success. A value of 16 denotes failure. An AT END ( 7.6.1 AT END + NOT AT END) condition on a RETURN is not considered a failure.

  • WHEN-COMPILED

    PIC X(16) — This register contains the date and time the program was compiled in the format ‘mm/dd/yyhh.mm.ss‘. Note that only a two-digit year is provided.

LENGTH OF Syntax

LENGTH OF numeric-literal-1 | identifier-1
~~~~~~

Alphanumeric literals and identifiers may optionally be prefixed with the LENGTH OF clause. The compile-time value generated by this clause will be the number of bytes in the alphanumeric literal or the defined size (in bytes) of the identifier.

  1. The reserved word OF is optional and may be omitted. The presence or absence of this word has no effect upon the program. Here is an example. The following two GnuCOBOL statements both display the same result (27):

    01  Demo-Identifier          PIC X(27).
    ...
        DISPLAY LENGTH OF "This is a LENGTH OF Example"
        DISPLAY LENGTH OF Demo-Identifier
    
  2. The LENGTH OF clause on a literal or identifier reference may generally be used anywhere a numeric literal might be specified, with the following exceptions:

7.8 GnuCOBOL Statements

7.8.1 ACCEPT

7.8.1.1 ACCEPT FROM CONSOLE

ACCEPT FROM CONSOLE Syntax

  ACCEPT { identifier-1 }   [ FROM mnemonic-name-1 ]
  ~~~~~~                      ~~~~
         { OMITTED      }
           ~~~~~~~

[ END-ACCEPT ]
  ~~~~~~~~~~

This format of the ACCEPT statement is used to read a value from the console window or the standard input device and store it into a data item (<identifier-1>).

  1. If no FROM clause is specified, FROM CONSOLE is assumed.

  2. The specified <mnemonic-name-1> must either be one of the built-in device names CONSOLE, STDIN, SYSIN or SYSIPT, or a user-defined ( 5.1.3 SPECIAL-NAMES) mnemonic name attached to one of those four device names.

  3. Input will be read either from the console window (CONSOLE) or from the system-standard input (pipe 0 = STDIN, SYSIN or SYSIPT) and will be saved in <identifier-1>.

  4. If <identifier-1> is a numeric data item, the character value read from the console or standard-input device will be parsed according to the rules for input to the NUMVAL intrinsic function ( 8.1.70 NUMVAL), except that none of the trailing sign formats are honoured.

7.8.1.2 ACCEPT FROM COMMAND-LINE

ACCEPT FROM COMMAND-LINE Syntax

  ACCEPT identifier-1
  ~~~~~~
         FROM { COMMAND-LINE                                }
         ~~~~ { ~~~~~~~~~~~~                                }
              { ARGUMENT-NUMBER                             }
              { ~~~~~~~~~~~~~~~                             }
              { ARGUMENT-VALUE                              }
              { ~~~~~~~~~~~~~~                              }
              [ ON EXCEPTION imperative-statement-1 ]
                   ~~~~~~~~~
              [ NOT ON EXCEPTION imperative-statement-2 ]
                ~~~    ~~~~~~~~~
[ END-ACCEPT ]
  ~~~~~~~~~~

This format of the ACCEPT statement is used to retrieve information from the program’s command line.

  1. The reserved word ON is optional and may be omitted. The presence or absence of this word has no effect upon the program.

  2. When you accept from the COMMAND-LINE option, you will retrieve the entire set of arguments entered on the command line that executed the program, exactly as they were specified. Parsing that returned data into its meaningful information will be your responsibility.

  3. Using COMMAND-LINE or ARGUMENT-VALUE in a *nix based platform and that includes Linux, OSX, BSD and under windows running msys or MinGW etc, the shell process will expand any arguments that have a ‘*‘ in the list — such as ‘a*‘, ‘abc*.*‘, etc. — and create a list of all files that match the pattern. To avoid this if not wanted, put all such argument within quotes, e.g., progundertest "a*" b c d "ef*" "*hg" and the text within quotes will be passed verbatim to the program (as in the example progundertest).

  4. By accepting from ARGUMENT-NUMBER, you will be asking the GnuCOBOL run-time system to parse the arguments from the command line and return the number of arguments found. Parsing will be conducted according to the following rules:

    1. Arguments will be separated by treating spaces and/or tab characters as the delimiters between arguments. The number of such delimiters separating two non-blank argument values is irrelevant.

    2. Strings enclosed in double-quote characters (’"‘) will be treated as a single argument, regardless of how many spaces or tab characters (if any) might be embedded within the quotation characters.

    3. On Windows systems, single-quote, or apostrophe, characters (’'‘) will be treated just like any other data character and will not delineate argument strings.

  5. By accepting from ARGUMENT-VALUE, you will be asking the GnuCOBOL run-time system to parse the arguments from the command line and return the “current” argument. You specify which argument number is “current” via the ARGUMENT-NUMBER option on the DISPLAY statement ( 7.8.12.2 DISPLAY UPON COMMAND-LINE). Parsing of arguments will be conducted according to the rules set forth above.

  6. The optional ON EXCEPTION and NOT ON EXCEPTION clauses may be used to detect and react to the failure or success, respectively, of an attempt to retrieve an ARGUMENT-VALUE. 7.6.4 ON EXCEPTION + NOT ON EXCEPTION, for additional information.

7.8.1.3 ACCEPT FROM ENVIRONMENT

ACCEPT FROM ENVIRONMENT Syntax

  ACCEPT identifier-1
  ~~~~~~
         FROM { ENVIRONMENT-VALUE            }
         ~~~~ { ~~~~~~~~~~~~~~~~~            }
              { ENVIRONMENT { literal-1    } }
              { ~~~~~~~~~~~ { identifier-1 } }
       [ ON EXCEPTION imperative-statement-1 ]
            ~~~~~~~~~
       [ NOT ON EXCEPTION imperative-statement-2 ]
         ~~~    ~~~~~~~~~
[ END-ACCEPT ]
  ~~~~~~~~~~

This format of the ACCEPT statement is used to retrieve environment variable values.

  1. The reserved word ON is optional and may be omitted. The presence or absence of this word has no effect upon the program.

  2. By accepting from ENVIRONMENT-VALUE, you will be asking the GnuCOBOL run-time system to retrieve the value of the environment variable whose name is currently in the ENVIRONMENT-NAME register. A value may be placed into the ENVIRONMENT-NAME register using the ENVIRONMENT-NAME option of the DISPLAY statement ( 7.8.12.3 DISPLAY UPON ENVIRONMENT-NAME).

  3. A simpler approach to retrieving an environment variables value is to use the ENVIRONMENT option, where you specify the environment variable whose value is to be retrieved right on the ACCEPT statement itself.

  4. The optional ON EXCEPTION and NOT ON EXCEPTION clauses may be used to detect and react to an attempt to retrieve the value of a non-existent environment variable or the successful retrieval of an environment variable’s value, respectively. 7.6.4 ON EXCEPTION + NOT ON EXCEPTION, for additional information.

7.8.1.4 ACCEPT data-item

ACCEPT data-item Syntax

  ACCEPT { identifier-1 }
  ~~~~~~
         { OMITTED      }
           ~~~~~~~
                          [{ FROM EXCEPTION-STATUS }]
                             ~~~~ ~~~~~~~~~~~~~~~~
                          [{ FROM CRT ] [ MODE IS BLOCK ]}
                             ~~~~ ~~~     ~~~~    ~~~~~

         [ AT { | LINE NUMBER { integer-1    }                | } ]
           ~~ { | ~~~~        { identifier-2 }                | }
              { | COLUMN|COL|POSITION|POS NUMBER { integer-2    }
              { | ~~~~~~ ~~~ ~~~~~~~~ ~~~        { identifier-3 }
              {                                                 }
              { { integer-3    }                                }
              { { identifier-4 }                                }

         [ WITH [ Attribute-Specification ]...
           ~~~~
                [ LOWER|UPPER ]
                  ~~~~~ ~~~~~
                [ SCROLL { UP   } [ { integer-4    } LINE|LINES ] ]
                  ~~~~~~ { ~~   }   { identifier-5 }
                         { DOWN }
                           ~~~~
                [ TIMEOUT|TIME-OUT AFTER { integer-5    } ]
                  ~~~~~~~ ~~~~~~~~       { identifier-6 }
                [ CONVERSION ]
                  ~~~~~~~~~~
                [ UPDATE ]
                  ~~~~~~
                [ SIZE  { integer-6    } ]
                  ~~~~  { identifier-7 }
                [ CONTROL        { literal-8    } ]
                  ~~~~~~~        { identifier-8 }
                [ { COLOUR } IS  { integer-9    } ]
                  { COLOR  }     { identifier-9 }
                    ~~~~~~

         [ ON EXCEPTION imperative-statement-1 ]
              ~~~~~~~~~
         [ NOT ON EXCEPTION imperative-statement-2 ]
           ~~~    ~~~~~~~~~
[ END-ACCEPT ]
  ~~~~~~~~~~

The FROM CRT, MODE IS BLOCK and CONVERSIONclauses are syntactically recognized but are otherwise non-functional. This format of the ACCEPT statement is used to retrieve data from a working storate item or a formatted console window screen.

  1. The reserved words AFTER, IS, NUMBER and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The reserved words COLUMN, COL and POSITION are interchangeable.

  3. The reserved words TIMEOUT and TIME-OUT are interchangeable.

  4. If <identifier-1> is defined in the SCREEN SECTION ( 6.7 SCREEN SECTION), any AT, <Attribute-Specification>, LOWER, UPPER or SCROLL clauses will be ignored. In these cases, an implied DISPLAY ( 7.8.12.4 DISPLAY data-item) of <identifier-1> will occur before input is accepted. Coding an explicit DISPLAY identifier-1 before an ACCEPT identifier-1 is redundant and will incur the performance penalty of painting the screen contents twice.

  5. The various AT clauses provide a means of positioning the cursor to a specific spot on the screen before the screen is read. One or the other (but not both) may be used, as follows:

    1. The LINE and COLUMN clauses provide one mechanism for specifying the line and column position to which the cursor will be positioned before allowing the user to enter data. In the absence of one or the other, a value of 1 will be assumed for the one that is missing. The author’s personal preference, however, is to explicitly code both.

    2. The <literal-3> or <identifier-4> value, if specified, must be a four- or six-digit value with the 1st half of the number indicating the line where the cursor should be positioned and the second half indicating the column. You may code only one of each clause on any ACCEPT.

  6. WITH options (including the various individual <Attribute-Specifications>) should be coded only once.

  7. The following <Attribute-Specification> clauses are allowed on the ACCEPT statement; these are the same as those allowed for SCREEN SECTION data items. A particular <Attribute-Specification> may be used only once in any ACCEPT:

  8. CONTROL ( CONTROL)

  9. The SCROLL option will cause the entire contents of the screen to be scrolled UP or DOWN by the specified number of lines before any value is displayed on the screen. It is syntactically allowable to specify a SCROLL UP clause as well as a SCROLL DOWN clause. In such an instance, it is the last one specified that will be honoured. If no LINES specification is made, 1 LINE will be assumed.

  10. The TIMEOUT option will cause the ACCEPT to wait no more than the specified number of seconds for input. The wait count may be specified as a positive integer or a numeric data item with a positive value.

  11. The UPDATE option will enable the supplied data field to be updated having been displayed on screen prior to data being entered by overwriting, if needed. When this option is not used the input field is cleared prior to input and this is the default but can be changed by the use of compiler steering command -faccept-with-update that can be input when starting the compiler or included in the configuration file e.g., default.conf used when selected by default -std=default. For more information see cobc - The GnuCOBOL Compiler option switches) and 10.1.7 Compiler Configuration Files.

  12. This format of the ACCEPT statement will be terminated by any of the following events:

    1. When the Enter key is pressed.

    2. Expiration of the TIMEOUT timer — this will be treated as if the Enter key had been pressed with no data being entered.

    3. When a function key (F<n>) is pressed.

    4. The pressing of the PgUp or PgDn keys, if the run-time environment variable ( 10.2.3 Run Time Environment Variables) is set to any non-blank value.

    5. The pressing of the Esc key if both the run-time environment variable as well as run-time environment variable are set to any non-blank value.

    6. The pressing of the Up-arrow, Down-Arrow or PrtSc (Print Screen) keys. These keys are not detectable on Windows systems, however.

  13. The following apply when <identifier-1> is defined in the SCREEN SECTION:

    1. Alphanumeric data entered into <identifier-1> or any screen data item subordinate to it must be consistent with the PICTURE ( 6.9.37 PICTURE) clause of that item. This will be enforced at runtime by the ACCEPT statement.

    2. If <identifier-1> or any screen data item subordinate to it are defined as numeric, entered data must be acceptable as NUMVAL intrinsic function ( 8.1.70 NUMVAL) input (no decimal points are allowed, however). The value stored into the screen data item will be as if the input were passed to that function.

    3. If <identifier-1> or any screen data item subordinate to it are defined as numeric edited, entered data must be acceptable as NUMVAL-C intrinsic function ( 8.1.71 NUMVAL-C) input (again, no decimal points are allowed). The value stored into the screen data item will be as if the input were passed to that function.

  14. The following apply when <identifier-1> is not defined in the SCREEN SECTION:

    1. Alphanumeric data entered into <identifier-1> should be consistent with the PICTURE ( 6.9.37 PICTURE) clause of that item, although that will not be enforced by the ACCEPT statement. You may use Class Conditions ( 2.2.6 Class Conditions) after the data is accepted to enforce the data type.

    2. If <identifier-1> is defined as numeric, entered data must be acceptable as NUMVAL intrinsic function ( 8.1.70 NUMVAL) input (no decimal points are allowed, however). The value stored into <identifier-1> will be as if the input were passed to that function.

    3. If <identifier-1> is defined as numeric edited, entered data must be acceptable as NUMVAL-C intrinsic function ( 8.1.71 NUMVAL-C) input (again, no decimal points are allowed). The value stored into <identifier-1> will be as if the input were passed to that function.

  15. The optional ON EXCEPTION and NOT ON EXCEPTION clauses may be used to detect and react to the failure or success, respectively, of the screen I/O attempt. 7.6.4 ON EXCEPTION + NOT ON EXCEPTION, for additional information.

    After this format of the ACCEPT statement is executed, the program’s CRT STATUS ( 5.1.3 SPECIAL-NAMES) identifier will be populated with one of the following:

    • Code Meaning

    • 0000 ENTER key pressed

    • 1001–1064 F1F64, respectively, were pressed

    • 2001 PgUp was pressed

    • 2002 PgDn was pressed

    • 2003 Up-Arrow was pressed

    • 2004 Down-Arrow was pressed

    • 2005 Esc was pressed

    • 2006 PrtSc (Print Screen) was pressed

    • 2007 Tab

    • 2008 Back Tab

    • 2009 Key Left

    • 2010 Key Right

    • 2011 Insert Key on accept omitted

    • 2012 Delete Key on accept omitted

    • 2013 Backspace Key on accept omitted

    • 2014 Home Key on accept omitted

    • 2015 End Key on accept omitted

    • 2040- 2095 Exception keys for Mouse Handling

    • 2040 Mouse Move

    • 2041 Left Pressed

    • 2042 Left Released

    • 2043 Left Dbl Click

    • 2044 Mid Pressed

    • 2045 Mid Released

    • 2046 Mid Dbl Click

    • 2047 Right Pressed

    • 2048 Right Released

    • 2049 Right Dbl Click

    • 2050 Shift Move

    • 2051 Shift Left Pressed

    • 2052 Shift Left Released

    • 2053 Shift Left Dbl Click

    • 2054 Shift Mid Pressed

    • 2055 Shift Mid Released

    • 2056- Shift Mid Dbl Click

    • 2057 Shift Right Pressed

    • 2058 Shift Right Released

    • 2059 Shift Right Dbl Click

    • 2060 Ctrl Move

    • 2061 Ctrl Left Pressed

    • 2062 Ctrl Left Released

    • 2063 Ctrl Left Dbl Click

    • 2064 Ctrl Mid Pressed

    • 2065 Ctrl Mid Released

    • 2066 Ctrl Mid Dbl Click

    • 2067 Ctrl Right Pressed

    • 2068 Ctrl Right Released

    • 2069 Ctrl Right Dbl Click

    • 2070 Alt Move

    • 2071 Alt Left Pressed

    • 2072 Alt Left Released

    • 2073- Alt Left Dbl Click

    • 2074 Alt Mid Pressed

    • 2075 Alt Mid Released

    • 2076 Alt Mid Dbl Click

    • 2077 Alt Right Pressed

    • 2078 Alt Right Released

    • 2079 Alt Right Dbl Click

    • 2080 Wheel Up

    • 2081 Wheel Down

    • 2082 Wheel Left

    • 2083 Wheel Right

    • 2084 Shift Wheel Up

    • 2085 Shift Wheel Down

    • 2086 Shift Wheel Left

    • 2087 Shift Wheel Right

    • 2088 Ctrl Wheel Up

    • 2089 Ctrl Wheel Down

    • 2090 Ctrl Wheel Left

    • 2091 Ctrl Wheel Right

    • 2092 Alt Wheel Up

    • 2093 Alt Wheel Down

    • 2094 Alt Wheel Left

    • 2095 Alt Wheel Right

    • Input validation

    • 8000 NO Field

    • 8001 Time Out

    • Other errors

    • 9000 Fatal

    • 9001 Max Field

  16. The actual key pressed to generate a function key (F<n>) will depend on the type of terminal device you’re using (PC, Macintosh, VT100, etc.) and what type of enhanced display driver was configured with the version of GnuCOBOL you’re using.

    For example, on a GnuCOBOL build for a Windows PC using MinGW and “PDCurses”, F1F12 are the actual F-keys on the PC keyboard, F<13>F<24> are entered by shifting the F-keys, F<25>F<36> are entered by holding Ctrl while pressing an F-key and F<37>F<48> are entered by holding Alt while pressing an F-key. On the other hand, a GnuCOBOL implementation built for Windows using Cygwin and NCurses treats the PCs F<1>F<12> keys as the actual F<1>F<12>, while shifted F-keys will enter F<11>F<2>0. With Cygwin/NCurses, Ctrl- and Alt-modified F-keys aren’t recognized, nor are Shift-F<11> or Shift-F<12>.

    Mouse Key codes are populated only if mouse management has been enabled. To enable mouse it is first necessary to set COB_MOUSE_FLAGS (either externally via terminal command, or internally via SET ENVIRONMENT to the applicable ?mouse mask? (specifying which activities you wish the program to detect). Here is an example of setting the mask from a COBOL program:

    COPY screenio.cpy.
    
    01  mouse-flags PIC 9(4).
    
    ...
    
        COMPUTE mouse-flags = COB-AUTO-MOUSE-HANDLING
                            + COB-ALLOW-LEFT-DOWN
                            + COB-ALLOW-MIDDLE-DOWN
                            + COB-ALLOW-RIGHT-DOWN
    
        SET ENVIRONMENT "COB_MOUSE_FLAGS" TO <mouse-flags>.
    
  17. Once that has been done, every (extended) ACCEPT, will return a value in COB_CRT_STATUS reflecting mouse activity, when such activity occurs. The applicable values are shown in screenio.cpy under ?Exception keys for mouse handling?. If you define a variable in SPECIAL NAMES as follows:

    SPECIAL-NAMES.
       CURSOR IS data-name.   *> where data-name is PIC 9(4) or 9(6).
    
  18. The cursor or mouse position will be returned as well. The position is expressed as row and column (rrcc or rrrccc).

  19. Numeric keypad keys are not recognizable on Windows MinGW/PDCurses builds of GnuCOBOL, regardless of the number lock settings. Windows Cygwin/NCurses builds recognize numeric keypad inputs properly. Although not tested during the preparation of this documentation, I would expect native Windows builds using PDCurses to behave as MinGW builds do and native Unix builds using NCurses to behave as do Cygwin builds.

  20. The optional EXCEPTION-STATUS clause may be used to detect exceptions from a prior arithmetic verb such as COMPUTE to recover any errors produced. These are recovered using the function EXCEPTION-STATUS.

  21. CONTROL The value of literal-8 and identifier-8 in the CONTROL phrase is used to specify a dynamic option list. The value must be a character-string consisting of a series of keywords delimited by commas; Some keywords allow assignment of a value by following the keyword with an equal sign and the value. Blanks are ignored in the character-string. Lowercase letters are treated as uppercase letters within keywords. Keywords specified override corresponding static options specified as phrases for the same identifier-1. Keywords may be specified in any order. Keywords, which specify options that do not apply to the statement, are ignored.

    The keywords that affect an ACCEPT statement are BEEP, BLINK, ECHO, PROMPT, REVERSE, TAB, UNDERLINE, UPDATE, ERASE, ERASE EOL, ERASE EOS, HIGH, LOW, UPPER, NO BEEP, NO BLINK,NO ECHO, NO PROMPT, NO REVERSE, NO TAB, NO UNDERLINE, NO UPDATE, NO ERASE,

    The meanings of these keywords when they appear in the value of the CONTROL phrase operand are the same as the corresponding phrases which may be written as static options of the ACCEPT statement, with the addition of the negative forms to allow suppression of statically declared options. The keywords UNDERLINE and UPPER are not available as static options of the ACCEPT statement. When specified, UPPER causes all lowercase alphabetic characters contained in the screen field to be changed to uppercase alphabetic characters before input data conversion and storing in the receiving field. When specified, UNDERLINE causes the field on the screen to be shown in underlined mode, provided the terminal supports that mode.

    GnuCOBOL provides two additional keywords in the CONTROL phrase that affect an ACCEPT field. 1. FCOLOR = color-name When FCOLOR is present, color-name specifies the foreground color of the ACCEPT field. This name is then used as the default value for subsequent ACCEPT statements in the program. The initial default for color-name is white. 2. BCOLOR = color-name When BCOLOR is present, color-name specifies the background color of the DISPLAY field. This value is then used as the default value for subsequent ACCEPT statements in the program. The initial default for color-name is black. Following table contains a list of all the possible names for color-name. The left column contains the valid color name. The right column shows the color that appears when high intensity is specified (the default intensity).

    +--------------------------------------------------------------+
    |                 Valid COBOL Color Names                      |
    +-------------------+------------------------------------------+
    |Valid Color Names  |  High-Intensity Color Values (Defaults)  |
    +-------------------+------------------------------------------+
    |Black              |  Gray                                    |
    |Blue               |  Light Blue                              |
    |Green              |  Light Green                             |
    |Cyan               |  Light Cyan                              |
    |Red                |  Light Red                               |
    |Magenta            |  Light Magenta                           |
    |Brown              |  Yellow                                  |
    |White              |  High-Intensity White                    |
    +-------------------+------------------------------------------+
    
  22. COLOR Phrase

    The COLOR phrase provides an alternate method for setting video attributes. Integer-9 must be a numeric literal. Identifier-9 must be a numeric data item. It also allows the specification of colors for screen fields and controls. They can be set to different numeric values to express various combinations of colors and video attributes. You may make combinations by adding the appropriate values together. The following color values are accepted:

    +--------+--------------+-------------+
    |Color   |  Foreground  | Background  |
    +--------+--------------+-------------+
    |Black   |      1       |     32      |
    |Blue    |      2       |     64      |
    |Green   |      3       |     96      |
    |Cyan    |      4       |    128      |
    |Red     |      5       |    160      |
    |Magenta |      6       |    192      |
    |Brown   |      7       |    224      |
    |White   |      8       |    256      |
    +--------+--------------+-------------+
    
  23. You may specify other video attributes by adding the following values:

    +-------------------------+--------+
    |Reverse video            |   1024 |
    |Low intensity            |   2048 |
    |High intensity           |   4096 |
    |Underline                |   8192 |
    |Blink                    |  16384 |
    |Protected                |  32768 |
    |Background low-intensity |  65536 |
    |Background high-intensity| 131072 |
    +-------------------------+--------+
    
  24. You may also specify high intensity by adding “8” to the foreground color value.

7.8.1.5 ACCEPT FROM DATE/TIME

ACCEPT FROM DATE/TIME Syntax

  ACCEPT identifier-1 FROM { DATE [ YYYYMMDD ] }
  ~~~~~~              ~~~~ { ~~~~   ~~~~~~~~   }
                           { DAY [ YYYYDDD ]   }
                           { ~~~   ~~~~~~~     }
                           { DAY-OF-WEEK       }
                           { ~~~~~~~~~~~       }
                           { TIME              }
                           { ~~~~              }
                           { MICROSECOND-TIME  }
                           { ~~~~~~~~~~~~~~~~  }
[ END-ACCEPT ]
  ~~~~~~~~~~

This format of the ACCEPT statement is used to retrieve the current system date, time or current day of the week and store it into a data item.

  1. The data retrieved from the system and the format in which it is structured will vary, as follows:

    • Syntax Data Retrieved Format

    • DATE Current date in Gregorian form yymmdd

    • DATE YYYYMMDD Current date in Gregorian form yyyymmdd

    • DAY Current date in Julian form yyddd

    • DAY YYYYDDD Current date in Julian form yyyyddd

    • DAY-OF-WEEK Current day within a week where 1 = Monday.., 7 = Sunday d

    • TIME Time, including hundredths of a second (n) hhmmssnn

    • MICROSECOND-TIME Time, including micro seconds (u) hhmmssuuuuuu

  2. When using one of --std=acu or --std=acu-strict,

    ACCEPT FROM TIME data-item with data-item providing more than 12 digits behaves as if ACCEPT FROM MICROSECOND-TIME data-item is used (six decimal places for fractional seconds).

  3. Consider using the standard FUNCTION FORMATTED-CURRENT-DATE if you need a

    high precision (up to eight decimal places for fractional seconds).

7.8.1.6 ACCEPT FROM Screen-Info

ACCEPT FROM Screen-Info Syntax

  ACCEPT identifier-1
  ~~~~~~
         FROM { LINES|LINE-NUMBER }
         ~~~~ { ~~~~~ ~~~~~~~~~~~ }
              { COLS|COLUMNS      }
              { ~~~~ ~~~~~~~      }
              { ESCAPE KEY        }
                ~~~~~~ ~~~
[ END-ACCEPT ]
  ~~~~~~~~~~

This format of the ACCEPT statement is used to retrieve information about the console window or about the user’s interactions with it.

  1. The reserved words LINES and LINE-NUMBER are interchangeable.

  2. The reserved words COLS and COLUMNS are interchangeable.

  3. The following points pertain to the use of the LINES and COLUMNS options:

    1. The LINES and COLUMNS options will retrieve the respective components of the size of the console display.

    2. When the console is running in a windowed environment, this will be the sizing of the window in which the program is executing, in terms of horizontal (COLUMNS) or vertical (LINES) character counts — not pixels.

    3. When the system is not running a windowing environment, the physical console screen attributes will be returned.

    4. Values of 0 will be returned if GnuCOBOL was not generated to include screen I/O.

    5. See the documentation on the CBL_GET_SCR_SIZE built-in system subroutine ( 8.2.36 CBL_GET_SCR_SIZE) for another way to retrieve this information.

  4. The ESCAPE KEY option may be used after the ACCEPT FROM Screen-Info statement ( 7.8.1.6 ACCEPT FROM Screen-Info) has executed. The result returned will be the four-digit CRT STATUS ( 5.1.3 SPECIAL-NAMES) identifier value. CRT STATUS Codes, for the specific code values.

7.8.1.7 ACCEPT FROM Runtime-Info

ACCEPT FROM Runtime-Info Syntax

  ACCEPT identifier-1
  ~~~~~~
         FROM { EXCEPTION STATUS }
         ~~~~ { ~~~~~~~~~ ~~~~~~ }
              { USER NAME        }
                ~~~~ ~~~~
[ END-ACCEPT ]
  ~~~~~~~~~~

This format of the ACCEPT statement is used to retrieve run-time information such as the most-recent error exception code and the current user’s user name.

  1. The following points pertain to the use of the EXCEPTION STATUS option:

    1. <identifier-1> must be defined as a PIC X(4) item.

    2. Error Exception Codes, for a complete list of the exception codes and their meanings.

    3. An alternative to the use of ACCEPT FROM Runtime-Info is to use the EXCEPTION-STATUS intrinsic function ( 8.1.26 EXCEPTION-STATUS).

  2. The following points pertain to the use of the USER NAME option:

    1. The returned result is the userid that was used to login to the system with, and not any actual first and/or last name of the user in question (unless, of course, that is the information used as a logon id). It is not the PID or UID numbers but the name associated with the UID under *nix based systems.

    2. <identifier-1> should be defined large enough to receive the longest user-name on the system.

    3. If insufficient space is allocated, the returned value will be truncated.

    4. If excess space is allocated, the returned value will be padded with spaces (to the right).

7.8.1.8 ACCEPT OMITTED

ACCEPT OMITTED Syntax

  ACCEPT OMITTED
  ~~~~~~

  1.  For console : See 6.17.1.1 (ACCEPT FROM CONSOLE Syntax)

  2.  For Screen  : See 6.17.1.4 (ACCEPT screen-data-item Syntax)

[ END-ACCEPT ]
  ~~~~~~~~~~

This format of the ACCEPT statement will wait for a keyboard event that terminates input; function keys, or Enter/Return, among others. CRT STATUS (COB-CRT-STATUS CRT STATUS ( 5.1.3 SPECIAL-NAMES) if not explicitly defined) is set with the keycode, listed in copy/screenio.cpy. It also handles a few other keycode terminations not normally used to complete an extended accept.

  1. The following are examples of keycodes that can be used:

    COB-SCR-INSERT
    COB-SCR-DELETE
    COB-SCR-BACKSPACE
    COB-SCR-KEY-HOME
    COB-SCR-KEY-END
    
  2. You can use extended attributes, useful for setting timeouts or positioning.

7.8.1.9 ACCEPT FROM EXCEPTION STATUS

ACCEPT FROM EXCEPTION STATUS Syntax

  ACCEPT exception-status-pic-9-4   FROM EXCEPTION STATUS
  ~~~~~~                            ~~~~ ~~~~~~~~~ ~~~~~~

[ END-ACCEPT ]
  ~~~~~~~~~~

This format of the ACCEPT statement will receive the status for any exceptions resulting from a previous valid verb.

  1. The following is an example of usage:

     In WS:
     01  exception-status  pic 9(4).
    ..
     In PD:
    
     ACCEPT unexpected-rounding  FROM EXCEPTION STATUS
     IF unexpected-rounding NOT EQUAL "0000" THEN
        DISPLAY "Unexpected rounding. Code " unexpected-rounding
                 UPON SYSERR
     END-IF
    

7.8.2 ADD

7.8.2.1 ADD TO

ADD TO Syntax

  ADD { literal-1    }...
  ~~~ { identifier-1 }

      TO { identifier-2
      ~~
         [ ROUNDED [ MODE IS { AWAY-FROM-ZERO         } ] ] }...
           ~~~~~~~   ~~~~    { ~~~~~~~~~~~~~~         }
                             { NEAREST-AWAY-FROM-ZERO }
                             { ~~~~~~~~~~~~~~~~~~~~~~ }
                             { NEAREST-EVEN           }
                             { ~~~~~~~~~~~~           }
                             { NEAREST-TOWARD-ZERO    }
                             { ~~~~~~~~~~~~~~~~~~~    }
                             { PROHIBITED             }
                             { ~~~~~~~~~~             }
                             { TOWARD-GREATER         }
                             { ~~~~~~~~~~~~~~         }
                             { TOWARD-LESSER          }
                             { ~~~~~~~~~~~~~          }
                             { TRUNCATION             }
                               ~~~~~~~~~~
    [ ON SIZE ERROR imperative-statement-1 ]
         ~~~~ ~~~~~
    [ NOT ON SIZE ERROR imperative-statement-2 ]
      ~~~    ~~~~ ~~~~~
[ END-ADD ]
  ~~~~~~~

This format of the ADD statement generates an intermediate arithmetic sum of the values of all <identifier-1> and <literal-1>) items. The value of each <identifier-2> will be replaced, in turn, by the sum of that <identifier-2>s value and the intermediate sum.

  1. The reserved words IS and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. Both <identifier-1> and <identifier-2> must be numeric unedited data items while <literal-1> must be a numeric literal.

  3. An <identifier-1> data item may also be coded as an <identifier-2>. Note, however, that the value of such a data item will therefore be included twice in the result.

  4. The contents of each <identifier-1> will remain unchanged by this statement.

  5. The optional ROUNDED ( 7.6.7 ROUNDED) clause available to each <identifier-2> will control how non-integer results will be saved.

  6. The optional ON SIZE ERROR and NOT ON SIZE ERROR clauses may be used to detect and react to the failure or success, respectively, of an attempt to perform a calculation. In this case, failure is defined as being an <identifier-2> with an insufficient number of digit positions available to the left of any implied decimal point. 7.6.6 ON SIZE ERROR + NOT ON SIZE ERROR, for additional information.

7.8.2.2 ADD GIVING

ADD GIVING Syntax

  ADD { literal-1    }...
  ~~~ { identifier-1 }

    [ TO identifier-2 ]
      ~~
      GIVING { identifier-3
      ~~~~~~
        [ ROUNDED [ MODE IS { AWAY-FROM-ZERO         } ] ] }...
          ~~~~~~~   ~~~~    { ~~~~~~~~~~~~~~         }
                            { NEAREST-AWAY-FROM-ZERO }
                            { ~~~~~~~~~~~~~~~~~~~~~~ }
                            { NEAREST-EVEN           }
                            { ~~~~~~~~~~~~           }
                            { NEAREST-TOWARD-ZERO    }
                            { ~~~~~~~~~~~~~~~~~~~    }
                            { PROHIBITED             }
                            { ~~~~~~~~~~             }
                            { TOWARD-GREATER         }
                            { ~~~~~~~~~~~~~~         }
                            { TOWARD-LESSER          }
                            { ~~~~~~~~~~~~~          }
                            { TRUNCATION             }
                              ~~~~~~~~~~
    [ ON SIZE ERROR imperative-statement-1 ]
         ~~~~ ~~~~~
    [ NOT ON SIZE ERROR imperative-statement-2 ]
      ~~~    ~~~~ ~~~~~
[ END-ADD ]
  ~~~~~~~

This format of the ADD statement generates the arithmetic sum of the values of all <identifier-1>, <literal-1>) and <identifier-2> (if any) items and then saves that sum to each <identifier-3>.

  1. The reserved words IS and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. Both <identifier-1> and <identifier-2> must be numeric unedited data items while <literal-1> must be a numeric literal; <identifier-3> may be either a numeric or numeric edited data item.

  3. An <identifier-1> or <identifier-2> data item may be used as an <identifier-3>, if desired.

  4. The contents of each <identifier-1> and <identifier-2> will remain unchanged by this statement, unless they happen to also be specified as an <identifier-3>.

  5. The current value in each <identifier-3> at the start of the statement’s execution is irrelevant, since the contents of each <identifier-3> will simply be replaced with the computed sum.

  6. The optional ROUNDED ( 7.6.7 ROUNDED) clause available to each <identifier-3> will control how non-integer results will be saved.

  7. The optional ON SIZE ERROR and NOT ON SIZE ERROR clauses may be used to detect and react to the failure or success, respectively, of an attempt to perform a calculation. In this case, failure is defined as being an <identifier-3> with an insufficient number of digit positions available to the left of any implied decimal point. 7.6.6 ON SIZE ERROR + NOT ON SIZE ERROR, for additional information.

7.8.2.3 ADD CORRESPONDING

ADD CORRESPONDING Syntax

  ADD CORRESPONDING identifier-1
  ~~~
      TO identifier-2
      ~~
    [ ROUNDED [ MODE IS { AWAY-FROM-ZERO         } ] ]
      ~~~~~~~   ~~~~    { ~~~~~~~~~~~~~~         }
                        { NEAREST-AWAY-FROM-ZERO }
                        { ~~~~~~~~~~~~~~~~~~~~~~ }
                        { NEAREST-EVEN           }
                        { ~~~~~~~~~~~~           }
                        { NEAREST-TOWARD-ZERO    }
                        { ~~~~~~~~~~~~~~~~~~~    }
                        { PROHIBITED             }
                        { ~~~~~~~~~~             }
                        { TOWARD-GREATER         }
                        { ~~~~~~~~~~~~~~         }
                        { TOWARD-LESSER          }
                        { ~~~~~~~~~~~~~          }
                        { TRUNCATION             }
                          ~~~~~~~~~~
    [ ON SIZE ERROR imperative-statement-1 ]
         ~~~~ ~~~~~
    [ NOT ON SIZE ERROR imperative-statement-2 ]
      ~~~    ~~~~ ~~~~~
[ END-ADD ]
  ~~~~~~~

This format of the ADD statement generates code equivalent to individual ADD TO ( 7.8.2.1 ADD TO) statements for corresponding matches of data items found subordinate to the two identifiers.

  1. The reserved words IS and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. Both <identifier-1> and <identifier-2> must be group items.

  3. 7.6.2 CORRESPONDING, for information on how corresponding matches will be found between <identifier-1> and <identifier-2>.

  4. The optional ROUNDED ( 7.6.7 ROUNDED) clause available to each <identifier-3> will control how non-integer results will be saved.

  5. The optional ON SIZE ERROR and NOT ON SIZE ERROR clauses may be used to detect and react to the failure or success, respectively, of an attempt to perform a calculation. In this case, failure is defined as being an <identifier-3> with an insufficient number of digit positions available to the left of any implied decimal point. 7.6.6 ON SIZE ERROR + NOT ON SIZE ERROR, for additional information.

7.8.3 ALLOCATE

ALLOCATE Syntax

FORMAT 1. ALLOCATE a "BASED" ITEM.

 ALLOCATE  identifier-1
 ~~~~~~~~
           [{ INITIALIZED } ]  [ RETURNING identifier-3 ]
           [{ ~~~~~~~~~~~ } ]    ~~~~~~~~~
           [{ INITIALISED } ]
           [{ ~~~~~~~~~~~ } ]


FORMAT 2. ALLOCATE a memory block.

 ALLOCATE   arithmetic-expression-1  CHARACTERS
 ~~~~~~~~                            ~~~~~~~~~~
           [{ INITIALIZED } [ TO { identifier-2}] ]  RETURNING identifier-3
           [{ ~~~~~~~~~~~ } [ ~~ {             }] ]  ~~~~~~~~~
           [{ INITIALISED } [    { literal-1   }] ]
           [{ ~~~~~~~~~~~ }                       ]

The ALLOCATE statement is used to dynamically allocate memory at run-time.

  1. The reserved words INITIALIZED and INITIALISED are interchangeable.

  2. If <identifier-1> is specified, the RETURNING phrase may be omitted; otherwise, the RETURNING phrase shall be specified.

  3. If used, <arithmetic-expression-1> must be an arithmetic expression with a non-zero positive integer value and the RETURNING phrase must be specified.

  4. If used, <identifier-1> should be an 01-level item defined in working-storage or local-storage with the BASED ( 6.9.8 BASED) attribute. It may be an 01 item defined in the linkage section without the BASED attribute, but using such a data item is not recommended.

  5. If used, <identifier-3> should be a POINTER ( 6.9.61 USAGE) data item.

  6. The optional RETURNING clause will return the address of the allocated memory block into the specified USAGE POINTER <identifier-3> data item. When this option is used, knowledge of the originally-requested size of the allocated memory block will be retained by the program in case a FREE ( 7.8.19 FREE) statement is ever issued against <identifier-3>.

  7. When the <identifier-1> option is used in conjunction with INITIALIZED (or its internationalized alternative INITIALISED), the allocated memory block will be initialized as if an INITIALIZE <identifier-1> WITH FILLER ALL TO VALUE THEN TO DEFAULT ( 7.8.24 INITIALIZE) were executed.

  8. When the <arithmetic-expression-1> CHARACTERS option is used, INITIALIZED will initialize the allocated memory block to binary zeros. If INITIALIZED is not used, the initial contents of allocated memory will be left to whatever rules of memory allocation are in effect for the operating system the program is running under.

  9. There are two basic ways in which this statement is used. The simplest is:

    ALLOCATE My-01-Item
    

    With this form, a block of storage equal in size to the defined size of My-01-Item (which must have been defined with the BASED attribute) will be allocated. The address of that block of storage will become the base address of My-01-Item so that it and its subordinate data items become usable within the program.

    A second (and equivalent) approach is:

    ALLOCATE LENGTH OF My-01-Item CHARACTERS RETURNING The-Pointer
    SET ADDRESS OF My-01-Item TO The-Pointer
    
  10. With this form My-01-Item can either be defined with the BASED attribute or be defined in LINKAGE SECTION. Instead of LENGTH OF My-01-Item you may also use a size smaller to the maximum field size as long as you ensure that the complete field is never used.

  11. Referencing a BASED data item either before its storage has been allocated or after its storage has been released (via the FREE statement) will lead to “unpredictable results”. That’s how reference manuals and standards specifications talk about this situation. In the author’s experience, the results are all too predictable: the program aborts from an attempt to reference an unallocated area of memory.

7.8.4 ALTER

ALTER Syntax

ALTER procedure-name-1 TO PROCEED TO procedure-name-2
~~~~~                  ~~

The ALTER statement was used in the early years of the COBOL language to edit the object code of a program at execution time, changing a GO TO ( 7.8.22.1 Simple GO TO) statement to branch to a spot in the program different than where the GO TO statement was originally compiled for.

  1. The reserved words PROCEED and TO (the one after PROCEED) are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. <procedure-name-1> must contain only a single statement, and that statement must be a simple GO TO.

  3. The effect of this statement will be as if the generated machine-language code for the GO TO statement in <procedure-name-1> is changed so that the GO TO statement now transfers control to <procedure-name-2>, rather than to whatever procedure name was specified in the program source code.

  4. Support for the ALTER verb has been added to GnuCOBOL for the purpose of enabling GnuCOBOL to pass those National Institute of Standards and Technology (NIST) tests for the COBOL programming language that require support for ALTER.

  5. Because of the catastrophic effect this statement has on program readability and therefore the programmer’s ability to debug problems with program logic, the use of ALTER in new programs is STRONGLY discouraged.

7.8.5 CALL

CALL Syntax

  CALL [ { STDCALL         } ] { literal-1    }
  ~~~~   { ~~~~~~~         }   { identifier-1 }
         { STATIC          }
         { ~~~~~~          }
         { mnemonic-name-1 }

       [ USING CALL-Argument... ]
         ~~~~~
       [ RETURNING|GIVING identifier-2 ]
         ~~~~~~~~~ ~~~~~~
       [ ON OVERFLOW|EXCEPTION imperative-statement-1 ]
            ~~~~~~~~ ~~~~~~~~~
       [ NOT ON OVERFLOW|EXCEPTION imperative-statement-2 ]
         ~~~    ~~~~~~~~ ~~~~~~~~~
[ END-CALL ]
  ~~~~~~~~

CALL Argument Syntax

[ BY { REFERENCE } ]
     { ~~~~~~~~~ }
     { CONTENT   }
     { ~~~~~~~   }
     { VALUE     }
       ~~~~~

     { OMITTED                                                   }
     { ~~~~~~~                                                   }
     { [ UNSIGNED ] [ SIZE IS { AUTO      } ] [ { literal-2    } }
         ~~~~~~~~     ~~~~    { ~~~~      }     { identifier-2 }
                              { DEFAULT   }
                              { ~~~~~~~   }
                              { integer-1 }

The CALL statement is used to transfer control to a subroutine. 11 Sub-Programming, for the specifics of using subprograms with GnuCOBOL programs.

  1. The reserved words BY, IS and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The reserved words EXCEPTION and OVERFLOW are interchangeable.

  3. The reserved words GIVING and RETURNING are interchangeable.

  4. The expectation is that the subroutine will eventually return control back to the calling program, at which point the CALLing program will resume execution starting with the statement immediately following the CALL. Subprograms are not required to return to their callers, however, and are free to halt program execution if they wish.

  5. The <mnemonic-name-1> / STATIC / STDCALL option, if used, affects the linkage conventions that will be used to the subroutine being called, as follows:

    • STATIC

      causes the linkage to the subroutine to be performed in such a way as to require the subroutine to be statically-linked with the calling program. Note that this enables static-linking to be used on a subroutine-by-subroutine selective basis.

    • STDCALL

      allows system standard calling conventions (as opposed to GnuCOBOL calling conventions) to be used when calling a subroutine. The definition of what constitutes “system standard” may vary from operating system to operating system. Use of this requires special knowledge about the linkage requirements of subroutines you are intending to CALL. Subroutines written in GnuCOBOL do not need this option.

    • <mnemonic-name-1>

      allows a custom defined calling convention to be used. Such mnemonic names are defined using the CALL-CONVENTION ( 5.1.3 SPECIAL-NAMES) clause. That clause associates a decimal integer value with <mnemonic-name-1> such that the individual bits set on or off in the binary equivalent of the integer affect linkage to the subroutine as described in the following chart. Those rows of the chart marked with a “No” in the Supported column represent bit positions (switch settings) in the integer value that are currently accepted (to provide compatibility to other COBOL implementations) if coded, but are otherwise unsupported.

      Note that bit 0 is the right-most bit in the binary value.

      • Bit Supported Meaning if 0 Meaning if 1

      • 0

        No Arguments will be passed in right-to-left sequence Arguments will be passed in left-to-right sequence.

      • 1

        No The calling program will flush processed arguments from the argument stack. The called program (subroutine) will flush processed arguments from the argument stack.

      • 2

        Yes The RETURN-CODE special register ( 7.7 Special Registers) will be updated in addition to any RETURNING or GIVING data item. The RETURN-CODE special register will not be updated (but any RETURNING or GIVING data item still will).

      • 3

        Yes If CALL <literal> is used, the subroutine will be located and linked in with the calling program at compile time or may be dynamically located and loaded at execution time, depending on compiler switch settings and operating system capabilities. If CALL <literal> is used, the subroutine can only be located and linked with the calling program at compilation time.

      • 4

        No OS/2 “OPTLINK” conventions will not be used to CALL the subprogram. OS/2 “OPTLINK” conventions will be used to CALL the subprogram.

      • 5

        No Windows 16-bit “thunking” will not be in effect. Windows 16-bit “thunking” will be used to call the subroutine as a DLL.

      • 6

        Yes The STDCALL convention will not be used. The STDCALL convention, required to use the Microsoft Win32 API, will be used.

      Using the STATIC option on a CALL statement is equivalent to using CALL-CONVENTION 8 (only bit 3 set).

      Using the STDCALL option on a CALL statement is equivalent to using CALL CONVENTION 64 (only bit 6 set).

  6. The value of <literal-1> or <identifier-1> is the entry-point of the subprogram you wish to call.

  7. When you call a subroutine using <identifier-1>, you are forcing the runtime system to call a dynamically-loadable subprogram. The contents of <identifier-1> will be the entry-point name within that module. If this is the first call to any entry-point within the module being made at run-time, the contents of <identifier-1> must be the primary entry-point name of the module (which must also match the filename, minus any OS-mandated extension) of the executable file comprising the module).

  8. You can force the GnuCOBOL runtime system to pre-load all dynamically-loaded modules that could ever be called by the program, at the time the program starts executing. This is accomplished through the use of the run-time environment variable ( 10.2.3 Run Time Environment Variables). If used, this will only pre-load those modules invoked via CALL <literal-1>, as the runtime contents of <identifier-1> cannot be predicted.

  9. If the subprogram being called is a GnuCOBOL program, and if that program had the INITIAL ( 4 IDENTIFICATION DIVISION) attribute specified on its PROGRAM-ID clause, all of the subprogram’s data division data will be restored to its initial state each time the subprogram is executed, regardless of which entry-point within the subprogram is being referenced.

    This [re]-initialization behaviour will always apply to any subprogram’s local-storage (if any), regardless of the use (or not) of INITIAL.

  10. The USING clause defines a list of arguments that may be passed from the calling program to the subprogram. The manner in which any given argument is passed to the subroutine depends upon the BY clause (if any) coded (or implied) for that argument, as follows:

    • BY REFERENCE

      passes the address of the argument to the subprogram. If the subprogram changes the contents of that argument, the change will be “visible” to the calling program.

    • BY CONTENT

      passes the address of a copy of the argument to the subprogram. If the subprogram changes the value of such an argument, the change only affects the copy back in the calling program, not the original version.

    • BY VALUE

      passes the actual numeric value of the literal or identifiers contents as the argument. This feature exists to provide compatibility with C, C++ and other languages and would not normally be used when calling GnuCOBOL subprograms. Only numeric literals or numeric data items should be passed in this manner.

    If an argument lacks a BY clause, the most-recently encountered BY specification on that CALL statement will be assumed. If the first argument specified on a CALL lacks a BY clause, BY REFERENCE will be assumed.

  11. No more than 251 arguments may be passed to a subroutine, unless the GnuCOBOL compiler was built with a specifically different argument limit specified for it. If you have access to the GnuCOBOL source code, you may adjust this limit by changing the value of the COB_MAX_FIELD_PARAMS in the call.c file (found in the libcob folder) as well as the last shown #if MAX_CALL_FIELD_PARAMS statement before you run make to build the compiler and run-time library.

  12. The RETURNING clause allows you to specify a numeric data item into which the subroutine should return a numeric value. If you use this clause on the CALL, the subroutine should include a RETURNING ( 7.3 PROCEDURE DIVISION RETURNING) clause on its procedure division header. Of course, a subroutine may pass a value of any kind back in any argument passed BY REFERENCE.

  13. The optional ON OVERFLOW and NOT ON OVERFLOW clauses (or ON EXCEPTION and NOT ON EXCEPTION — they are interchangeable) may be used to detect and react to the failure or success, respectively, of an attempt to CALL the subroutine. Failure, in this context, is defined as the inability to either locate or load the object code of the subroutine at execution time. 7.6.5 ON OVERFLOW + NOT ON OVERFLOW, for additional information.

  14. Call also supports using an entry point stored in a PROGRAM-POINTER, avoiding the dynamic runtime lookup. GnuCOBOL keeps a cache of lookups during a program run. Repeated use of a named function does not suffer much penalty, but PROGRAM-POINTER will be just that little bit faster. To set a PROGRAM-POINTER use SET <program-reference> TO ENTRY "<name>" (or get the address from an API, and take part in callback programming).

  15. An extension of CALL allows a call to a <Program-Pointer-1> which is preset using SET <program-pointer-1> TO ENTRY <x>. Additional the RETURNING clause may return a data pointer or a PROGRAM-POINTER

7.8.6 CANCEL

CANCEL Syntax

CANCEL { literal-1    }...
~~~~~~ { identifier-1 }

The CANCEL statement unloads the dynamically-loadable subprogram module containing the entry-point specified as <literal-1> or <identifier-1> from memory.

  1. If a dynamically-loadable module unloaded by the CANCEL statement is subsequently re-executed, all data division storage for that module will once again be in its initial state.

  2. Whether the CANCEL statement actually physically unloads a dynamically-loaded module or simply marks it as logically-unloaded depends on the use and value of the run-time environment variable ( 10.2.3 Run Time Environment Variables).

7.8.7 CLOSE

CLOSE Syntax

CLOSE { file-name-1 [ { REEL|UNIT [ FOR REMOVAL ] } ] }...
~~~~~                 { ~~~~ ~~~~       ~~~~~~~   }
                      { WITH LOCK                 }
                      {      ~~~~                 }
                      { WITH NO REWIND            }
                             ~~ ~~~~~~

The REEL, LOCK and NO REWINDclauses are syntactically recognized but are otherwise non-functional, except for the CLOSE...NO REWIND statement, which will generate a file status of 07 rather than the usual 00 (but take no other action). The CLOSE statement terminates the program’s access to the specified file(s).

  1. The reserved words FOR and WITH are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The reserved words REEL and UNIT are interchangeable.

  3. The CLOSE statement may only be executed against files that have been successfully opened.

  4. A successful CLOSE will write any remaining unwritten record buffers to the file (similar to an UNLOCK statement ( 7.8.50 UNLOCK)) and release any file locks for the file, regardless of open mode. A closed file will then be no longer available for subsequent I/O statements until it is once again OPENED.

  5. When a ORGANIZATION LINE SEQUENTIAL ( 5.2.1.2 ORGANIZATION LINE SEQUENTIAL) or LINE ADVANCING ( LINE ADVANCING) file is closed, a final delimiter sequence will be written to the file to signal the termination point of the final data record in the file. This will only be necessary if the final record written to the file was written with the AFTER ADVANCING ( 7.8.52 WRITE) option.

7.8.8 COMMIT

COMMIT Syntax

COMMIT
~~~~~~

The COMMIT statement performs an UNLOCK against every currently-open file, but does not close any of the files. See the UNLOCK statement ( 7.8.50 UNLOCK) for additional details.

7.8.9 COMPUTE

COMPUTE Syntax

  COMPUTE { identifier-1
  ~~~~~~~
      [ ROUNDED [ MODE IS { AWAY-FROM-ZERO         } ] }...
        ~~~~~~~   ~~~~    { ~~~~~~~~~~~~~~         }
                          { NEAREST-AWAY-FROM-ZERO }
                          { ~~~~~~~~~~~~~~~~~~~~~~ }
                          { NEAREST-EVEN           }
                          { ~~~~~~~~~~~~           }
                          { NEAREST-TOWARD-ZERO    }
                          { ~~~~~~~~~~~~~~~~~~~    }
                          { PROHIBITED             }
                          { ~~~~~~~~~~             }
                          { TOWARD-GREATER         }
                          { ~~~~~~~~~~~~~~         }
                          { TOWARD-LESSER          }
                          { ~~~~~~~~~~~~~          }
                          { TRUNCATION             }
                            ~~~~~~~~~~
        = | EQUAL arithmetic-expression-1
          ~~~~~
      [ ON SIZE ERROR imperative-statement-1 ]
           ~~~~ ~~~~~
      [ NOT ON SIZE ERROR imperative-statement-2 ]
        ~~~    ~~~~ ~~~~~
[ END-COMPUTE ]
  ~~~~~~~~~~~

The COMPUTE statement provides a means of easily performing complex arithmetic operations with a single statement, instead of using cumbersome and possibly confusing sequences of ADD, SUBTRACT, MULTIPLY and DIVIDE statements. COMPUTE also allows the use of exponentiation — an arithmetic operation for which no other statement exists in COBOL.

  1. The reserved words IS and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The reserved word EQUAL is interchangeable with the use of ‘=‘.

  3. Each <identifier-1> must be a numeric or numeric-edited data item.

  4. The optional ROUNDED ( 7.6.7 ROUNDED) clause available to each <identifier-1> will control how non-integer results will be saved.

  5. 2.2.3 Arithmetic Expressions, for more information on arithmetic expressions.

  6. The optional ON SIZE ERROR and NOT ON SIZE ERROR clauses may be used to detect and react to the failure or success, respectively, of an attempt to perform a calculation. In this case, failure is defined either as having an <identifier-3> with an insufficient number of digit positions available to the left of any implied decimal point or attempting to divide by zero. 7.6.6 ON SIZE ERROR + NOT ON SIZE ERROR, for additional information.

7.8.10 CONTINUE

CONTINUE Syntax

CONTINUE
~~~~~~~~

                { identifier-1            }
CONTINUE AFTER  { literal-1               }   SECONDS
~~~~~~~~ ~~~~~  { arithmetic-expression-1 }   ~~~~~~~

The CONTINUE statement is a no-operation statement that may be coded anywhere an imperative statement ( Imperative Statement) may be coded.

  1. The CONTINUE statement has no effect on the execution of the program.

  2. This statement (perhaps in combination with an appropriate comment or two) makes a convenient “place holder” — particularly in ELSE ( 7.8.23 IF) or WHEN ( 7.8.15 EVALUATE) clauses where no code is currently expected to be needed, but a place for code to handle the conditions in question is to be reserved in case it’s ever needed.

  3. The optional extension of (AFTER) when used with the CONTINUE statement pauses execution for a specified length of time.

7.8.11 DELETE

DELETE Syntax

  DELETE file-name-1 RECORD
  ~~~~~~
    [ INVALID KEY imperative-statement-1 ]
      ~~~~~~~
    [ NOT INVALID KEY imperative-statement-2 ]
      ~~~ ~~~~~~~
[ END-DELETE ]
  ~~~~~~~~~~

The DELETE statement logically deletes a record from a COBOL file.

  1. The reserved words KEY and RECORD are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The ORGANIZATION of <file-name-1> cannot be ORGANIZATION LINE SEQUENTIAL ( 5.2.1.2 ORGANIZATION LINE SEQUENTIAL).

  3. The <file-name-1> file cannot be a sort/merge work file (a file described using a SD ( 6.2.1 File/Sort-Description)).

  4. For files in the SEQUENTIAL access mode, the last input-output statement executed against <file-name-1> prior to the execution of the DELETE statement must have been a successfully executed sequential-format READ statement ( 7.8.32.1 Sequential READ). That READ will therefore identify the record to be deleted.

  5. If <file-name-1> is a RELATIVE file whose ACCESS MODE ( 5.2.1.3 ORGANIZATION RELATIVE) is either RANDOM or DYNAMIC, the record to be deleted is the one whose relative record number is currently the value of the field specified as the files RELATIVE KEY in its SELECT statement.

  6. If <file-name-1> is an INDEXED file whose ACCESS MODE ( 5.2.1.4 ORGANIZATION INDEXED) is RANDOM or DYNAMIC, the record to be deleted is the one whose primary key is currently the value of the field specified as the RECORD KEY in the file’s SELECT statement.

  7. The optional INVALID KEY and NOT INVALID KEY clauses may be used to detect and react to the failure or success, respectively, of an attempt to delete a record. 7.6.3 INVALID KEY + NOT INVALID KEY, for additional information.

  8. No INVALID KEY or NOT INVALID KEY clause may be specified for a file who’s ACCESS MODE IS SEQUENTIAL.

7.8.12 DISPLAY

7.8.12.1 DISPLAY UPON device

DISPLAY UPON device Syntax

  DISPLAY { literal-1    }...
  ~~~~~~~ { identifier-1 }
     [ UPON mnemonic-name-1 ]
       ~~~~
     [ WITH NO ADVANCING ]
            ~~ ~~~~~~~~~
     [ ON EXCEPTION imperative-statement-1 ]
          ~~~~~~~~~
     [ NOT ON EXCEPTION imperative-statement-2 ]
       ~~~    ~~~~~~~~~
[ END-DISPLAY ]
  ~~~~~~~~~~~

This format of the DISPLAY statement displays the specified identifier contents and/or literal values on the system output device specified via the UPON clause.

  1. The reserved words ON and WITH are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. If no UPON clause is specified, UPON CONSOLE will be assumed. If the UPON clause is specified, <mnemonic-name-1> must be one of the built-in output device names CONSOLE, PRINTER, STDERR, STDOUT, SYSERR, SYSLIST, SYSLST or SYSOUT or a mnemonic name assigned to one of those devices via the SPECIAL-NAMES ( 5.1.3 SPECIAL-NAMES) paragraph.

    When displaying upon the STDERR or SYSERR devices or to a <mnemonic-name-1> attached to one of those two devices, the output will be written to output pipe #2, which will normally cause the output to appear in the console output window. You may, if desired, redirect that output to a file by appending 2> filename to the end of the command that executes the program. This applies to both Windows (any type) or Unix versions of GnuCOBOL.

    When displaying upon the CONSOLE, PRINTER, STDOUT, SYSLIST, SYSLST or SYSOUT devices or to a <mnemonic-name-1> attached to one of them, the output will be written to output pipe #1, which will normally cause the output to appear in the console output window. You may, if desired, redirect that output to a file by appending 1> filename or simply > filename to the end of the command that executes the program. This applies to both Windows (any type) or Unix versions of GnuCOBOL.

  3. The NO ADVANCING clause, if used, will suppress the carriage-return / line-feed sequence that is normally added to the end of any console display.

  4. The optional ON EXCEPTION and NOT ON EXCEPTION clauses may be used to detect and react to the failure or success, respectively, of an attempt to display output to the specified device. 7.6.4 ON EXCEPTION + NOT ON EXCEPTION, for additional information.

7.8.12.2 DISPLAY UPON COMMAND-LINE

DISPLAY UPON COMMAND-LINE Syntax

  DISPLAY { literal-1    }...
  ~~~~~~~ { identifier-1 }
       UPON { ARGUMENT-NUMBER|COMMAND-LINE }
       ~~~~ { ~~~~~~~~~~~~~~~ ~~~~~~~~~~~~ }
     [ ON EXCEPTION imperative-statement-1 ]
          ~~~~~~~~~
     [ NOT ON EXCEPTION imperative-statement-2 ]
       ~~~    ~~~~~~~~~
[ END-DISPLAY ]
  ~~~~~~~~~~~

This form of the DISPLAY statement may be used to specify the command-line argument number to be retrieved by a subsequent ACCEPT FROM ARGUMENT-VALUE statement ( 7.8.1.2 ACCEPT FROM COMMAND-LINE) or to specify a new value for the command-line arguments themselves.

  1. The reserved word ON is optional and may be omitted. The presence or absence of this word has no effect upon the program.

  2. By displaying a numeric integer value UPONARGUMENT-NUMBER, you will specify which argument (by its relative number) will be retrieved by a subsequent ACCEPT FROM ARGUMENT-VALUE statement.

  3. Executing a DISPLAY UPON COMMAND-LINE will influence subsequent ACCEPT FROM COMMAND-LINE statements (which will then return the value you displayed), but will not influence subsequent ACCEPT FROM ARGUMENT-VALUE statements — these will continue to return the original program execution parameters.

  4. The optional ON EXCEPTION and NOT ON EXCEPTION clauses may be used to detect and react to the failure or success, respectively, of an attempt to display output to the specified item. 7.6.4 ON EXCEPTION + NOT ON EXCEPTION, for additional information.

7.8.12.3 DISPLAY UPON ENVIRONMENT-NAME

DISPLAY UPON ENVIRONMENT-NAME Syntax

  DISPLAY { literal-1    }... UPON { ENVIRONMENT-VALUE }
  ~~~~~~~ { identifier-1 }    ~~~~ { ~~~~~~~~~~~~~~~~~ }
                                   { ENVIRONMENT-NAME  }
                                     ~~~~~~~~~~~~~~~~
     [ ON EXCEPTION imperative-statement-1 ]
          ~~~~~~~~~
     [ NOT ON EXCEPTION imperative-statement-2 ]
       ~~~    ~~~~~~~~~
[ END-DISPLAY ]
  ~~~~~~~~~~~

This form of the DISPLAY statement can be used to create or modify environment variables.

  1. The reserved word ON is optional and may be omitted. The presence or absence of this word has no effect upon the program.

  2. To create or change an environment variable will require two DISPLAY statements. The following example sets the environment variable MY_ENV_VAR to a value of ‘Demonstration Value‘:

    DISPLAY "MY_ENV_VAR" UPON ENVIRONMENT-NAME
    DISPLAY "Demonstration Value" UPON ENVIRONMENT-VALUE
    
  3. Environment variables created or changed from within GnuCOBOL programs will be available to any sub-shell processes spawned by that program (i.e. CALL 'SYSTEM' ( 8.2.52 SYSTEM)) but will not be known to the shell or console window that started the GnuCOBOL program.

  4. Consider using SET ENVIRONMENT ( 7.8.41.1 SET ENVIRONMENT) in lieu of DISPLAY to set environment variables as it is much simpler.

  5. The optional ON EXCEPTION and NOT ON EXCEPTION clauses may be used to detect and react to the failure or success, respectively, of an attempt to display output to the specified item. 7.6.4 ON EXCEPTION + NOT ON EXCEPTION, for additional information.

7.8.12.4 DISPLAY data-item

DISPLAY data-item Syntax

DISPLAY identifier-1 [ UPON CRT|CRT-UNDER ]
~~~~~~~                ~~~~ ~~~ ~~~~~~~~~
        OMITTED
        ~~~~~~~
    [ AT { | LINE NUMBER { integer-1    }            | } ]
      ~~ { | ~~~~        { identifier-2 }            | }
         { | COLUMN|COL|POSITION|POS NUMBER { integer-2    }
         { | ~~~~~~ ~~~ ~~~~~~~~ ~~~        { identifier-3 }
         {                                             }
         { { integer-3    }                            }
         { { identifier-4 }                            }

    [ WITH [ Attribute-Specification ]...
      ~~~~
           [ SCROLL { UP   } [ { integer-4    } LINE|LINES ] ]
             ~~~~~~ { ~~   }   { identifier-5 }
                    { DOWN }
                      ~~~~
           [ SIZE { integer-5    }
             ~~~~ { identifier-6 }  ]
           [ CONTROL  { literal-7    } ]
             ~~~~~~~  { identifier-7 }
           [ COLOR  { IS } { integer-8    } ]
             COLOUR { IS } { identifier-8 } ]
               ~~~~~~
           [ NO ADVANCING ]
             ~~~~~~~~~~~~
    [ ON EXCEPTION imperative-statement-1 ]
         ~~~~~~~~~
    [ NOT ON EXCEPTION imperative-statement-2 ]
      ~~~    ~~~~~~~~~
[ END-DISPLAY ]
  ~~~~~~~~~~~

The UPON CRT, UPON CRT-UNDER and CONVERSIONclauses are syntactically recognized but are otherwise non-functional. They are supported to provide compatibility with COBOL source written for other COBOL implementations. This format of the DISPLAY statement presents data onto a formatted screen.

  1. The reserved words AFTER, LINE, LINES, NUMBER and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The reserved words COLUMN and POSITION are interchangeable.

  3. The reserved words LINE and LINES are interchangeable.

  4. If <identifier-1> is defined in the SCREEN SECTION ( 6.7 SCREEN SECTION), any AT, <Attribute-Specification> and WITH clauses will be ignored. All field definition, cursor positioning and screen control will occur as a result of the screen section definition of <identifier-1>.

  5. The reserved word OMITTED when used, will act to position the cursor or any screen clearance without changing any content of the screen.

  6. The following points apply if <identifier-1> is not defined in the screen section:

    1. The purpose of the AT clause is to define where on the screen <identifier-1> should be displayed. 7.8.1.4 ACCEPT data-item, for additional information.

    2. The purpose of the WITH clause is to define the visual attributes that should be applied to <identifier-1> when it is displayed on the screen as well as other presentation-control characteristics.

    3. The following <Attribute-Specification> clauses are allowed on the DISPLAY statement — these are the same as those allowed for SCREEN SECTION data items. A particular <Attribute-Specification> may be used only once in any DISPLAY:

    4. CONTROL The CONTROL phrase allow dynamic (runtime as opposed to compile time) specification of characteristics. Literal-7 must be a nonnumeric literal. Identifier-7 must be a nonnumeric data item. The value of identifier-7 or literal-7 in the CONTROL phrase must be a character-string consisting of a series of keywords delimited by commas; some keywords allow assignment of a value by following the keyword with an equal sign and the value. Blanks are ignored in the character-string. Lowercase letters are treated as uppercase letters within keywords. Keywords specified override corresponding static options specified as phrases. Keywords may be specified in any order. Keywords, which specify options that do not apply to the statement, are ignored.

    5. The keywords that affect a DISPLAY statement are BEEP, BLINK, CONVERT, REVERSE, UNDERLINE, ERASE, ERASE EOL, ERASE EOS, HIGH, LOW, NO BEEP, NO BLINK, NO CONVERT, NO REVERSE, NO UNDERLINE NO ERASE. The meanings of these keywords when they appear in the value of the CONTROL phrase operand are the same as the corresponding phrases which may be written as static options of the DISPLAY statement, with the addition of the negative forms to allow suppression of statically declared options.

    6. GnuCOBOL provides three additional keywords in the CONTROL phrase that affect a DISPLAY field. 1. FCOLOR = color-name When FCOLOR is present, color-name specifies the foreground color of the DISPLAY field. This name is then used as the default value for subsequent DISPLAY statements in the program. The initial default for color-name is white. 2. BCOLOR = color-name When BCOLOR is present, color-name specifies the background color of the DISPLAY field. This value is then used as the default value for subsequent DISPLAY statements in the program. The initial default for color-name is black. Following table contains a list of all the possible names for color-name. The left column contains the valid color name. The right column shows the color that appears when high intensity is specified (the default intensity).

      +--------------------------------------------------------------+
      |                 Valid COBOL Color Names                      |
      +-------------------+------------------------------------------+
      |Valid Color Names  |  High-Intensity Color Values (Defaults)  |
      +-------------------+------------------------------------------+
      |Black              |  Gray                                    |
      |Blue               |  Light Blue                              |
      |Green              |  Light Green                             |
      |Cyan               |  Light Cyan                              |
      |Red                |  Light Red                               |
      |Magenta            |  Light Magenta                           |
      |Brown              |  Yellow                                  |
      |White              |  High-Intensity White                    |
      +-------------------+------------------------------------------+
      
    7. GRAPHICS The GRAPHICS keyword causes the characters in following table to be translated to line draw characters. Characters that are not listed in the following table are output unchanged.

      +-------------------------------------------------------------------+
      |                       Line Draw Characters                        |
      +-------------------+-----------------------+-----------------------+
      |Description        | Single-Line Character | Double-Line Character |
      |lower-right corner |        j(+)           |        J(+)           |
      |upper-right corner |        k(+)           |        K(+)           |
      |upper-left corner  |        l(+)           |        L(+)           |
      |lower-left corner  |        m(+)           |        M(+)           |
      |plus               |        n(+)           |        N(+)           |
      |horizontal line    |        q(-)           |        Q(-)           |
      |left tee           |        t(+)           |        T(Š)           |
      |right tee          |        u(Š)           |        U(Š)           |
      |bottom tee         |        v(-)           |        V(-)           |
      |top tee            |        w(-)           |        W(-)           |
      |vertical line      |        x(Š)           |        X(Š)           |
      +-------------------+-----------------------+-----------------------+
      
    8. If the requested line draw characters are not available, the runtime system uses the best available characters. If double-line characters are requested and only single-line characters are available, they are used. If no line draw characters are available, then plus-characters, vertical bars, and dashes are used.

      Sample program that demonstrates how boxes are drawn:
      
              >>SOURCE FREE
              IDENTIFICATION   DIVISION.
              PROGRAM-ID.      CONTROL1.
              DATA             DIVISION.
              WORKING-STORAGE  SECTION.
              01  success-flag PIC X VALUE 'Y'.
                  88  success  VALUE 'Y', 'y'.
              77  LIN-START    PIC 99    COMP-5.
              77  LIN          PIC 99    COMP-5.
              01  scr1 PIC X(75)
                      VALUE 'Enter "y" if you see line draw characters. '
                      & 'The first set (single/double)'.
              01  scr2 PIC X(75)
                      VALUE 'uses HIGHLIGHT, the second uses '
                      & 'LOWLIGHT, BLINK and MAGENTA.'.
              01  graphcontrol PIC X(50) VALUE 'HIGH, GRAPHICS'.
              PROCEDURE DIVISION.
                  MOVE 2 TO LIN
                  DISPLAY scr1 AT LINE LIN COL 2
                  ADD  1 TO LIN
                  DISPLAY scr2 AT LINE LIN COL 2
                  MOVE 5 TO LIN-START
                  PERFORM DSPCOL
                  MOVE 12 TO LIN-START
                  MOVE "LOW BLINK FCOLOR=MAGENTA GRAPHICS" TO graphcontrol
                  PERFORM DSPCOL
                  ACCEPT success-flag AT 1801 UPDATE REQUIRED
                  IF success AND COB-CRT-STATUS = 0
                      GOBACK RETURNING 0
                  ELSE
                      GOBACK RETURNING 1.
              DSPCOL.
             *>   Single-line graphics
                  MOVE LIN-START TO LIN
                  DISPLAY "lqqqqwqqqqk" LINE LIN COL 05, CONTROL graphcontrol.
                  ADD  1 TO LIN
                  DISPLAY "x    x    x" LINE LIN COL 05, CONTROL graphcontrol.
                  ADD  1 TO LIN
                  DISPLAY "tqqqqnqqqqu" LINE LIN COL 05, CONTROL graphcontrol.
                  ADD  1 TO LIN
                  DISPLAY "x    x    x" LINE LIN COL 05, CONTROL graphcontrol.
                  ADD  1 TO LIN
                  DISPLAY "mqqqqvqqqqj" LINE LIN COL 05, CONTROL graphcontrol.
             *>   Double-line graphics
                  MOVE LIN-START TO LIN
                  DISPLAY "LQQQQWQQQQK" LINE LIN COL 20, CONTROL graphcontrol.
                  ADD  1 TO LIN
                  DISPLAY "X    X    X" LINE LIN COL 20, CONTROL graphcontrol.
                  ADD  1 TO LIN
                  DISPLAY "TQQQQNQQQQU" LINE LIN COL 20, CONTROL graphcontrol.
                  ADD  1 TO LIN
                  DISPLAY "X    X    X" LINE LIN COL 20, CONTROL graphcontrol.
                  ADD  1 TO LIN
                  DISPLAY "MQQQQVQQQQJ" LINE LIN COL 20, CONTROL graphcontrol.
      

      COLOUR The COLOR phrase provides an alternate method for setting video attributes. Integer-8 must be a numeric literal. Identifier-8 must be a numeric data item. It also allows the specification of colors for screen fields and controls. They can be set to different numeric values to express various combinations of colors and video attributes. You may make combinations by adding the appropriate values together. The following color values are accepted:

      +--------+--------------+-------------+
      |Color   |  Foreground  | Background  |
      +--------+--------------+-------------+
      |Black   |      1       |     32      |
      |Blue    |      2       |     64      |
      |Green   |      3       |     96      |
      |Cyan    |      4       |    128      |
      |Red     |      5       |    160      |
      |Magenta |      6       |    192      |
      |Brown   |      7       |    224      |
      |White   |      8       |    256      |
      +--------+--------------+-------------+
      
    9. You may specify other video attributes by adding the following values:

      +-------------------------+--------+
      |Reverse video            |   1024 |
      |Low intensity            |   2048 |
      |High intensity           |   4096 |
      |Underline                |   8192 |
      |Blink                    |  16384 |
      |Protected                |  32768 |
      |Background low-intensity |  65536 |
      |Background high-intensity| 131072 |
      +-------------------------+--------+
      
    10. You may also specify high intensity by adding “8” to the foreground color value.

      Sample program that demonstrates how COLOR is used.
      
              >>SOURCE FREE
      IDENTIFICATION DIVISION.
      PROGRAM-ID. COLOR1.
      *> Sample for using "COLOR" clause
      DATA DIVISION.
      WORKING-STORAGE SECTION.
      01 wLIN            PIC     99 value zero.
      01 wCOLOR          PIC 999999 value zero.
      01 wBlack-Fore     PIC 999 value   1.
      01 wBlack-Back     PIC 999 value  32.
      01 wBlue-Fore      PIC 999 value   2.
      01 wBlue-Back      PIC 999 value  64.
      01 wGreen-Fore     PIC 999 value   3.
      01 wGreen-Back     PIC 999 value  96.
      01 wCyan-Fore      PIC 999 value   4.
      01 wCyan-Back      PIC 999 value 128.
      01 wRed-Fore       PIC 999 value   5.
      01 wRed-Back       PIC 999 value 160.
      01 wMagenta-Fore   PIC 999 value   6.
      01 wMagenta-Back   PIC 999 value 192.
      01 wBrown-Fore     PIC 999 value   7.
      01 wBrown-Back     PIC 999 value 224.
      01 wWhite-Fore     PIC 999 value   8.
      01 wWhite-Back     PIC 999 value 256.
      01 wReverseVideo              PIC 999999 value   1024.
      01 wLowIntensity              PIC 999999 value   2048.
      01 wHighIntensity             PIC 999999 value   4096.
      01 wUnderline                 PIC 999999 value   8192.
      01 wBlink                     PIC 999999 value  16384.
      01 wProtected                 PIC 999999 value  32768.
      01 wBackground-low-intensity  PIC 999999 value  65536.
      01 wBackground-high-intensity PIC 999999 value 131072.
      
       PROCEDURE DIVISION.
        ADD 1 to WLIN
        compute wCOLOR = wCyan-Fore + wWhite-Back + wUnderline
        DISPLAY FUNCTION CONCATENATE ("XXX COLOR=" wCOLOR " XXXXXXXXX ")
                          AT LINE wLIN COL 001 COLOR wCOLOR.
        ADD 1 to WLIN
        compute wCOLOR = wBrown-Fore + wRed-Back + wHighIntensity
        DISPLAY FUNCTION CONCATENATE ("XXX COLOR=" wCOLOR " XXXXXXXXX ")
                          AT LINE wLIN COL 001 COLOR wCOLOR.
        ADD 1 to WLIN
        compute wCOLOR = wBrown-Fore + wRed-Back + wHighIntensity + wReverseVideo
        DISPLAY FUNCTION CONCATENATE ("XXX COLOR=" wCOLOR " XXXXXXXXX ")
                          AT LINE wLIN COL 001 COLOR wCOLOR.
        ADD 1 to WLIN
        compute wCOLOR = wWhite-Fore + wGreen-Back + wBlink
        DISPLAY FUNCTION CONCATENATE ("XXX COLOR="  wCOLOR " XXXXXXXXX ")
                          AT LINE wLIN COL 001 COLOR wCOLOR.
        STOP RUN.
      
    11. 7.8.1.4 ACCEPT data-item, for additional information on the other WITH clause options.

  7. The optional ON EXCEPTION and NOT ON EXCEPTION clauses may be used to detect and react to the failure or success, respectively, of the screen I/O attempt. 7.6.4 ON EXCEPTION + NOT ON EXCEPTION, for additional information.

When DISPLAY is used with Line and column where multiple variables or literals are used before LINE only the first will be displayed.

If this is needed then the use of CONCATENATE to built more than one element together prior to the display, e.g., DISPLAY FUNCTION CONCATENATE (VARS-1 VARS-2) AT 0201.

When DISPLAY is used without line or column controls only one variable or literal may will appear on a line, so the use of the above example should also be employed.

7.8.12.5 DISPLAY data-item (Microsoft v1-v2)

DISPLAY data-item Syntax

DISPLAY  [position-spec] {identifier-2 | literal-1} ...
~~~~~~~

  [ WITH [ Attribute-Specification ]...
    ~~~~
         [ ERASE  { SCREEN|LINE }  ]
         [ SCROLL { UP   } [ { integer-3    } LINE|LINES ] ]
           ~~~~~~  { ~~   }   { identifier-3 }
                                     { DOWN }
                                       ~~~~
         [ SIZE { integer-4    }
           ~~~~ { identifier-4 } ]
[ END-DISPLAY ]
  ~~~~~~~~~~~


  where  position-spec is
  { (position-spec-num, position-spec-num) }
  { (,position-spec-num)                   }
  { (position-spec-num,)                   }

  where  position-spec-num  is
  { identifier-1 } [{ + } integer-1 ]
  { integer-2    } [{ - }           ]

This format of the DISPLAY statement presents data onto a formatted screen using the Microsoft format from v1 and v2 compilers (MsDos).

7.8.13 DIVIDE

7.8.13.1 DIVIDE INTO

DIVIDE INTO Syntax

DIVIDE { literal-1    } INTO { literal-2    } GIVING { identifier-3
~~~~~~ { identifier-1 } ~~~~ { identifier-2 } ~~~~~~

           [ ROUNDED [ MODE IS { AWAY-FROM-ZERO         } ] ] }...
             ~~~~~~~   ~~~~    { ~~~~~~~~~~~~~~         }
                               { NEAREST-AWAY-FROM-ZERO }
                               { ~~~~~~~~~~~~~~~~~~~~~~ }
                               { NEAREST-EVEN           }
                               { ~~~~~~~~~~~~           }
                               { NEAREST-TOWARD-ZERO    }
                               { ~~~~~~~~~~~~~~~~~~~    }
                               { PROHIBITED             }
                               { ~~~~~~~~~~             }
                               { TOWARD-GREATER         }
                               { ~~~~~~~~~~~~~~         }
                               { TOWARD-LESSER          }
                               { ~~~~~~~~~~~~~          }
                               { TRUNCATION             }
                                 ~~~~~~~~~~
   [ REMAINDER identifier-4 ]
     ~~~~~~~~~
   [ ON SIZE ERROR imperative-statement-1 ]
        ~~~~ ~~~~~
   [ NOT ON SIZE ERROR imperative-statement-2 ]
     ~~~    ~~~~ ~~~~~
[ END-DIVIDE ]
  ~~~~~~~~~~
For further clarification, the following examples are provided to be used with
the various flavours of the DIVIDE statement when using BY, INTO and GIVING.

--------------------------------------+---+-----+--------------+-------------------+
DIVIDE Operation                      | A |  B  |      C       |         D         |
--------------------------------------+---+-----+--------------+-------------------+
DIVIDE A INTO B                       | A | B/A |              |                   |
--------------------------------------+---+-----+--------------+-------------------+
DIVIDE A INTO B GIVING C              | A |  B  |     B/A      |                   |
--------------------------------------+---+-----+--------------+-------------------+
DIVIDE A BY B GIVING C                | A |  B  |     A/B      |                   |
--------------------------------------+---+-----+--------------+-------------------+
DIVIDE A INTO B GIVING C REMAINDER D  | A |  B  | Integer(B/A) | Integer remainder |
--------------------------------------+---+-----+--------------+-------------------+

This format of the DIVIDE statement will divide a numeric value (specified as a literal or numeric data item) into another numeric value (also specified as a literal or numeric data item) and will then replace the contents of one or more receiving data items with the results of that division.

  1. The reserved words IS and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. Both <identifier-1> and <identifier-2> must be numeric unedited data items and <literal-1> must be a numeric literal.

  3. A division operation will be performed for each <identifier-2>, in turn. Each of the results of those divisions will be saved to the corresponding <identifier-2> data item(s).

  4. Should any <identifier-2> be an integer numeric data item, the result computed when that <identifier-2> is divided by <literal-1> or <identifier-1> will also be an integer — any remainder from that division will be discarded.

  5. The optional ROUNDED ( 7.6.7 ROUNDED) clause available to each <identifier-2> will control how non-integer results will be saved.

  6. The optional ON SIZE ERROR and NOT ON SIZE ERROR clauses may be used to detect and react to the failure or success, respectively, of an attempt to perform a calculation. In this case, failure is defined as being numeric truncation caused by an <identifier-2> with an insufficient number of digit positions available to the left of any implied decimal point, or an attempt to divide by zero. 7.6.6 ON SIZE ERROR + NOT ON SIZE ERROR, for additional information.

7.8.13.2 DIVIDE INTO GIVING

DIVIDE INTO GIVING Syntax

DIVIDE { literal-1    } INTO { literal-2    } GIVING { identifier-3
~~~~~~ { identifier-1 } ~~~~ { identifier-2 } ~~~~~~

           [ ROUNDED [ MODE IS { AWAY-FROM-ZERO         } ] ] }...
             ~~~~~~~   ~~~~    { ~~~~~~~~~~~~~~         }
                               { NEAREST-AWAY-FROM-ZERO }
                               { ~~~~~~~~~~~~~~~~~~~~~~ }
                               { NEAREST-EVEN           }
                               { ~~~~~~~~~~~~           }
                               { NEAREST-TOWARD-ZERO    }
                               { ~~~~~~~~~~~~~~~~~~~    }
                               { PROHIBITED             }
                               { ~~~~~~~~~~             }
                               { TOWARD-GREATER         }
                               { ~~~~~~~~~~~~~~         }
                               { TOWARD-LESSER          }
                               { ~~~~~~~~~~~~~          }
                               { TRUNCATION             }
                                 ~~~~~~~~~~
   [ REMAINDER identifier-4 ]
     ~~~~~~~~~
   [ ON SIZE ERROR imperative-statement-1 ]
        ~~~~ ~~~~~
   [ NOT ON SIZE ERROR imperative-statement-2 ]
     ~~~    ~~~~ ~~~~~
[ END-DIVIDE ]
  ~~~~~~~~~~

This format of the DIVIDE statement will divide one numeric value (specified as a literal or numeric data item) into another numeric value (also specified as a literal or numeric data item) and will then replace the contents of one or more receiving data items with the results of that division.

  1. The reserved words IS and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. Both <identifier-1> and <identifier-2> must be numeric unedited data items while both <identifier-3> and <identifier-4> must be numeric (edited or unedited) data items.

  3. Both <literal-1> and <literal-2> must be numeric literals.

  4. If the REMAINDER clause is coded, there may be only one <identifier-3> specified.

  5. The result obtained when the value of <literal-2> or <identifier-2> is divided by the value of <literal-1> or <identifier-1> is computed; this result is then moved into each <identifier-3>, in turn, applying the rules defined by the ROUNDED ( 7.6.7 ROUNDED) clause (if any) for that <identifier-3> to the move.

  6. If a REMAINDER clause is specified, the value of the one and only <identifier-3> (as stated earlier, if REMAINDER is specified there may only be a single <identifier-3> coded on the statement) after it was assigned a value according to the previous rule will be multiplied by the value of <literal-1> or <identifier-1>; that result is then subtracted from the value of <literal-2> or <identifier-2> and that result is the value which is moved to <identifier-4>.

  7. The optional ON SIZE ERROR and NOT ON SIZE ERROR clauses may be used to detect and react to the failure or success, respectively, of an attempt to perform a calculation. In this case, failure is defined as being an <identifier-2> with an insufficient number of digit positions available to the left of any implied decimal point, or an attempt to divide by zero. 7.6.6 ON SIZE ERROR + NOT ON SIZE ERROR, for additional information.

7.8.13.3 DIVIDE BY GIVING

DIVIDE BY GIVING Syntax

DIVIDE { literal-1    } BY { literal-2    } GIVING { identifier-3
~~~~~~ { identifier-1 } ~~ { identifier-2 } ~~~~~~

           [ ROUNDED [ MODE IS { AWAY-FROM-ZERO         } ] ] }...
             ~~~~~~~   ~~~~    { ~~~~~~~~~~~~~~         }
                               { NEAREST-AWAY-FROM-ZERO }
                               { ~~~~~~~~~~~~~~~~~~~~~~ }
                               { NEAREST-EVEN           }
                               { ~~~~~~~~~~~~           }
                               { NEAREST-TOWARD-ZERO    }
                               { ~~~~~~~~~~~~~~~~~~~    }
                               { PROHIBITED             }
                               { ~~~~~~~~~~             }
                               { TOWARD-GREATER         }
                               { ~~~~~~~~~~~~~~         }
                               { TOWARD-LESSER          }
                               { ~~~~~~~~~~~~~          }
                               { TRUNCATION             }
                                 ~~~~~~~~~~
   [ REMAINDER identifier-4 ]
     ~~~~~~~~~
   [ ON SIZE ERROR imperative-statement-1 ]
        ~~~~ ~~~~~
   [ NOT ON SIZE ERROR imperative-statement-2 ]
     ~~~    ~~~~ ~~~~~
[ END-DIVIDE ]
  ~~~~~~~~~~

This format of the DIVIDE statement will divide one numeric value (specified as a literal or numeric data item) by another numeric value (also specified as a literal or numeric data item) and will then replace the contents of one or more receiving data items with the results of that division.

  1. The reserved words IS and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. Both <identifier-1> and <identifier-2> must be numeric unedited data items while both <identifier-3> and <identifier-4> must be numeric (edited or unedited) data items.

  3. Both <literal-1> and <literal-2> must be numeric literals.

  4. If the REMAINDER clause is coded, there may be only one <identifier-3> specified.

  5. The result obtained when the value of <literal-1> or <identifier-1> is divided by the value of <literal-2> or <identifier-2> is computed; this result is then moved into each <identifier-3>, in turn, applying the rules defined by the ROUNDED ( 7.6.7 ROUNDED) clause (if any) for that <identifier-3> to the move.

  6. If a REMAINDER clause is specified, the value of the one and only <identifier-3> (as stated earlier, if REMAINDER is specified there may only be a single <identifier-3> coded on the statement) after it was assigned a value according to the previous rule will be multiplied by the value of <literal-2> or <identifier-2>; that result is then subtracted from the value of <literal-1> or <identifier-1> and that result is the value which is moved to <identifier-4>.

  7. The optional ON SIZE ERROR and NOT ON SIZE ERROR clauses may be used to detect and react to the failure or success, respectively, of an attempt to perform a calculation. In this case, failure is defined as being an <identifier-2> with an insufficient number of digit positions available to the left of any implied decimal point, or an attempt to divide by zero. 7.6.6 ON SIZE ERROR + NOT ON SIZE ERROR, for additional information.

7.8.14 ENTRY

ENTRY Syntax

ENTRY [ call-convention-phrase ] literal-1
~~~~~
    [ linkage-phrase ]

 [ USING ENTRY-Argument ... ]
   ~~~~~

Format 2 (Special purpose and for GO TO )

ENTRY FOR GO TO literal-3
~~~~~ ~~~ ~~ ~~

ENTRY-Argument Syntax

[ BY { REFERENCE } ] { OMITTED }
     { ~~~~~~~~~ }
     { CONTENT   } ] { [ size-phrase ] { identifier-1 } }
     { ~~~~~~~   }                     { literal-2    } }
     { VALUE     } ] { [ size-phrase ] { identifier-1 } }
       ~~~~~                           { literal-2    } }

The ENTRY statement is used to define an alternate entry-point into a subroutine, along with the arguments that subroutine will be expecting.

  1. The reserved word BY is optional and may be omitted. The presence or absence of this word has no effect upon the program.

  2. You may not use an ENTRY statement in a nested subprogram, nor may you use it in any form of user-defined function.

  3. The USING clause defines the arguments the subroutine entry-point supports. This list of arguments must match up against the USING clause of any CALL statement that will be invoking the subroutine using this entry-point.

  4. Each <ENTRY-Argument> specified on the ENTRY statement must be defined in the linkage section of the subroutine in which the ENTRY statement exists.

  5. The <literal-1> value will specify the entry-point name of the subroutine. It must be specified exactly on CALL statements (with regard to the use of upper- and lower-case letters) as it is specified on the ENTRY statement.

  6. The meaning of REFERENCE, CONTENT and VALUE are the same as the equivalent specifications on the CALL statement ( 7.8.5 CALL). Whatever specification will be used for an argument on the CALL to this entry-point should match the specification used in the corresponding <ENTRY-Argument>. The same rules regarding the presence or absence of a BY clause on a CALL statement apply to the presence or absence of a BY clause on the corresponding argument of the ENTRY statement.

  7. The <GO TO> with the ENTRY FOR is an GnuCOBOL special purpose extension for use with various GnuCobol tools.

7.8.15 EVALUATE

EVALUATE Syntax

  EVALUATE Selection-Subject-1 [ ALSO Selection-Subject-2 ]...
  ~~~~~~~~                       ~~~~
{ { WHEN Selection-Object-1 [ ALSO Selection-Object-2 ] }...
    ~~~~                      ~~~~
        [ imperative-statement-1 ] }...
  [ WHEN OTHER
    ~~~~ ~~~~~
        imperative-statement-other ]

[ END-EVALUATE ]
  ~~~~~~~~~~~~

EVALUATE Selection Subject Syntax

{ TRUE         }
{ ~~~~         }
{ FALSE        }
{ ~~~~~        }
{ expression-1 }
{ identifier-1 }
{ literal-1    }

EVALUATE Selection Object Syntax

{ ANY                                                }
{ ~~~                                                }
{ TRUE                                               }
{ ~~~~                                               }
{ FALSE                                              }
{ ~~~~~                                              }
{ partial-expression-1                               }
{                                                    }
{ { expression-2 } [ THRU|THROUGH { expression-3 } ] }
{ { identifier-2 }   ~~~~ ~~~~~~~ { identifier-3 }   }
{ { literal-2    }                { literal-3    }   }

The EVALUATE statement provides a means of defining processing that should take place under any number of mutually-exclusive conditions.

  1. The reserved words THRU and THROUGH are interchangeable.

  2. There must be at least one WHEN clause (in addition to any WHEN OTHER clause) specified on any EVALUATE statement.

  3. There must be at least one <Selection-Subject> specified on the EVALUATE statement. Any number of additional <Selection-Subject> clauses may be specified, using the ALSO reserved word to separate each from the prior.

  4. Each WHEN clause (other than the WHEN OTHER clause, if any) must have the same number of <Selection-Object> clauses as there are <Selection-Subject> clauses.

  5. When using THRU, the values on both sides of the THRU must be the same class (both numeric, both alphanumeric, etc.).

  6. A <partial-expression> is one of the following:

    1. A Class Condition without a leading <identifier-1> ( 2.2.6 Class Conditions).

    2. A Sign Condition without a leading <identifier-1> ( 2.2.7 Sign Conditions).

    3. A Relation Condition with nothing to the left of the relational operator ( 2.2.9 Relation Conditions).

  7. At execution time, each <Selection-Subject> on the EVALUATE statement will have its value matched against that of the corresponding <Selection-Object> on a WHEN clause, in turn, until:

    1. A WHEN clause has each of its <Selection-Object>(s) successfully matched by the corresponding <Selection-Subject>; this will be referred to as the ‘Selected WHEN clause‘.

    2. The complete list of WHEN clauses (except for the WHEN OTHER clause, if any) has been exhausted. In this case, there is no ‘Selected WHEN Clause‘.

  8. If a ‘Selected WHEN Clause‘ was identified:

    1. The <imperative-statement-1> ( Imperative Statement) immediately following the ‘Selected WHEN Clause‘ will be executed. If the ‘Selected WHEN Clause‘ is lacking an <imperative-statement-1>, the first <imperative-statement-1> found after any following WHEN clause will be executed.

    2. Once the <imperative-statement-1> has been executed, or no <imperative-statement-1> was found anywhere after the ‘Selected WHEN Clause‘, control will proceed to the statement following the END-EVALUATE or, if there is no END-EVALUATE, the first statement that follows the next period. If, however, the <imperative-statement-1> included a GO TO statement, and that GO TO was executed, then control will transfer to the procedure named on the GO TO instead.

  9. If no ‘Selected WHEN Clause‘ was identified:

    1. The WHEN OTHER clause’s <imperative-statement-other> will be executed, if such a clause was coded.

    2. Control will then proceed to the statement following the END-EVALUATE or the first statement that follows the next period if there is no END-EVALUATE. If,however, the <imperative-statement-other> included a GO TO statement, and that GO TO was executed, then control will transfer to the procedure named on the GO TO instead.

  10. In order for a <Selection-Subject> to match the corresponding <Selection-Object> on a WHEN clause, at least one of the following must be true:

    1. The <Selection-Object> is ANY

    2. The implied Relation Condition <Selection-Subject> = <Selection Object> is TRUE2.2.9 Relation Conditions, for the rules on how the comparison will be made.

    3. The value of the <Selection-Subject> falls within the range of values specified by the THRU clause of the <Selection-Object>

    4. If the <Selection-Object> is a <partial-expression>, then the conditional expression that would be represented by coding <Selection-Subject> <Selection-Object> evaluates to TRUE

  11. Here is a sample program that illustrates the EVALUATE statement.

    IDENTIFICATION DIVISION.
    PROGRAM-ID. DEMOEVALUATE.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01  Test-Digit                  PIC 9(1).
        88 Digit-Is-Odd VALUE 1, 3, 5, 7, 9.
        88 Digit-Is-Prime VALUE 1, 3, 5, 7.
    PROCEDURE DIVISION.
    P1. PERFORM UNTIL EXIT
        DISPLAY "Enter a digit (0 Quits): "
            WITH NO ADVANCING
        ACCEPT Test-Digit
        IF Test-Digit = 0
            EXIT PERFORM
        END-IF
        EVALUATE Digit-Is-Odd ALSO Digit-Is-Prime
        WHEN TRUE ALSO FALSE
            DISPLAY Test-Digit " is ODD"
                WITH NO ADVANCING
        WHEN TRUE ALSO TRUE
            DISPLAY Test-Digit " is PRIME"
                WITH NO ADVANCING
        WHEN FALSE ALSO ANY
            DISPLAY Test-Digit " is EVEN"
                WITH NO ADVANCING
        END-EVALUATE
        EVALUATE Test-Digit
        WHEN < 5
            DISPLAY " and it's small too"
        WHEN < 8
            DISPLAY " and it's medium too"
        WHEN OTHER
            DISPLAY " and it's large too"
        END-EVALUATE
    END-PERFORM
    DISPLAY "Bye!"
    STOP RUN
    .
    

    Console output when run (user input follows the colons on the prompts for input):

    Enter a digit (0 Quits): 1
    1 is PRIME and it's small too
    Enter a digit (0 Quits): 2
    2 is EVEN and it's small too
    Enter a digit (0 Quits): 3
    3 is PRIME and it's small too
    Enter a digit (0 Quits): 4
    4 is EVEN and it's small too
    Enter a digit (0 Quits): 5
    5 is PRIME and it's medium too
    Enter a digit (0 Quits): 6
    6 is EVEN and it's medium too
    Enter a digit (0 Quits): 7
    7 is PRIME and it's medium too
    Enter a digit (0 Quits): 8
    8 is EVEN and it's large too
    Enter a digit (0 Quits): 9
    9 is ODD and it's large too
    Enter a digit (0 Quits): 0
    Bye!
    

7.8.16 EXAMINE

EXAMINE Syntax

EXAMINE { identifier } TALLYING
~~~~~~~                ~~~~~~~~
    { ALL|LEADING|UNTIL FIRST } literal-1  REPLACING BY literal-2
      ~~~ ~~~~~~~ ~~~~~~~~~~~              ~~~~~~~~~~~~

EXAMINE { identifier } REPLACING { ALL|FIRST|LEADING|UNTIL FIRST }
~~~~~~~                ~~~~~~~~~   ~~~ ~~~~~ ~~~~~~~ ~~~~~~~~~~~
      literal-3 BY literal-4
                ~~

The EXAMINE statement is the pre runner for INSPECT which should be used over the pre 1970 Cobol standard EXAMINE, and it is used to count the number of times a specified character appears in a data item and/or to replace a character with another character.

  1. This statement is only available subject to specific dialects being set when running the GnuCOBOL compiler.

  2. In all cases, the description of identifier must be such that its usage is display (explicitly or implicitly).

  3. When identifier represents a non numeric data item, examination starts at the leftmost character and proceeds to the right. Each character in the data item is examined in turn. For purposes of the EXAMINE statement, external floating point items are treated as non numeric data items.

  4. When identifier represents a numeric data item, this data item must consist of numeric characters, and may possess an operational sign. Examination starts at the leftmost character and proceeds to the right. Each character is examined in turn.

  5. If the letter ‘S’ is used in the PICTURE of the data item description to indicate the presence of an operational sign, the sign is ignored by the EXAMINE statement.

  6. Each literal must consist of a single character belonging to a class consistent with that of the identifier; in addition, each literal may be any figurative constant except ALL. If identifier is numeric, each literal must be an unsigned integer or the figurative constant ZERO (ZEROES, ZEROS).

  7. When Format 1 is used, an integral count is created which replaces the value of a special register called TALLY, whose implicit description is that of an unsigned integer of five digits.

  8. When the ALL option is used, this count represents the number of occurrences of literal-1.

  9. When the LEADING option is used, this count represents the number of occurrences of literal-1 prior to encountering a character other than literal-1.

  10. When the UNTIL FIRST option is used, this count represents all characters encountered before the first occurrence of literal-1.

  11. Whether Format 2 is used, or the REPLACING option of Format 1, the replacement rules are the same. They are as follows:

  12. When the ALL option is used, literal-2 is substituted for each occurrence of literal-1.

  13. When the LEADING option is used, the substitution of literal-2 for each occurrence of literal-1 terminates as soon as a character other than literal-1 or the right hand boundary of the data item is encountered.

  14. When the UNTIL FIRST option is used, the substitution of literal-2 terminates as soon as literal-1 or the right hand boundary of the data item is encountered.

7.8.17 EXHIBIT

EXHIBIT Syntax

EXHIBIT [CHANGED][NAMED] [position-spec] [ERASE] {identifier-1 | literal-1} ...
~~~~~~~  ~~~~~~~  ~~~~~                   ~~~~~
        [UPON mnemonic-name-1]
         ~~~~

where position-spec is

  {(position-spec-num, position-spec-num)}
  {(, position-spec-num)                 }
  {(position-spec-num, )                 }

where position-spec-num is

  {identifier-2} [{+} integer-2]
  {integer-1   } [{-}          ]

The EXHIBIT statement causes an (optionally conditional) display of the literals, and/or identifiers (optionally preceded by the identifier name) specified in the statement for the purposes of debugging.

  1. EXHIBIT is only present to ease migrations, this is an archaic language element in GnuCOBOL (but without the archaic message warning because there is no explicit dialect configuration for that other than the reserved word). Depending on the -std used it will either compile or not. As the standard says about archaic language elements:

    it should not be used in new compilation groups because better programming practices exist

    The use of DISPLAY is more portable and allows for the same feature-set (with the exception of CHANGED which GnuCOBOL may not support for a long time and with the need of a literal for NAMED). This statement can be removed from any later version.

  2. The reserved words NAMED, CHANGED are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  3. Each identifier specified in the EXHIBIT statement can be any class of data. TALLY and RETURN-CODE are the only special registers that can be used as identifiers.

  4. Literals and identifiers displayed by the EXHIBIT statement are separated by a space on the displayed line.

  5. Each literal can be any figurative constant other than ALL.

  6. If the literal is numeric, it must be an unsigned integer.

  7. Each execution of an EXHIBIT NAMED statement displays each identifier or literal specified, with each identifier (including any qualifiers and subscripts) followed by a “=” (equal sign) and its current value. They all appear on a single line on the order in which they appear in the statement.

  8. Each execution of an EXHIBIT CHANGED NAMED statement displays each identifier or literal specified, with each identifier (including any qualifiers and subscripts) followed by a “=” (equal sign) and its current value. They all appear on a single line on the order in which they appear in the statement. However, the display for each identifier (name and value) is conditional on the value of that identifier having changed since the last execution of the current EXHIBIT statement. If one or more of the identifier values have not changed, neither the name nor the value is printed for those identifiers. If none of the identifier values has changed, and no literals are specified, no display takes place (display of a blank line is suppressed).

  9. Each execution of an EXHIBIT CHANGED statement displays the current value of each identifier or literal specified. They all appear on a single line on the order in which they appear in the statement. However, the value display for each identifier is conditional on the value of that identifier having changed since the last execution of the current EXHIBIT statement. If one or more of the identifier values have not changed, the value for those identifiers are not printed and spaces are inserted instead. If none of the identifier values has changed, and no literals are specified, a blank line is displayed (display of a blank line is not suppressed).

  10. Each execution of an EXHIBIT statement with neither the CHANGED nor the NAMED option displays each identifier or literal specified. They all appear on a single line in the order in which they appear in the statement.

  11. An EXHIBIT statement is the same as an EXHIBIT NAMED statement.

  12. ERASE is a display attribute which got into GnuCOBOL when MS-COBOL support was increased, it is not yet implemented.

  13. The CHANGED clause is not yet implemented but recognised by GnuCOBOL.

  14. The UPON mnemonic-name-1 clause is not yet implemented but recognised by GnuCOBOL.

7.8.18 EXIT

EXIT Syntax

EXIT [ { PROGRAM           }   [ { RETURNING } ] { identifier-1 } ]
~~~~                           [ { GIVING    } ] { literal-1    } ]
       { FUNCTION          } ]
       { ~~~~~~~~          } ]
       { PERFORM [ CYCLE ] } ]
       { ~~~~~~~   ~~~~~   } ]
       { SECTION           } ]
       { ~~~~~~~           } ]
       { PARAGRAPH         } ]
         ~~~~~~~~~

The EXIT statement is a multi-purpose statement; it may provide a common end point for a series of procedures, exit an in-line PERFORM, paragraph or section or it may mark the logical end of a subprogram, returning control back to the calling program.

  1. The EXIT PROGRAM statement is not legal anywhere within a user-defined function.

  2. The EXIT FUNCTION statement cannot be used anywhere within a subroutine.

  3. Neither EXIT PROGRAM nor EXIT FUNCTION may be used within a USE GLOBAL routine in DECLARATIVES ( 7.5 DECLARATIVES).

  4. The following points describe the EXIT statement with none of the optional clauses:

    1. When this form of an EXIT statement is used, it must be the only statement in the procedure (paragraph or section) in which it occurs. This is not enforced in GnuCOBOL.

    2. This usage of the EXIT statement simply provides a common “GO TO” end point for a series of procedures, as may be seen in the following example:

      01  Switches.
          05 Input-File-Switch PIC X(1).
             88 EOF-On-Input-File VALUE "Y" FALSE "N".
      ...
          SET EOF-On-Input-File TO FALSE.
          PERFORM 100-Process-A-Transaction THRU 199-Exit
              UNTIL EOF-On-Input-File.
      ...
      100-Process-A-Transaction.
          READ Input-File AT END
              SET EOF-On-Input-File TO TRUE
              GO TO 199-Exit
          END-READ.
          IF Input-Rec of Input-File = SPACES
              GO TO 199-Exit  *> IGNORE BLANK RECORDS!
          END-IF.
          <<<process the record just read>>>
      199-Exit.
          EXIT.
      
    3. In this case, the EXIT statement takes no other run-time action.

  5. The following points apply to the EXIT PARAGRAPH and EXIT SECTION statements:

    1. If an EXIT PARAGRAPH statement or EXIT SECTION statement resides in a paragraph within the scope of a procedural PERFORM ( 7.8.31.1 Procedural PERFORM), control will be returned back to the PERFORM for evaluation of any TIMES, VARYING and/or UNTIL clauses.

    2. If an EXIT PARAGRAPH statement or EXIT SECTION statement resides outside the scope of a procedural PERFORM, control simply transfers to the first executable statement in the next paragraph (EXIT PARAGRAPH) or section (EXIT SECTION).

    3. The following shows how the previous example could have been coded without a GO TO by utilizing an EXIT PARAGRAPH statement.

      01  Switches.
          05 Input-File-Switch PIC X(1).
             88 EOF-On-Input-File VALUE "Y" FALSE "N".
      ...
          SET EOF-On-Input-File TO FALSE.
          PERFORM 100-Process-A-Transaction
              UNTIL EOF-On-Input-File.
      ...
      100-Process-A-Transaction.
          READ Input-File AT END
              SET EOF-On-Input-File TO TRUE
              EXIT PARAGRAPH
          END-READ.
          IF Input-Rec of Input-File = SPACES
              EXIT PARAGRAPH *> IGNORE BLANK RECORDS!
          END-IF.
          <<<process the record just read>>>
      
  6. The following points apply to the EXIT PERFORM and EXIT PERFORM CYCLE statements:

    1. The EXIT PERFORM and EXIT PERFORM CYCLE statements are intended to be used in conjunction with an in-line PERFORM statement ( 7.8.31.2 Inline PERFORM).

    2. An EXIT PERFORM CYCLE statement will terminate the current iteration of the in-line PERFORM, giving control to any TIMES, VARYING and/or UNTIL clauses for them to determine if another cycle needs to be performed.

    3. An EXIT PERFORM statement will terminate the in-line PERFORM outright, transferring control to the first statement following the END-PERFORM (if there is one) or to the next sentence following the PERFORM if there is no END-PERFORM.

    4. This last example shows the final modification to the previous examples by using an in-line PERFORM along with EXIT PERFORM and EXIT PERFORM CYCLE statements:

      PERFORM FOREVER
          READ Input-File AT END
              EXIT PERFORM
          END-READ
          IF Input-Rec of Input-File = SPACES
              EXIT PERFORM CYCLE *> IGNORE BLANK RECORDS!
          END-IF
          <<<process the record just read>>>
      END PERFORM
      
  7. The following points apply to the EXIT PROGRAM and EXIT FUNCTION statements:

    1. The EXIT PROGRAM and EXIT FUNCTION statements terminate the execution of a subroutine (i.e. a program that has been CALLed by another) or user-defined function, respectively, returning control back to the calling program.

    2. An EXIT PROGRAM statement returns control back to the statement following the CALL ( 7.8.5 CALL) of the subprogram. An EXIT FUNCTION statement returns control back to the processing of the statement in the calling program that invoked the user-defined function.

    3. For EXIT PROGRAM statement usage of RETURNING statement or GIVING statement will provide value defined by indentifer-1 or literal-1 back to the calling routine.

    4. If executed by a main program, neither the EXIT PROGRAM nor EXIT FUNCTION statements will take any action.

    5. The COBOL2002 standard has made a common extension to the COBOL language — the GOBACK statement ( 7.8.21 GOBACK) — a standard language element; the GOBACK statement should be strongly considered as the preferred alternative to both EXIT PROGRAM and EXIT FUNCTION for new subprograms.

7.8.19 FREE

FREE Syntax

FREE { [ ADDRESS OF ] identifier-1 }...
~~~~     ~~~~~~~

The FREE statement releases memory previously allocated to the program by the ALLOCATE statement ( 7.8.3 ALLOCATE).

  1. The ADDRESS OF clause is optional and may be omitted. The presence or absence of this clause has no effect upon the program.

  2. <identifier-1> must have a USAGE ( 6.9.61 USAGE) of POINTER, or it must be an 01-level data item with the BASED ( 6.9.8 BASED) attribute.

  3. If <identifier-1> is a USAGE POINTER data item and it contains a valid address, the FREE statement will release the memory block the pointer references. In addition, any BASED data items that the pointer was used to provide an address for will become un-based and therefore unusable. If <identifier-1> did not contain a valid address, no action will be taken.

  4. If <identifier-1> is a BASED data item and that data item is currently based (meaning it currently has memory allocated to it), its memory is released and <identifier-1> will become un-based and therefore unusable. If <identifier-1> was not based, no action will be taken.

7.8.20 GENERATE

GENERATE Syntax

GENERATE { report-name-1 }
~~~~~~~~ { identifier-1  }

The GENERATE statement presents data to a report.

  1. The following points apply when <identifier-1> is specified:

    1. <identifier-1> must be the name of a DETAIL ( 9.1 RWCS Lexicon) report group.

    2. If necessary, <identifier-1> may be qualified with a report name.

    3. The file in whose FD a REPORT clause exists for the report in which <identifier-1> is a detail group must be opened for OUTPUT or EXTEND at the time the GENERATE is executed. 7.8.30 OPEN, for information on file open modes.

    4. The report in which <identifier-1> is a DETAIL group must have been successfully initiated via the INITIATE statement ( 7.8.25 INITIATE) and not yet terminated via the TERMINATE statement ( 7.8.48 TERMINATE) at the time the GENERATE is executed.

    5. If at least one GENERATE statement of this form is executed against a report, the report is said to be a detail report. If no GENERATE statements of this form are executed against a report, the report is said to be a summary report.

  2. The following points apply when <report-name-1> is specified:

    1. <report-name-1> must be the name of a report having an RD defined for it in the report section.

    2. There must be at least one CONTROL ( 9.1 RWCS Lexicon) group defined for <report-name-1>.

    3. There cannot be more than one DETAIL group defined for <report-name-1>.

    4. The file in whose FD a REPORT <report-name-1> clause exists must be open for OUTPUT or EXTEND at the time the GENERATE is executed.

    5. <report-name-1> must have been successfully initiated (via INITIATE <report-name-1>) and not yet terminated (via TERMINATE) at the time the GENERATE is executed. 7.8.30 OPEN, for information on file open modes.

    6. The DETAIL group which is defined for <report-name-1> will be processed but will not actually be presented to any report page. This will allow summary processing to take place. If all GENERATE statements are of this form, the report is said to be a summary report. If at least one GENERATE <identifier-1> is executed, the report is considered to be a detail report.

  3. When the first GENERATE statement for a report is executed, the contents of all control fields are saved so they may be referenced during the processing of subsequent GENERATE statements.

  4. When, during the processing of a subsequent GENERATE, it is determined that a control field has changed value (ie. a control break has occurred), the appropriate control footing and control heading processing will take place and a snapshot of the current values of all control fields will again be saved.

7.8.21 GOBACK

GOBACK Syntax

GOBACK [ { RETURNING|GIVING { literal-1    }  ]
~~~~~~   { ~~~~~~~~~ ~~~~~~ { identifier-1 }

The GOBACK statement is used to logically terminate an executing program.

  1. If executed within a subprogram (i.e. a subroutine or user-defined function), GOBACK behaves like an EXIT PROGRAM or EXIT FUNCTION statement, respectively.

  2. If executed within a main program, GOBACK will act as a STOP RUN statement.

  3. The optional RETURNING clause provides the opportunity to return a numeric value to the operating system (technically, an exit status The manner in which the exit status value is interrogated by the operating system varies. Windows can use %ERRORLEVEL% to query the exit status while Unix shells such as sh, bash and ksh can query the exit status as $?. Other Unix shells may have different ways to access the exit status.

7.8.22 GO TO

7.8.22.1 Simple GO TO

Simple GO TO Syntax

GO TO procedure-name-1
~~
GO TO ENTRY literal-3
~~    ~~~~~

This form of the GO TO statement unconditionally transfers control in a program to the first executable statement within the specified <procedure-name-1>.

  1. The reserved word TO is optional and may be omitted. The presence or absence of this word has no effect upon the program.

  2. If this format of the GO TO statement appears in a consecutive sequence of imperative statements ( Imperative Statement) within a sentence, it must be the final statement in the sentence.

  3. If a GO TO is executed within the scope of…

    1. …an in-line PERFORM ( 7.8.31 PERFORM), the PERFORM is terminated as control of execution transfers to <procedure-name-1>.

    2. …a procedural PERFORM ( 7.8.31 PERFORM), and <procedure-name-1> lies outside the scope of that PERFORM, the PERFORM is terminated as control of execution transfers to <procedure-name-1>.

    3. …a MERGE statement ( 7.8.27 MERGE) OUTPUT PROCEDURE or within the scope of either an INPUT PROCEDURE or OUTPUT PROCEDURE of a SORT statement ( 7.8.42.1 File-Based SORT), and <procedure-name-1> lies outside the scope of that procedure, the SORT or MERGE operation is terminated as control of execution transfers to <procedure-name-1>. Any sorted or merged data accumulated to that point is lost.

  4. A GO TO ENTRY is an GnuCOBOL special purpose extension for use with various GnuCobol tools and is not part of any current ISO standard. See also ENTRY.

  5. The GO TO ENTRY format has to be used together with ENTRY FOR GO TO.

7.8.22.2 GO TO DEPENDING ON

GO TO DEPENDING ON Syntax

GO TO {procedure-name-1} ...
~~
                             DEPENDING ON identifier-1
                             ~~~~~~~~~
GO TO ENTRY {literal-3} ...
~~    ~~~~~
                             DEPENDING ON identifier-1
                             ~~~~~~~~~

This form of the GO TO statement will transfer control to any one of a number of specified procedure names depending on the numeric value of the identifier specified on the statement.

  1. The reserved word TO is optional and may be omitted. The presence or absence of this word has no effect upon the program but does help with read-ability.

  2. The PICTURE ( 6.9.37 PICTURE) and/or USAGE ( 6.9.61 USAGE) of the specified <identifier-1> must be such as to define it as a numeric, unedited, preferably unsigned integer data item.

  3. If the value of <identifier-1> has the value 1, control will be transferred to the 1st specified procedure name. If the value is 2, control will transfer to the 2nd procedure name, and so on.

  4. The GO TO ENTRY ... DEPENDING ON format has to be used together with ENTRY FOR GO TO.

    If control of execution is transferred to a procedure named on the statement, and the GO TO is executed within the scope of…

    1. …an in-line PERFORM ( 7.8.31 PERFORM), the PERFORM is terminated as control of execution transfers to the procedure named on the statement.

    2. …a procedural PERFORM ( 7.8.31 PERFORM), and <procedure-name-1> lies outside the scope of that PERFORM, the PERFORM is terminated as control of execution transfers to the procedure named on the statement.

    3. …a MERGE statement ( 7.8.27 MERGE) OUTPUT PROCEDURE or within the scope of either an INPUT PROCEDURE or OUTPUT PROCEDURE of a SORT statement ( 7.8.42.1 File-Based SORT), and <procedure-name-1> lies outside the scope of that procedure, the SORT or MERGE operation is terminated as control of execution transfers to the procedure named on the statement. Any sorted or merged data accumulated to that point is lost.

  5. If the value of <identifier-1> is less than 1 or exceeds the total number of procedure names specified on the statement, control will simply fall through into the next statement following the GO TO.

  6. The following example shows how GO TO ... DEPENDING ON may be used in a real application situation, and compares it against an alternative — EVALUATE ( 7.8.15 EVALUATE).

    • GO TO DEPENDING ON EVALUATE

    •     GO TO
            ACCT-TYPE-1
            ACCT-TYPE-2
            ACCT-TYPE-3
          DEPENDING ON Acct-Type.
          <<< Invalid Acct Type >>>
          GO TO All-Done.
      Acct-Type-1.
          <<< Handle Acct Type 1 >>>
          GO TO All-Done.
      Acct-Type-2.
          <<< Handle Acct Type 2 >>>
          GO TO All-Done.
      Acct-Type-3.
          <<< Handle Acct Type 3 >>>
      All-Done.
      
      EVALUATE Acct-Type
      WHEN 1
          <<< Handle Acct Type 1 >>>
      WHEN 2
          <<< Handle Acct Type 2 >>>
      WHEN 3
          <<< Handle Acct Type 3 >>>
      WHEN OTHER
          <<< Invalid Acct Type >>>
      END-EVALUATE.
      
  7. Current programming philosophy would prefer the use of the EVALUATE statement to that of this form of the GO TO statement.

7.8.23 IF

IF Syntax

  IF conditional-expression
  ~~
  THEN { imperative-statement-1 }
       { NEXT SENTENCE          }
         ~~~~ ~~~~~~~~
[ ELSE { imperative-statement-2 } ]
  ~~~~ { NEXT SENTENCE          }
         ~~~~ ~~~~~~~~
[ END-IF ]
  ~~~~~~

The IF statement is used to conditionally execute an imperative statement ( Imperative Statement) or to select one of two different imperative statements to execute based upon the TRUE/FALSE value of a conditional expression.

  1. The reserved word THEN is optional and may be omitted. The presence or absence of this word has no effect upon the program.

  2. You cannot use both NEXT SENTENCE and the END-IF scope terminator in the same IF statement.

  3. If <conditional-expression> evaluates to TRUE, <imperative-statement-1> will be executed regardless of whether or not an ELSE clause is present. Once <imperative-statement-1> has been executed, control falls into the first statement following the END-IF or to the first statement of the next sentence if there is no END-IF clause.

  4. If the optional ELSE clause is present and conditional-expression evaluates to false, then (and only then) <imperative-statement-2> will be executed. Once <imperative-statement-2> has been executed, control falls into the first statement following the END-IF or to the first statement of the next sentence if there is no END-IF clause.

  5. The clause NEXT SENTENCE may be substituted for either imperative-statement, but not both. If control reaches a NEXT SENTENCE clause due to the truth or falsehood of <conditional-expression>, control will be transferred to the first statement of the next sentence found in the program (the first statement after the next period).

    NEXT SENTENCE was needed for COBOL programs that were coded according to pre-1985 standards that wish to nest one IF statement inside another. 2.2.13 Use of VERB/END-VERB Constructs, for an explanation of why NEXT SENTENCE was necessary.

    Programs coded for 1985 (and beyond) standards don’t need it, instead using the explicit scope-terminator END-IF to inform the compiler where <imperative-statement-2> (or <imperative-statement-1> if there is no ELSE clause coded) ends. New GnuCOBOL programs should be coded to use the END-IF scope terminator for IF statements. 2.2.13 Use of VERB/END-VERB Constructs, for additional information.

7.8.24 INITIALIZE

INITIALIZE Syntax

INITIALIZE|INITIALISE identifier-1...
~~~~~~~~~~ ~~~~~~~~~~
    [ WITH FILLER ]
           ~~~~~~
    [ { category-name-1 } TO VALUE ]
      { ALL             }    ~~~~~
        ~~~
    [ THEN REPLACING { category-name-2 DATA BY
           ~~~~~~~~~                        ~~
          [ LENGTH OF ] { literal-1    } }... ]
            ~~~~~~      { identifier-1 }

    [ THEN TO DEFAULT ]
              ~~~~~~~

The INITIALIZE statement initializes each <identifier-1> with certain specific values, depending upon the options specified.

  1. The reserved words DATA, OF, THEN, TO and WITH are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The reserved words INITIALIZE and INITIALISE are interchangeable.

  3. The WITH FILLER, REPLACING and DEFAULT clauses are meaningful only if <identifier-1> is a group item. They are accepted if it’s an elementary item, but will serve no purpose. The VALUE clause is meaningful in both cases.

  4. A <category-name-1> and/or <category-name-2> may be any of the following:

    • ALPHABETIC

      The PICTURE ( 6.9.37 PICTURE) of the data item only contains A symbols.

    • ALPHANUMERIC

      The PICTURE of the data item contains only X or a combination of A and 9 symbols.

    • ALPHANUMERIC-EDITED

      The PICTURE of the data item contains only X or a combination of A and 9 symbols plus at least one B, 0 (zero) or / symbol.

    • NUMERIC

      The data item is one that is described with a picture less USAGE ( 6.9.61 USAGE) or has a PICTURE composed of nothing but P, 9, S and V symbols.

    • NUMERIC-EDITED

      The PICTURE of the data item contains nothing but the symbol 9 and at least one of the editing symbols $, +, -, CR, DB, ., ,, * or Z.

    • NATIONAL

      The data item is one containing nothing but the N symbol.

    • NATIONAL-EDITED

      The data item contains nothing but N, B, / and 0 symbols.

  5. From the sequence of <identifier-1> data items specified on the INITIALIZE statement, a list of initialized fields referred to as the field list in the remainder of this section, will include:

    1. Every <identifier-1> that is an elementary item, including any that may have the REDEFINES ( 6.9.41 REDEFINES) clause in their descriptions.

    2. Every non-FILLER elementary item subordinate to <identifier-1>, provided that elementary item neither contains a REDEFINES clause in its definition nor belongs to a group item subordinate to <identifier-1> which contains a REDEFINES clause in its definition.

    3. If the optional WITH FILLER clause is included on the INITIALIZE statement, then every FILLER elementary item subordinate to each <identifier-1> will be included as well, provided that elementary item neither contains a REDEFINES clause in its definition nor belongs to a group item subordinate to <identifier-1> which contains a REDEFINES clause in its definition..

  6. Once a field list has been determined, each item in that field list will be initialized as if an individual MOVE ( 7.8.28 MOVE) statement to that effect had been coded. The rules for initialization are as follows:

  7. If no VALUE, REPLACING or DEFAULT clauses are coded, each member of the field list will be initialized as if the figurative constant ZERO (if the field list item is numeric or numeric-edited) or SPACES (otherwise) were being moved to it.

  8. If a VALUE clause is specified on the INITIALIZE statement, each qualifying member of the field list having a compile-time VALUE ( 6.9.63 VALUE) specified in its definition will be initialized to that value. Field list members with VALUE clauses will qualify for this treatment as follows:

    1. If the ALL keyword was specified on the VALUE clause, all members of the field list with VALUE clauses will qualify.

    2. If <category-name-1> is specified instead of ALL, only those members of the field list with VALUE clauses that also meet the criteria set down for the specified <category-name> (see the list above) will qualify.

    3. If you need to apply VALUE initialization to multiple <category-name-1> values, you will need to use multiple INITIALIZE statements.

  9. If a REPLACING clause is specified on the INITIALIZE statement, each qualifying member of the field list that was not already initialized by a VALUE clause, if any, will be initialized to the specified <literal-1> or <identifier-1> value.

    Only those as-yet uninitialized list members meeting the criteria set forth for the specified <category-name-2> will qualify for this initialization.

    If you need to apply REPLACING initialization to multiple <category-name-2> values, you may repeat the syntax after the reserved word REPLACING, as necessary.

  10. If a DEFAULT clause is specified, any remaining uninitialized members of the field list will be initialized according to the default for their class (numeric and numeric-edited are initialized to ZERO, all others are initialized to SPACES).

  11. The following example may help your understanding of how the INITIALIZE statement works. The sample code makes use of the COBDUMP program to dump the storage that is (or is not) being initialized. COBDUMP (in Sample Programs), for a source and cross-reference listing of the COBDUMP program.

    IDENTIFICATION DIVISION.
    PROGRAM-ID. DemoInitialize.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01  Item-1.
        05 I1-A VALUE ALL '*'.
           10 FILLER                PIC X(1).
           10 I1-A-1                PIC 9(1) VALUE 9.
        05 I1-B                     USAGE BINARY-CHAR.
        05 I1-C                     PIC A(1) VALUE 'C'.
        05 I1-D                     PIC X/X VALUE 'ZZ'.
        05 I1-E                     OCCURS 2 TIMES PIC 9.
    PROCEDURE DIVISION.
    000-Main.
        DISPLAY "MOVE HIGH-VALUES TO Item-1"
            PERFORM 100-Init-Item-1
            CALL "COBDUMP" USING Item-1
            DISPLAY " "
    
        DISPLAY "INITIALIZE Item-1"
            INITIALIZE Item-1
            CALL "COBDUMP" USING Item-1
            PERFORM 100-Init-Item-1
            DISPLAY " "
    
        DISPLAY "INITIALIZE Item-1 WITH FILLER"
            MOVE HIGH-VALUES TO Item-1
            INITIALIZE Item-1 WITH FILLER
            CALL "COBDUMP" USING Item-1
            PERFORM 100-Init-Item-1
            DISPLAY " "
    
        DISPLAY "INITIALIZE Item-1 ALL TO VALUE"
            MOVE HIGH-VALUES TO Item-1
            INITIALIZE Item-1 ALPHANUMERIC TO VALUE
            CALL "COBDUMP" USING Item-1
            PERFORM 100-Init-Item-1
            DISPLAY " "
    
        DISPLAY "INITIALIZE Item-1 REPLACING NUMERIC BY 1"
            MOVE HIGH-VALUES TO Item-1
            INITIALIZE Item-1 REPLACING NUMERIC BY 1
            CALL "COBDUMP" USING Item-1
            PERFORM 100-Init-Item-1
            DISPLAY " "
    
        STOP RUN
        .
    
    100-Init-Item-1.
        MOVE HIGH-VALUES TO Item-1
        .
    

    When executed, this program produces the following output:

    MOVE HIGH-VALUES TO Item-1
    <-Addr-> Byte <---------------- Hexadecimal ----------------> <---- Char ---->
    ======== ==== =============================================== ================
    00404058    1 FF FF FF FF FF FF FF FF FF                      .........
    
    INITIALIZE Item-1
    <-Addr-> Byte <---------------- Hexadecimal ----------------> <---- Char ---->
    ======== ==== =============================================== ================
    00404058    1 FF 30 00 20 20 2F 20 30 30                      .0.  / 00
    
    INITIALIZE Item-1 WITH FILLER
    <-Addr-> Byte <---------------- Hexadecimal ----------------> <---- Char ---->
    ======== ==== =============================================== ================
    00404058    1 20 30 00 20 20 2F 20 30 30                       0.  / 00
    
    INITIALIZE Item-1 ALL TO VALUE
    <-Addr-> Byte <---------------- Hexadecimal ----------------> <---- Char ---->
    ======== ==== =============================================== ================
    00404058    1 2A 2A FF 43 5A 5A 20 FF FF                      **.CZZ ..
    
    INITIALIZE Item-1 REPLACING NUMERIC BY 1
    <-Addr-> Byte <---------------- Hexadecimal ----------------> <---- Char ---->
    ======== ==== =============================================== ================
    00404058    1 FF 31 01 FF FF FF FF 31 31                      .1.....11
    

7.8.25 INITIATE

INITIATE Syntax

INITIATE report-name-1
~~~~~~~~

The INITIATE statement starts Report-Writer Control System (RWCS) processing for a report.

  1. Each <report-name-1> must be the name of a report having an RD ( 6.6 REPORT SECTION) defined for it.

  2. The file in whose FD ( 6.2.1 File/Sort-Description) a REPORT <report-name-1> clause exists must be open for OUTPUT or EXTEND at the time the INITIATE statement is executed. 7.8.30 OPEN, for more information on file open modes.

  3. The INITIATE statement will initialize all of the following for each report named on the statement:

    • All sum counters, if any, will be set to 0

    • The report’s LINE-COUNTER special register ( 7.7 Special Registers) will be set to 0

    • The report’s PAGE-COUNTER special register will be set to 1

  4. No report content will actually presented to the report file as a result of a successful INITIATE statement — that will not occur until the first GENERATE statement ( 7.8.20 GENERATE) is executed.

7.8.26 INSPECT

INSPECT Syntax

INSPECT { literal-1            }
~~~~~~~ { identifier-1         }
        { function-reference-1 }

 [ TALLYING { identifier-2 FOR { ALL|LEADING|TRAILING { literal-2    } }
   ~~~~~~~~                ~~~ { ~~~ ~~~~~~~ ~~~~~~~~ { identifier-3 } }
                               { CHARACTERS                            }
                                 ~~~~~~~~~~
              [ | { AFTER|BEFORE } INITIAL { literal-3    } | ] }... ]
                |   ~~~~~ ~~~~~~           { identifier-4 } |

 [ REPLACING { { { ALL|FIRST|LEADING|TRAILING { literal-4    } }
   ~~~~~~~~~   { { ~~~ ~~~~~ ~~~~~~~ ~~~~~~~~ { identifier-5 } }
               { CHARACTERS                                    }
               { ~~~~~~~~~~                                    }

                BY { [ ALL ] literal-5 }
                ~~ {   ~~~             }
                   { identifier-6      }

              [ | { AFTER|BEFORE } INITIAL { literal-6    } | ] }... ]
                |   ~~~~~ ~~~~~~           { identifier-7 } |

 [ CONVERTING { { literal-7    } TO { literal-8    }
   ~~~~~~~~~~   { identifier-8 } ~~ { identifier-9 }

              [ | { AFTER|BEFORE } INITIAL { literal-9     } | ] ]
                |   ~~~~~ ~~~~~~           { identifier-10 } |

The INSPECT statement is used to perform various counting and/or data-alteration operations against strings.

  1. The reserved word INITIAL is optional and may be omitted. The presence or absence of this words has no effect upon the program.

  2. If a CONVERTING clause is specified, neither the TALLYING nor REPLACING clauses may be used.

  3. If either the TALLYING or REPLACING clauses are specified, the CONVERTING clause cannot be used.

  4. If both the TALLYING and REPLACING clauses are specified, they must be specified in the order shown.

  5. All literals and identifiers must be explicitly or implicitly defined as alphanumeric or alphabetic.

  6. If <function-reference-1> is specified, it must be an invocation of an intrinsic function that returns a string result. Additionally, only the TALLYING clause may be specified.

  7. If <literal-1> is specified, only the TALLYING clause may be specified.

  8. Whichever is specified — <literal-1>, <identifier-1> or <function-reference-1> — that item will be referred to in the discussions that follows as the ‘inspect subject‘.

  9. The three optional clauses control the operation of this statement as follows:

    1. The CONVERTING clause replaces one or more individual characters found in the inspect subject with a different character in much the same manner as is possible with the TRANSFORM statement ( 7.8.49 TRANSFORM).

    2. The REPLACING clause replaces one or more sub strings located in the inspect subject with a different, but equally-sized replacement sub string. If you need to replace a sub string with another of a different length, consider using either the SUBSTITUTE intrinsic function ( 8.1.90 SUBSTITUTE) or the SUBSTITUTE-CASE intrinsic function ( 8.1.91 SUBSTITUTE-CASE).

    3. The TALLYING clause counts the number of occurrences of one or more strings of characters in the inspect subject.

  10. The optional INITIAL clauses may be used to limit the range of characters in the inspect subject that the CONVERTING, REPLACING or TALLYING instruction in which they occur will apply. We call this the ‘target range‘ of the inspect subject. The target range is defined as follows:

    1. If there is no INITIAL clause specified, the target range is the entire inspect subject.

    2. Either a BEFORE phrase, an AFTER phrase or both may be specified. They may be specified in any order.

    3. The starting point of the target range will be the first character following the sub string identified by the AFTER specification. The ending point will be the last character immediately preceding the sub string identified by the BEFORE specification.

    4. If no AFTER is specified, the first character position of the target range will be character position #1 of the inspect subject.

    5. If no BEFORE is specified, the last character position of the target range will be the last character position of the inspect subject.

  11. The following points apply to the use of the TALLYING clause:

    1. While there will typically be only be a single set of counting instructions on an INSPECT:

      INSPECT Character-String
          TALLYING C-ABC FOR ALL "ABC"
      

      There could be multiple counting instructions specified:

      INSPECT Character-String
          TALLYING C-ABC FOR ALL "ABC"
                   C-BCDE FOR ALL "BCDE"
      

      When there are multiple instructions, the one specified first will take priority over the one specified second, (and so forth) as the INSPECT proceeds forward through the inspect subject, character-by-character.

      With the above example, if the inspect subject were --ABCDEF----BCDEF--, the final result of the counting would be that C-ABC would be incremented by 1 while C-BCDE would be incremented only once; although the human eye clearly sees two ‘BCDE‘ sequences, the INSPECT ... TALLYING would only “see” the second — the first would have been processed by the first (higher-priority) counting instruction.

    2. Each set of counting instructions contains the following information:

      1. A target range, specified by the presence of an AFTER INITIAL and/or BEFORE INITIAL clause; the rules for specifying target ranges were covered previously.

      2. A Target Sub string — this is a sequence of characters to be located somewhere in the inspect subject and counted. Target sub strings may be defined as a literal value (figurative constants are allowed) or by the contents of an identifier. If the target sub string is specified as a figurative constant, it will be assumed to have a length of one (’1‘) character. The keywords before the literal or identifier control how many target sub strings could be identified from that replacement instruction, as follows:

        ALL — identifies every possible target sub string that occurs within the target range. There are three occurrences of ALL 'XX' found in aXXabbXXccXXdd.

        LEADING — identifies only an occurrence of the target sub string found either at the first character position of the target range or immediately following a previously-found occurrence. There are no occurrences of LEADING 'XX' found in aXXabbXXccXXdd, but there is one occurrence of LEADING 'a' (the first character).

        TRAILING — identifies only an occurrence of the target sub string found either at the very end of the target range or toward the end, followed by nothing but other occurrences. There are no occurrences of LEADING 'XX' found in aXXabbXXccXXdd, but there are two occurrences of TRAILING 'd'.

        The CHARACTERS option will match any one single character, regardless of what that character is.

    3. <identifier-2> will be incremented by 1 each time the target sub string is found within the target range of the inspect subject. The INSPECT statement will not zero-out <identifier-2> at the start of execution of the INSPECT — it is the programmer’s responsibility to ensure that all <identifier-2> data items are properly initialized to the desired starting values prior to execution of the INSPECT.

  12. The following points apply to the use of the REPLACING clause:

    1. While there will typically be only be a single set of replacement instructions on an INSPECT:

      INSPECT Character-String
          REPLACING ALL "ABC" BY "DEF"
      

      There could be multiple replacement instructions:

      INSPECT Character-String
          REPLACING ALL "ABC" BY "DEF"
                    ALL "BCDE" BY "WXYZ"
      

      When there are multiple replacement instructions, the one specified first will take priority over the one specified second, (and so forth) as the INSPECT proceeds forward through the inspect subject, character-by-character.

      With the above example, if the inspect subject were --ABCDEF----BCDEF--, the final result of the replacement would be --DEFDEF----WXYZF--.

    2. Each set of replacement instructions contains the following information:

      1. A target range, specified by the presence of an AFTER INITIAL and/or BEFORE INITIAL clause; the rules for specifying target ranges were covered previously.

      2. A Target Sub string — this is a sequence of characters to be located somewhere in the inspect subject and subsequently replaced with a new value. Target sub strings, which are specified before the BY keyword, may be defined as a literal value (figurative constants are allowed) or by the contents of an identifier. If the target sub string is specified as a figurative constant, it will be assumed to have a length of one (’1‘) character. The keywords before the literal or identifier control how many target sub strings could be identified from that replacement instruction, as follows:

        ALL — identifies every possible target sub string that occurs within the target range. There are three occurrences of ALL 'XX' found in aXXabbXXccXXdd.

        FIRST — the first occurrence of the target sub string found within the target range. The FIRST 'XX' found in aXXabbXXccXXdd would be the one found between the ‘a‘ and ‘b‘ characters.

        LEADING — an occurrence of the target sub string found either at the first character position of the target range or immediately following a previously-found occurrence. There are no occurrences of LEADING 'XX' found in aXXabbXXccXXdd, but there is one occurrence of LEADING 'a' (the first character).

        TRAILING — an occurrence of the target sub string found either at the very end of the target range or toward the end, followed by nothing but other occurrences. There are no occurrences of LEADING 'XX' found in aXXabbXXccXXdd, but there are two occurrences of TRAILING 'd'.

        The CHARACTERS option will match any one single character. When you use this option, the replacement sub string (see the next item) must be exactly one character in length.

      3. A Replacement Sub string — this is the sequence of characters that should replace the target sub string. Replacement sub strings are specified after the BY keyword. They too may be specified as a literal, either with or without an ALL prefix (again, figurative constants are allowed) or the value of an identifier. If a figurative constant is coded, the ALL keyword will be assumed, even if it wasn’t specified. Literals without ALL will either be truncated or padded with spaces on the right to match the length of the target sub string. Literals with ALL or figurative constants will be repeated as necessary to match the length of the target sub string. Identifiers specified as replacement sub strings must be defined with a length equal to that of the target sub string.

  13. When both REPLACING and TALLYING are specified:

    1. The INSPECT statement will make a single pass through the sequence of characters comprising the inspect subject. As the pointer to the current inspect target character reaches a point where it falls within the explicit or implicit target ranges specified on the operational instructions of the two clauses, the actions specified by those instructions will become eligible to be taken. As the character pointer reaches a point where it falls past the end of target ranges, the instructions belonging to those target ranges will become disabled.

    2. At any point in time, there may well be multiple REPLACING and/or TALLYING operational instructions active. Only one of the TALLYING and one of the REPLACING instructions (if any) can be executed for any one character pointer position. In each case, it will be the first of the instructions in each category that produces a match with its target string specification.

    3. When both a TALLYING and a REPLACING instruction have been selected for execution, the TALLYING instruction will be executed first. This guarantees that TALLYING will compute occurrences based upon the initial value of the inspect subject before any replacements occur.

  14. The following points apply to the use of the CONVERTING clause:

    1. A CONVERTING clause performs a series of single-character substitutions against a data item in much the same manner as is possible with the TRANSFORM statement ( 7.8.49 TRANSFORM).

    2. Unlike the TALLYING and REPLACING clauses, both of which may have multiple operations specified, there may be only one CONVERTING operation per INSPECT.

    3. If the length of <literal-7> or <identifier-8> (the “from” string) exceeds the length of <literal-8> or <identifier-9> (the “to” string), then the “to” string will be assumed to be padded to the right with enough spaces to make it the same length as the “from” string.

    4. If the length of the “from” string is less than the length of the “to” string, then the “to” string will be truncated to the length of the “from” string.

    5. Each character, in turn, within the “from” string will be searched for in the target range of the inspect subject. Each located occurrence will be replaced by the corresponding character of the “to” string.

7.8.27 MERGE

MERGE Syntax

MERGE sort-file-1
~~~~~
   { ON { ASCENDING  } KEY identifier-1... }...
        { ~~~~~~~~~  }
        { DESCENDING }
          ~~~~~~~~~~
   [ WITH DUPLICATES IN ORDER ]
          ~~~~~~~~~~
   [ COLLATING SEQUENCE IS alphabet-name-1 ]
     ~~~~~~~~~
     USING file-name-1 file-name-2...
     ~~~~~
   { OUTPUT PROCEDURE IS procedure-name-1    }
   { ~~~~~~ ~~~~~~~~~                        }
   {       [ THRU|THROUGH procedure-name-2 ] }
   {         ~~~~ ~~~~~~~                    }
   { GIVING file-name-3...                   }
   { ~~~~~~                                  }

The DUPLICATES clause is syntactically recognized but is otherwise non-functional. The MERGE statement merges the contents of two or more files that have each been pre-sorted on a set of specified identical keys.

  1. The reserved words IN, IS, KEY, ON, ORDER, SEQUENCE and WITH are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The reserved words THRU and THROUGH are interchangeable.

  3. GnuCOBOL always behaves as if the WITH DUPLICATES IN ORDER clause is specified, even if it isn’t.

    While any COBOL implementation’s sort or merge facilities guarantee that records with duplicate key values will be in proper sequence with regard to other records with different key values, they generally make no promises as to the resulting relative sequence of records having duplicate key values with one another.

    Some COBOL implementations provide this optional clause to force their sort and merge facilities to retain duplicate key-value records in their original input sequence, relative to one another.

  4. The <sort-file-1> named on the MERGE statement must be defined using a sort description (SD ( 6.2.1 File/Sort-Description)). This file is referred to in the remainder of this discussion as the merge work file.

  5. Each <file-name-1>, <file-name-2> and <file-name-3> (if specified) must reference ORGANIZATION LINE SEQUENTIAL ( 5.2.1.2 ORGANIZATION LINE SEQUENTIAL) or ORGANIZATION SEQUENTIAL ( 5.2.1.1 ORGANIZATION SEQUENTIAL) files. These files must be defined using a file description (FD ( 6.2.1 File/Sort-Description)).

  6. The <identifier-1> … field(s) must be defined as field(s) within a record of <sort-file-1>.

  7. The record descriptions of <file-name-1>, <file-name-2>, <file-name-3> (if any) and <sort-file-1> are assumed to be identical in layout and size. While the actual data names used for fields in these files’ records may differ, the structure of records, PICTURE ( 6.9.37 PICTURE) of fields, USAGE ( 6.9.61 USAGE) of fields, size of fields and location of fields within the records should match field-by-field across all files, at least as far as the KEY fields are concerned.

  8. A common programming technique when using the MERGE statement is to define the records of all files involved as simple elementary items of the form 01 record-name PIC X(n). where n is the record size. The only file where records are actually described in detail would then be <sort-file-1>.

  9. The following rules apply to the files named on the USING clause:

    1. None of them may be open at the time the MERGE is executed.

    2. Each of those files is assumed to be already sorted according to the specifications set forth on the MERGE statement’s KEY clause.

    3. No two of those files may be referenced on a SAME RECORD AREA ( 5.2.2 SAME RECORD AREA), SAME SORT AREA or SAME SORT-MERGE AREA statement.

  10. The merging process is as follows:

    1. As the MERGE statement begins execution, the first record in each of the USING files is read automatically.

    2. As the MERGE statement executes, the current record from each of the USING files is examined and compared to each other according to the rules set forth by the KEY clause and the alphabet ( 5.1.3.1 Alphabet-Name-Clause) specified on the COLLATING SEQUENCE clause. The record that should be next in sequence will be written to the merge work file and the USING file from which that record came will be read so that its next record is available. As end-of-file conditions are reached on USING files, those files will be excluded from further processing — processing continues with the remaining files until all the contents of all of them have been exhausted.

    3. After the merge work file has been populated, the merged data will be written to each <file-name-3> if the GIVING clause was specified, or will be processed by utilizing an OUTPUT PROCEDURE.

    4. When GIVING is specified, none of the <file-name-3> files can be open at the time the MERGE statement is executed.

    5. When an output procedure is used, the procedure(s) specified on the OUTPUT PROCEDURE clause will be invoked as if by a procedural PERFORM ( 7.8.31.1 Procedural PERFORM) statement with no VARYING, TIMES or UNTIL options specified. Merged records may be read from the merge work file — one at a time — within the output procedure using the RETURN ( 7.8.36 RETURN) statement.

      A GO TO statement ( 7.8.22 GO TO) that transfers control out of the output procedure will terminate the MERGE statement but allows the program to continue executing from the point where the GO TO statement transferred control to. Once an output procedure has been “aborted” using a GO TO it cannot be resumed, and the contents of the merge work file are lost. You may, however, re-execute the MERGE statement itself. Using a GO TO statement to prematurely terminate a merge, or re-starting a previously-cancelled merge is not considered good programming style and should be avoided.

      An output procedure should be terminated in the same way a procedural PERFORM statement would be. Usually, this action will be taken once the RETURN statement indicates that all records in the merge work file have been processed, but termination could occur at any time — via an EXIT statement ( 7.8.18 EXIT) — if required.

      Neither a file-based SORT statement ( 7.8.42.1 File-Based SORT) nor another MERGE statement may be executed within the scope of the procedures comprising the output procedure unless those statements utilize a different sort or merge work file.

    6. Once the output procedure terminates, or the last <file-name-3> file has been populated with merged data, the output phase — and the MERGE statement itself — is complete.

7.8.28 MOVE

7.8.28.1 Simple MOVE

Simple MOVE Syntax

MOVE { literal-1    } TO identifier-2...
~~~~ { identifier-1 } ~~

The Simple MOVE statement moves a specific value to one or more receiving data items.

  1. The MOVE statement will replace the contents of one or more receiving data items (<identifier-2>) with a new value — the one specified by <literal-1> or <identifier-1>.

  2. Only numeric data can be moved to a numeric or numeric-edited <identifier-2>. A MOVE involving numeric data will perform any necessary format conversions that might be necessary due to differing USAGE ( 6.9.61 USAGE) specifications.

  3. The contents of the <identifier-1> data item will not be changed, unless that same data item appears as an <identifier-2>. Note that such situations will cause a warning message to be issued by the compiler, if warning messages are enabled.

7.8.28.2 MOVE CORRESPONDING

MOVE CORRESPONDING Syntax

MOVE CORRESPONDING identifier-1 TO identifier-2...
~~~~ ~~~~                       ~~

The MOVE CORRESPONDING statement similarly-named items from one group item to another.

  1. The reserved word CORRESPONDING may be abbreviated as CORR.

  2. Both <identifier-1> and <identifier-2> must be group items.

  3. 7.6.2 CORRESPONDING, for a discussion of how corresponding matches between two group items are established.

  4. When corresponding matches are established, the effect of a MOVE CORRESPONDING on those matches will be as if a series of individual MOVEs were done — one for each match.

7.8.29 MULTIPLY

7.8.29.1 MULTIPLY BY

MULTIPLY BY Syntax

MULTIPLY { literal-1    } BY { identifier-2
~~~~~~~~ { identifier-1 } ~~

     [ ROUNDED [ MODE IS { AWAY-FROM-ZERO         } ] ] }...
       ~~~~~~~   ~~~~    { ~~~~~~~~~~~~~~         }
                         { NEAREST-AWAY-FROM-ZERO }
                         { ~~~~~~~~~~~~~~~~~~~~~~ }
                         { NEAREST-EVEN           }
                         { ~~~~~~~~~~~~           }
                         { NEAREST-TOWARD-ZERO    }
                         { ~~~~~~~~~~~~~~~~~~~    }
                         { PROHIBITED             }
                         { ~~~~~~~~~~             }
                         { TOWARD-GREATER         }
                         { ~~~~~~~~~~~~~~         }
                         { TOWARD-LESSER          }
                         { ~~~~~~~~~~~~~          }
                         { TRUNCATION             }
                           ~~~~~~~~~~
   [ ON SIZE ERROR imperative-statement-1 ]
        ~~~~ ~~~~~
   [ NOT ON SIZE ERROR imperative-statement-2 ]
     ~~~    ~~~~ ~~~~~
[ END-MULTIPLY ]
  ~~~~~~~~~~~~

The MULTIPLY BY statement computes the product of one or more data items (<identifier-2>) and either a numeric literal or another data item.

  1. The reserved words IS and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. Both <identifier-1> and <identifier-2> must be numeric un-edited data items; <literal-1> must be a numeric literal.

  3. The product of <identifier-1> or <literal-1> and each <identifier-2>, in turn, will be computed and moved to each of the <identifier-2> data items, replacing the prior contents.

  4. The value of <identifier-1> is not altered, unless that same data item appears as an <identifier-2>.

  5. The optional ROUNDED ( 7.6.7 ROUNDED) clause available to each <identifier-2> will control how non-integer results will be saved.

  6. The optional ON SIZE ERROR and NOT ON SIZE ERROR clauses may be used to detect and react to the failure or success, respectively, of an attempt to perform a calculation. In this case, failure is defined as being an <identifier-2> with an insufficient number of digit positions available to the left of any implied decimal point. 7.6.6 ON SIZE ERROR + NOT ON SIZE ERROR, for additional information.

7.8.29.2 MULTIPLY GIVING

MULTIPLY GIVING Syntax

MULTIPLY { literal-1    } BY { literal-2    } GIVING { identifier-3
~~~~~~~~ { identifier-1 } ~~ { identifier-2 } ~~~~~~

     [ ROUNDED [ MODE IS { AWAY-FROM-ZERO         } ] ] }...
       ~~~~~~~   ~~~~    { ~~~~~~~~~~~~~~         }
                         { NEAREST-AWAY-FROM-ZERO }
                         { ~~~~~~~~~~~~~~~~~~~~~~ }
                         { NEAREST-EVEN           }
                         { ~~~~~~~~~~~~           }
                         { NEAREST-TOWARD-ZERO    }
                         { ~~~~~~~~~~~~~~~~~~~    }
                         { PROHIBITED             }
                         { ~~~~~~~~~~             }
                         { TOWARD-GREATER         }
                         { ~~~~~~~~~~~~~~         }
                         { TOWARD-LESSER          }
                         { ~~~~~~~~~~~~~          }
                         { TRUNCATION             }
                           ~~~~~~~~~~
   [ ON SIZE ERROR imperative-statement-1 ]
        ~~~~ ~~~~~
   [ NOT ON SIZE ERROR imperative-statement-2 ]
     ~~~    ~~~~ ~~~~~
[ END-MULTIPLY ]
  ~~~~~~~~~~~~

The MULTIPLY GIVING statement computes the product of two literals and/or data items and saves that result in one or more other data items.

  1. The reserved words IS and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. Both <identifier-1> and <identifier-2> must be numeric un-edited data items; <literal-1> and <literal-2> must be numeric literals.

  3. The product of <identifier-1> or <literal-1> and <identifier-2> or <literal-2> will be computed and moved to each of the <identifier-3> data items, replacing their old contents.

  4. Neither the value of <identifier-1> nor <identifier-2> will be altered, unless either appears as an <identifier-3>.

  5. The optional ROUNDED ( 7.6.7 ROUNDED) clause available to each <identifier-2> will control how non-integer results will be saved.

  6. The optional ON SIZE ERROR and NOT ON SIZE ERROR clauses may be used to detect and react to the failure or success, respectively, of an attempt to perform a calculation. In this case, failure is defined as being an <identifier-2> with an insufficient number of digit positions available to the left of any implied decimal point. 7.6.6 ON SIZE ERROR + NOT ON SIZE ERROR, for additional information.

7.8.30 OPEN

OPEN Syntax

OPEN { { INPUT  } [ SHARING WITH { ALL OTHER } ] file-name-1
~~~~   { ~~~~~  }   ~~~~~~~      { ~~~       }
       { OUTPUT }                { NO OTHER  }
       { ~~~~~~ }                { ~~        }
       { I-O    }                { READ ONLY }
       { ~~~    }                  ~~~~ ~~~~
       { EXTEND }
         ~~~~~~
     [ { REVERSED           } ] }...
       { ~~~~~~~~           }
       { WITH { NO REWIND } }
       {      { ~~ ~~~~~~ } }
       {      { LOCK      } }
                ~~~~

The NO REWIND, and REVERSEDclauses are syntactically recognized but are otherwise non-functional. The OPEN statement makes one or more files described in your program available for use.

  1. The reserved words OTHER and WITH are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The SHARING and WITH LOCK clauses may not both be specified in the same OPEN statement.

  3. Any file defined in a GnuCOBOL program must be successfully opened before it or any of its record descriptions may be referenced on:

    A CLOSE statement ( 7.8.7 CLOSE)

    A DELETE statement ( 7.8.11 DELETE)

    A READ statement ( 7.8.32 READ)

    A REWRITE statement ( 7.8.37 REWRITE)

    A START statement ( 7.8.43 START)

    An UNLOCK statement ( 7.8.50 UNLOCK)

    A WRITE statement ( 7.8.52 WRITE)

  4. Any attempt to open a file that is already open will fail with a file status of 41 ( File Status Codes).

  5. Any open failure (including status 41) may be trapped using DECLARATIVES ( 7.5 DECLARATIVES) or an error procedure established using the CBL_ERROR_PROC built-in system subroutine ( 8.2.25 CBL_ERROR_PROC) built-in subroutine or even just checking the status field defined. It is up to the programmer to check for bad statuses and respond accordingly such as issue a CLOSE before dealing with the problem.

  6. The INPUT, OUTPUT, I-O and EXTEND open modes inform GnuCOBOL of the manner in which you wish to use the file, as follows:

    • INPUT

      You may only read the existing contents of the file — only the CLOSE, READ, START and UNLOCK statements will be allowed. This enforcement takes place at execution time, not compilation time.

    • OUTPUT

      You may only write new content (which will completely replace any previous file contents) to the file — only the CLOSE, UNLOCK and WRITE statements will be allowed. This enforcement takes place at execution time, not compilation time.

    • I-O

      You may perform any operation you wish against the file — all file I/O statements will be allowed.

    • EXTEND

      You may only write new content (which will be appended after the previously existing file contents) to the file — only the CLOSE, UNLOCK and WRITE statements will be allowed. This enforcement takes place at execution time, not compilation time. You cannot extend an empty file; this will not generate a runtime error, but no output will appear in the file.

  7. The SHARING clause informs the GnuCOBOL file runtime modules how you are willing to co-exist with any other GnuCOBOL programs that may attempt to open the same file after your program does. 2.2.15 File Sharing, for an explanation of the SHARING clause.

  8. The WITH LOCK option will be functional only if your GnuCOBOL build can support it. GnuCOBOL built for MinGW or native Windows will not, because the Unix fcntl primitive doesn’t exist in those environments. GnuCOBOL built for Cygwin or Unix will.

7.8.31 PERFORM

7.8.31.1 Procedural PERFORM

Procedural PERFORM Syntax

PERFORM procedure-name-1 [ THRU|THROUGH procedure-name-2 ]
~~~~~~~                    ~~~~ ~~~~~~~
   [ { [ WITH TEST { BEFORE } ] { VARYING-Clause                 } } ]
     {        ~~~~ { ~~~~~~ }   { UNTIL conditional-expression-1 } }
     {             { AFTER  }     ~~~~~                            }
     {               ~~~~~                                         }
     { UNTIL EXIT|FOREVER                                          }
     { ~~~~~ ~~~~ ~~~~~~~                                          }
     { { literal-1    } TIMES                                      }
     { { identifier-1 } ~~~~~                                      }

This format of the PERFORM statement is used to transfer control to one or more procedures, which will return control back when complete. Execution of the procedure(s) can be done a single time, multiple times, repeatedly until a condition becomes TRUE or forever (with some way of breaking out of the control of the PERFORM or of halting program execution within the procedure(s)).

  1. The reserved word WITH is optional and may be omitted. The presence or absence of this word has no effect upon the program.

  2. The reserved words THRU and THROUGH are interchangeable.

  3. The reserved word and phrase FOREVER and UNTIL EXIT are interchangeable.

  4. Both <procedure-name-1> and <procedure-name-2> must be procedure division sections or paragraphs defined in the same program as the PERFORM statement. If <procedure-name-2> is specified, it must follow <procedure-name-1> in the program’s source code.

  5. The perform scope is defined as being the statements within <procedure-name-1>, the statements within <procedure-name-2> and all statements in all procedures defined between them.

  6. <literal-1> must be a numeric literal or a reference to a function that returns a numeric value. The value must be an integer greater than zero.

  7. <identifier-1> must be an elementary un-edited numeric data item with an integer value greater than zero.

  8. Without the UNTIL, UNTIL EXIT, TIMES, VARYING-Clause ( 7.8.31.3 VARYING) or FOREVER clauses, the code within the perform scope will be executed once, after which control will return to the statement following the PERFORM.

  9. The FOREVER option will repeatedly execute the code within the perform scope with no conditions defined for termination of the repetition — it will be up to the programmer to include an EXIT SECTION statement ( 7.8.18 EXIT) or EXIT PARAGRAPH statement within the procedure(s) being performed that will break out of the loop.

  10. The TIMES option will repeat the execution of the code within the perform scope a fixed number of times. When the PERFORM statement begins execution, an internal repeat counter (not accessible to the programmer) will be set to the value of <literal-1> or the value within <identifier-1>.

    If the counter has a value greater than zero, the statement(s) within the PERFORM scope will be executed, after which the counter will be decremented by 1 with each repetition. Once that counter reaches zero, repetition will cease and control will fall into the next statement following the PERFORM.

    If the <identifier-1> option was used, altering the value of that data item within the perform scope will not affect the repetition count.

  11. The UNTIL <conditional-expression-1> option will repeat the code within the perform scope until the specified conditional expression evaluates to a TRUE value.

  12. The optional WITH TEST clause will control whether UNTIL testing occurs BEFORE the statements within the perform scope are executed on each iteration (creating the possibility — if <conditional-expression-1> is initially TRUE — that the statements within the perform scope will never be executed) or AFTER (guaranteeing the statements within the perform scope will be executed at least once).

    The default, if this clause is absent, is WITH TEST BEFORE.

    This clause may not be coded when the TIMES clause is used.

  13. The optional <VARYING-Clause> is a mechanism that creates an advanced loop-management mechanism complete with one or more numeric data items being automatically incremented (or decremented) on each loop iteration as well as the termination control of an UNTIL clause. 7.8.31.3 VARYING, for the details.

7.8.31.2 Inline PERFORM

Inline PERFORM Syntax

  PERFORM
  ~~~~~~~
   [ { [ WITH TEST { BEFORE } ] { VARYING-Clause                 } } ]
     {        ~~~~ { ~~~~~~ }   { UNTIL conditional-expression-1 } }
     {             { AFTER  }     ~~~~~                            }
     {               ~~~~~                                         }
     { UNTIL EXIT|FOREVER                                          }
     { ~~~~~ ~~~~ ~~~~~~~                                          }
     { { literal-1    } TIMES                                      }
     { { identifier-1 } ~~~~~                                      }

     imperative-statement-1

[ END-PERFORM ]
  ~~~~~~~~~~~

This format of the PERFORM statement is identical in operation to the procedural PERFORM, except for the fact that the statement(s) comprising the perform scope (<imperative-statement-1>) ( Imperative Statement) are now specified in-line with the PERFORM code rather than in procedures located elsewhere within the program.

7.8.31.3 VARYING

VARYING Syntax

VARYING identifier-2 FROM { literal-2    } [ BY { literal-3    } ]
~~~~~~~              ~~~~ { identifier-3 }   ~~ { identifier-4 }
        [ UNTIL conditional-expression-1 ]
          ~~~~~
[ AFTER identifier-5 FROM { literal-4    } [ BY { literal-5    } ]
  ~~~~~              ~~~~ { identifier-6 }   ~~ { identifier-7 }
        [ UNTIL conditional-expression-2 ] ]...
          ~~~~~

The VARYING clause, available on both formats of the PERFORM statement, is a looping mechanism that allows for the specification of one or more numeric data items that will be initialized to a programmer-specified value and automatically incremented by another programmer-specified value after each loop iteration.

  1. All identifiers used in a <VARYING-Clause> must be elementary, un-edited numeric data items. All literals must be numeric literals.

  2. The following points describe the sequence of events that take place as a result of the VARYING portion of the clause:

    1. When the PERFORM begins execution, the FROM value will be moved to <identifier>.

    2. If the PERFORM specifies or implies WITH TEST BEFORE, <conditional-expression-1> will be evaluated and processing of the PERFORM will halt if the expression evaluates to TRUE. If WITH TEST BEFORE was not specified or implied, or if the conditional expression evaluated to FALSE, processing proceeds with step C.

    3. The statements within the perform scope will be executed. If a GO TO executed within the perform scope transfers control to a point outside the perform scope, processing of the PERFORM will halt.

    4. When the statements within the perform scope terminate the loop iteration, by one of:

      • allowing the flow of execution to attempt to fall past the last statement in the perform scope

      • executing an EXIT PERFORM CYCLE statement ( 7.8.18 EXIT)

      • executing an EXIT PARAGRAPH statement or EXIT SECTION statement when there is only one paragraph (or section) in the perform scope ( this option only applies to a procedural PERFORM)

      If WITH TEST AFTER was specified, control will return back to the PERFORM, where <conditional-expression-1> will be evaluated, and processing of the PERFORM will halt if the expression evaluates to TRUE. If WITH TEST AFTER was not specified, or if the conditional expression evaluated to FALSE, processing continues with the next step.

    5. The BY value, if any, will be added to <identifier-2>. If no BY is specified, it will be treated as if BY 1 had been specified.

    6. Return to step C.

  3. Most <VARYING-Clause>s have no AFTER specified. Those that do, however, are establishing a loop-within-a-loop situation where the process described above in steps (’A‘) through (’F‘) will take place from the AFTER, and those six processing steps actually replace step C of the VARYING. This “nesting” process can continue indefinitely, with each additional AFTER.

An example should really help you see this at work. Observe the following code which defines a two-dimensional (3 row by 4 column) table and a pair of numeric data items to be used to subscript references to each element of the table:

01  PERFORM-DEMO.
    05 PD-ROW             OCCURS 3 TIMES.
       10 PD-COL          OCCURS 4 TIMES
          15 PD           PIC X(1).
01  PD-Col-No             PIC 9 COMP.
01  PD-Row-No             PIC 9 COMP.

Let’s say the 3x4 “grid” defined by the above structure has these values:

A B C D
E F G H
I J K L

This code will display ABCDEFGHIJKL on the console output window:

PERFORM WITH TEST AFTER
        VARYING PD-Row-No FROM 1 BY 1 UNTIL PD-Row-No = 3
          AFTER PD-Col-No FROM 1 BY 1 UNTIL PD-Col-No = 4
    DISPLAY PD (PD-Row-No, PD-Col-No) WITH NO ADVANCING
END-PERFORM

While this code will display AEIBFJCGKDHL on the console output window:

PERFORM WITH TEST AFTER
        VARYING PD-Col-No FROM 1 BY 1 UNTIL PD-Col-No = 4
          AFTER PD-Row-No FROM 1 BY 1 UNTIL PD-Row-No = 3
    DISPLAY PD (PD-Row-No, PD-Col-No) WITH NO ADVANCING
END-PERFORM

While we’re looking at sample code, this code displays ABCEFG:

PERFORM
        VARYING PD-Row-No FROM 1 BY 1 UNTIL PD-Row-No = 3
          AFTER PD-Col-No FROM 1 BY 1 UNTIL PD-Col-No = 4
    DISPLAY PD (PD-Row-No, PD-Col-No) WITH NO ADVANCING
END-PERFORM

By removing the WITH TEST clause, the statement is now assuming WITH TEST BEFORE. Since testing now happens before the DISPLAY statement gets executed, when PD-Row-No is 3 and PD-Col-No is 4 the DISPLAY statement won’t be executed.

Most COBOL programmers, when using WITH TEST BEFORE explicitly or implicitly have developed the habit of using ‘>‘ rather than ‘=‘ on UNTIL clauses. This would make the sample code:

PERFORM
        VARYING PD-Row-No FROM 1 BY 1 UNTIL PD-Row-No > 3
          AFTER PD-Col-No FROM 1 BY 1 UNTIL PD-Col-No > 4
    DISPLAY PD (PD-Row-No, PD-Col-No) WITH NO ADVANCING
END-PERFORM

With this change, ABCDEFGHIJKL is once again displayed.

7.8.32 READ

7.8.32.1 Sequential READ

Sequential READ Syntax

  READ file-name-1 [ { NEXT|PREVIOUS } ] RECORD [ INTO identifier-1 ]
  ~~~~               { ~~~~ ~~~~~~~~ }            ~~~~
   [ { IGNORING LOCK    } ]
     { ~~~~~~~~ ~~~~    }
     { WITH [ NO ] LOCK }
     {        ~~   ~~~~ }
     { WITH KEPT LOCK   }
     {      ~~~~ ~~~~   }
     { WITH IGNORE LOCK }
     {      ~~~~~~ ~~~~ }
     { WITH WAIT        }
            ~~~~
   [ AT END imperative-statement-1 ]
        ~~~
   [ NOT AT END imperative-statement-2 ]
     ~~~    ~~~
[ END-READ ]
  ~~~~~~~~

This form of the READ statement retrieves the next (or previous) record from a file.

  1. The reserved words AT, RECORD and WITH are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The <file-name-1> file must have been defined via an FD ( 6.2.1 File/Sort-Description), not an SD.

  3. The <file-name-1> file must currently be open for INPUT ( File OPEN Modes) or I-O.

  4. If <file-name-1> is an ORGANIZATION RELATIVE ( 5.2.1.3 ORGANIZATION RELATIVE) or ORGANIZATION INDEXED ( 5.2.1.4 ORGANIZATION INDEXED) file with an ACCESS MODE RANDOM, this statement cannot be used.

  5. If <file-name-1> was specified as ACCESS MODE SEQUENTIAL, this is the only format of the READ statement that is available.

  6. If <file-name-1> is an ORGANIZATION RELATIVE ( 5.2.1.3 ORGANIZATION RELATIVE) or ORGANIZATION INDEXED ( 5.2.1.4 ORGANIZATION INDEXED) file with ACCESS MODE DYNAMIC, this statement as well as a random READ ( 7.8.32.2 Random READ) may be used.

  7. The keywords NEXT and PREVIOUS specify what “direction of travel” the reading process will take through the file. If neither is specified, NEXT is assumed.

  8. The PREVIOUS option is available only for ORGANIZATION INDEXED files.

  9. When reading any sequential (any organization) or relative file, the “next” direction refers to the physical sequence of records in the file. When reading an indexed file, the “next” and “previous” directions refer to the sequence of primary or alternate record key values in the file’s records, regardless of where the records physically occur within the file.

  10. The minimal statement READ <file-name-1> is perfectly legal according to both READ formats. For that reason, when ACCESS MODE DYNAMIC has been specified and you want to tell the GnuCOBOL compiler that this minimal statement should be treated as a sequential READ, you must add either NEXT or PREVIOUS to the statement (otherwise it will be treated as a random READ).

  11. A successful sequential READ will retrieve the next available record from <file-name-1>, in either a “next” or “previous” direction from the most-recently-read record, depending upon the use of the NEXT or PREVIOUS option. The newly-retrieved record data will be saved into the 01-level record structure(s) that immediately follow the file’s FD. If the optional INTO clause is present, a copy of the just-retrieved record will be automatically moved to <identifier-1>.

  12. When an ORGANIZATION RELATIVE file has been successfully read, the file’s RELATIVE KEY ( 5.2.1.3 ORGANIZATION RELATIVE) field will be automatically populated with the relative record number (ordinal occurrence number) of the record in the file.

  13. The optional LOCK options may be used to manually control access to the retrieved record by other programs while this program is running. 2.2.16 Record Locking, to review the various record locking behaviours.

  14. The optional AT END clause, if coded, is used to detect and react to the failure of an attempt to retrieve another record from the file due to an end-of-file (i.e. no more records) condition.

  15. The optional NOT AT END clause, if coded, will check for a file status value of 00. File Status Codes, for additional information.

7.8.32.2 Random READ

Random READ Syntax

  READ file-name-1 RECORD [ INTO identifier-1 ]
  ~~~~                      ~~~~
   [ { IGNORING LOCK    } ]
     { ~~~~~~~~ ~~~~    }
     { WITH [ NO ] LOCK }
     {        ~~   ~~~~ }
     { WITH KEPT LOCK   }
     {      ~~~~ ~~~~   }
     { WITH IGNORE LOCK }
     {      ~~~~~~ ~~~~ }
     { WITH WAIT        }
            ~~~~
   [ KEY IS identifier-2 ]
     ~~~
   [ INVALID KEY imperative-statement-1 ]
     ~~~~~~~
   [ NOT INVALID KEY imperative-statement-2 ]
     ~~~ ~~~~~~~
[ END-READ ]
  ~~~~~~~~

This form of the READ statement retrieves an arbitrary record from an ORGANIZATION RELATIVE ( 5.2.1.3 ORGANIZATION RELATIVE) or ORGANIZATION INDEXED ( 5.2.1.4 ORGANIZATION INDEXED) file.

  1. The reserved words IS, KEY (on the INVALID and NOT INVALID clauses), RECORD and WITH are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The <file-name-1> file must have been defined via an FD ( 6.2.1 File/Sort-Description), not an SD.

  3. The <file-name-1> file must currently be open for INPUT ( File OPEN Modes) or I-O.

  4. If the ACCESS MODE of <file-name-1> is SEQUENTIAL, or the ORGANIZATION of the file is any form of sequential, this format of the READ statement cannot be used.

  5. If the ACCESS MODE of <file-name-1> is RANDOM, this is the only format of the READ statement that is available.

  6. If <file-name-1> is an ORGANIZATION RELATIVE ( 5.2.1.3 ORGANIZATION RELATIVE) or ORGANIZATION INDEXED ( 5.2.1.4 ORGANIZATION INDEXED) file with ACCESS MODE DYNAMIC, this statement as well as a sequential READ ( 7.8.32.1 Sequential READ) may be used.

  7. The minimal statement READ <file-name-1> is perfectly legal according to both READ formats. For that reason, when ACCESS MODE DYNAMIC has been specified and you want to tell the GnuCOBOL compiler that this minimal statement should be treated as a random READ, you must omit the NEXT or PREVIOUS available to the sequential format of the READ statement to ensure the statement will be treated as a random READ.

  8. The optional KEY clause tells the compiler how a record is to be located in the file.

    If the KEY clause is absent, and the file is

    • ORGANIZATION RELATIVE

      the contents of the field declared as the file’s RELATIVE KEY will be used to identify a record

    • ORGANIZATION INDEXED

      the contents of the field declared as the file’s RECORD KEY will be used to identify a record.

    If the KEY clause is specified, and the file is

    • ORGANIZATION RELATIVE

      the contents of <identifier-2> will be used as the relative record number of the record to be accessed. <identifier-2> need not be the RELATIVE KEY ( 5.2.1.3 ORGANIZATION RELATIVE) field of the file (although it could be if you wish).

    • ORGANIZATION INDEXED

      <identifier-2> must be the RECORD KEY ( 5.2.1.4 ORGANIZATION INDEXED) or one of the file’s ALTERNATE RECORD KEY fields (if any). The current contents of that field will identify the record to be accessed. If an alternate record key is used, and that key allows duplicate values, the record accessed will be the first one having that key value.

  9. Once read from the file, the newly-retrieved record data will be saved into the 01-level record structure(s) that immediately follow the file’s FD. If the optional INTO clause is present, a copy of the just-retrieved record will be automatically moved to <identifier-1>.

  10. When an ORGANIZATION RELATIVE file has been successfully read, the file’s RELATIVE KEY ( 5.2.1.3 ORGANIZATION RELATIVE) field will be automatically populated with the relative record number (ordinal occurrence number) of the record in the file.

  11. The optional LOCK options may be used to manually control access to the retrieved record by other programs while this program is running. 2.2.16 Record Locking, to review the various record locking behaviours.

  12. The optional INVALID KEY and NOT INVALID KEY clauses may be used to detect and react to the failure or success, respectively, by detecting non-zero (typically 23 = key not found = record not found) and 00 file status codes, respectively. File Status Codes, for additional information.

7.8.33 READY TRACE

READY TRACE Syntax

READY TRACE
~~~~~ ~~~~~

The READY TRACE statement turns procedure or procedure-and-statement tracing on.

  1. In order for this statement to be functional, tracing code must have been generated into the compiled program using either the -ftrace switch (procedures only) or -ftraceall switch (procedures and statements).

  2. Tracing may be turned off at any point by executing the RESET TRACE statement ( 7.8.35 RESET TRACE).

  3. The run-time environment variable ( 10.2.3 Run Time Environment Variables) provides another way to control tracing. If this environment variable is set to a value of ‘Y‘ prior to the start of program execution, tracing starts at the point the program begins execution, as if READY TRACE were the first executed statement.

7.8.34 RELEASE

RELEASE Syntax

RELEASE record-name-1 [ FROM { literal-1    } ]
~~~~~~~                 ~~~~ { identifier-1 }

The RELEASE statement adds a new record to a sort work file.

  1. This statement is valid only within the INPUT PROCEDURE of a file-based SORT statement ( 7.8.42.1 File-Based SORT).

  2. The specified <record-name-1> must be a record defined to the sort description (SD ( 6.2.1 File/Sort-Description)) of the sort work file being processed by the current sort.

  3. The optional FROM clause will cause <literal-1> or <identifier-1> to be automatically moved into <record-name-1> prior to writing <record-name-1>’s contents to the <file-name-1>. If this clause is not specified, it is the programmer’s responsibility to populate <record-name-1> with the desired data prior to executing the RELEASE.

7.8.35 RESET TRACE

RESET TRACE Syntax

RESET TRACE
~~~~~ ~~~~~

The RESET TRACE statement turns procedure or procedure-and-statement tracing off.

  1. By default, procedure and procedure-and-statement tracing is off as programs begin execution. The READY TRACE statement ( 7.8.33 READY TRACE) can be used to turn tracing on.

  2. In order for this statement to be functional, tracing code must have been generated into the compiled program using either the -ftrace switch (procedures only) or -ftraceall switch (procedures and statements).

  3. The run-time environment variable ( 10.2.3 Run Time Environment Variables) provides another way to control tracing. If this environment variable is set to a value of ‘Y‘ prior to the start of program execution, tracing started at the point the program begins execution, as if READY TRACE were the first executed statement. The RESET TRACE statement, if executed, will then turn off tracing.

7.8.36 RETURN

RETURN Syntax

  RETURN sort-file-name-1 RECORD
  ~~~~~~
   [ INTO identifier-1 ]
     ~~~~
     AT END imperative-statement-1
        ~~~
   [ NOT AT END imperative-statement-2 ]
     ~~~    ~~~
[ END-RETURN ]
  ~~~~~~~~~~

The RETURN statement reads a record from a sort or merge work file.

  1. The reserved words AT and RECORD are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The RETURN statement is valid only within the OUTPUT PROCEDURE of a file-based SORT ( 7.8.42.1 File-Based SORT) or a MERGE statement ( 7.8.27 MERGE) statement.

  3. The <sort-file-name-1> file must be a sort- or merge work file defined with a SD ( 6.2.1 File/Sort-Description), not an FD.

  4. A successful RETURN will retrieve the next available record from <sort-file-name-1>. The newly-retrieved record data will be saved into the 01-level record structure(s) that immediately follow the file’s SD. If the optional INTO clause is present, a copy of the just-retrieved record will be automatically moved to <identifier-1>.

  5. The mandatory AT END clause is used to detect and react to the failure of an attempt to retrieve another record from the file due to an end-of-file (i.e. no more records) condition.

  6. The optional NOT AT END clause, if coded, will check checking for a file status value of 00. File Status Codes, for additional information.

7.8.37 REWRITE

REWRITE Syntax

  REWRITE record-name-1
  ~~~~~~~
     [ FROM { literal-1    } ]
       ~~~~ { identifier-1 }

     [ WITH [ NO ] LOCK ]
              ~~   ~~~~
     [ INVALID KEY imperative-statement-1 ]
       ~~~~~~~
     [ NOT INVALID KEY imperative-statement-2 ]
       ~~~ ~~~~~~~
[ END-REWRITE ]
  ~~~~~~~~~~~

The REWRITE statement replaces a logical record on a disk file.

  1. The reserved words KEY and WITH are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The <record-name-1> specified on the statement must be defined as an 01-level record subordinate to the File Description (FD ( 6.2.1 File/Sort-Description)) of a file that is currently open for I-O ( File OPEN Modes).

  3. The optional FROM clause will cause <literal-1> or <identifier-1> to be automatically moved into <record-name-1> prior to writing <record-name-1>’s contents to the <file-name-1>. If this clause is not specified, it is the programmer’s responsibility to populate <record-name-1> with the desired data prior to executing the REWRITE.

  4. This statement may not be used with ORGANIZATION LINE SEQUENTIAL ( 5.2.1.2 ORGANIZATION LINE SEQUENTIAL) files.

  5. Rewriting a record does not cause the contents of the file to be physically updated until the next block of the file is read, a COMMIT ( 7.8.8 COMMIT) or UNLOCK statement ( 7.8.50 UNLOCK) is issued or that file is closed.

  6. If the file has ORGANIZATION SEQUENTIAL ( 5.2.1.1 ORGANIZATION SEQUENTIAL):

    1. The record to be rewritten will be the one retrieved by the most-recently executed READ ( 7.8.32 READ) of the file.

    2. If the FD of the file contains the RECORD CONTAINS or RECORD IS VARYING clause, and that clause allows the record size to vary, the size of <record-name-1> cannot be altered.

  7. If the file has ORGANIZATION RELATIVE ( 5.2.1.3 ORGANIZATION RELATIVE) or ORGANIZATION INDEXED ( 5.2.1.4 ORGANIZATION INDEXED):

    1. If the file has ACCESS MODE SEQUENTIAL, the record to be rewritten will be the one retrieved by the most-recently executed READ of the file. If the file has ACCESS MODE RANDOM or ACCESS MODE DYNAMIC, no READ is required before a record may be rewritten — the RELATIVE KEY or RECORD KEY definition for the file, respectively, will specify the record to be updated.

    2. If the FD of the file contains the RECORD CONTAINS or RECORD IS VARYING clause, and that clause allows the record size to vary, the size can be altered.

  8. The optional LOCK options may be used to manually control access to the re-written record by other programs while this program is running. 2.2.16 Record Locking, to review the various record locking behaviours.

  9. The optional INVALID KEY and NOT INVALID KEY clauses may be used to detect and react to the failure or success, respectively, by detecting non-zero (typically 23 = key not found = record not found) and 00 file status codes, respectively. File Status Codes, for additional information.

7.8.38 ROLLBACK

ROLLBACK Syntax

ROLLBACK
~~~~~~~~

The ROLLBACK statement has the same effect as if an UNLOCK statement ( 7.8.50 UNLOCK) were executed against every open file in the program.

  1. All locks currently being held for all open files will be released.

  2. 2.2.16 Record Locking, to review the various record locking behaviours.

7.8.40 SEARCH ALL

SEARCH ALL Syntax

  SEARCH ALL table-name-1
  ~~~~~~ ~~~
     [ AT END imperative-statement-1 ]
          ~~~
       WHEN conditional-expression-1 imperative-statement-2
       ~~~~
[ END-SEARCH ]
  ~~~~~~~~~~

The SEARCH ALL statement performs a binary, or half-interval, search against a sorted table. This is generally significantly faster than performing a sequential SEARCH of a table, especially if the table contains a large number of entries.

  1. The reserved word AT is optional and may be omitted. The presence or absence of this word has no effect upon the program.

  2. To be eligible for searching via SEARCH ALL:

    1. The OCCURS clause of <table-name-1> must contain the following elements:

      • An INDEXED BY entry to define an implicit search index data item with a USAGE ( 6.9.61 USAGE) of INDEX.

      • An ASCENDING KEY or DESCENDING KEY clause to specify the field within the table by which all entries in the table are sorted.

    2. Just because the table has one or more KEY clauses doesn’t mean the data is actually in that sequence in the table — the actual sequence of the data must agree with the KEY clause(s)! A table-based SORT ( 7.8.42.2 Table SORT) can prove very useful in this regard.

    3. No two records in the table may have the same KEY field values. If the table has multiple KEY definitions, then no two records in the table may have the same combination of KEY field values.

  3. If rule A is violated, the compiler will reject the SEARCH ALL. If rules B and/or C are violated, there will be no message issued by the compiler, but the run-time results of a SEARCH ALL against the table will probably be incorrect.

  4. The <conditional-expression-1> should involve the KEY field(s), using the search index (the table’s INDEXED BY index name) as a subscript.

  5. The function of the single, mandatory, WHEN clause is to compare the key field(s) of the table, as indexed by the search index data item, against whatever literal and/or identifier values you are comparing the key field(s) to in the <conditional-expression-1> in order to locate the desired entry in the table. The search index will be automatically varied in a manner designed to require the minimum number of tests.

  6. The internal processing of the SEARCH ALL statement begins by setting internal “first” and “last” pointers to the 1st and last entry locations of the table. Processing then proceeds as follows:

    1. The entry half-way between “first” and “last” is identified. We’ll call this the “current” entry, and will set its table entry location into <index-name-1>.

    2. The <conditional-expression-1> is evaluated. This comparison of the key(s) against the target literal/identifier values will have one of three possible outcomes:

      • If the key(s) and value(s) match, <imperative-statement-2> ( Imperative Statement) is executed, after which control falls through into the next statement following the SEARCH ALL.

      • If the key(s) are LESS THAN the value(s), then the table entry being searched for can only occur in the “current” to “last” range of the table, so a new “first” pointer value is set (it will be set to the “current” pointer).

      • If the key(s) are GREATER THAN the value(s), then the table entry being searched for can only occur in the “first” to “current” range of the table, so a new “last” pointer value is set (it will be set to the “current” pointer).

    3. If the new “first” and “last” pointers are different than the old “first” and “last” pointers, there’s more left to be searched, so return to step A and continue.

    4. If the new “first” and “last” pointers are the same as the old “first” and “last” pointers, the table has been exhausted and the entry being searched for cannot be found; <imperative-statement-1> is executed, after which control falls through into the next statement following the SEARCH ALL. If there is no AT END clause coded, control simply falls into the next statement following the SEARCH ALL.

  7. The net effect of the above algorithm is that only a fraction of the number of elements in the table need ever be tested in order to decide whether or not a particular entry exists. This is because the half the remaining entries in the table are discarded each time an entry is checked.

  8. Computer scientists will compare the two techniques implemented by the SEARCH and SEARCH ALL statements as follows:

  9. When searching a table with N entries, a sequential search will need an average of N/2 tests and a worst case of N tests in order to find an entry and N tests to identify that an entry doesn’t exist.

  10. When searching a table with N entries, a binary search will need a worst-case of log2(N) tests in order to find an entry and log2(N) tests to identify that an entry doesn’t exist (N = the number of entries in the table), where log2 is the base-2 logarithm function.

Here’s a more practical view of the difference. Let’s say that a table has 1,000 entries in it. With a sequential search, on average, you’ll have to check 500 of them to find an entry and you’ll have to look at all 1,000 of them to find that an entry doesn’t exist.

With a binary search, express the number of entries as a binary number (1,000 = 1111101000), count the number of digits in the result (which is, essentially, what a logarithm is, when rounded up to the next integer — the number of digits a decimal number would have if expressed in the logarithm’s number base). In this case, we end up with 10 — that is the worst-case number of tests required to find an entry or to identify that it doesn’t exist. That’s quite an improvement!

7.8.41 SET

7.8.41.1 SET ENVIRONMENT

SET ENVIRONMENT Syntax

SET ENVIRONMENT { literal-1    } TO { literal-2    }
~~~ ~~~~~~~~~~~ { identifier-1 } ~~ { identifier-2 }

The SET ENVIRONMENT statement provides a straight-forward means of setting environment values from within a program.

  1. The value of <literal-1> or <identifier-1> specifies the name of the environment variable to set.

  2. The value of <literal-2> or <identifier-2> specifies the value to be assigned to the environment variable.

  3. Environment variables created or changed from within GnuCOBOL programs will be available to any sub-shell processes spawned by that program (i.e. CALL "SYSTEM") but will not be known to the shell or console window that started the GnuCOBOL program.

This is a much simpler and more readable means of setting environment variables than by using the DISPLAY UPON ENVIRONMENT-NAME statement ( 7.8.12.3 DISPLAY UPON ENVIRONMENT-NAME). For example, these two code sequences produce identical results:

DISPLAY "VARNAME" UPON ENVIRONMENT-NAME
DISPLAY "VALUE" UPON ENVIRONMENT-VALUE

SET ENVIRONMENT "VARNAME" TO "VALUE"

7.8.41.2 SET Program-Pointer

SET Program-Pointer Syntax

SET program-pointer-1 TO ENTRY { literal-1    }
~~~                   ~~ ~~~~~ { identifier-1 }

The SET <Program-Pointer> statement allows you to retrieve the address of a procedure division code module — specifically the PROGRAM-ID, FUNCTION-ID or an entry-point established via the ENTRY statement ( 7.8.14 ENTRY).

  1. The USAGE ( 6.9.61 USAGE) of <program-pointer-1> must be PROGRAM-POINTER.

  2. The <literal-1> or <identifier-1> value specified must name a primary entry-point name (PROGRAM-ID of a subroutine or FUNCTION-ID of a user-defined function) or an alternate entry-point defined via an ENTRY statement within a subprogram.

  3. Once the address of a procedure division code area has been acquired in this way, the address could be passed to a subroutine (usually written in C) for whatever use it needs it for. For examples of PROGRAM-POINTERs at work, see the discussions of the CBL_ERROR_PROC built-in system subroutine ( 8.2.25 CBL_ERROR_PROC) and CBL_EXIT_PROC built-in system subroutine ( 8.2.26 CBL_EXIT_PROC).

7.8.41.3 SET ADDRESS

SET ADDRESS Syntax

SET [ ADDRESS OF ] { pointer-name-1 }...
~~~   ~~~~~~~ ~~   { identifier-1   }

    TO [ ADDRESS OF ]  { pointer-name-2 }
    ~~   ~~~~~~~ ~~    { identifier-2   }

The SET ADDRESS statement can be used to work with the addresses of data items rather than their contents.

  1. When the ADDRESS OF clause is used before the TO you will be using this statement to alter the address of a linkage section or BASED ( 6.9.8 BASED) data item. Without that clause you will be assigning an address to one or more data items whose USAGE ( 6.9.61 USAGE) is POINTER.

  2. When the ADDRESS OF clause is used after the TO, this statement will be identifying the address of <identifier-2> as the address to be assigned to <identifier-1> or stored in <pointer-name-1>.

  3. If the ADDRESS OF clause is absent after the TO, the contents of <pointer-name-2> will serve as the address to be assigned.

7.8.41.4 SET Index

SET Index Syntax

SET index-name-1 TO { literal-1    }
~~~              ~~ { identifier-2 }

This statement assigns a value to a USAGE INDEX data item.

  1. Either the USAGE ( 6.9.61 USAGE) of <index-name-1> should be INDEX, or <index-name-1> must be identified in a table INDEXED BY clause.

7.8.41.5 SET UP/DOWN

SET UP/DOWN Syntax

SET identifier-1 { UP   } BY [ LENGTH OF ] { literal-1    }
~~~              { ~~   } ~~   ~~~~~~ ~~   { identifier-2 }
                 { DOWN }
                   ~~~~

Use this statement to increment or decrement the value of an index or pointer by a specified amount.

  1. The USAGE ( 6.9.61 USAGE) of <identifier-1> must be INDEX, POINTER or PROGRAM-POINTER.

  2. The typical usage when <identifier-1> is a USAGE INDEX data item is to increment its value UP or DOWN by 1, since an index is usually being used to sequentially walk through the elements of a table.

7.8.41.6 SET Condition Name

SET Condition Name Syntax

SET condition-name-1... TO { TRUE  }
~~~                     ~~ { ~~~~  }
                           { FALSE }
                             ~~~~~

The SET <Condition Name> statement provides one method of specifying the TRUE / FALSE value of a level-88 condition name.

  1. By setting the specified <condition-name-1>(s) to a TRUE or FALSE value, you will actually be assigning a value to the parent data item(s) to which the condition name data item(s) is(are) subordinate to.

  2. When specifying TRUE, the value assigned to each parent data item will be the first value specified on the condition name’s VALUE clause.

  3. When specifying FALSE, the value assigned to each parent data item will be the value specified for the FALSE clause of the condition name’s definition; if any <condition-name-1> occurrence lacks a FALSE clause, the SET statement will be rejected by the compiler.

7.8.41.7 SET Switch

SET Switch Syntax

SET mnemonic-name-1... TO { ON  }
~~~                    ~~ { ~~  }
                          { OFF }
                            ~~~

This form of the SET statement is used to turn switches on or off.

  1. Switches are defined using the SPECIAL-NAMES ( 5.1.3 SPECIAL-NAMES) paragraph.

  2. Switches may be tested via the IF statement ( 7.8.23 IF) and a Switch-Status Condition. 2.2.8 Switch-Status Conditions, for more information.

7.8.41.8 SET ATTRIBUTE

SET ATTRIBUTE Syntax

SET identifier-1 ATTRIBUTE { { BELL          } { ON  }...
~~~              ~~~~~~~~~   { ~~~~          } { ~~  }
                             { BLINK         } { OFF }
                             { ~~~~~         }   ~~~
                             { HIGHLIGHT     }
                             { ~~~~~~~~~     }
                             { LEFTLINE      }
                             { ~~~~~~~~      }
                             { LOWLIGHT      }
                             { ~~~~~~~~      }
                             { OVERLINE      }
                             { ~~~~~~~~      }
                             { REVERSE-VIDEO }
                             { ~~~~~~~~~~~~~ }
                             { UNDERLINE     }
                               ~~~~~~~~~

The SET ATTRIBUTE statement may be used to modify one or more attributes of a screen section data item at run-time.

  1. When making an attribute change to <identifier-1>, the change will not become visible on the screen until the screen section data item containing <identifier-1> is next accepted (if <identifier-1> is an input field) or is next displayed (if <identifier-1> is not an input field).

  2. The attributes shown in the syntax diagram are the only ones that may be altered by this statement. 6.9 Data Description Clauses, for information on their usage.

7.8.41.9 SET LAST EXCEPTION

SET ATTRIBUTE Syntax

SET LAST EXCEPTION TO { OFF }
~~~ ~~~~ ~~~~~~~~~ ~~   ~~~

The SET LAST EXCEPTION statement will set the last program exception status to indicate no exception.

  1. The predefined object reference EXCEPTION-OBJECT is set to null, and the last exception status is set to indicate no exception.

  2. This action resets the global exception object completely (FUNCTION EXCEPTION-{FILE, LOCATION, STATEMENT, STATUS } ), and will not show anything afterwards), no matter what the last exception was (such as a divide by zero). Use with care.

7.8.42 SORT

7.8.42.1 File-Based SORT

File-Based SORT Syntax

SORT sort-file-1
~~~~
   { ON { ASCENDING  } KEY identifier-1... }...
        { ~~~~~~~~~  }
        { DESCENDING }
          ~~~~~~~~~~
   [ WITH DUPLICATES IN ORDER ]
          ~~~~~~~~~~
   [ COLLATING SEQUENCE IS alphabet-name-1 ]
     ~~~~~~~~~

   { INPUT PROCEDURE IS procedure-name-1      }
   { ~~~~~~ ~~~~~~~~~                         }
   {       [ THRU|THROUGH procedure-name-2 ]  }
   {         ~~~~ ~~~~~~~                     }
   { USING file-name-1...                     }
     ~~~~~
   { OUTPUT PROCEDURE IS procedure-name-3     }
   { ~~~~~~ ~~~~~~~~~                         }
   {       [ THRU|THROUGH procedure-name-4 ]  }
   {         ~~~~ ~~~~~~~                     }
   { GIVING file-name-2...                    }
     ~~~~~~

The DUPLICATES clause is syntactically recognized but is otherwise non-functional. This format of the SORT statement is designed to sort large volumes of data according to one or more key fields.

  1. The reserved words IN, IS, KEY, ON, ORDER, SEQUENCE and WITH are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The reserved words THRU and THROUGH are interchangeable.

  3. GnuCOBOL always behaves as if the WITH DUPLICATES IN ORDER clause is specified, even if it isn’t.

    While any COBOL implementation’s sort or merge facilities guarantee that records with duplicate key values will be in proper sequence with regard to other records with different key values, they generally make no promises as to the resulting relative sequence of records having duplicate key values with one another.

    Some COBOL implementations provide this optional clause to force their sort and merge facilities to retain duplicate key-value records in their original input sequence, relative to one another.

  4. The <sort-file-1> named on the SORT statement must be defined using a sort description (SD ( 6.2.1 File/Sort-Description)). This file is referred to in the remainder of this discussion as the sort work file.

  5. If specified, <file-name-1> and <file-name-2> must reference ORGANIZATION LINE SEQUENTIAL ( 5.2.1.2 ORGANIZATION LINE SEQUENTIAL) or ORGANIZATION SEQUENTIAL ( 5.2.1.1 ORGANIZATION SEQUENTIAL) files. These files must be defined using a file description (FD ( 6.2.1 File/Sort-Description)). The same file(s) may be used for <file-name-1> and <file-name-2>.

  6. The <identifier-1> … field(s) must be defined as field(s) within a record of <sort-file-1>.

  7. A sort work file is never opened or closed.

  8. The sorting process works in three stages — the Input Stage, the Sort Stage and the Output Stage.

  9. The following points pertain to the Input Stage:

    1. The data to be sorted is loaded into the sort work file either by copying the entire contents of the file(s) named on the USING clause (done automatically by the sort) or by utilizing an input procedure.

    2. When USING is specified, none of the <file-name-1> files may be open at the time the SORT statement is executed.

    3. When an input procedure is used, the procedure(s) specified on the INPUT PROCEDURE clause will be invoked as if by a procedural PERFORM statement ( 7.8.31.1 Procedural PERFORM) with no VARYING, TIMES or UNTIL options specified. Records will be loaded into the sort work file — one at a time — within the input procedure using the RELEASE statement ( 7.8.34 RELEASE). This, by the way, is how you could sort the contents of relative or indexed files.

      A GO TO statement ( 7.8.22 GO TO) that transfers control out of the input procedure will terminate the SORT statement but allows the program to continue executing from the point where the GO TO statement transferred control to. Once an input procedure has been “aborted” using a GO TO it cannot be resumed, and the contents of the sort work file are lost. You may, however, re-execute the SORT statement itself. [1]

      An input procedure should be terminated in the same way a procedural PERFORM statement would be.

      Neither a another file-based SORT statement nor a MERGE statement may be executed within the input procedure unless those statements utilize a different sort or merge work file.

    4. Once the input procedure terminates, the input phase is complete.

    5. As data is loaded into the sort work file, it is actually being buffered in dynamically-allocated memory. Only if the amount of data to be sorted exceeds the amount of available sort memory (128 MB) will actual disk files be allocated and utilized. There is a run-time environment variable ( 10.2.3 Run Time Environment Variables) that you may use to allocate more or less memory to the sorting process.

  10. The following points pertain to the Sort Stage:

    1. The sort will take place by arranging the data records in the sequence defined by the KEY specification(s) on the SORT statement according to the COLLATING SEQUENCE specified on the SORT (if any) or — if none was defined — the PROGRAM COLLATING SEQUENCE ( 5.1.2 OBJECT-COMPUTER). Keys may be any supported data type and USAGE ( 6.9.61 USAGE) except for level-78 or level-88 data items.

    2. For example, let’s assume we’re sorting a series of financial transactions. The SORT statement might look like this:

      SORT Sort-File
          ASCENDING  KEY Transaction-Date
          ASCENDING  KEY Account-Number
          DESCENDING KEY Transaction-Amount
      

      The effect of this statement will be to sort all transactions into ascending order of the date the transaction took place (oldest first, newest last). Unless the business running this program is going out of business, there are most-likely many transactions for any given date. Therefore, within each grouping of transactions all with the same date, transactions will be sub-sorted into ascending sequence of the account number the transactions apply to. Since it’s quite possible there might be multiple transactions for an account on any given date, a third level sub-sort will arrange all transactions for the same account on the same date into descending sequence of the actual amount of the transaction (largest first, smallest last). If two or more transactions of $100.00 were recorded for account #12345 on the 31st of August 2009, those transactions will be retained in the order in which they were loaded into the sort work file.

    3. Should disk work files be necessary due to the amount of data being sorted, they will be automatically allocated to disk in a folder defined by the run-time environment variable, run-time environment variable or run-time environment variable run-time environment variables ( 10.2.3 Run Time Environment Variables) (checked for existence in that sequence). These disk files will be automatically purged upon SORT termination or program execution termination (normal or otherwise).

  11. The following points pertain to the Output Stage:

    1. Once the sort stage is complete, a copy of the sorted data will be written to each <file-name-2> if the GIVING clause was specified. None of the <file-name-2> files can be open at the time the sort is executed.

    2. When an output procedure is used, the procedure(s) specified on the OUTPUT PROCEDURE clause will be invoked as if by a procedural PERFORM statement ( 7.8.31.1 Procedural PERFORM) with no VARYING, TIMES or UNTIL options specified. Records will be retrieved from the sort work file — one at a time — within the output procedure using the RETURN statement ( 7.8.36 RETURN).

      A GO TO statement ( 7.8.22 GO TO) that transfers control out of the output procedure will terminate the SORT statement but allows the program to continue executing from the point where the GO TO statement transferred control to. Once an output procedure has been “aborted” using a GO TO it cannot be resumed, and the contents of the sort work file are lost. You may, however, re-execute the SORT statement itself. USING A GO TO statement [2]

      An output procedure should be terminated in the same way a procedural PERFORM statement would be.

      Neither a another file-based SORT statement nor a MERGE statement may be executed within the output procedure unless those statements utilize a different sort or merge work file.

    3. Once the output procedure terminates, the sort is complete.

7.8.42.2 Table SORT

Table SORT Syntax

SORT table-name-1
~~~~
   { ON { ASCENDING  } KEY identifier-1... }...
        { ~~~~~~~~~  }
        { DESCENDING }
          ~~~~~~~~~~
   [ WITH DUPLICATES IN ORDER ]
          ~~~~~~~~~~
   [ COLLATING SEQUENCE IS alphabet-name-1 ]
     ~~~~~~~~~

The DUPLICATES clause is syntactically recognized but is otherwise non-functional. This format of the SORT statement sorts relatively small quantities of data — namely data contained in a data division table — according to one or more key fields.

  1. The reserved words IN, IS, KEY, ON, ORDER, SEQUENCE and WITH are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. GnuCOBOL always behaves as if the WITH DUPLICATES IN ORDER clause is specified, even if it isn’t.

    While any COBOL implementation’s sort or merge facilities guarantee that records with duplicate key values will be in proper sequence with regard to other records with different key values, they generally make no promises as to the resulting relative sequence of records having duplicate key values with one another.

    Some COBOL implementations provide this optional clause to force their sort and merge facilities to retain duplicate key-value records in their original input sequence, relative to one another.

  3. The <table-name-1> data item must be a table defined in any data division section except the report or screen sections.

  4. The data within <table-name-1> will be sorted in-place (i.e. no sort file is required).

  5. The sort will take place by rearranging the data in <table-name-1> into the sequence defined by the KEY specification(s) on the SORT statement, according to the COLLATING SEQUENCE specified on the SORT (if any) or — if none was defined — the PROGRAM COLLATING SEQUENCE ( 5.1.2 OBJECT-COMPUTER). Keys may be any supported data type and USAGE ( 6.9.61 USAGE) except for level-78 or level-88 data items.

  6. If you are sorting <table-name-1> for the purpose of preparing the table for use with a SEARCH ALL statement ( 7.8.40 SEARCH ALL), care must be taken that the KEY specifications on the SORT agree with those in the table’s definition.

  7. Although the specification of one or more KEY clauses is optional, currently, a table sort with no KEY specification(s) made on the SORT statement is unsupported by GnuCOBOL and will be rejected by the compiler.

7.8.43 START

START Syntax

  START file-name-1
  ~~~~~
    [ { FIRST                                                    } ]
      { ~~~~~                                                    }
      { LAST                                                     }
      { ~~~~                                                     }
      { KEY { IS EQUAL TO | IS = | EQUALS         } identifier-1 }
        ~~~ {    ~~~~~             ~~~~~~         }
            { IS GREATER THAN | IS >              }
            {    ~~~~~~~                          }
            { IS GREATER THAN OR EQUAL TO | IS >= }
            {    ~~~~~~~      ~~ ~~~~~            }
            { IS NOT LESS THAN                    }
            {    ~~~ ~~~~                         }
            { IS LESS THAN | IS <                 }
            {    ~~~~                             }
            { IS LESS THAN OR EQUAL TO | IS <=    }
            {    ~~~~      ~~ ~~~~~               }
            { IS NOT GREATER THAN                 }
                 ~~~ ~~~~~~~

       [ WITH {SIZE}   arithmetic-expression ]
               ~~~~
       [      {LENGTH} arithmetic-expression ]
               ~~~~~~

   [ INVALID KEY imperative-statement-1 ]
     ~~~~~~~
   [ NOT INVALID KEY imperative-statement-2 ]
     ~~~ ~~~~~~~
[ END-START ]
  ~~~~~~~~~

The START statement defines the logical starting point within a relative or indexed file for subsequent sequential read operations. It positions an internal logical record pointer to a particular record in the file, but does not actually transfer any of that record’s data into the record buffer.

  1. The reserved words IS, THAN and TO are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. To use this statement, <file-name-1> must be an ORGANIZATION RELATIVE ( 5.2.1.3 ORGANIZATION RELATIVE) or ORGANIZATION INDEXED ( 5.2.1.4 ORGANIZATION INDEXED) file that must have been defined with an ACCESS MODE DYNAMIC or ACCESS MODE SEQUENTIAL in its SELECT statement ( 5.2.1 SELECT).

  3. At the time this statement is executed, <file-name-1> must be open in either INPUT or I-O ( File OPEN Modes) mode.

  4. If <file-name-1> is a relative file, <identifier-1> must be the defined RELATIVE KEY of the file.

  5. If <file-name-1> is an indexed file, <identifier-1> must be the defined RECORD KEY of the file or any of the ALTERNATE RECORD KEY fields for the file.

  6. If no FIRST, LAST or KEY clause is specified, KEY IS EQUAL TO <xxx> will be assumed, where <xxx> is the defined RELATIVE KEY of (if <file-name-1> is a relative file) or the defined RECORD KEY (if <file-name-1> is an indexed file).

  7. After successful execution of a START statement, the internal logical record pointer into the <file-name-1> data will be positioned to the record which satisfied the actual or implied FIRST, LAST or KEY clause specification, as follows:

    • FIRST

      the logical record pointer will point to the first record in the file.

    • LAST

      the logical record pointer will point to the last record in the file.

    • KEY

      (specified or implied), and the relation used is. Warning: Later versions of the compiler may well not use implied, so always specify it and it makes the code easier to read any way.

    • SIZE

      WITH SIZE or LENGTH arithmetic-expression specifies the number of characters in the key to be used in the positioning process.

    • LENGTH

      WITH LENGTH or SIZE arithmetic-expression specifies the number of characters in the key to be used in the positioning process.

      SIZE and LENGTH are interchangeable and mean exactly the same.

      • EQUAL TO, GREATER THAN or GREATER THAN OR EQUAL TO (or equivalent)

        the logical record pointer will be specified to the first record satisfying the relation condition; to identify this record. The file’s contents are searched in a first-to-last (in sequence of the key implied by the KEY clause), provided the relation is

      • LESS THAN, LESS THAN OR EQUAL TO or NOT GREATER THAN (or equivalent)

        the logical record pointer will be specified to the last record satisfying the relation condition; to identify this record. The file’s contents are searched in a last-to-first (in sequence of the key implied by the KEY clause)

    The next sequential READ statement will read the record that is pointed to by the logical record pointer.

  8. The optional INVALID KEY and NOT INVALID KEY clauses may be used to detect and react to the failure or success, respectively, by detecting non-zero (typically 23 = key not found = record not found) and 00 file status codes, respectively. File Status Codes, for additional information.

7.8.44 STOP

STOP Syntax

STOP { RUN [ { RETURNING|GIVING { literal-1    }           } ] }
~~~~ { ~~~   { ~~~~~~~~~ ~~~~~~ { identifier-1 }           }   }
     {       {                                             }   }
     {       { WITH { ERROR  } STATUS [ { literal-2    } ] }   }
     {       {      { ~~~~~  }          { identifier-2 }   }   }
     {       {      { NORMAL }                             }   }
     {                ~~~~~~                                   }
     { literal-3                                               }

The STOP statement suspends program execution. Some options will allow program execution to resume while others return control to the operating system.

  1. The reserved words STATUS and WITH are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The reserved words RETURNING and GIVING are interchangeable.

  3. The RUN clause halts the program without displaying any special message to that effect.

  4. The <literal-3> clause displays the specified text on the SYSOUT/STDOUT device, waits for the user to press the Enter key and then — once the key has been pressed — allows the program to continue execution.

  5. The optional RETURNING clause provides the opportunity to return a numeric value to the operating system (an exit status). The manner in which the exit status may be interrogated by the operating system varies, but Windows can use %ERRORLEVEL% to query the exit status while Unix shells such as sh, bash and ksh can query the exit status as $?. Other Unix shells may have different ways to access return code values.

  6. The STATUS clause provides another means of returning an exit status. Using the STATUS clause is functionally equivalent to using the RETURNING clause.

  7. Using the STATUS clause without a <literal-2> or <identifier-2> will return an exit status of 0 if the NORMAL keyword is used or a 1 if ERROR was specified.

  8. Your program will always return an exit status, even if no RETURNING or STATUS clause is specified. In the absence of the use of these clauses, the value in the RETURN-CODE special register ( 7.7 Special Registers) at the time the STOP statement is executed will be used as the exit status.

  9. Any programmer-defined exit procedure (established via the CBL_EXIT_PROC built-in system subroutine ( 8.2.26 CBL_EXIT_PROC)) will be executed by STOP RUN, but not by STOP <literal-3>.

  10. Valid return code values can be in the range -2147483648 to +2147483647.

  11. The three code snippets below are all equivalent. They show different ways in which a GnuCOBOL program may be coded to pass an exit status value of 16 back to the operating system and then halt.

    1. STOP RUN RETURNING 16
      
    2. MOVE 16 TO RETURN-CODE
      STOP RUN
      
    3. STOP RUN WITH ERROR STATUS 16
      

7.8.45 STRING

STRING Syntax

  STRING
  ~~~~~~
     { { literal-1    } [ DELIMITED BY { SIZE         } ] }...
       { identifier-1 }   ~~~~~~~~~    { ~~~~         }
                                       { literal-2    }
                                       { identifier-2 }
       INTO identifier-3
       ~~~~
     [ WITH POINTER identifier-4 ]
            ~~~~~~~
     [ ON OVERFLOW imperative-statement-1 ]
          ~~~~~~~~
     [ NOT ON OVERFLOW imperative-statement-2 ]
       ~~~    ~~~~~~~~
[ END-STRING ]
  ~~~~~~~~~~

The STRING statement is used to concatenate all or a part of one or more strings together, forming a new string.

  1. The reserved words BY, ON and WITH are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. All literals and identifiers (except for <identifier-4>) must be explicitly or implicitly defined with a USAGE ( 6.9.61 USAGE) of DISPLAY. Any of the identifiers may be group items.

  3. The POINTER data item — <identifier-4> — must be a non-edited elementary integer numeric data item with a value greater than zero.

  4. Each <literal-1> / <identifier-1> will be referred to as a source item. The receiving data item is <identifier-3>.

  5. The STRING statement’s processing is based upon a current character pointer. The initial value of the current character pointer will be the value of <identifier-4> at the time the STRING statement began execution. If no POINTER clause is coded, a value of 1 (meaning “the 1st character position”) will be assumed for the current character pointer’s initial value.

  6. For each source item, the contents of the sending item will be copied — character-by-character — into <identifier-3> at the character position specified by the current character pointer. After each character is copied, the current character pointer will be incremented by 1 so that it points to the position within <identifier-3> where the next character should be copied.

  7. The DELIMITED BY clause specifies how much of each source item will be copied into <identifier-3>. DELIMITED BY SIZE (the default if no DELIMITED BY clause is specified) causes the entire contents of the source item to be copied into <identifier-3>.

  8. Using DELIMITED BY <literal-2> or DELIMITED BY <identifier-2> causes only the contents of the source item up to but not including the character sequence specified by the literal or identifier to be copied.

  9. STRING processing will cease when one of the following occurs:

    1. The initial value of the current character pointer is less than 1 or greater than the number of characters in <identifier-3>, or…

    2. The value of the current character pointer exceeds the size of <identifier-3> at the point the STRING statement wants to copy a character into <identifier-3>, or…

    3. All sending items have been fully processed

  10. If event A occurs, <identifier-3> will remain unchanged.

  11. The occurrence of either event A or B triggers what is referred to as an overflow condition.

  12. The <identifier-3>) is neither automatically initialized (to spaces or any other value) at the start of a STRING statement nor will it be space-filled should the total number of sending item characters copied into it be less than its size. You may explicitly initialize <identifier-3> yourself via the INITIALIZE ( 7.8.24 INITIALIZE) or MOVE ( 7.8.28 MOVE) statements before executing the STRING if you wish.

  13. The optional ON OVERFLOW and NOT ON OVERFLOW clauses may be used to detect and react to the occurrence or not, respectively, of an overflow condition. 7.6.5 ON OVERFLOW + NOT ON OVERFLOW, for additional information.

7.8.46 SUBTRACT

7.8.46.1 SUBTRACT FROM

SUBTRACT FROM Syntax

  SUBTRACT { literal-1    }... FROM { identifier-2
  ~~~~~~~~ { identifier-1 }    ~~~~

         [ ROUNDED [ MODE IS { AWAY-FROM-ZERO         } ] ] }...
           ~~~~~~~   ~~~~    { ~~~~~~~~~~~~~~         }
                             { NEAREST-AWAY-FROM-ZERO }
                             { ~~~~~~~~~~~~~~~~~~~~~~ }
                             { NEAREST-EVEN           }
                             { ~~~~~~~~~~~~           }
                             { NEAREST-TOWARD-ZERO    }
                             { ~~~~~~~~~~~~~~~~~~~    }
                             { PROHIBITED             }
                             { ~~~~~~~~~~             }
                             { TOWARD-GREATER         }
                             { ~~~~~~~~~~~~~~         }
                             { TOWARD-LESSER          }
                             { ~~~~~~~~~~~~~          }
                             { TRUNCATION             }
                               ~~~~~~~~~~
    [ ON SIZE ERROR imperative-statement-1 ]
         ~~~~ ~~~~~
    [ NOT ON SIZE ERROR imperative-statement-2 ]
      ~~~    ~~~~ ~~~~~
[ END-SUBTRACT ]
  ~~~~~~~~~~~~

This format of the SUBTRACT statement generates the arithmetic sum of all arguments that appear before the FROM (<identifier-1> or <literal-1>) and subtracts that sum from each <identifier-2>.

  1. The reserved words IS and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. Both <identifier-1> and <identifier-2> must be numeric unedited data items.

  3. <literal-1> must be a numeric literal.

  4. The optional ROUNDED ( 7.6.7 ROUNDED) clause available to each <identifier-2> will control how non-integer results will be saved.

  5. The optional ON SIZE ERROR and NOT ON SIZE ERROR clauses may be used to detect and react to the failure or success, respectively, of an attempt to perform a calculation. In this case, failure is defined as being an <identifier-2> with an insufficient number of digit positions available to the left of any implied decimal point. 7.6.6 ON SIZE ERROR + NOT ON SIZE ERROR, for additional information.

7.8.46.2 SUBTRACT GIVING

SUBTRACT GIVING Syntax

  SUBTRACT { literal-1    }... FROM identifier-2
  ~~~~~~~~ { identifier-1 }    ~~~~

      GIVING { identifier-3
      ~~~~~~
         [ ROUNDED [ MODE IS { AWAY-FROM-ZERO         } ] ] }...
           ~~~~~~~   ~~~~    { ~~~~~~~~~~~~~~         }
                             { NEAREST-AWAY-FROM-ZERO }
                             { ~~~~~~~~~~~~~~~~~~~~~~ }
                             { NEAREST-EVEN           }
                             { ~~~~~~~~~~~~           }
                             { NEAREST-TOWARD-ZERO    }
                             { ~~~~~~~~~~~~~~~~~~~    }
                             { PROHIBITED             }
                             { ~~~~~~~~~~             }
                             { TOWARD-GREATER         }
                             { ~~~~~~~~~~~~~~         }
                             { TOWARD-LESSER          }
                             { ~~~~~~~~~~~~~          }
                             { TRUNCATION             }
                               ~~~~~~~~~~
    [ ON SIZE ERROR imperative-statement-1 ]
         ~~~~ ~~~~~
    [ NOT ON SIZE ERROR imperative-statement-2 ]
      ~~~    ~~~~ ~~~~~
[ END-SUBTRACT ]
  ~~~~~~~~~~~~

The SUBTRACT GIVING statement generates the arithmetic sum of all arguments that appear before the FROM (<identifier-1> or <literal-1>), subtracts that sum from the contents of <identifier-2> and then replaces the contents of the identifiers listed after the GIVING (<identifier-3>) with that result.

  1. The reserved words IS and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. Both <identifier-1> and <identifier-2> must be numeric unedited data items.

  3. <literal-1> must be a numeric literal.

  4. <identifier-3> must be a numeric (edited or unedited) data item.

  5. The optional ROUNDED ( 7.6.7 ROUNDED) clause available to each <identifier-2> will control how non-integer results will be saved.

  6. The optional ON SIZE ERROR and NOT ON SIZE ERROR clauses may be used to detect and react to the failure or success, respectively, of an attempt to perform a calculation. In this case, failure is defined as being an <identifier-2> with an insufficient number of digit positions available to the left of any implied decimal point. 7.6.6 ON SIZE ERROR + NOT ON SIZE ERROR, for additional information.

7.8.46.3 SUBTRACT CORRESPONDING

SUBTRACT CORRESPONDING Syntax

  SUBTRACT CORRESPONDING identifier-1 FROM identifier-2
  ~~~~~~~~                            ~~~~
    [ ROUNDED [ MODE IS { AWAY-FROM-ZERO         } ] ]
      ~~~~~~~   ~~~~    { ~~~~~~~~~~~~~~         }
                        { NEAREST-AWAY-FROM-ZERO }
                        { ~~~~~~~~~~~~~~~~~~~~~~ }
                        { NEAREST-EVEN           }
                        { ~~~~~~~~~~~~           }
                        { NEAREST-TOWARD-ZERO    }
                        { ~~~~~~~~~~~~~~~~~~~    }
                        { PROHIBITED             }
                        { ~~~~~~~~~~             }
                        { TOWARD-GREATER         }
                        { ~~~~~~~~~~~~~~         }
                        { TOWARD-LESSER          }
                        { ~~~~~~~~~~~~~          }
                        { TRUNCATION             }
                          ~~~~~~~~~~
    [ ON SIZE ERROR imperative-statement-1 ]
         ~~~~ ~~~~~
    [ NOT ON SIZE ERROR imperative-statement-2 ]
      ~~~    ~~~~ ~~~~~
[ END-SUBTRACT ]
  ~~~~~~~~~~~~

The SUBTRACT CORRESPONDING statement generates code equivalent to individual SUBTRACT FROM statements for corresponding matches of data items found subordinate to the two identifiers.

  1. The reserved words IS and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. Both <identifier-1> and <identifier-2> must be group items.

  3. 7.6.2 CORRESPONDING, for information on how corresponding matches will be found between <identifier-1> and <identifier-2>.

  4. The optional ROUNDED ( 7.6.7 ROUNDED) clause available to each <identifier-2> will control how non-integer results will be saved.

  5. The optional ON SIZE ERROR and NOT ON SIZE ERROR clauses may be used to detect and react to the failure or success, respectively, of an attempt to perform a calculation. In this case, failure is defined as being an <identifier-2> with an insufficient number of digit positions available to the left of any implied decimal point. 7.6.6 ON SIZE ERROR + NOT ON SIZE ERROR, for additional information.

7.8.47 SUPPRESS

SUPPRESS Syntax

SUPPRESS PRINTING
~~~~~~~~

The SUPPRESS statement causes the presentation of a report group to be suppressed.

  1. The reserved word PRINTING is optional and may be omitted. The presence or absence of this word has no effect upon the program.

  2. This statement may only appear within a USE BEFORE REPORTING procedure (in DECLARATIVES ( 7.5 DECLARATIVES)).

  3. SUPPRESS only prevents the presentation of the report group within whose USE BEFORE REPORTING procedure the statement occurs.

  4. This statement must be executed each time presentation of the report group is to be suppressed.

  5. When a report group’s presentation is suppressed, none of the following operations for the report will take place:

    1. Actual presentation of the report group in question.

    2. Processing of any LINE ( 6.9.29 LINE) clauses within the report group in question.

    3. Processing of the NEXT GROUP ( 6.9.32 NEXT GROUP) clause (if any) within the report group in question.

    4. Any modification to the LINE-COUNTER special register ( 7.7 Special Registers).

    5. Any modification to the PAGE-COUNTER special register.

7.8.48 TERMINATE

TERMINATE Syntax

TERMINATE report-name-1...
~~~~~~~~~

The TERMINATE statement causes the processing of the specified report(s) to be completed.

  1. Each <report-name-1> must be the name of a report having an RD ( 6.6 REPORT SECTION) defined for it.

  2. The specified report name(s) must be currently initiated (via INITIATE ( 7.8.25 INITIATE)) and cannot yet have been terminated.

  3. The TERMINATE statement will present each CONTROL FOOTING (if any), in reverse sequence of the control hierarchy, starting with the most minor up to FINAL (if any). During the presentation of these groups and the processing of any USE BEFORE REPORTING procedures for those groups, the prior set of control data item values will be available, as though a control break had been detected at the most major control data name.

  4. During the presentation of the CONTROL FOOTING groups, any necessary PAGE FOOTING and PAGE HEADING groups will be presented as well.

  5. Finally,the REPORT FOOTING group, if any, will be presented.

  6. If an INITIATE is followed by a TERMINATE with no intervening GENERATE ( 7.8.20 GENERATE) statements (all pertaining to the same report, of course), no report groups will be presented to the output file.

7.8.49 TRANSFORM

TRANSFORM Syntax

TRANSFORM identifier-1 CHARACTERS FROM { literal-1    } TO { literal-2    }
~~~~~~~~~                         ~~~~ { identifier-2 } ~~ { identifier-3 }

The TRANSFORM statement scans a data item performing a series of mono-alphabetic substitutions, defined by the arguments before and after the TO clause.

  1. Both <literal-1> and/or <literal-2> must be alphanumeric literals.

  2. All of <identifier-1>, <identifier-2> and <identifier-3> must either be group items or alphanumeric data items. Numeric data items with a USAGE ( 6.9.61 USAGE) of DISPLAY are accepted, but will generate warning messages from the compiler.

  3. The TRANSFORM statement will replace characters within <identifier-1> that are found in the string specified before the TO keyword with the corresponding characters from the string specified after the TO keyword.

  4. Usage of word CHARACTERS has no effect on operations other than for appearance.

  5. This statement exists within GnuCOBOL to provide compatibility with COBOL programs written to pre-1985 standards. The TRANSFORM statement was made obsolete in the 1985 standard of COBOL, having been replaced by the CONVERTING clause of the INSPECT statement ( 7.8.26 INSPECT). New programs should be coded to use INSPECT CONVERTING rather than TRANSFORM.

7.8.50 UNLOCK

UNLOCK Syntax

UNLOCK filename-1 RECORD|RECORDS
~~~~~~

This statement synchronizes any as-yet unwritten file I/O buffers to the specified file (if any) and releases any record locks held for records belonging to <file-name-1>.

  1. The reserved words RECORD and RECORDS are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. If <file-name-1> is a Sort/Merge work file, no action will be taken.

  3. Not all GnuCOBOL implementations support locking. Whether they do or not depends upon the operating system they were built for and the build options that were used when GnuCOBOL was generated. When a program using one of those GnuCOBOL implementations issues an UNLOCK, it will ignored. There will be no compiler message issued. Buffer syncing, if needed, will still occur.

  4. For GnuCOBOL UNLOCK is implied in GnuCOBOL on file close so there’s no use to do it afterwards. A CLOSE will always trigger syncing the file to disk, too.

  5. Doing UNLOCK before a close, will explicit unlock any records with a lock when running on INDEXED files, for other files it will release any locks on the file if it wasn’t opened for exclusive locking and will trigger syncing to disk (not done for any INDEXED file).

  6. When using Linux and for that matter most *nix platforms, the system maintains it’s own cache and buffers for file processing so there can and most likely will be a short delay before all data is written out to disk.

  7. 2.2.16 Record Locking, for additional information on record locking.

7.8.51 UNSTRING

UNSTRING Syntax

  UNSTRING identifier-1
  ~~~~~~~~
       DELIMITED BY { [ ALL ] literal-1 } [ OR { [ ALL ] literal-2 } ]...
       ~~~~~~~~~    {   ~~~             }   ~~ {   ~~~             }
                    { identifier-2      }      { identifier-3      }

       INTO { identifier-4
       ~~~~ [ DELIMITER IN identifier-5 ] [ COUNT IN identifier-6 ] }...
              ~~~~~~~~~                     ~~~~~
     [ WITH POINTER identifier-7 ]
            ~~~~~~~
     [ TALLYING IN identifier-8 ]
       ~~~~~~~~
     [ ON OVERFLOW imperative-statement-1 ]
          ~~~~~~~~
     [ NOT ON OVERFLOW imperative-statement-2 ]
       ~~~    ~~~~~~~~
[ END-UNSTRING ]
  ~~~~~~~~~~~~

The UNSTRING statement parses a string, extracting any number of sub strings from it.

  1. The reserved words BY, IN and ON are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. <identifier-1> through <identifier-5> must be explicitly or implicitly defined with a USAGE ( 6.9.61 USAGE) of DISPLAY. Any of those identifiers may be group items.

  3. Both <literal-1> and <literal-2> must be alphanumeric literals.

  4. Each of <identifier-6>, <identifier-7> and <identifier-8> must be elementary non-edited integer numeric items.

  5. At the time the UNSTRING statement begins execution, <identifier-7> must have a value greater than 0.

  6. <identifier-1> will be referred to as the source string and each <identifier-4> will be referred to as a destination field in the following discussions.

  7. The UNSTRING statement’s processing is based upon a current character pointer, the initial value of which will be the value of <identifier-7> at the time the UNSTRING statement began execution. If no POINTER clause is coded, a value of 1 (meaning “the 1st character position”) will be assumed for the current character pointer’s initial value.

  8. The source string will be parsed into sub strings starting from the current character pointer position. Sub strings are identified by using the various delimiter strings specified on the DELIMITED BY clause as inter-sub string separators.

  9. Using the ALL option allows a delimiter sequence to be an arbitrarily long sequence of occurrences of the delimiter literal whereas its absence treats each occurrence as a separate delimiter. When multiple delimiters are specified, they will be looked for in the source string in the sequence in which they are coded.

  10. Two consecutive delimiter sequences will identify a null sub string.

  11. Identified sub strings will be moved into each destination field in the sequence they are identified; values moved into a destination field will be truncated if the sub string length exceeds the destination field length, or padded with spaces if the destination field length exceeds the sub string length. Both truncation and padding will be controlled by the presence or absence of a JUSTIFIED ( 6.9.26 JUSTIFIED) clause on the destination field.

  12. Each destination field may have an optional DELIMITER clause. If a DELIMITER clause is specified, <identifier-5> will have the delimiter character string used to identify the sub string for the destination field moved into it. If a destination field was not altered (because an insufficient number of sub strings were identified), <identifier-5> for that destination field will also be unchanged.

  13. Each destination field may have an optional COUNT clause. If a COUNT clause is specified, <identifier-6> will have the size of the sub string (in characters) for the destination field moved into it. If a destination field was not altered (because an insufficient number of sub strings were identified), <identifier-6> for that destination field will also be unchanged.

  14. If a TALLYING clause is coded, <identifier-8> will be incremented by 1 each time a destination field is populated.

  15. None of <identifier-4>, <identifier-5>, <identifier-6>, <identifier-7> or <identifier-8> are initialized by the UNSTRING statement. You need to do that yourself via a MOVE ( 7.8.28 MOVE) or INITIALIZE statement ( 7.8.24 INITIALIZE).

  16. UNSTRING processing will cease when one of the following occurs:

    1. The initial value of the current character pointer is less than 1 or greater than the number of character positions in <identifier-1>, or…

    2. All destination fields have been fully processed

  17. If event A occurs, none of the destination field contents (or the contents of their DELIMITER or <COUNT> identifiers) will be changed.

  18. An overflow condition exists if either event A occurs, or if event B occurs with at least one character position in <identifier-1> not having been processed.

  19. The optional ON OVERFLOW and NOT ON OVERFLOW clauses may be used to detect and react to the occurrence or not, respectively, of an overflow condition. 7.6.5 ON OVERFLOW + NOT ON OVERFLOW, for additional information.

The following sample program illustrates the UNSTRING statement statement.

IDENTIFICATION DIVISION.
PROGRAM-ID. DEMOUNSTRING.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  Full-Name                   PIC X(40).
01  Parsed-Info.
    05 Last-Name                PIC X(15).
    05 First-Name               PIC X(15).
    05 MI                       PIC X(1).
    05 Delim-LN                 PIC X(1).
    05 Delim-FN                 PIC X(1).
    05 Delim-MI                 PIC X(1).
    05 Count-LN                 BINARY-CHAR.
    05 Count-FN                 BINARY-CHAR.
    05 Count-MI                 BINARY-CHAR.
    05 Tallying-Ctr             BINARY-CHAR.
PROCEDURE DIVISION.
P1. PERFORM UNTIL EXIT
      DISPLAY "Enter Full Name (null quits):"
          WITH NO ADVANCING
      ACCEPT Full-Name
      IF Full-Name = SPACES
        EXIT PERFORM
      END-IF
      INITIALIZE Parsed-Info
      UNSTRING Full-Name
        DELIMITED BY ", "
                  OR ","
                  OR ALL SPACES
        INTO Last-Name
                 DELIMITER IN Delim-LN
                 COUNT IN Count-LN
             First-Name
                 DELIMITER IN Delim-FN
                 COUNT IN Count-FN
             MI
                 DELIMITER IN Delim-MI
                 COUNT IN Count-MI
        TALLYING Tallying-Ctr
    DISPLAY "First-Name=" First-Name
            " Delim='"    Delim-FN
            "' Count="    Count-FN
    DISPLAY "MI        =" MI "              "
            " Delim='"    Delim-MI
            "' Count="    Count-MI
    DISPLAY "Last-Name =" Last-Name
            " Delim='"    Delim-LN
            "' Count="    Count-LN
    DISPLAY "Tally=     " Tallying-Ctr
  END-PERFORM
  DISPLAY "Bye!"
  STOP RUN   .

The following is sample output from the program:

Enter Full Name (null quits):Cutler, Gary L
First-Name=Gary            Delim=' ' Count=+004
MI        =L               Delim=' ' Count=+001
Last-Name =Cutler          Delim=',' Count=+006
Tally=     +003
Enter Full Name (null quits):Snoddgrass,Throckmorton,P
First-Name=Throckmorton    Delim=',' Count=+012
MI        =P               Delim=' ' Count=+001
Last-Name =Snoddgrass      Delim=',' Count=+010
Tally=     +003
Enter Full Name (null quits):Munster   Herman
First-Name=Herman          Delim=' ' Count=+006
MI        =                Delim=' ' Count=+000
Last-Name =Munster         Delim=' ' Count=+007
Tally=     +002
Enter Full Name (null quits):
Bye!

7.8.52 WRITE

WRITE Syntax

  WRITE record-name-1
  ~~~~~
     [ FROM { literal-1    } ]
       ~~~~ { identifier-1 }

     [ WITH [ NO ] LOCK ]
              ~~   ~~~~
     [ { BEFORE } ADVANCING { { literal-2    } LINE|LINES } ]
       { ~~~~~~ }           { { identifier-2              }
       { AFTER  }           { PAGE                        }
         ~~~~~              { ~~~~                        }
                            { mnemonic-name-1             }

     [ AT END-OF-PAGE|EOP imperative-statement-1 ]
          ~~~~~~~~~~~ ~~~
     [ NOT AT END-OF-PAGE|EOP imperative-statement-2 ]
       ~~~    ~~~~~~~~~~~ ~~~
     [ INVALID KEY imperative-statement-3 ]
       ~~~~~~~
     [ NOT INVALID KEY imperative-statement-4 ]
       ~~~ ~~~~~~~
[ END-WRITE ]
  ~~~~~~~~~

The WRITE statement writes a new record to an open file.

  1. The reserved words ADVANCING, AT, KEY, LINE, LINES and WITH are optional and may be omitted. The presence or absence of these words has no effect upon the program.

  2. The reserved words END-OF-PAGE and EOP are interchangeable.

  3. The <record-name-1> specified on the statement must be defined as an 01-level record subordinate to the File Description (FD ( 6.2.1 File/Sort-Description)) of a file that is currently open for OUTPUT ( File OPEN Modes), EXTEND or I-O.

  4. The optional FROM clause will cause <literal-1> or <identifier-1> to be automatically moved into <record-name-1> prior to writing <record-name-1>’s contents to the appropriate file. If this clause is not specified, it is the programmer’s responsibility to populate <record-name-1> with the desired data prior to executing the WRITE.

  5. The optional LOCK options may be used to manually control access to the just-written record by other programs while this program is running. 2.2.16 Record Locking, to review the various record locking behaviour.

  6. The optional INVALID KEY and NOT INVALID KEY clauses may be used when writing to relative or indexed files to detect and react to the failure (non-zero file status code) or success (00 file status code), respectively, of the statement. File Status Codes, for additional information.

  7. When WRITE is used against an ORGANIZATION LINE SEQUENTIAL ( 5.2.1.2 ORGANIZATION LINE SEQUENTIAL) file, with or without the LINE ADVANCING ( LINE ADVANCING) option, an end-of-record delimiter character sequence will be written to the file to signify where one record ends and the next record begins. This delimiter sequence will be either of the following:

    • A line-terminator sequence consisting of an ASCII carriage-return/line-feed character sequence (X'0D0A') if you are running a MinGW or native Windows build of GnuCOBOL

    • A line-terminator sequence consisting of an ASCII line-feed character (X'0A') if you are running a Cygwin, Linux, Unix or OSX build of GnuCOBOL

  8. The following points pertain to the use (or not) of the ADVANCING clause:

    1. Using this clause with any organization other than ORGANIZATION LINE SEQUENTIAL will either be rejected outright by the compiler (relative or indexed files) or may introduce unwanted characters into the file (ORGANIZATION SEQUENTIAL ( 5.2.1.1 ORGANIZATION SEQUENTIAL)).

    2. If no ADVANCING clause is specified on a WRITE to a line-advancing file, AFTER ADVANCING 1 LINE will be assumed; on other than line-advancing files, BEFORE ADVANCING 1 LINE will be assumed.

    3. When BEFORE ADVANCING is used (or implied), the record is written to the file before the ADVANCING action writes line-terminator characters to the file.

    4. If AFTER ADVANCING is used (or implied), the ADVANCING action writes line-terminator characters to the file and then the record data is written to the file.

    5. The ADVANCING n LINES clause will introduce the specified number of line-terminator character sequences into the file either before the written record (AFTER ADVANCING) or after the written record (BEFORE ADVANCING).

    6. If the LINAGE ( 6.2.1 File/Sort-Description) clause is absent from the file’s FD:

      1. The ADVANCING PAGE clause will introduce an ASCII formfeed character into the file either before the written record (AFTER PAGE) or after the written record (BEFORE PAGE).

      2. Management of areas on the printed page such as top-of page headers, bottom-of-page footers, dealing with “full page” situations and the like are the complete responsibility of the programmer.

    7. If the LINAGE clause is present in the file’s FD:

      1. The ADVANCING PAGE clause will introduce the appropriate number of line-terminator character sequences into the file either before the written record (AFTER ADVANCING) or after the written record (BEFORE ADVANCING) so as to force the printer to automatically advance to a new sheet of paper when the file prints. No formfeed characters will be generated when LINAGE is specified — instead, it is assumed that the printer to which the report will be printed will be loaded with special forms that conform to the specifications defined by the LINAGE clause.

      2. Management of areas on the printed page such as top-of page headers, bottom-of-page footers, dealing with “full page” situations and the like are now the joint responsibility of the programmer and the GnuCOBOL run-time library, which provides tools such as the LINAGE-COUNTER special register ( 7.7 Special Registers) and the END-OF-PAGE clause to deal with page formatting issues.

      3. The AT END-OF-PAGE clause will be triggered, thus executing <imperative-statement-1> ( Imperative Statement), if the WRITE statement introduces a data line or line-feed character into the file at a line position within the Page Footer area defined by the LINAGE clause. The NOT AT END-OF-PAGE clause will be triggered (thus executing <imperative-statement-2>) if no end-of-page condition occurred during the WRITE.