.. |_| unicode:: 0xA0 :trim: .. role:: small-caps :class: small-caps .. include:: .. index:: single:PROCEDURE DIVISION .. _PROCEDUREADIVISION: 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 \ :code:`PROCEDURE DIVISION`\ of any GnuCOBOL program marks the point where all executable code is written. .. index:: single:PROCEDURE DIVISION USING .. _PROCEDUREADIVISIONAUSING: 7.1 PROCEDURE DIVISION USING ---------------------------- PROCEDURE DIVISION Subprogram-Argument Syntax :: [ BY { REFERENCE [ OPTIONAL ] } ] identifier-1 { ~~~~~~~~~ ~~~~~~~~ } { VALUE [ [ UNSIGNED ] SIZE IS { AUTO } ] } ~~~~~ ~~~~~~~~ ~~~~ { ~~~~ } { DEFAULT } { ~~~~~~~ } { integer-1 } The \ :code:`USING`\ clause defines the arguments that will be passed to a GnuCOBOL program which is serving as a subprogram. #. The reserved words \ :code:`BY`\ and \ :code:`IS`\ are optional and may be omitted. The presence or absence of these words have no effect upon the program. .. index:: single:USING #. The \ \ :code:`USING`\ clause should only be used on the procedure division header of subprograms (subroutines or user-defined functions). #. The calling program will pass zero or more data items, known as arguments, to this subprogram --- there must be exactly as many data items specified on the \ :code:`USING`\ clause as the maximum number of arguments the subprogram will ever be passed. #. If a subprogram does not expect any arguments, it should not have a \ :code:`USING`\ clause specified on its procedure division header. #. The order in which arguments are defined on the \ :code:`USING`\ clause must correspond to the order in which those arguments will be passed to the subprogram by the calling program. #. The identifiers specified on the \ :code:`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. #. 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. \ :code:`USAGE BINARY-LONG`\ ( :ref:`USAGE`)) which is the actual argument being passed to the subprogram. .. index:: single:BY VALUE .. index:: single:BY REFERENCE In the case of the former, the \ :code:`USING`\ clause on the procedure division header should describe the argument via the \ \ :code:`BY REFERENCE`\ clause --- in the latter case, a \ \ :code:`BY VALUE`\ specification should be coded. This allows the code generated by the compiler to properly reference the subprogram arguments at run-time. #. \ :code:`BY REFERENCE`\ is the assumed default for the first \ :code:`USING`\ argument should no \ :code:`BY`\ clause be specified for it. Subsequent arguments will assume the \ :code:`BY`\ specification of the argument prior to them should they lack a \ :code:`BY`\ clause of their own. #. Changes made by a subprogram to the value of an argument specified on the \ :code:`USING`\ clause will "be visible" to the calling program only if \ :code:`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 \ :code:`BY REFERENCE`\ by the calling program. :ref:`SubprogramAArguments`, for additional information on the mechanics of how arguments are passed to subprograms. #. The optional \ :code:`SIZE`\ clause allows you to specify the number of bytes a \ :code:`BY VALUE`\ argument will occupy, with \ :code:`SIZE DEFAULT`\ specifying 4 bytes (this is the default if no \ :code:`SIZE`\ clause is used), \ :code:`SIZE AUTO`\ specifying the size of the argument in the calling program and \ :code:`SIZE `\ specifying a specific byte count. #. The optional \ :code:`UNSIGNED`\ keyword, legal only if \ :code:`SIZE AUTO`\ or \ :code:`SIZE `\ are coded, will add the \ :code:`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. .. index:: single:OMITTED .. index:: single:OPTIONAL #. The \ \ :code:`OPTIONAL`\ keyword, legal only on \ :code:`BY REFERENCE`\ arguments, allows calling programs to code \ \ :code:`OMITTED`\ for that corresponding argument when they call this subprogram. :ref:`CALL`. for additional information on this feature. .. index:: single:PROCEDURE DIVISION CHAINING .. _PROCEDUREADIVISIONACHAINING: 7.2 PROCEDURE DIVISION CHAINING ------------------------------- PROCEDURE DIVISION Main-Program-Argument Syntax :: [ BY REFERENCE ] [ OPTIONAL ] identifier-1 ~~~~~~~~~ ~~~~~~~~ The \ :code:`CHAINING`\ term provides one mechanism a programmer may use to retrieve command-line arguments passed to a program at execution time. #. \ :code:`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. #. The \ :code:`CHAINING`\ clause defines arguments that will be passed to a main program from the operating system. The argument identifiers specified on the \ :code:`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: #. 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 :command:`/usr/local/myprog THIS IS A TEST`, there will be five tokens identified by the operating system --- '\ :code:`/usr/local/myprog`\ ', '\ :code:`THIS`\ ', '\ :code:`IS`\ ', '\ :code:`A`\ ' and '\ :code:`TEST`\ '. #. 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 :command:`C:\Pgms\myprog.exe '\ :code:`THIS IS A`\ ' TEST` --- '\ :code:`C:\Pgms\myprog.exe`\ ', '\ :code:`THIS IS A`\ ' and '\ :code:`TEST`\ '. When quote characters are used to create multi-word tokens, the quote characters themselves are stripped from the token's value. #. Once tokens have been identified, the first one (the command) will be discarded; the rest will be stored into the \ :code:`CHAINING`\ arguments when the program begins execution, with the 2nd token going to the 1\ :sup:`st`\ argument, the 3rd token going to the 2nd argument and so forth. #. If there are more tokens than there are arguments, the excess tokens will be discarded. #. If there are fewer tokens than there are arguments, the excess arguments will be initialized as if the \ :code:`INITIALIZE `\ ( :ref:`INITIALIZE`) statement were executed. #. All identifiers specified on the \ :code:`CHAINING`\ clause should be defined as \ :code:`PIC X, PIC A`\ , group items (which are treated implicitly as \ :code:`PIC X`\ ) or as \ :code:`PIC 9 USAGE DISPLAY`\ . The use of \ :code:`USAGE BINARY`\ (or the like) data items as \ :code:`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. #. 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 \ :code:`JUSTIFIED RIGHT`\ clause on such an argument identifier will be ignored. #. 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 \ :code:`PIC 9 USAGE DISPLAY`\ , in which case unmodified bytes will be filled with '\ :code:`0`\ ' characters from the systems native character set. This behaviour when the argument is defined as \ :code:`PIC 9`\ may be unacceptable, as an argument defined as \ :code:`PIC 9(3)`\ but passed in a value of '\ :code:`1`\ ' from the command line will receive a value of '\ :code:`100`\ ', not '\ :code:`001`\ '. Consider defining "numeric" command line arguments as \ :code:`PIC X`\ and then using the \ :code:`NUMVAL`\ intrinsic function ( :ref:`NUMVAL`) function to determine the proper numeric value. .. index:: single:PROCEDURE DIVISION RETURNING .. _PROCEDUREADIVISIONARETURNING: 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. #. The \ :code:`RETURNING`\ clause is optional within a subroutine, as not all subroutines return a value to their caller. #. The \ :code:`RETURNING`\ clause is mandatory within a user-defined function, as all such must return a numeric result. #. The data item should be defined as a \ :code:`USAGE BINARY-LONG`\ data item. #. Main programs that wish to "pass back" a return code value to the operating system when they exit do not use \ :code:`RETURNING`\ - they do so simply by MOVEing a value to the \ :code:`RETURN-CODE`\ special register. #. This is not the only mechanism that a subprogram may use to pass a value back to its caller. Other possibilities are: #. The subprogram may modify any argument that is specified as \ :code:`BY REFERENCE`\ on its \ :code:`PROCEDURE DIVISION`\ header. Whether the calling program can actually "see" any modifications depends upon how the calling program passed the argument to the subprogram. :ref:`CALL`, for more information. #. A data item with the \ :code:`GLOBAL`\ ( :ref:`GLOBAL`) attribute specified in its description in the calling program is automatically visible to and updatable by a subprogram nested with the calling program. :ref:`IndependentAvsAContainedAvsANestedASubprograms`, for more information on subprogram nesting. #. A data item defined with the \ :code:`EXTERNAL`\ ( :ref:`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. .. index:: single:PROCEDURE DIVISION Sections and Paragraphs .. _PROCEDUREADIVISIONASectionsAandAParagraphs: 7.4 PROCEDURE DIVISION Sections and Paragraphs ---------------------------------------------- .. index:: single:Procedure Names .. index:: single:Procedures 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 ('\ :code:`-`\ ') or underscore ('\ :code:`_`\ ') character. This means that \ :code:`Main`\ , \ :code:`0100-Read-Transaction`\ and \ :code:`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: #. When \ :code:`DECLARATIVES`\ ( :ref:`DECLARATIVES`) are specified. #. When the \ :code:`ENTRY`\ statement ( :ref:`ENTRY`) is being used. #. When any procedure division statement that references procedures is used. These statements are: * \ :code:`ALTER `\ * \ :code:`GO TO `\ * \ :code:`MERGE ... OUTPUT PROCEDURE `\ * \ :code:`PERFORM `\ * \ :code:`SORT ... INPUT PROCEDURE `\ and/or \ :code:`SORT ... INPUT PROCEDURE `\ .. index:: single:DECLARATIVES .. _DECLARATIVES: 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} } ~~ ~~~~~~~~~ ~~~~~~~~~ .. index:: single:AFTER EXCEPTION CONDITION The \ \ :code:`AFTER EXCEPTION CONDITION`\ and \ :code:`AFTER EC`\ clauses are syntactically recognized but are otherwise non-functional. The \ :code:`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. #. The reserved words \ :code:`AFTER`\ , \ :code:`FOR`\ , \ :code:`ON`\ , \ :code:`PROCEDURE`\ and \ :code:`STANDARD`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. \ :code:`EC`\ and \ :code:`EXCEPTION CONDITION`\ are interchangeable. #. The declaratives area may contain any number of declarative procedures, but no two declarative procedures should be coded to trap the same event. .. index:: single:USE BEFORE REPORTING #. The following points apply to the \ \ :code:`USE BEFORE REPORTING`\ clause: #. must be a report group. #. 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 \ :code:`SUM`\ ( :ref:`SUM`) or \ :code:`SOURCE`\ ( :ref:`SOURCE`) clauses in the report group. * You may execute the \ :code:`SUPPRESS`\ ( :ref:`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. .. index:: single:USE FOR DEBUGGING #. The following points apply to the \ \ :code:`USE FOR DEBUGGING`\ clause: #. This clause allows you to define a declarative procedure that will be invoked whenever... * ... is referenced on any statement. * ... is executed. * ...any procedure is executed (\ :code:`ALL PROCEDURES`\ ). .. index:: single:-debug Compiler Switch .. index:: single:Compiler Switches, -debug .. index:: single:-fdebugging-line Compiler Switch .. index:: single:Compiler Switches, -fdebugging-line #. A \ :code:`USE FOR DEBUGGING`\ declarative procedure will be ignored at \ *compilation*\ time unless \ :code:`WITH DEBUGGING MODE`\ is specified in the \ :code:`SOURCE-COMPUTER`\ ( :ref:`SOURCE-COMPUTER`) paragraph. Neither the compiler's \ \ \ :code:`-fdebugging-line`\ switch nor \ \ \ :code:`-debug`\ switch will activate this feature. .. index:: single:Environment Variables, COB_SET_DEBUG .. index:: single:COB_SET_DEBUG Environment Variable #. Any \ :code:`USE FOR DEBUGGING`\ declarative procedures will be ignored at \ *execution*\ time unless the \ \ run-time environment variable ( :ref:`RunATimeAEnvironmentAVariables`) has been set to a value of '\ :code:`Y`\ ', '\ :code:`y`\ ' or '\ :code:`1`\ '. .. index:: single:Special Registers, DEBUG-ITEM .. index:: single:DEBUG-ITEM Special Register #. The typical use of a \ :code:`USE FOR DEBUGGING`\ declarative procedure is to display the \ \ \ :code:`DEBUG-ITEM`\ special register, which will be implicitly and automatically created in your program for you if \ :code:`WITH DEBUGGING MODE`\ is active. The structure of \ :code:`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... * \ :code:`DEBUG-LINE`\ ... is the program line number of the statement that triggered the declaratives procedure. * \ :code:`DEBUG-NAME`\ ... is the procedure name or identifier name that triggered the declaratives procedure. * \ :code:`DEBUG-SUB-1`\ ... is the first subscript value (if any) for the reference of the identifier that triggered the declaratives procedure. * \ :code:`DEBUG-SUB-2`\ ... is the second subscript value (if any) for the reference of the identifier that triggered the declaratives procedure. * \ :code:`DEBUG-SUB-3`\ ... is the third subscript value (if any) for the reference of the identifier that triggered the declaratives procedure. * \ :code:`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). .. index:: single:USE AFTER STANDARD ERROR PROCEDURE #. The \ \ :code:`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)). #. The \ :code:`GLOBAL`\ ( :ref:`GLOBAL`) option, if used, allows a declarative procedure to be used across the program containing the \ :code:`USE`\ statement and any subprograms nested within that program. #. Declarative procedures may not reference any other procedures defined outside the scope of DECLARATIVES. .. index:: single:Common Clauses on Executable Statements .. _CommonAClausesAonAExecutableAStatements: 7.6 Common Clauses on Executable Statements ------------------------------------------- .. index:: single:AT END + NOT AT END .. _ATAENDAAANOTAATAEND: 7.6.1 AT END + NOT AT END ~~~~~~~~~~~~~~~~~~~~~~~~~ AT END Syntax :: [ AT END imperative-statement-1 ] ~~~ [ NOT AT END imperative-statement-2 ] ~~~ ~~~ \ :code:`AT END`\ clauses may be specified on \ :code:`READ`\ ( :ref:`READ`), \ :code:`RETURN`\ ( :ref:`RETURN`), \ :code:`SEARCH`\ ( :ref:`SEARCH`) and \ :code:`SEARCH ALL`\ ( :ref:`SEARCHAALL`) statements. #. The following points pertain to the use of these clauses on \ :code:`READ`\ ( :ref:`READ`) and \ :code:`RETURN`\ ( :ref:`RETURN`) statements: #. The \ :code:`AT END`\ clause will --- if present --- cause ( :ref:`Imperative Statement `) to be executed if the statement fails due to a file status of 10 (end-of-file). :ref:`File Status Codes `, for a list of possible File Status codes. An \ :code:`AT END`\ clause \ *will not detect other non-zero file-status values*\ . Use a \ :code:`DECLARATIVES`\ ( :ref:`DECLARATIVES`) routine or an explicitly-declared file status field tested after the \ :code:`READ`\ or \ :code:`RETURN`\ to detect error conditions other than end-of-file. #. A \ :code:`NOT AT END`\ clause will cause to be executed if the \ :code:`READ`\ or \ :code:`RETURN`\ attempt is successful. #. The following points pertain to the use of these clauses on \ :code:`SEARCH`\ ( :ref:`SEARCH`) and \ :code:`SEARCH ALL`\ ( :ref:`SEARCHAALL`) statements: #. An \ :code:`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. #. The \ :code:`NOT AT END`\ clause is not allowed on either form of table search. .. index:: single:CORRESPONDING .. _CORRESPONDING: 7.6.2 CORRESPONDING ~~~~~~~~~~~~~~~~~~~ Three GnuCOBOL statements --- \ :code:`ADD`\ ( :ref:`ADDACORRESPONDING`), \ :code:`MOVE`\ ( :ref:`MOVEACORRESPONDING`) and \ :code:`SUBTRACT`\ ( :ref:`SUBTRACTACORRESPONDING`) support the use of a \ :code:`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 ( --- the first named on the statement) to be paired with correspondingly-named (hence the name) in a second group item ( --- the second named on the statement). The contents of will remain unaffected by the statement while one or more data items within will be changed. In order for , defined subordinate to group item to be a \ *corresponding*\ match to which is subordinate to , each of the following must be true: #. Both and must have the same name, and that name may not explicitly or implicitly be \ :code:`FILLER`\ . #. Both and ... #. ...must exist at the same relative structural "depth" of definition within and , respectively #. ...and all "parent" data items defined within each group item must have identical (but non-\ :code:`FILLER`\ ) names. #. When used with a \ :code:`MOVE`\ verb... #. ...one of or (but not both) is allowed to be a group item #. ...and it must be valid to move TO . #. When used with \ :code:`ADD`\ or \ :code:`SUBTRACT`\ verbs, both and must be numeric, elementary, unedited items. #. Neither nor may be a \ :code:`REDEFINES`\ ( :ref:`REDEFINES`) or \ :code:`RENAMES`\ ( :ref:`RENAMES`) of another data item. #. Neither nor may have an \ :code:`OCCURS`\ ( :ref:`OCCURS`) clause, although either may contain subordinate data items that \ *do*\ have an \ :code:`OCCURS`\ clause (assuming rule 3a applies) Observe the definitions of data items '\ :code:`Q`\ ' and '\ :code:`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 \ :code:`CORRESPONDING`\ matches, assuming the statement \ :code:`MOVE CORRESPONDING X TO Y`\ is being executed (there are no valid corresponding matches for \ :code:`ADD CORRESPONDING`\ or \ :code:`SUBTRACT CORRESPONDING`\ because every potential match up violates rule #4): A, B, C, G The following are the \ :code:`CORRESPONDING`\ match ups that passed rule #1 (but failed on another rule), and the reasons why they failed. * Data Item Failure Reason * \ :code:`D`\ Fails due to rule #2b * \ :code:`E`\ Fails due to rule #3b * \ :code:`F`\ Fails due to rule #5 * \ :code:`G1`\ Fails due to rule #3a * \ :code:`G2`\ Fails due to rule #3a * \ :code:`G3`\ Fails due to rule #3a * \ :code:`G4`\ Fails due to rule #1 * \ :code:`G5`\ Fails due to rule #1 * \ :code:`G6`\ Fails due to rule #6 * \ :code:`H`\ Fails due to rule #6 * \ :code:`I`\ Fails due to rule #5 * \ :code:`J`\ Fails due to rule #3a * \ :code:`K`\ Fails due to rule #3a * \ :code:`L`\ Fails due to rule #1 * \ :code:`M`\ Fails due to rule #2a .. index:: single:INVALID KEY + NOT INVALID KEY .. _INVALIDAKEYAAANOTAINVALIDAKEY: 7.6.3 INVALID KEY + NOT INVALID KEY ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ INVALID KEY Syntax :: [ INVALID KEY imperative-statement-1 ] ~~~~~~~ [ NOT INVALID KEY imperative-statement-2 ] ~~~ ~~~~~~~ \ :code:`INVALID KEY`\ clauses may be specified on \ :code:`DELETE`\ ( :ref:`DELETE`), \ :code:`READ`\ ( :ref:`RandomAREAD`), \ :code:`REWRITE`\ ( :ref:`REWRITE`), \ :code:`START`\ ( :ref:`START`) and \ :code:`WRITE`\ ( :ref:`WRITE`) statements. Specification of an \ :code:`INVALID KEY`\ clause will allow your program to trap an I/O failure condition (with an I/O error code in the file's \ :code:`FILE-STATUS`\ ( :ref:`SELECT`) field) that has occurred due to a record-not-found condition and handle it gracefully by executing ( :ref:`Imperative Statement `). .. index:: single:NOT INVALID KEY An optional \ \ :code:`NOT INVALID KEY`\ clause will cause to be executed if the statement's execution was successful. .. index:: single:ON EXCEPTION + NOT ON EXCEPTION .. _ONAEXCEPTIONAAANOTAONAEXCEPTION: 7.6.4 ON EXCEPTION + NOT ON EXCEPTION ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ON EXCEPTION Syntax :: [ ON EXCEPTION imperative-statement-1 ] ~~~~~~~~~ [ NOT ON EXCEPTION imperative-statement-2 ] ~~~ ~~~~~~~~~ \ :code:`EXCEPTION`\ clauses may be specified on \ :code:`ACCEPT`\ ( :ref:`ACCEPT`), \ :code:`CALL`\ ( :ref:`CALL`) and \ :code:`DISPLAY`\ ( :ref:`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 ( :ref:`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 \ :code:`SYSERR`\ device (pipe 2). The program may also be terminated, depending upon the type and severity of the error. .. index:: single:NOT ON EXCEPTION An optional \ \ :code:`NOT ON EXCEPTION`\ clause will cause to be executed if the statement's execution was successful. .. index:: single:ON OVERFLOW + NOT ON OVERFLOW .. _ONAOVERFLOWAAANOTAONAOVERFLOW: 7.6.5 ON OVERFLOW + NOT ON OVERFLOW ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ON OVERFLOW Syntax :: [ ON OVERFLOW imperative-statement-1 ] ~~~~~~~~ [ NOT ON OVERFLOW imperative-statement-2 ] ~~~ ~~~~~~~~ \ :code:`OVERFLOW`\ clauses may be specified on \ :code:`CALL`\ ( :ref:`CALL`), \ :code:`STRING`\ ( :ref:`STRING`) and \ :code:`UNSTRING`\ ( :ref:`UNSTRING`) statements. An \ :code:`ON OVERFLOW`\ clause will allow your program to trap a failure condition that has occurred and handle it gracefully by executing ( :ref:`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 \ :code:`SYSERR`\ device (pipe 2). The program may also be terminated, depending upon the type and severity of the error. .. index:: single:NOT ON OVERFLOW An optional \ \ :code:`NOT ON OVERFLOW`\ clause will cause to be executed if the statement's execution was successful. .. index:: single:ON SIZE ERROR + NOT ON SIZE ERROR .. _ONASIZEAERRORAAANOTAONASIZEAERROR: 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 ] ~~~ ~~~~ ~~~~~ \ :code:`SIZE ERROR`\ clauses may be included on \ :code:`ADD`\ ( :ref:`ADD`), \ :code:`COMPUTE`\ ( :ref:`COMPUTE`), \ :code:`DIVIDE`\ ( :ref:`DIVIDE`), \ :code:`MULTIPLY`\ ( :ref:`MULTIPLY`) and \ :code:`SUBTRACT`\ ( :ref:`SUBTRACT`) statements. Including an \ :code:`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 ( :ref:`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 \ :code:`ON SIZE ERROR`\ clause exists, will produce an error message (by the GnuCOBOL runtime library) to the \ :code:`SYSERR`\ device (pipe 2) and will also abort the program. .. index:: single:NOT ON SIZE ERROR An optional \ \ :code:`NOT ON SIZE ERROR`\ clause will cause to be executed if the arithmetic statement's execution was successful. .. index:: single:ROUNDED .. _ROUNDED: 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 (\ :code:`ADD`\ ( :ref:`ADD`), \ :code:`COMPUTE`\ ( :ref:`COMPUTE`), \ :code:`DIVIDE`\ ( :ref:`DIVIDE`), \ :code:`MULTIPLY`\ ( :ref:`MULTIPLY`) and \ :code:`SUBTRACT`\ ( :ref:`SUBTRACT`)) statements allow an optional \ :code:`ROUNDED`\ clause to be applied to each receiving data item. The following rules apply to the rounding behaviour induced by this clause. #. Rounding only applies when the result being saved to a receiving field with a \ :code:`ROUNDED`\ clause is a non-integer value. #. Absence of a \ :code:`ROUNDED`\ clause is the same as specifying \ :code:`ROUNDED MODE IS TRUNCATION`\ . #. Use of a \ :code:`ROUNDED`\ clause without a \ :code:`MODE`\ specification is the same as specifying \ :code:`ROUNDED MODE IS NEAREST-AWAY-FROM-ZERO`\ . The behaviour of the eight different rounding modes is defined in the following table. Note that a '\ :code:`...`\ ' indicates the last digit repeats. The examples assume an integer receiving field. * \ :code:`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 * \ :code:`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 * \ :code:`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 * \ :code:`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 * \ :code:`PROHIBITED`\ No rounding is performed. If the value cannot be represented exactly in the desired format, the \ :code:`EC-SIZE-TRUNCATION`\ condition (exception code 1005) is set (and may be retrieved via the \ :code:`ACCEPT`\ ( :ref:`ACCEPTAFROMARuntime-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 * \ :code:`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 * \ :code:`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 * \ :code:`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 .. index:: single:Special Registers .. _SpecialARegisters: 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: * \ :code:`COB-CRT-STATUS`\ PIC 9(4) --- This is the default data item allocated for use by the \ :code:`ACCEPT `\ statement ( :ref:`ACCEPTAdata-item`), if no \ :code:`CRT STATUS`\ ( :ref:`SPECIAL-NAMES`) clause was specified.. * \ :code:`DEBUG-ITEM`\ Group Item --- A group item in which debugging information generated by a \ :code:`USE FOR DEBUGGING`\ section in the declaratives area of the procedure division will place information documenting why the \ :code:`USE FOR DEBUGGING`\ procedure was invoked. Consult the \ :code:`DECLARATIVES`\ ( :ref:`DECLARATIVES`) documentation for information on the structure of this register. * \ :code:`LINAGE-COUNTER`\ \ :code:`BINARY-LONG SIGNED`\ --- An occurrence of this register exists for each selected file having a \ :code:`LINAGE`\ ( :ref:`FileASort-Description`) clause. If there are multiple files whose file descriptions have \ :code:`LINAGE`\ clauses, any explicit references to this register will require qualification (using \ :code:`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. * \ :code:`LINE-COUNTER`\ \ :code:`BINARY-LONG SIGNED`\ --- An occurrence of this register exists for each report defined in the program (via an \ :code:`RD`\ ( :ref:`REPORTASECTION`)). If there are multiple reports, any explicit references to this register not made in the report section will require qualification (\ :code:`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. * \ :code:`NUMBER-OF-CALL-PARAMETERS`\ \ :code:`BINARY-LONG SIGNED`\ --- This register contains the number of arguments passed to a subroutine --- the same value that would be returned by the \ :code:`C$NARG`\ built-in system subroutine ( :ref:`CANARG`). 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 ('\ :code:`1`\ ') if the function has any number of arguments and a zero if it has no arguments. * \ :code:`PAGE-COUNTER`\ \ :code:`BINARY-LONG SIGNED`\ --- An occurrence of this register exists for each report having an \ :code:`RD`\ ( :ref:`REPORTASECTION`). If there are multiple such reports, any explicit references to this register not made in the report section will require qualification ( \ :code:`OF report-name`\ ). The value of this register will be the current report page number. The value of this register cannot be modified. * \ :code:`RETURN-CODE`\ \ :code:`BINARY-LONG SIGNED`\ --- This register provides a numeric data item into which a subroutine may \ :code:`MOVE`\ ( :ref:`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 \ :code:`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 \ :code:`RETURNING`\ ( :ref:`PROCEDUREADIVISIONARETURNING`) clause. * \ :code:`SORT-RETURN`\ \ :code:`BINARY-LONG SIGNED`\ --- This register is used to report the success/fail status of a \ :code:`RELEASE`\ ( :ref:`RELEASE`) or \ :code:`RETURN`\ ( :ref:`RETURN`) statement. A value of 0 is reported on success. A value of 16 denotes failure. An \ :code:`AT END`\ ( :ref:`ATAENDAAANOTAATAEND`) condition on a \ :code:`RETURN`\ is not considered a failure. * \ :code:`WHEN-COMPILED`\ \ :code:`PIC X(16)`\ --- This register contains the date and time the program was compiled in the format '\ :code:`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 \ :code:`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. #. The reserved word \ :code:`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 #. The \ :code:`LENGTH OF`\ clause on a literal or identifier reference may generally be used anywhere a numeric literal might be specified, with the following exceptions: * As part of the \ :code:`FROM`\ clause of a \ :code:`WRITE`\ ( :ref:`WRITE`) or \ :code:`RELEASE`\ statement ( :ref:`RELEASE`). * As part of the \ :code:`TIMES`\ clause of a \ :code:`PERFORM`\ statement ( :ref:`PERFORM`). .. index:: single:GnuCOBOL Statements .. _GnuCOBOLAStatements: 7.8 GnuCOBOL Statements ----------------------- .. index:: single:ACCEPT .. _ACCEPT: 7.8.1 ACCEPT ~~~~~~~~~~~~ .. index:: single:ACCEPT FROM CONSOLE .. _ACCEPTAFROMACONSOLE: 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 \ :code:`ACCEPT`\ statement is used to read a value from the console window or the standard input device and store it into a data item (). #. If no \ :code:`FROM`\ clause is specified, \ :code:`FROM CONSOLE`\ is assumed. #. The specified must either be one of the built-in device names \ :code:`CONSOLE`\ , \ :code:`STDIN`\ , \ :code:`SYSIN`\ or \ :code:`SYSIPT`\ , or a user-defined ( :ref:`SPECIAL-NAMES`) mnemonic name \ *attached*\ to one of those four device names. #. Input will be read either from the console window (\ :code:`CONSOLE`\ ) or from the system-standard input (pipe 0 = \ :code:`STDIN`\ , \ :code:`SYSIN`\ or \ :code:`SYSIPT`\ ) and will be saved in . #. If 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 \ :code:`NUMVAL`\ intrinsic function ( :ref:`NUMVAL`), except that none of the trailing sign formats are honoured. .. index:: single:ACCEPT FROM COMMAND-LINE .. _ACCEPTAFROMACOMMAND-LINE: 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 \ :code:`ACCEPT`\ statement is used to retrieve information from the program's command line. #. The reserved word \ :code:`ON`\ is optional and may be omitted. The presence or absence of this word has no effect upon the program. .. index:: single:COMMAND-LINE #. When you accept from the \ \ :code:`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. #. Using \ :code:`COMMAND-LINE`\ or \ :code:`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 '\ :code:`\*`\ ' in the list --- such as '\ :code:`a\*`\ ', '\ :code:`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.*\ , \ :code:`progundertest "a*" b c d "ef*" "*hg"`\ and the text within quotes will be passed verbatim to the program (as in the example :command:`progundertest`). .. index:: single:ARGUMENT-NUMBER #. By accepting from \ \ :code:`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: #. 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. #. Strings enclosed in double-quote characters ('\ :code:`"`\ ') will be treated as a single argument, regardless of how many spaces or tab characters (if any) might be embedded within the quotation characters. #. On Windows systems, single-quote, or apostrophe, characters ('\ :code:`'`\ ') will be treated just like any other data character and will \ *not*\ delineate argument strings. .. index:: single:ARGUMENT-VALUE #. By accepting from \ \ :code:`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 \ :code:`ARGUMENT-NUMBER`\ option on the \ :code:`DISPLAY`\ statement ( :ref:`DISPLAYAUPONACOMMAND-LINE`). Parsing of arguments will be conducted according to the rules set forth above. #. The optional \ :code:`ON EXCEPTION`\ and \ :code:`NOT ON EXCEPTION`\ clauses may be used to detect and react to the failure or success, respectively, of an attempt to retrieve an \ :code:`ARGUMENT-VALUE`\ . :ref:`ONAEXCEPTIONAAANOTAONAEXCEPTION`, for additional information. .. index:: single:ACCEPT FROM ENVIRONMENT .. _ACCEPTAFROMAENVIRONMENT: 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 \ :code:`ACCEPT`\ statement is used to retrieve environment variable values. #. The reserved word \ :code:`ON`\ is optional and may be omitted. The presence or absence of this word has no effect upon the program. .. index:: single:ENVIRONMENT-NAME .. index:: single:ENVIRONMENT-VALUE #. By accepting from \ \ :code:`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 \ \ :code:`ENVIRONMENT-NAME`\ register. A value may be placed into the \ :code:`ENVIRONMENT-NAME`\ register using the \ :code:`ENVIRONMENT-NAME`\ option of the \ :code:`DISPLAY`\ statement ( :ref:`DISPLAYAUPONAENVIRONMENT-NAME`). .. index:: single:ENVIRONMENT #. A simpler approach to retrieving an environment variables value is to use the \ \ :code:`ENVIRONMENT`\ option, where you specify the environment variable whose value is to be retrieved right on the \ :code:`ACCEPT`\ statement itself. #. The optional \ :code:`ON EXCEPTION`\ and \ :code:`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. :ref:`ONAEXCEPTIONAAANOTAONAEXCEPTION`, for additional information. .. index:: single:ACCEPT data-item .. _ACCEPTAdata-item: 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 ] ~~~~~~~~~~ .. index:: single:CONVERSION .. index:: single:MODE IS BLOCK .. index:: single:FROM CRT The \ \ :code:`FROM CRT`\ , \ \ :code:`MODE IS BLOCK`\ and \ \ :code:`CONVERSION`\ clauses are syntactically recognized but are otherwise non-functional. This format of the \ :code:`ACCEPT`\ statement is used to retrieve data from a working storate item or a formatted console window screen. #. The reserved words \ :code:`AFTER`\ , \ :code:`IS`\ , \ :code:`NUMBER`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The reserved words \ :code:`COLUMN`\ , \ :code:`COL`\ and \ :code:`POSITION`\ are interchangeable. #. The reserved words \ :code:`TIMEOUT`\ and \ :code:`TIME-OUT`\ are interchangeable. #. If is defined in the \ :code:`SCREEN SECTION`\ ( :ref:`SCREENASECTION`), any \ :code:`AT`\ , , \ :code:`LOWER`\ , \ :code:`UPPER`\ or \ :code:`SCROLL`\ clauses will be ignored. In these cases, an implied \ :code:`DISPLAY`\ ( :ref:`DISPLAYAdata-item`) of will occur before input is accepted. Coding an explicit \ :code:`DISPLAY identifier-1`\ before an \ :code:`ACCEPT identifier-1`\ is redundant and will incur the performance penalty of painting the screen contents twice. #. The various \ :code:`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: #. The \ :code:`LINE`\ and \ :code:`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. #. The or value, if specified, must be a four- or six-digit value with the 1\ :sup:`st`\ 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 \ :code:`ACCEPT`\ . #. \ :code:`WITH`\ options (including the various individual ) should be coded only once. #. The following clauses are allowed on the \ :code:`ACCEPT`\ statement; these are the same as those allowed for \ :code:`SCREEN SECTION`\ data items. A particular may be used only once in any \ :code:`ACCEPT`\ : * \ :code:`AUTO`\ ( :ref:`AUTO`), \ :code:`AUTO-SKIP`\ ( :ref:`AUTO-SKIP`), \ :code:`AUTOTERMINATE`\ ( :ref:`AUTOTERMINATE`), \ :code:`TAB`\ * \ :code:`BACKGROUND-COLOR`\ ( :ref:`BACKGROUND-COLOR`) * \ :code:`BEEP`\ ( :ref:`BEEP`), \ :code:`BELL`\ ( :ref:`BELL`) * \ :code:`BEFORE TIME`\ ( :ref:`BEFOREATIME`) * \ :code:`BLINK`\ ( :ref:`BLINK`) * \ :code:`FOREGROUND-COLOR`\ ( :ref:`FOREGROUND-COLOR`) * \ :code:`FULL`\ ( :ref:`FULL`), \ :code:`LENGTH-CHECK`\ ( :ref:`LENGTH-CHECK`) * \ :code:`HIGHLIGHT`\ ( :ref:`HIGHLIGHT`) * \ :code:`LEFTLINE`\ ( :ref:`LEFTLINE`) * \ :code:`LOWER`\ ( :ref:`LOWER`) * \ :code:`LOWLIGHT`\ ( :ref:`LOWLIGHT`) * \ :code:`NO UPDATE`\ ( :ref:`NOAUPDATE`) * \ :code:`OVERLINE`\ ( :ref:`OVERLINE`) * \ :code:`PROMPT`\ ( :ref:`PROMPT`) * \ :code:`PROTECTED`\ ( :ref:`PROTECTED`) * \ :code:`REQUIRED`\ ( :ref:`REQUIRED`), \ :code:`EMPTY-CHECK`\ ( :ref:`EMPTY-CHECK`) * \ :code:`REVERSE-VIDEO`\ ( :ref:`REVERSE-VIDEO`) * \ :code:`SCROLL DOWN`\ ( :ref:`SCROLLADOWN`) * \ :code:`SCROLL UP`\ ( :ref:`SCROLLAUP`) * \ :code:`SIZE`\ ( :ref:`SIZE`) * \ :code:`SECURE`\ ( :ref:`SECURE`), \ :code:`NO-ECHO`\ ( :ref:`NO-ECHO`) * \ :code:`TIME OUT`\ ( :ref:`TIMEAOUT`) * \ :code:`UPDATE`\ ( :ref:`UPDATE`) * \ :code:`UPPER`\ ( :ref:`UPPER`) * \ :code:`UNDERLINE`\ ( :ref:`UNDERLINE`) #. \ :code:`CONTROL`\ ( :ref:`CONTROL`) .. index:: single:SCROLL #. The \ \ :code:`SCROLL`\ option will cause the entire contents of the screen to be scrolled \ :code:`UP`\ or \ :code:`DOWN`\ by the specified number of lines before any value is displayed on the screen. It is syntactically allowable to specify a \ :code:`SCROLL UP`\ clause as well as a \ :code:`SCROLL DOWN`\ clause. In such an instance, it is the last one specified that will be honoured. If no \ :code:`LINES`\ specification is made, \ :code:`1 LINE`\ will be assumed. .. index:: single:TIMEOUT #. The \ \ :code:`TIMEOUT`\ option will cause the \ :code:`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. .. index:: single:UPDATE #. The \ \ :code:`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 \ :code:`-std=default`\ . For more information see `cobc - The GnuCOBOL Compiler `_ option switches) and :ref:`CompilerAConfigurationAFiles`. #. This format of the \ :code:`ACCEPT`\ statement will be terminated by any of the following events: #. When the \ :code:`Enter`\ key is pressed. #. Expiration of the \ :code:`TIMEOUT`\ timer --- this will be treated as if the \ :code:`Enter`\ key had been pressed with no data being entered. #. When a function key (\ :code:`F`\ ) is pressed. .. index:: single:Environment Variables, COB_SCREEN_EXCEPTIONS .. index:: single:COB_SCREEN_EXCEPTIONS Environment Variable #. The pressing of the \ :code:`PgUp`\ or \ :code:`PgDn`\ keys, if the \ \ run-time environment variable ( :ref:`RunATimeAEnvironmentAVariables`) is set to any non-blank value. .. index:: single:Environment Variables, COB_SCREEN_EXCEPTIONS .. index:: single:COB_SCREEN_EXCEPTIONS Environment Variable .. index:: single:Environment Variables, COB_SCREEN_ESC .. index:: single:COB_SCREEN_ESC Environment Variable #. The pressing of the \ :code:`Esc`\ key if \ *both*\ the \ \ run-time environment variable as well as \ \ run-time environment variable are set to any non-blank value. #. The pressing of the \ :code:`Up-arrow`\ , \ :code:`Down-Arrow`\ or \ :code:`PrtSc`\ (Print Screen) keys. These keys are not detectable on Windows systems, however. #. The following apply when is defined in the \ :code:`SCREEN SECTION`\ : #. Alphanumeric data entered into or any screen data item subordinate to it \ *must*\ be consistent with the \ :code:`PICTURE`\ ( :ref:`PICTURE`) clause of that item. This will be enforced at runtime by the \ :code:`ACCEPT`\ statement. #. If or any screen data item subordinate to it are defined as numeric, entered data must be acceptable as \ :code:`NUMVAL`\ intrinsic function ( :ref:`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. #. If or any screen data item subordinate to it are defined as numeric edited, entered data must be acceptable as \ :code:`NUMVAL-C`\ intrinsic function ( :ref:`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. #. The following apply when is \ *not*\ defined in the \ :code:`SCREEN SECTION`\ : #. Alphanumeric data entered into \ *should*\ be consistent with the \ :code:`PICTURE`\ ( :ref:`PICTURE`) clause of that item, although that will not be enforced by the \ :code:`ACCEPT`\ statement. You may use \ :code:`Class Conditions`\ ( :ref:`ClassAConditions`) after the data is accepted to enforce the data type. #. If is defined as numeric, entered data must be acceptable as \ :code:`NUMVAL`\ intrinsic function ( :ref:`NUMVAL`) input (no decimal points are allowed, however). The value stored into will be as if the input were passed to that function. #. If is defined as numeric edited, entered data must be acceptable as \ :code:`NUMVAL-C`\ intrinsic function ( :ref:`NUMVAL-C`) input (again, no decimal points are allowed). The value stored into will be as if the input were passed to that function. #. The optional \ :code:`ON EXCEPTION`\ and \ :code:`NOT ON EXCEPTION`\ clauses may be used to detect and react to the failure or success, respectively, of the screen I/O attempt. :ref:`ONAEXCEPTIONAAANOTAONAEXCEPTION`, for additional information. After this format of the \ :code:`ACCEPT`\ statement is executed, the program's \ :code:`CRT STATUS`\ ( :ref:`SPECIAL-NAMES`) identifier will be populated with one of the following: .. index:: single:CRT STATUS Codes .. _CRTASTATUSACodes: * Code Meaning * 0000 \ :code:`ENTER`\ key pressed * 1001--1064 \ :code:`F1`\ --\ :code:`F64`\ , respectively, were pressed * 2001 \ :code:`PgUp`\ was pressed * 2002 \ :code:`PgDn`\ was pressed * 2003 \ :code:`Up-Arrow`\ was pressed * 2004 \ :code:`Down-Arrow`\ was pressed * 2005 \ :code:`Esc`\ was pressed * 2006 \ :code:`PrtSc`\ (Print Screen) was pressed * 2007 \ :code:`Tab`\ * 2008 \ :code:`Back Tab`\ * 2009 \ :code:`Key Left`\ * 2010 \ :code:`Key Right`\ * 2011 \ :code:`Insert`\ Key on accept omitted * 2012 \ :code:`Delete`\ Key on accept omitted * 2013 \ :code:`Backspace`\ Key on accept omitted * 2014 \ :code:`Home`\ Key on accept omitted * 2015 \ :code:`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 #. The actual key pressed to generate a function key (\ :code:`F`\ ) 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", \ :code:`F1`\ --\ :code:`F12`\ are the actual F-keys on the PC keyboard, \ :code:`F<13>`\ --\ :code:`F<24>`\ are entered by shifting the F-keys, \ :code:`F<25>`\ --\ :code:`F<36>`\ are entered by holding Ctrl while pressing an F-key and \ :code:`F<37>`\ --\ :code:`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 \ :code:`F<1>`\ --\ :code:`F<12>`\ keys as the actual \ :code:`F<1>`\ --\ :code:`F<12>`\ , while shifted F-keys will enter \ :code:`F<11>`\ --\ :code:`F<2>`\ 0. With Cygwin/NCurses, Ctrl- and Alt-modified F-keys aren't recognized, nor are \ :code:`Shift-F<11>`\ or \ :code:`Shift-F<12>`\ . Mouse Key codes are populated only if mouse management has been enabled. To enable mouse it is first necessary to set \ :code:`COB_MOUSE_FLAGS`\ (either externally via terminal command, or internally via \ :code:`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 . #. 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). #. The cursor or mouse position will be returned as well. The position is expressed as row and column (rrcc or rrrccc). #. 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. #. The optional \ :code:`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 \ :code:`EXCEPTION-STATUS`\ . .. index:: single:CONTROL #. \ \ :code:`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 | +-------------------+------------------------------------------+ #. 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 | +--------+--------------+-------------+ #. 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 | +-------------------------+--------+ #. You may also specify high intensity by adding "8" to the foreground color value. .. index:: single:ACCEPT FROM DATE/TIME .. _ACCEPTAFROMADATEATIME: 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 \ :code:`ACCEPT`\ statement is used to retrieve the current system date, time or current day of the week and store it into a data item. #. The data retrieved from the system and the format in which it is structured will vary, as follows: * Syntax Data Retrieved Format * \ :code:`DATE`\ Current date in Gregorian form yymmdd * \ :code:`DATE YYYYMMDD`\ Current date in Gregorian form yyyymmdd * \ :code:`DAY`\ Current date in Julian form yyddd * \ :code:`DAY YYYYDDD`\ Current date in Julian form yyyyddd * \ :code:`DAY-OF-WEEK`\ Current day within a week where 1 = Monday.., 7 = Sunday d * \ :code:`TIME`\ Time, including hundredths of a second (n) hhmmssnn * \ :code:`MICROSECOND-TIME`\ Time, including micro seconds (u) hhmmssuuuuuu #. When using one of \ :code:`--std=acu`\ or \ :code:`--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). #. Consider using the standard \ :code:`FUNCTION FORMATTED-CURRENT-DATE`\ if you need a high precision (up to eight decimal places for fractional seconds). .. index:: single:ACCEPT FROM Screen-Info .. _ACCEPTAFROMAScreen-Info: 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 \ :code:`ACCEPT`\ statement is used to retrieve information about the console window or about the user's interactions with it. #. The reserved words \ :code:`LINES`\ and \ :code:`LINE-NUMBER`\ are interchangeable. #. The reserved words \ :code:`COLS`\ and \ :code:`COLUMNS`\ are interchangeable. .. index:: single:COLUMNS .. index:: single:LINES #. The following points pertain to the use of the \ \ :code:`LINES`\ and \ \ :code:`COLUMNS`\ options: .. index:: single:COLUMNS .. index:: single:LINES #. The \ \ :code:`LINES`\ and \ \ :code:`COLUMNS`\ options will retrieve the respective components of the size of the console display. #. 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 (\ :code:`COLUMNS`\ ) or vertical (\ :code:`LINES`\ ) character counts --- not pixels. #. When the system is not running a windowing environment, the physical console screen attributes will be returned. #. Values of 0 will be returned if GnuCOBOL was not generated to include screen I/O. #. See the documentation on the \ :code:`CBL_GET_SCR_SIZE`\ built-in system subroutine ( :ref:`CBLAGETASCRASIZE`) for another way to retrieve this information. .. index:: single:ESCAPE KEY #. The \ \ :code:`ESCAPE KEY`\ option may be used after the \ :code:`ACCEPT FROM Screen-Info`\ statement ( :ref:`ACCEPTAFROMAScreen-Info`) has executed. The result returned will be the four-digit \ :code:`CRT STATUS`\ ( :ref:`SPECIAL-NAMES`) identifier value. :ref:`CRT STATUS Codes `, for the specific code values. .. index:: single:ACCEPT FROM Runtime-Info .. _ACCEPTAFROMARuntime-Info: 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 \ :code:`ACCEPT`\ statement is used to retrieve run-time information such as the most-recent error exception code and the current user's user name. .. index:: single:EXCEPTION STATUS #. The following points pertain to the use of the \ \ :code:`EXCEPTION STATUS`\ option: #. must be defined as a \ :code:`PIC X(4)`\ item. #. :ref:`Error Exception Codes `, for a complete list of the exception codes and their meanings. #. An alternative to the use of \ :code:`ACCEPT FROM Runtime-Info`\ is to use the \ :code:`EXCEPTION-STATUS`\ intrinsic function ( :ref:`EXCEPTION-STATUS`). .. index:: single:USER NAME #. The following points pertain to the use of the \ \ :code:`USER NAME`\ option: #. 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. #. should be defined large enough to receive the longest user-name on the system. #. If insufficient space is allocated, the returned value will be truncated. #. If excess space is allocated, the returned value will be padded with spaces (to the right). .. index:: single:ACCEPT OMITTED .. _ACCEPTAOMITTED: 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 \ :code:`ACCEPT`\ statement will wait for a keyboard event that terminates input; function keys, or Enter/Return, among others. CRT STATUS (COB-CRT-STATUS \ :code:`CRT STATUS`\ ( :ref:`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. #. 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 #. You can use extended attributes, useful for setting timeouts or positioning. .. index:: single:ACCEPT FROM EXCEPTION STATUS .. _ACCEPTAFROMAEXCEPTIONASTATUS: 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 \ :code:`ACCEPT`\ statement will receive the status for any exceptions resulting from a previous valid verb. #. 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 .. index:: single:ADD .. _ADD: 7.8.2 ADD ~~~~~~~~~ .. index:: single:ADD TO .. _ADDATO: 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 \ :code:`ADD`\ statement generates an intermediate arithmetic sum of the values of all and ) items. The value of each will be replaced, in turn, by the sum of that s value and the intermediate sum. #. The reserved words \ :code:`IS`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. Both and must be numeric unedited data items while must be a numeric literal. #. An data item may also be coded as an . Note, however, that the value of such a data item will therefore be included \ *twice*\ in the result. #. The contents of each will remain unchanged by this statement. #. The optional \ :code:`ROUNDED`\ ( :ref:`ROUNDED`) clause available to each will control how non-integer results will be saved. #. The optional \ :code:`ON SIZE ERROR`\ and \ :code:`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 with an insufficient number of digit positions available to the left of any implied decimal point. :ref:`ONASIZEAERRORAAANOTAONASIZEAERROR`, for additional information. .. index:: single:ADD GIVING .. _ADDAGIVING: 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 \ :code:`ADD`\ statement generates the arithmetic sum of the values of all , ) and (if any) items and then saves that sum to each . #. The reserved words \ :code:`IS`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. Both and must be numeric unedited data items while must be a numeric literal; may be either a numeric or numeric edited data item. #. An or data item may be used as an , if desired. #. The contents of each and will remain unchanged by this statement, unless they happen to also be specified as an . #. The current value in each at the start of the statement's execution is irrelevant, since the contents of each will simply be replaced with the computed sum. #. The optional \ :code:`ROUNDED`\ ( :ref:`ROUNDED`) clause available to each will control how non-integer results will be saved. #. The optional \ :code:`ON SIZE ERROR`\ and \ :code:`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 with an insufficient number of digit positions available to the left of any implied decimal point. :ref:`ONASIZEAERRORAAANOTAONASIZEAERROR`, for additional information. .. index:: single:ADD CORRESPONDING .. _ADDACORRESPONDING: 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 \ :code:`ADD`\ statement generates code equivalent to individual \ :code:`ADD TO`\ ( :ref:`ADDATO`) statements for corresponding matches of data items found subordinate to the two identifiers. #. The reserved words \ :code:`IS`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. Both and must be group items. #. :ref:`CORRESPONDING`, for information on how corresponding matches will be found between and . #. The optional \ :code:`ROUNDED`\ ( :ref:`ROUNDED`) clause available to each will control how non-integer results will be saved. #. The optional \ :code:`ON SIZE ERROR`\ and \ :code:`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 with an insufficient number of digit positions available to the left of any implied decimal point. :ref:`ONASIZEAERRORAAANOTAONASIZEAERROR`, for additional information. .. index:: single:ALLOCATE .. _ALLOCATE: 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 \ :code:`ALLOCATE`\ statement is used to dynamically allocate memory at run-time. #. The reserved words \ :code:`INITIALIZED`\ and \ :code:`INITIALISED`\ are interchangeable. #. If is specified, the RETURNING phrase may be omitted; otherwise, the RETURNING phrase shall be specified. #. If used, must be an arithmetic expression with a non-zero positive integer value and the RETURNING phrase must be specified. #. If used, should be an 01-level item defined in working-storage or local-storage with the \ :code:`BASED`\ ( :ref:`BASED`) attribute. It may be an 01 item defined in the linkage section without the \ :code:`BASED`\ attribute, but using such a data item is not recommended. #. If used, should be a \ :code:`POINTER`\ ( :ref:`USAGE`) data item. .. index:: single:RETURNING #. The optional \ \ :code:`RETURNING`\ clause will return the address of the allocated memory block into the specified \ :code:`USAGE POINTER`\ 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 \ :code:`FREE`\ ( :ref:`FREE`) statement is ever issued against . .. index:: single:INITIALIZED #. When the option is used in conjunction with \ \ :code:`INITIALIZED`\ (or its internationalized alternative \ :code:`INITIALISED`\ ), the allocated memory block will be initialized as if an \ :code:`INITIALIZE WITH FILLER ALL TO VALUE THEN TO DEFAULT`\ ( :ref:`INITIALIZE`) were executed. #. When the \ :code:` CHARACTERS`\ option is used, \ :code:`INITIALIZED`\ will initialize the allocated memory block to binary zeros. If \ :code:`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. #. 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 \ :code:`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 #. With this form My-01-Item can either be defined with the \ :code:`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. #. Referencing a \ :code:`BASED`\ data item either before its storage has been allocated or after its storage has been released (via the \ :code:`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. .. index:: single:ALTER .. _ALTER: 7.8.4 ALTER ~~~~~~~~~~~ ALTER Syntax :: ALTER procedure-name-1 TO PROCEED TO procedure-name-2 ~~~~~ ~~ The \ :code:`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 \ :code:`GO TO`\ ( :ref:`SimpleAGOATO`) statement to branch to a spot in the program different than where the \ :code:`GO TO`\ statement was originally compiled for. #. The reserved words \ :code:`PROCEED`\ and \ :code:`TO`\ (the one \ *after*\ \ :code:`PROCEED`\ ) are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. must contain only a single statement, and that statement must be a simple \ :code:`GO TO`\ . #. The effect of this statement will be as if the generated machine-language code for the \ :code:`GO TO`\ statement in is changed so that the \ :code:`GO TO`\ statement now transfers control to , rather than to whatever procedure name was specified in the program source code. #. Support for the \ :code:`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 \ :code:`ALTER`\ . #. 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 \ :code:`ALTER`\ in new programs is \ **STRONGLY**\ discouraged. .. index:: single:CALL .. _CALL: 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 \ :code:`CALL`\ statement is used to transfer control to a subroutine. :ref:`Sub-Programming`, for the specifics of using subprograms with GnuCOBOL programs. #. The reserved words \ :code:`BY`\ , \ :code:`IS`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The reserved words \ :code:`EXCEPTION`\ and \ :code:`OVERFLOW`\ are interchangeable. #. The reserved words \ :code:`GIVING`\ and \ :code:`RETURNING`\ are interchangeable. #. The expectation is that the subroutine will eventually return control back to the calling program, at which point the \ :code:`CALL`\ ing program will resume execution starting with the statement immediately following the \ :code:`CALL`\ . Subprograms are not required to return to their callers, however, and are free to halt program execution if they wish. .. index:: single:STDCALL .. index:: single:STATIC #. The / \ \ :code:`STATIC`\ / \ \ :code:`STDCALL`\ option, if used, affects the linkage conventions that will be used to the subroutine being called, as follows: * \ :code:`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. * \ :code:`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 \ :code:`CALL`\ . Subroutines written in GnuCOBOL do not need this option. * allows a custom defined calling convention to be used. Such mnemonic names are defined using the \ :code:`CALL-CONVENTION`\ ( :ref:`SPECIAL-NAMES`) clause. That clause associates a decimal integer value with 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. .. index:: single:Special Registers, RETURN-CODE .. index:: single:RETURN-CODE Special Register * 2 Yes The \ \ \ :code:`RETURN-CODE`\ special register ( :ref:`SpecialARegisters`) will be updated in addition to any \ :code:`RETURNING`\ or \ :code:`GIVING`\ data item. The \ :code:`RETURN-CODE`\ special register will not be updated (but any \ :code:`RETURNING`\ or \ :code:`GIVING`\ data item still will). * 3 Yes If \ :code:`CALL `\ 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 \ :code:`CALL `\ 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 \ :code:`STDCALL`\ convention will not be used. The \ :code:`STDCALL`\ convention, required to use the Microsoft Win32 API, will be used. Using the \ :code:`STATIC`\ option on a \ :code:`CALL`\ statement is equivalent to using \ :code:`CALL-CONVENTION 8`\ (only bit 3 set). Using the \ :code:`STDCALL`\ option on a \ :code:`CALL`\ statement is equivalent to using \ :code:`CALL CONVENTION 64`\ (only bit 6 set). #. The value of or is the entry-point of the subprogram you wish to call. #. When you call a subroutine using , you are forcing the runtime system to call a dynamically-loadable subprogram. The contents of 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 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). .. index:: single:Environment Variables, COB_PRE_LOAD .. index:: single:COB_PRE_LOAD Environment Variable #. 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 ( :ref:`RunATimeAEnvironmentAVariables`). If used, this will only pre-load those modules invoked via \ :code:`CALL `\ , as the runtime contents of cannot be predicted. #. If the subprogram being called is a GnuCOBOL program, and if that program had the \ :code:`INITIAL`\ ( :ref:`IDENTIFICATIONADIVISION`) attribute specified on its \ :code:`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 \ :code:`INITIAL`\ . .. index:: single:USING #. The \ \ :code:`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 \ :code:`BY`\ clause (if any) coded (or implied) for that argument, as follows: .. index:: single:BY REFERENCE * \ :code:`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. .. index:: single:BY CONTENT * \ :code:`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. .. index:: single:BY VALUE * \ :code:`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 \ :code:`BY`\ clause, the most-recently encountered \ :code:`BY`\ specification on that \ :code:`CALL`\ statement will be assumed. If the first argument specified on a \ :code:`CALL`\ lacks a \ :code:`BY`\ clause, \ :code:`BY REFERENCE`\ will be assumed. #. 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 \ :code:`COB_MAX_FIELD_PARAMS`\ in the :file:`call.c` file (found in the :file:`libcob` folder) as well as the last shown \ :code:`#if MAX_CALL_FIELD_PARAMS`\ statement before you run :command:`make` to build the compiler and run-time library. .. index:: single:RETURNING #. The \ \ :code:`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 \ :code:`CALL`\ , the subroutine should include a \ :code:`RETURNING`\ ( :ref:`PROCEDUREADIVISIONARETURNING`) clause on its procedure division header. Of course, a subroutine may pass a value of any kind back in any argument passed \ :code:`BY REFERENCE`\ . #. The optional \ :code:`ON OVERFLOW`\ and \ :code:`NOT ON OVERFLOW`\ clauses (or \ :code:`ON EXCEPTION`\ and \ :code:`NOT ON EXCEPTION`\ --- they are interchangeable) may be used to detect and react to the failure or success, respectively, of an attempt to \ :code:`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. :ref:`ONAOVERFLOWAAANOTAONAOVERFLOW`, for additional information. #. Call also supports using an entry point stored in a \ :code:`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 \ :code:`PROGRAM-POINTER`\ will be just that little bit faster. To set a \ :code:`PROGRAM-POINTER`\ use \ :code:`SET TO ENTRY ""`\ (or get the address from an API, and take part in callback programming). #. An extension of \ :code:`CALL`\ allows a call to a which is preset using \ :code:`SET TO ENTRY `\ . Additional the \ :code:`RETURNING`\ clause may return a data pointer or a \ :code:`PROGRAM-POINTER`\ .. index:: single:CANCEL .. _CANCEL: 7.8.6 CANCEL ~~~~~~~~~~~~ CANCEL Syntax :: CANCEL { literal-1 }... ~~~~~~ { identifier-1 } The \ :code:`CANCEL`\ statement unloads the dynamically-loadable subprogram module containing the entry-point specified as or from memory. #. If a dynamically-loadable module unloaded by the \ :code:`CANCEL`\ statement is subsequently re-executed, all data division storage for that module will once again be in its initial state. .. index:: single:Environment Variables, COB_PHYSICAL_CANCEL .. index:: single:COB_PHYSICAL_CANCEL Environment Variable #. Whether the \ :code:`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 ( :ref:`RunATimeAEnvironmentAVariables`). .. index:: single:CLOSE .. _CLOSE: 7.8.7 CLOSE ~~~~~~~~~~~ CLOSE Syntax :: CLOSE { file-name-1 [ { REEL|UNIT [ FOR REMOVAL ] } ] }... ~~~~~ { ~~~~ ~~~~ ~~~~~~~ } { WITH LOCK } { ~~~~ } { WITH NO REWIND } ~~ ~~~~~~ .. index:: single:NO REWIND .. index:: single:LOCK .. index:: single:REEL The \ \ :code:`REEL`\ , \ \ :code:`LOCK`\ and \ \ :code:`NO REWIND`\ clauses are syntactically recognized but are otherwise non-functional, except for the \ :code:`CLOSE...NO REWIND`\ statement, which will generate a file status of 07 rather than the usual 00 (but take no other action). The \ :code:`CLOSE`\ statement terminates the program's access to the specified file(s). #. The reserved words \ :code:`FOR`\ and \ :code:`WITH`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The reserved words \ :code:`REEL`\ and \ :code:`UNIT`\ are interchangeable. #. The \ :code:`CLOSE`\ statement may only be executed against files that have been successfully opened. #. A successful \ :code:`CLOSE`\ will write any remaining unwritten record buffers to the file (similar to an \ :code:`UNLOCK`\ statement ( :ref:`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. #. When a \ :code:`ORGANIZATION LINE SEQUENTIAL`\ ( :ref:`ORGANIZATIONALINEASEQUENTIAL`) or \ :code:`LINE ADVANCING`\ ( :ref:`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 \ :code:`AFTER ADVANCING`\ ( :ref:`WRITE`) option. .. index:: single:COMMIT .. _COMMIT: 7.8.8 COMMIT ~~~~~~~~~~~~ COMMIT Syntax :: COMMIT ~~~~~~ The \ :code:`COMMIT`\ statement performs an \ :code:`UNLOCK`\ against every currently-open file, but does not close any of the files. See the \ :code:`UNLOCK`\ statement ( :ref:`UNLOCK`) for additional details. .. index:: single:COMPUTE .. _COMPUTE: 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 \ :code:`COMPUTE`\ statement provides a means of easily performing complex arithmetic operations with a single statement, instead of using cumbersome and possibly confusing sequences of \ :code:`ADD`\ , \ :code:`SUBTRACT`\ , \ :code:`MULTIPLY`\ and \ :code:`DIVIDE`\ statements. \ :code:`COMPUTE`\ also allows the use of exponentiation --- an arithmetic operation for which no other statement exists in COBOL. #. The reserved words \ :code:`IS`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The reserved word \ :code:`EQUAL`\ is interchangeable with the use of '\ :code:`=`\ '. #. Each must be a numeric or numeric-edited data item. #. The optional \ :code:`ROUNDED`\ ( :ref:`ROUNDED`) clause available to each will control how non-integer results will be saved. #. :ref:`ArithmeticAExpressions`, for more information on arithmetic expressions. #. The optional \ :code:`ON SIZE ERROR`\ and \ :code:`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 with an insufficient number of digit positions available to the left of any implied decimal point or attempting to divide by zero. :ref:`ONASIZEAERRORAAANOTAONASIZEAERROR`, for additional information. .. index:: single:CONTINUE .. _CONTINUE: 7.8.10 CONTINUE ~~~~~~~~~~~~~~~ CONTINUE Syntax :: CONTINUE ~~~~~~~~ { identifier-1 } CONTINUE AFTER { literal-1 } SECONDS ~~~~~~~~ ~~~~~ { arithmetic-expression-1 } ~~~~~~~ The \ :code:`CONTINUE`\ statement is a no-operation statement that may be coded anywhere an imperative statement ( :ref:`Imperative Statement `) may be coded. #. The \ :code:`CONTINUE`\ statement has no effect on the execution of the program. #. This statement (perhaps in combination with an appropriate comment or two) makes a convenient "place holder" --- particularly in \ :code:`ELSE`\ ( :ref:`IF`) or \ :code:`WHEN`\ ( :ref:`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. #. The optional extension of (AFTER) when used with the \ :code:`CONTINUE`\ statement pauses execution for a specified length of time. .. index:: single:DELETE .. _DELETE: 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 \ :code:`DELETE`\ statement logically deletes a record from a COBOL file. #. The reserved words \ :code:`KEY`\ and \ :code:`RECORD`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The \ :code:`ORGANIZATION`\ of cannot be \ :code:`ORGANIZATION LINE SEQUENTIAL`\ ( :ref:`ORGANIZATIONALINEASEQUENTIAL`). #. The file cannot be a sort/merge work file (a file described using a \ :code:`SD`\ ( :ref:`FileASort-Description`)). #. For files in the \ :code:`SEQUENTIAL`\ access mode, the last input-output statement executed against prior to the execution of the \ :code:`DELETE`\ statement must have been a successfully executed sequential-format \ :code:`READ`\ statement ( :ref:`SequentialAREAD`). That \ :code:`READ`\ will therefore identify the record to be deleted. .. index:: single:RELATIVE KEY #. If is a \ :code:`RELATIVE`\ file whose \ :code:`ACCESS MODE`\ ( :ref:`ORGANIZATIONARELATIVE`) is either \ :code:`RANDOM`\ or \ :code:`DYNAMIC`\ , the record to be deleted is the one whose relative record number is currently the value of the field specified as the files \ \ :code:`RELATIVE KEY`\ in its \ :code:`SELECT`\ statement. .. index:: single:RECORD KEY #. If is an \ :code:`INDEXED`\ file whose \ :code:`ACCESS MODE`\ ( :ref:`ORGANIZATIONAINDEXED`) is \ :code:`RANDOM`\ or \ :code:`DYNAMIC`\ , the record to be deleted is the one whose primary key is currently the value of the field specified as the \ \ :code:`RECORD KEY`\ in the file's \ :code:`SELECT`\ statement. #. The optional \ :code:`INVALID KEY`\ and \ :code:`NOT INVALID KEY`\ clauses may be used to detect and react to the failure or success, respectively, of an attempt to delete a record. :ref:`INVALIDAKEYAAANOTAINVALIDAKEY`, for additional information. #. No \ :code:`INVALID KEY`\ or \ :code:`NOT INVALID KEY`\ clause may be specified for a file who's \ :code:`ACCESS MODE IS SEQUENTIAL`\ . .. index:: single:DISPLAY .. _DISPLAY: 7.8.12 DISPLAY ~~~~~~~~~~~~~~ .. index:: single:DISPLAY UPON device .. _DISPLAYAUPONAdevice: 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 \ :code:`DISPLAY`\ statement displays the specified identifier contents and/or literal values on the system output device specified via the \ :code:`UPON`\ clause. #. The reserved words \ :code:`ON`\ and \ :code:`WITH`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. .. index:: single:UPON #. If no \ \ :code:`UPON`\ clause is specified, \ :code:`UPON CONSOLE`\ will be assumed. If the \ :code:`UPON`\ clause \ *is*\ specified, must be one of the built-in output device names \ :code:`CONSOLE`\ , \ :code:`PRINTER`\ , \ :code:`STDERR`\ , \ :code:`STDOUT`\ , \ :code:`SYSERR`\ , \ :code:`SYSLIST`\ , \ :code:`SYSLST`\ or \ :code:`SYSOUT`\ or a mnemonic name assigned to one of those devices via the \ :code:`SPECIAL-NAMES`\ ( :ref:`SPECIAL-NAMES`) paragraph. When displaying upon the \ :code:`STDERR`\ or \ :code:`SYSERR`\ devices or to a 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 \ :code:`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 \ :code:`CONSOLE`\ , \ :code:`PRINTER`\ , \ :code:`STDOUT`\ , \ :code:`SYSLIST`\ , \ :code:`SYSLST`\ or \ :code:`SYSOUT`\ devices or to a 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 \ :code:`1> filename`\ or simply \ :code:`> filename`\ to the end of the command that executes the program. This applies to both Windows (any type) or Unix versions of GnuCOBOL. .. index:: single:NO ADVANCING #. The \ \ :code:`NO ADVANCING`\ clause, if used, will suppress the carriage-return / line-feed sequence that is normally added to the end of any console display. #. The optional \ :code:`ON EXCEPTION`\ and \ :code:`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. :ref:`ONAEXCEPTIONAAANOTAONAEXCEPTION`, for additional information. .. index:: single:DISPLAY UPON COMMAND-LINE .. _DISPLAYAUPONACOMMAND-LINE: 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 \ :code:`DISPLAY`\ statement may be used to specify the command-line argument number to be retrieved by a subsequent \ :code:`ACCEPT FROM ARGUMENT-VALUE`\ statement ( :ref:`ACCEPTAFROMACOMMAND-LINE`) or to specify a new value for the command-line arguments themselves. #. The reserved word \ :code:`ON`\ is optional and may be omitted. The presence or absence of this word has no effect upon the program. .. index:: single:ARGUMENT-NUMBER #. By displaying a numeric integer value \ :code:`UPON`\ \ \ :code:`ARGUMENT-NUMBER`\ , you will specify which argument (by its relative number) will be retrieved by a subsequent \ :code:`ACCEPT FROM ARGUMENT-VALUE`\ statement. #. Executing a \ :code:`DISPLAY UPON COMMAND-LINE`\ will influence subsequent \ :code:`ACCEPT FROM COMMAND-LINE`\ statements (which will then return the value you displayed), but will not influence subsequent \ :code:`ACCEPT FROM ARGUMENT-VALUE`\ statements --- these will continue to return the original program execution parameters. #. The optional \ :code:`ON EXCEPTION`\ and \ :code:`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. :ref:`ONAEXCEPTIONAAANOTAONAEXCEPTION`, for additional information. .. index:: single:DISPLAY UPON ENVIRONMENT-NAME .. _DISPLAYAUPONAENVIRONMENT-NAME: 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 \ :code:`DISPLAY`\ statement can be used to create or modify environment variables. #. The reserved word \ :code:`ON`\ is optional and may be omitted. The presence or absence of this word has no effect upon the program. #. To create or change an environment variable will require two \ :code:`DISPLAY`\ statements. The following example sets the environment variable \ :code:`MY_ENV_VAR`\ to a value of '\ :code:`Demonstration Value`\ ': :: DISPLAY "MY_ENV_VAR" UPON ENVIRONMENT-NAME DISPLAY "Demonstration Value" UPON ENVIRONMENT-VALUE #. Environment variables created or changed from within GnuCOBOL programs will be available to any sub-shell processes spawned by that program (i.e. \ :code:`CALL 'SYSTEM'`\ ( :ref:`SYSTEM`)) but will not be known to the shell or console window that started the GnuCOBOL program. #. Consider using \ :code:`SET ENVIRONMENT`\ ( :ref:`SETAENVIRONMENT`) in lieu of \ :code:`DISPLAY`\ to set environment variables as it is much simpler. #. The optional \ :code:`ON EXCEPTION`\ and \ :code:`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. :ref:`ONAEXCEPTIONAAANOTAONAEXCEPTION`, for additional information. .. index:: single:DISPLAY data-item .. _DISPLAYAdata-item: 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 ] ~~~~~~~~~~~ .. index:: single:CONVERSION .. index:: single:UPON CRT-UNDER .. index:: single:UPON CRT The \ \ :code:`UPON CRT`\ , \ \ :code:`UPON CRT-UNDER`\ and \ \ :code:`CONVERSION`\ clauses 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 \ :code:`DISPLAY`\ statement presents data onto a formatted screen. #. The reserved words \ :code:`AFTER`\ , \ :code:`LINE`\ , \ :code:`LINES`\ , \ :code:`NUMBER`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The reserved words \ :code:`COLUMN`\ and \ :code:`POSITION`\ are interchangeable. #. The reserved words \ :code:`LINE`\ and \ :code:`LINES`\ are interchangeable. #. If is defined in the \ :code:`SCREEN SECTION`\ ( :ref:`SCREENASECTION`), any \ :code:`AT`\ , and \ :code:`WITH`\ clauses will be ignored. All field definition, cursor positioning and screen control will occur as a result of the screen section definition of . #. The reserved word \ :code:`OMITTED`\ when used, will act to position the cursor or any screen clearance without changing any content of the screen. #. The following points apply if is not defined in the screen section: #. The purpose of the \ :code:`AT`\ clause is to define where on the screen should be displayed. :ref:`ACCEPTAdata-item`, for additional information. #. The purpose of the \ :code:`WITH`\ clause is to define the visual attributes that should be applied to when it is displayed on the screen as well as other presentation-control characteristics. #. The following clauses are allowed on the \ :code:`DISPLAY`\ statement --- these are the same as those allowed for \ :code:`SCREEN SECTION`\ data items. A particular may be used only once in any \ :code:`DISPLAY`\ : * \ :code:`BACKGROUND-COLOR`\ ( :ref:`BACKGROUND-COLOR`) * \ :code:`BEEP`\ ( :ref:`BEEP`), \ :code:`BELL`\ ( :ref:`BELL`) * \ :code:`BLANK`\ ( :ref:`BLANK`) * \ :code:`BLINK`\ ( :ref:`BLINK`) * \ :code:`ERASE`\ ( :ref:`ERASE`) * \ :code:`FOREGROUND-COLOR`\ ( :ref:`FOREGROUND-COLOR`) * \ :code:`HIGHLIGHT`\ ( :ref:`HIGHLIGHT`) * \ :code:`LOWLIGHT`\ ( :ref:`LOWLIGHT`) * \ :code:`OVERLINE`\ ( :ref:`OVERLINE`) * \ :code:`REVERSE-VIDEO`\ ( :ref:`REVERSE-VIDEO`) * \ :code:`UNDERLINE`\ ( :ref:`UNDERLINE`) .. index:: single:CONTROL #. \ \ :code:`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. #. 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. #. 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 | +-------------------+------------------------------------------+ .. index:: single:GRAPHICS #. \ \ :code:`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(Å ) | +-------------------+-----------------------+-----------------------+ #. 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. .. index:: single:COLOUR \ \ :code:`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 | +--------+--------------+-------------+ #. 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 | +-------------------------+--------+ #. 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. #. :ref:`ACCEPTAdata-item`, for additional information on the other \ :code:`WITH`\ clause options. #. The optional \ :code:`ON EXCEPTION`\ and \ :code:`NOT ON EXCEPTION`\ clauses may be used to detect and react to the failure or success, respectively, of the screen I/O attempt. :ref:`ONAEXCEPTIONAAANOTAONAEXCEPTION`, for additional information. When \ :code:`DISPLAY`\ is used with Line and column where multiple variables or literals are used before \ :code:`LINE`\ only the first will be displayed. If this is needed then the use of \ :code:`CONCATENATE`\ to built more than one element together prior to the display, \ *e.g.*\ , \ :code:`DISPLAY FUNCTION CONCATENATE (VARS-1 VARS-2) AT 0201`\ . When \ :code:`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. .. index:: single:DISPLAY data-item (Microsoft v1-v2) .. _DISPLAYAdata-itemAAMicrosoftAv1-v2A: 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 \ :code:`DISPLAY`\ statement presents data onto a formatted screen using the Microsoft format from v1 and v2 compilers (MsDos). .. index:: single:DIVIDE .. _DIVIDE: 7.8.13 DIVIDE ~~~~~~~~~~~~~ .. index:: single:DIVIDE INTO .. _DIVIDEAINTO: 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 \ :code:`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. #. The reserved words \ :code:`IS`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. Both and must be numeric unedited data items and must be a numeric literal. #. A division operation will be performed for each , in turn. Each of the results of those divisions will be saved to the corresponding data item(s). #. Should any be an integer numeric data item, the result computed when that is divided by or will also be an integer --- any remainder from that division will be discarded. #. The optional \ :code:`ROUNDED`\ ( :ref:`ROUNDED`) clause available to each will control how non-integer results will be saved. #. The optional \ :code:`ON SIZE ERROR`\ and \ :code:`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 with an insufficient number of digit positions available to the left of any implied decimal point, or an attempt to divide by zero. :ref:`ONASIZEAERRORAAANOTAONASIZEAERROR`, for additional information. .. index:: single:DIVIDE INTO GIVING .. _DIVIDEAINTOAGIVING: 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 \ :code:`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. #. The reserved words \ :code:`IS`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. Both and must be numeric unedited data items while both and must be numeric (edited or unedited) data items. #. Both and must be numeric literals. .. index:: single:REMAINDER #. If the \ \ :code:`REMAINDER`\ clause is coded, there may be only one specified. #. The result obtained when the value of or is divided by the value of or is computed; this result is then moved into each , in turn, applying the rules defined by the \ :code:`ROUNDED`\ ( :ref:`ROUNDED`) clause (if any) for that to the move. #. If a \ :code:`REMAINDER`\ clause is specified, the value of the one and only (as stated earlier, if \ :code:`REMAINDER`\ is specified there may only be a single coded on the statement) after it was assigned a value according to the previous rule will be multiplied by the value of or ; that result is then subtracted from the value of or and \ *that*\ result is the value which is moved to . #. The optional \ :code:`ON SIZE ERROR`\ and \ :code:`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 with an insufficient number of digit positions available to the left of any implied decimal point, or an attempt to divide by zero. :ref:`ONASIZEAERRORAAANOTAONASIZEAERROR`, for additional information. .. index:: single:DIVIDE BY GIVING .. _DIVIDEABYAGIVING: 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 \ :code:`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. #. The reserved words \ :code:`IS`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. Both and must be numeric unedited data items while both and must be numeric (edited or unedited) data items. #. Both and must be numeric literals. .. index:: single:REMAINDER #. If the \ \ :code:`REMAINDER`\ clause is coded, there may be only one specified. #. The result obtained when the value of or is divided by the value of or is computed; this result is then moved into each , in turn, applying the rules defined by the \ :code:`ROUNDED`\ ( :ref:`ROUNDED`) clause (if any) for that to the move. #. If a \ :code:`REMAINDER`\ clause is specified, the value of the one and only (as stated earlier, if \ :code:`REMAINDER`\ is specified there may only be a single coded on the statement) after it was assigned a value according to the previous rule will be multiplied by the value of or ; that result is then subtracted from the value of or and \ *that*\ result is the value which is moved to . #. The optional \ :code:`ON SIZE ERROR`\ and \ :code:`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 with an insufficient number of digit positions available to the left of any implied decimal point, or an attempt to divide by zero. :ref:`ONASIZEAERRORAAANOTAONASIZEAERROR`, for additional information. .. index:: single:ENTRY .. _ENTRY: 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 \ :code:`ENTRY`\ statement is used to define an alternate entry-point into a subroutine, along with the arguments that subroutine will be expecting. #. The reserved word \ :code:`BY`\ is optional and may be omitted. The presence or absence of this word has no effect upon the program. #. You may not use an \ :code:`ENTRY`\ statement in a nested subprogram, nor may you use it in any form of user-defined function. .. index:: single:USING #. The \ \ :code:`USING`\ clause defines the arguments the subroutine entry-point supports. This list of arguments must match up against the \ :code:`USING`\ clause of any \ :code:`CALL`\ statement that will be invoking the subroutine using this entry-point. #. Each specified on the \ :code:`ENTRY`\ statement must be defined in the linkage section of the subroutine in which the \ :code:`ENTRY`\ statement exists. #. The value will specify the entry-point name of the subroutine. It must be specified exactly on \ :code:`CALL`\ statements (with regard to the use of upper- and lower-case letters) as it is specified on the \ :code:`ENTRY`\ statement. .. index:: single:VALUE .. index:: single:CONTENT .. index:: single:REFERENCE #. The meaning of \ \ :code:`REFERENCE`\ , \ \ :code:`CONTENT`\ and \ \ :code:`VALUE`\ are the same as the equivalent specifications on the \ :code:`CALL`\ statement ( :ref:`CALL`). Whatever specification will be used for an argument on the \ :code:`CALL`\ to this entry-point should match the specification used in the corresponding . The same rules regarding the presence or absence of a \ :code:`BY`\ clause on a \ :code:`CALL`\ statement apply to the presence or absence of a \ :code:`BY`\ clause on the corresponding argument of the \ :code:`ENTRY`\ statement. #. The with the ENTRY FOR is an GnuCOBOL special purpose extension for use with various GnuCobol tools. .. index:: single:EVALUATE .. _EVALUATE: 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 \ :code:`EVALUATE`\ statement provides a means of defining processing that should take place under any number of mutually-exclusive conditions. #. The reserved words \ :code:`THRU`\ and \ :code:`THROUGH`\ are interchangeable. .. index:: single:WHEN OTHER .. index:: single:WHEN #. There must be at least one \ \ :code:`WHEN`\ clause (in addition to any \ \ :code:`WHEN OTHER`\ clause) specified on any \ :code:`EVALUATE`\ statement. .. index:: single:ALSO #. There must be at least one specified on the \ :code:`EVALUATE`\ statement. Any number of additional clauses may be specified, using the \ \ :code:`ALSO`\ reserved word to separate each from the prior. .. index:: single:WHEN OTHER #. Each \ :code:`WHEN`\ clause (other than the \ \ :code:`WHEN OTHER`\ clause, if any) must have the same number of clauses as there are clauses. .. index:: single:THRU #. When using \ \ :code:`THRU`\ , the values on both sides of the \ :code:`THRU`\ must be the same class (both numeric, both alphanumeric, etc.). #. A is one of the following: #. A Class Condition without a leading ( :ref:`ClassAConditions`). #. A Sign Condition without a leading ( :ref:`SignAConditions`). #. A Relation Condition with nothing to the left of the relational operator ( :ref:`RelationAConditions`). #. At execution time, each on the \ :code:`EVALUATE`\ statement will have its value matched against that of the corresponding on a \ :code:`WHEN`\ clause, in turn, until: #. A \ :code:`WHEN`\ clause has \ *each*\ of its (s) successfully matched by the corresponding ; this will be referred to as the '\ *Selected WHEN clause*\ '. #. The complete list of \ :code:`WHEN`\ clauses (except for the \ :code:`WHEN OTHER`\ clause, if any) has been exhausted. In this case, there is no '\ *Selected WHEN Clause*\ '. #. If a '\ *Selected WHEN Clause*\ ' was identified: #. The ( :ref:`Imperative Statement `) immediately following the '\ *Selected WHEN Clause*\ ' will be executed. If the '\ *Selected WHEN Clause*\ ' is lacking an , the first found after any following \ :code:`WHEN`\ clause will be executed. #. Once the has been executed, or no was found anywhere after the '\ *Selected WHEN Clause*\ ', control will proceed to the statement following the \ :code:`END-EVALUATE`\ or, if there is no \ :code:`END-EVALUATE`\ , the first statement that follows the next period. If, however, the included a \ :code:`GO TO`\ statement, and that \ :code:`GO TO`\ was executed, then control will transfer to the procedure named on the \ :code:`GO TO`\ instead. #. If no '\ *Selected WHEN Clause*\ ' was identified: #. The \ :code:`WHEN OTHER`\ clause's will be executed, if such a clause was coded. #. Control will then proceed to the statement following the \ :code:`END-EVALUATE`\ or the first statement that follows the next period if there is no \ :code:`END-EVALUATE`\ . If,however, the included a \ :code:`GO TO`\ statement, and that \ :code:`GO TO`\ was executed, then control will transfer to the procedure named on the \ :code:`GO TO`\ instead. #. In order for a to match the corresponding on a \ :code:`WHEN`\ clause, at least one of the following must be true: .. index:: single:ANY #. The is \ \ :code:`ANY`\ #. The implied Relation Condition \ :code:` = `\ is \ :code:`TRUE`\ --- :ref:`RelationAConditions`, for the rules on how the comparison will be made. #. The value of the falls within the range of values specified by the \ :code:`THRU`\ clause of the #. If the is a , then the conditional expression that would be represented by coding \ :code:` `\ evaluates to \ :code:`TRUE`\ #. 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! .. index:: single:EXAMINE .. _EXAMINE: 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 \ :code:`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. #. This statement is only available subject to specific dialects being set when running the GnuCOBOL compiler. #. In all cases, the description of identifier must be such that its usage is display (explicitly or implicitly). #. 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. #. 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. #. 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. #. 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). #. 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. #. When the ALL option is used, this count represents the number of occurrences of literal-1. #. 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. #. When the UNTIL FIRST option is used, this count represents all characters encountered before the first occurrence of literal-1. #. Whether Format 2 is used, or the REPLACING option of Format 1, the replacement rules are the same. They are as follows: #. When the ALL option is used, literal-2 is substituted for each occurrence of literal-1. #. 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. #. 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. .. index:: single:EXHIBIT .. _EXHIBIT: 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 \ :code:`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. #. 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. #. The reserved words \ :code:`NAMED`\ , \ :code:`CHANGED`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. 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. #. Literals and identifiers displayed by the EXHIBIT statement are separated by a space on the displayed line. #. Each literal can be any figurative constant other than ALL. #. If the literal is numeric, it must be an unsigned integer. #. 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. #. 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). #. 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). #. 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. #. An EXHIBIT statement is the same as an EXHIBIT NAMED statement. #. ERASE is a display attribute which got into GnuCOBOL when MS-COBOL support was increased, it is not yet implemented. #. The CHANGED clause is not yet implemented but recognised by GnuCOBOL. #. The UPON mnemonic-name-1 clause is not yet implemented but recognised by GnuCOBOL. .. index:: single:EXIT .. _EXIT: 7.8.18 EXIT ~~~~~~~~~~~ EXIT Syntax :: EXIT [ { PROGRAM } [ { RETURNING } ] { identifier-1 } ] ~~~~ [ { GIVING } ] { literal-1 } ] { FUNCTION } ] { ~~~~~~~~ } ] { PERFORM [ CYCLE ] } ] { ~~~~~~~ ~~~~~ } ] { SECTION } ] { ~~~~~~~ } ] { PARAGRAPH } ] ~~~~~~~~~ The \ :code:`EXIT`\ statement is a multi-purpose statement; it may provide a common end point for a series of procedures, exit an in-line \ :code:`PERFORM`\ , paragraph or section or it may mark the logical end of a subprogram, returning control back to the calling program. #. The \ :code:`EXIT PROGRAM`\ statement is not legal anywhere within a user-defined function. #. The \ :code:`EXIT FUNCTION`\ statement cannot be used anywhere within a subroutine. #. Neither \ :code:`EXIT PROGRAM`\ nor \ :code:`EXIT FUNCTION`\ may be used within a \ :code:`USE GLOBAL`\ routine in \ :code:`DECLARATIVES`\ ( :ref:`DECLARATIVES`). #. The following points describe the \ :code:`EXIT`\ statement with none of the optional clauses: #. When this form of an \ :code:`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. #. This usage of the \ :code:`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. <<>> 199-Exit. EXIT. #. In this case, the \ :code:`EXIT`\ statement takes no other run-time action. #. The following points apply to the \ :code:`EXIT PARAGRAPH`\ and \ :code:`EXIT SECTION`\ statements: #. If an \ :code:`EXIT PARAGRAPH`\ statement or \ :code:`EXIT SECTION`\ statement resides in a paragraph \ *within*\ the scope of a procedural \ :code:`PERFORM`\ ( :ref:`ProceduralAPERFORM`), control will be returned back to the \ :code:`PERFORM`\ for evaluation of any \ :code:`TIMES`\ , \ :code:`VARYING`\ and/or \ :code:`UNTIL`\ clauses. #. If an \ :code:`EXIT PARAGRAPH`\ statement or \ :code:`EXIT SECTION`\ statement resides \ *outside*\ the scope of a procedural \ :code:`PERFORM`\ , control simply transfers to the first executable statement in the next paragraph (\ :code:`EXIT PARAGRAPH`\ ) or section (\ :code:`EXIT SECTION`\ ). #. The following shows how the previous example could have been coded without a \ :code:`GO TO`\ by utilizing an \ :code:`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. <<>> #. The following points apply to the \ :code:`EXIT PERFORM`\ and \ :code:`EXIT PERFORM CYCLE`\ statements: #. The \ :code:`EXIT PERFORM`\ and \ :code:`EXIT PERFORM CYCLE`\ statements are intended to be used in conjunction with an in-line \ :code:`PERFORM`\ statement ( :ref:`InlineAPERFORM`). #. An \ :code:`EXIT PERFORM CYCLE`\ statement will terminate the current iteration of the in-line \ :code:`PERFORM`\ , giving control to any \ :code:`TIMES`\ , \ :code:`VARYING`\ and/or \ :code:`UNTIL`\ clauses for them to determine if another cycle needs to be performed. #. An \ :code:`EXIT PERFORM`\ statement will terminate the in-line PERFORM outright, transferring control to the first statement following the \ :code:`END-PERFORM`\ (if there is one) or to the next sentence following the \ :code:`PERFORM`\ if there is no \ :code:`END-PERFORM`\ . #. This last example shows the final modification to the previous examples by using an in-line \ :code:`PERFORM`\ along with \ :code:`EXIT PERFORM`\ and \ :code:`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 <<>> END PERFORM #. The following points apply to the \ :code:`EXIT PROGRAM`\ and \ :code:`EXIT FUNCTION`\ statements: #. The \ :code:`EXIT PROGRAM`\ and \ :code:`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. #. An \ :code:`EXIT PROGRAM`\ statement returns control back to the statement following the \ :code:`CALL`\ ( :ref:`CALL`) of the subprogram. An \ :code:`EXIT FUNCTION`\ statement returns control back to the processing of the statement in the calling program that invoked the user-defined function. #. For \ :code:`EXIT PROGRAM`\ statement usage of \ :code:`RETURNING`\ statement or \ :code:`GIVING`\ statement will provide value defined by indentifer-1 or literal-1 back to the calling routine. #. If executed by a main program, neither the \ :code:`EXIT PROGRAM`\ nor \ :code:`EXIT FUNCTION`\ statements will take any action. #. The COBOL2002 standard has made a common extension to the COBOL language --- the \ :code:`GOBACK`\ statement ( :ref:`GOBACK`) --- a standard language element; the \ :code:`GOBACK`\ statement should be strongly considered as the preferred alternative to both \ :code:`EXIT PROGRAM`\ and \ :code:`EXIT FUNCTION`\ for new subprograms. .. index:: single:FREE .. _FREE: 7.8.19 FREE ~~~~~~~~~~~ FREE Syntax :: FREE { [ ADDRESS OF ] identifier-1 }... ~~~~ ~~~~~~~ The \ :code:`FREE`\ statement releases memory previously allocated to the program by the \ :code:`ALLOCATE`\ statement ( :ref:`ALLOCATE`). #. The \ :code:`ADDRESS OF`\ clause is optional and may be omitted. The presence or absence of this clause has no effect upon the program. #. must have a \ :code:`USAGE`\ ( :ref:`USAGE`) of \ :code:`POINTER`\ , or it must be an 01-level data item with the \ :code:`BASED`\ ( :ref:`BASED`) attribute. #. If is a \ :code:`USAGE POINTER`\ data item and it contains a valid address, the \ :code:`FREE`\ statement will release the memory block the pointer references. In addition, any \ :code:`BASED`\ data items that the pointer was used to provide an address for will become un-based and therefore unusable. If did not contain a valid address, no action will be taken. #. If is a \ :code:`BASED`\ data item and that data item is currently based (meaning it currently has memory allocated to it), its memory is released and will become un-based and therefore unusable. If was not based, no action will be taken. .. index:: single:GENERATE .. _GENERATE: 7.8.20 GENERATE ~~~~~~~~~~~~~~~ GENERATE Syntax :: GENERATE { report-name-1 } ~~~~~~~~ { identifier-1 } The \ :code:`GENERATE`\ statement presents data to a report. #. The following points apply when is specified: #. must be the name of a \ :code:`DETAIL`\ ( :ref:`RWCSALexicon`) report group. #. If necessary, may be qualified with a report name. #. The file in whose \ :code:`FD`\ a \ :code:`REPORT`\ clause exists for the report in which is a detail group must be opened for \ :code:`OUTPUT`\ or \ :code:`EXTEND`\ at the time the \ :code:`GENERATE`\ is executed. :ref:`OPEN`, for information on file open modes. #. The report in which is a \ :code:`DETAIL`\ group must have been successfully initiated via the \ :code:`INITIATE`\ statement ( :ref:`INITIATE`) and not yet terminated via the \ :code:`TERMINATE`\ statement ( :ref:`TERMINATE`) at the time the \ :code:`GENERATE`\ is executed. .. index:: single:summary report .. index:: single:detail report #. If at least one \ :code:`GENERATE`\ statement of this form is executed against a report, the report is said to be a \ \ *detail report*\ . If no \ :code:`GENERATE`\ statements of this form are executed against a report, the report is said to be a \ \ *summary report*\ . #. The following points apply when is specified: #. must be the name of a report having an \ :code:`RD`\ defined for it in the report section. #. There must be at least one \ :code:`CONTROL`\ ( :ref:`RWCSALexicon`) group defined for . #. There cannot be more than one \ :code:`DETAIL`\ group defined for . #. The file in whose \ :code:`FD`\ a \ :code:`REPORT `\ clause exists must be open for \ :code:`OUTPUT`\ or \ :code:`EXTEND`\ at the time the GENERATE is executed. #. must have been successfully initiated (via \ :code:`INITIATE `\ ) and not yet terminated (via TERMINATE) at the time the \ :code:`GENERATE`\ is executed. :ref:`OPEN`, for information on file open modes. .. index:: single:detail report .. index:: single:summary report #. The \ :code:`DETAIL`\ group which is defined for \ *will*\ be processed but will not actually be presented to any report page. This will allow summary processing to take place. If all \ :code:`GENERATE`\ statements are of this form, the report is said to be a \ \ *summary report*\ . If at least one \ :code:`GENERATE `\ is executed, the report is considered to be a \ \ *detail report*\ . #. When the first \ :code:`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 \ :code:`GENERATE`\ statements. #. When, during the processing of a subsequent \ :code:`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. .. index:: single:GOBACK .. _GOBACK: 7.8.21 GOBACK ~~~~~~~~~~~~~ GOBACK Syntax :: GOBACK [ { RETURNING|GIVING { literal-1 } ] ~~~~~~ { ~~~~~~~~~ ~~~~~~ { identifier-1 } The \ :code:`GOBACK`\ statement is used to logically terminate an executing program. #. If executed within a subprogram (i.e. a subroutine or user-defined function), \ :code:`GOBACK`\ behaves like an \ :code:`EXIT PROGRAM`\ or \ :code:`EXIT FUNCTION`\ statement, respectively. #. If executed within a main program, \ :code:`GOBACK`\ will act as a \ :code:`STOP RUN`\ statement. #. The optional \ :code:`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 \ :code:`%ERRORLEVEL%`\ to query the exit status while Unix shells such as :command:`sh`, :command:`bash` and :command:`ksh` can query the exit status as \ :code:`$?`\ . Other Unix shells may have different ways to access the exit status. .. index:: single:GO TO .. _GOATO: 7.8.22 GO TO ~~~~~~~~~~~~ .. index:: single:Simple GO TO .. _SimpleAGOATO: 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 \ :code:`GO TO`\ statement unconditionally transfers control in a program to the first executable statement within the specified . #. The reserved word \ :code:`TO`\ is optional and may be omitted. The presence or absence of this word has no effect upon the program. #. If this format of the \ :code:`GO TO`\ statement appears in a consecutive sequence of imperative statements ( :ref:`Imperative Statement `) within a sentence, it must be the \ *final*\ statement in the sentence. #. If a \ :code:`GO TO`\ is executed within the scope of... #. ...an in-line \ :code:`PERFORM`\ ( :ref:`PERFORM`), the \ :code:`PERFORM`\ is terminated as control of execution transfers to . #. ...a procedural \ :code:`PERFORM`\ ( :ref:`PERFORM`), and lies outside the scope of that \ :code:`PERFORM`\ , the \ :code:`PERFORM`\ is terminated as control of execution transfers to . #. ...a \ :code:`MERGE`\ statement ( :ref:`MERGE`) \ :code:`OUTPUT PROCEDURE`\ or within the scope of either an \ :code:`INPUT PROCEDURE`\ or \ :code:`OUTPUT PROCEDURE`\ of a \ :code:`SORT`\ statement ( :ref:`File-BasedASORT`), and lies outside the scope of that procedure, the \ :code:`SORT`\ or \ :code:`MERGE`\ operation is terminated as control of execution transfers to . Any sorted or merged data accumulated to that point is lost. #. A \ :code:`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 \ :code:`ENTRY`\ . #. The \ :code:`GO TO ENTRY`\ format has to be used together with \ :code:`ENTRY FOR GO TO`\ . .. index:: single:GO TO DEPENDING ON .. _GOATOADEPENDINGAON: 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 \ :code:`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. #. The reserved word \ :code:`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. #. The \ :code:`PICTURE`\ ( :ref:`PICTURE`) and/or \ :code:`USAGE`\ ( :ref:`USAGE`) of the specified must be such as to define it as a numeric, unedited, preferably unsigned integer data item. #. If the value of has the value 1, control will be transferred to the 1\ :sup:`st`\ specified procedure name. If the value is 2, control will transfer to the 2nd procedure name, and so on. #. The \ :code:`GO TO ENTRY ... DEPENDING ON`\ format has to be used together with \ :code:`ENTRY FOR GO TO`\ . If control of execution is transferred to a procedure named on the statement, and the \ :code:`GO TO`\ is executed within the scope of... #. ...an in-line \ :code:`PERFORM`\ ( :ref:`PERFORM`), the \ :code:`PERFORM`\ is terminated as control of execution transfers to the procedure named on the statement. #. ...a procedural \ :code:`PERFORM`\ ( :ref:`PERFORM`), and lies outside the scope of that \ :code:`PERFORM`\ , the \ :code:`PERFORM`\ is terminated as control of execution transfers to the procedure named on the statement. #. ...a \ :code:`MERGE`\ statement ( :ref:`MERGE`) \ :code:`OUTPUT PROCEDURE`\ or within the scope of either an \ :code:`INPUT PROCEDURE`\ or \ :code:`OUTPUT PROCEDURE`\ of a \ :code:`SORT`\ statement ( :ref:`File-BasedASORT`), and lies outside the scope of that procedure, the \ :code:`SORT`\ or \ :code:`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. #. If the value of 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 \ :code:`GO TO`\ . #. The following example shows how \ :code:`GO TO ... DEPENDING ON`\ may be used in a real application situation, and compares it against an alternative --- \ :code:`EVALUATE`\ ( :ref:`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. #. Current programming philosophy would prefer the use of the \ :code:`EVALUATE`\ statement to that of this form of the \ :code:`GO TO`\ statement. .. index:: single:IF .. _IF: 7.8.23 IF ~~~~~~~~~ IF Syntax :: IF conditional-expression ~~ THEN { imperative-statement-1 } { NEXT SENTENCE } ~~~~ ~~~~~~~~ [ ELSE { imperative-statement-2 } ] ~~~~ { NEXT SENTENCE } ~~~~ ~~~~~~~~ [ END-IF ] ~~~~~~ The \ :code:`IF`\ statement is used to conditionally execute an imperative statement ( :ref:`Imperative Statement `) or to select one of two different imperative statements to execute based upon the \ :code:`TRUE`\ /\ :code:`FALSE`\ value of a conditional expression. #. The reserved word \ :code:`THEN`\ is optional and may be omitted. The presence or absence of this word has no effect upon the program. #. You cannot use both \ :code:`NEXT SENTENCE`\ and the \ :code:`END-IF`\ scope terminator in the same \ :code:`IF`\ statement. .. index:: single:ELSE #. If evaluates to \ :code:`TRUE`\ , will be executed regardless of whether or not an \ \ :code:`ELSE`\ clause is present. Once has been executed, control falls into the first statement following the \ :code:`END-IF`\ or to the first statement of the next sentence if there is no \ :code:`END-IF`\ clause. #. If the optional \ :code:`ELSE`\ clause is present and conditional-expression evaluates to false, then (and only then) will be executed. Once has been executed, control falls into the first statement following the \ :code:`END-IF`\ or to the first statement of the next sentence if there is no \ :code:`END-IF`\ clause. .. index:: single:NEXT SENTENCE #. The clause \ \ :code:`NEXT SENTENCE`\ may be substituted for either imperative-statement, but not both. If control reaches a \ :code:`NEXT SENTENCE`\ clause due to the truth or falsehood of , control will be transferred to the first statement of the next sentence found in the program (the first statement after the next period). \ :code:`NEXT SENTENCE`\ was needed for COBOL programs that were coded according to pre-1985 standards that wish to nest one \ :code:`IF`\ statement inside another. :ref:`UseAofAVERBAEND-VERBAConstructs`, for an explanation of why \ :code:`NEXT SENTENCE`\ was necessary. Programs coded for 1985 (and beyond) standards don't need it, instead using the explicit scope-terminator \ :code:`END-IF`\ to inform the compiler where (or if there is no \ :code:`ELSE`\ clause coded) ends. New GnuCOBOL programs should be coded to use the \ :code:`END-IF`\ scope terminator for \ :code:`IF`\ statements. :ref:`UseAofAVERBAEND-VERBAConstructs`, for additional information. .. index:: single:INITIALIZE .. _INITIALIZE: 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 \ :code:`INITIALIZE`\ statement initializes each with certain specific values, depending upon the options specified. #. The reserved words \ :code:`DATA`\ , \ :code:`OF`\ , \ :code:`THEN`\ , \ :code:`TO`\ and \ :code:`WITH`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The reserved words \ :code:`INITIALIZE`\ and \ :code:`INITIALISE`\ are interchangeable. #. The \ :code:`WITH FILLER`\ , \ :code:`REPLACING`\ and \ :code:`DEFAULT`\ clauses are meaningful only if is a group item. They are accepted if it's an elementary item, but will serve no purpose. The \ :code:`VALUE`\ clause is meaningful in both cases. #. A and/or may be any of the following: .. index:: single:ALPHABETIC * \ ALPHABETIC The \ :code:`PICTURE`\ ( :ref:`PICTURE`) of the data item only contains \ :code:`A`\ symbols. .. index:: single:ALPHANUMERIC * \ ALPHANUMERIC The \ :code:`PICTURE`\ of the data item contains only \ :code:`X`\ or a combination of \ :code:`A`\ and \ :code:`9`\ symbols. .. index:: single:ALPHANUMERIC-EDITED * \ ALPHANUMERIC-EDITED The \ :code:`PICTURE`\ of the data item contains only \ :code:`X`\ or a combination of \ :code:`A`\ and \ :code:`9`\ symbols plus at least one \ :code:`B`\ , \ :code:`0`\ (zero) or \ :code:`/`\ symbol. .. index:: single:NUMERIC * \ NUMERIC The data item is one that is described with a picture less \ :code:`USAGE`\ ( :ref:`USAGE`) or has a \ :code:`PICTURE`\ composed of nothing but \ :code:`P`\ , \ :code:`9`\ , \ :code:`S`\ and \ :code:`V`\ symbols. .. index:: single:NUMERIC-EDITED * \ NUMERIC-EDITED The \ :code:`PICTURE`\ of the data item contains nothing but the symbol \ :code:`9`\ and at least one of the editing symbols \ :code:`$`\ , \ :code:`+`\ , \ :code:`-`\ , \ :code:`CR`\ , \ :code:`DB`\ , \ :code:`.`\ , \ :code:`,`\ , \ :code:`*`\ or \ :code:`Z`\ . .. index:: single:NATIONAL * \ NATIONAL The data item is one containing nothing but the \ :code:`N`\ symbol. .. index:: single:NATIONAL-EDITED * \ NATIONAL-EDITED The data item contains nothing but \ :code:`N`\ , \ :code:`B`\ , \ :code:`/`\ and \ :code:`0`\ symbols. #. From the sequence of data items specified on the \ :code:`INITIALIZE`\ statement, a list of initialized fields referred to as the \ *field list*\ in the remainder of this section, will include: #. Every that is an elementary item, including any that may have the \ :code:`REDEFINES`\ ( :ref:`REDEFINES`) clause in their descriptions. #. Every non-\ :code:`FILLER`\ elementary item subordinate to , provided that elementary item neither contains a \ :code:`REDEFINES`\ clause in its definition nor belongs to a group item \ *subordinate to*\ which contains a \ :code:`REDEFINES`\ clause in its definition. .. index:: single:WITH FILLER #. If the optional \ \ :code:`WITH FILLER`\ clause is included on the \ :code:`INITIALIZE`\ statement, then every FILLER elementary item subordinate to each will be included as well, provided that elementary item neither contains a \ :code:`REDEFINES`\ clause in its definition nor belongs to a group item \ *subordinate to*\ which contains a \ :code:`REDEFINES`\ clause in its definition.. #. Once a field list has been determined, each item in that field list will be initialized as if an individual \ :code:`MOVE`\ ( :ref:`MOVE`) statement to that effect had been coded. The rules for initialization are as follows: .. index:: single:DEFAULT .. index:: single:REPLACING .. index:: single:VALUE #. If no \ \ :code:`VALUE`\ , \ \ :code:`REPLACING`\ or \ \ :code:`DEFAULT`\ clauses are coded, each member of the field list will be initialized as if the figurative constant \ :code:`ZERO`\ (if the field list item is numeric or numeric-edited) or \ :code:`SPACES`\ (otherwise) were being moved to it. #. If a \ :code:`VALUE`\ clause is specified on the \ :code:`INITIALIZE`\ statement, each qualifying member of the field list having a compile-time \ :code:`VALUE`\ ( :ref:`VALUE`) specified in its definition will be initialized to that value. Field list members with \ :code:`VALUE`\ clauses will qualify for this treatment as follows: #. If the \ :code:`ALL`\ keyword was specified on the \ :code:`VALUE`\ clause, all members of the field list with \ :code:`VALUE`\ clauses will qualify. #. If is specified instead of \ :code:`ALL`\ , only those members of the field list with \ :code:`VALUE`\ clauses that also meet the criteria set down for the specified (see the list above) will qualify. #. If you need to apply \ :code:`VALUE`\ initialization to multiple values, you will need to use multiple \ :code:`INITIALIZE`\ statements. #. If a \ :code:`REPLACING`\ clause is specified on the \ :code:`INITIALIZE`\ statement, each qualifying member of the field list that was not already initialized by a \ :code:`VALUE`\ clause, if any, will be initialized to the specified or value. Only those as-yet uninitialized list members meeting the criteria set forth for the specified will qualify for this initialization. If you need to apply \ :code:`REPLACING`\ initialization to multiple values, you may repeat the syntax after the reserved word \ :code:`REPLACING`\ , as necessary. #. If a \ :code:`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 \ :code:`ZERO`\ , all others are initialized to \ :code:`SPACES`\ ). #. The following example may help your understanding of how the \ :code:`INITIALIZE`\ statement works. The sample code makes use of the :command:`COBDUMP` program to dump the storage that is (or is not) being initialized. `COBDUMP (in Sample Programs) <../gnucobsp/chapter2.html#cobdump>`_, for a source and cross-reference listing of the :command:`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 .. index:: single:INITIATE .. _INITIATE: 7.8.25 INITIATE ~~~~~~~~~~~~~~~ INITIATE Syntax :: INITIATE report-name-1 ~~~~~~~~ The \ :code:`INITIATE`\ statement starts Report-Writer Control System (RWCS) processing for a report. #. Each must be the name of a report having an \ :code:`RD`\ ( :ref:`REPORTASECTION`) defined for it. #. The file in whose \ :code:`FD`\ ( :ref:`FileASort-Description`) a \ :code:`REPORT `\ clause exists must be open for \ :code:`OUTPUT`\ or \ :code:`EXTEND`\ at the time the \ :code:`INITIATE`\ statement is executed. :ref:`OPEN`, for more information on file open modes. #. The \ :code:`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 .. index:: single:Special Registers, LINE-COUNTER .. index:: single:LINE-COUNTER Special Register * The report's \ \ \ :code:`LINE-COUNTER`\ special register ( :ref:`SpecialARegisters`) will be set to 0 .. index:: single:Special Registers, PAGE-COUNTER .. index:: single:PAGE-COUNTER Special Register * The report's \ \ \ :code:`PAGE-COUNTER`\ special register will be set to 1 #. No report content will actually presented to the report file as a result of a successful \ :code:`INITIATE`\ statement --- that will not occur until the first \ :code:`GENERATE`\ statement ( :ref:`GENERATE`) is executed. .. index:: single:INSPECT .. _INSPECT: 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 \ :code:`INSPECT`\ statement is used to perform various counting and/or data-alteration operations against strings. #. The reserved word \ :code:`INITIAL`\ is optional and may be omitted. The presence or absence of this words has no effect upon the program. .. index:: single:REPLACING .. index:: single:TALLYING .. index:: single:CONVERTING #. If a \ \ :code:`CONVERTING`\ clause is specified, neither the \ \ :code:`TALLYING`\ nor \ \ :code:`REPLACING`\ clauses may be used. #. If either the \ :code:`TALLYING`\ or \ :code:`REPLACING`\ clauses are specified, the \ :code:`CONVERTING`\ clause cannot be used. #. If both the \ :code:`TALLYING`\ and \ :code:`REPLACING`\ clauses are specified, they must be specified in the order shown. #. All literals and identifiers must be explicitly or implicitly defined as alphanumeric or alphabetic. #. If is specified, it must be an invocation of an intrinsic function that returns a \ *string*\ result. Additionally, only the \ :code:`TALLYING`\ clause may be specified. #. If is specified, only the \ :code:`TALLYING`\ clause may be specified. #. Whichever is specified --- , or --- that item will be referred to in the discussions that follows as the '\ *inspect subject*\ '. #. The three optional clauses control the operation of this statement as follows: #. The \ :code:`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 \ :code:`TRANSFORM`\ statement ( :ref:`TRANSFORM`). #. The \ :code:`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 \ :code:`SUBSTITUTE`\ intrinsic function ( :ref:`SUBSTITUTE`) or the \ :code:`SUBSTITUTE-CASE`\ intrinsic function ( :ref:`SUBSTITUTE-CASE`). #. The \ :code:`TALLYING`\ clause counts the number of occurrences of one or more strings of characters in the inspect subject. #. The optional \ :code:`INITIAL`\ clauses may be used to limit the range of characters in the inspect subject that the \ :code:`CONVERTING`\ , \ :code:`REPLACING`\ or \ :code:`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: #. If there is no \ :code:`INITIAL`\ clause specified, the target range is the entire inspect subject. #. Either a \ :code:`BEFORE`\ phrase, an \ :code:`AFTER`\ phrase or both may be specified. They may be specified in any order. #. The starting point of the target range will be the first character following the sub string identified by the \ :code:`AFTER`\ specification. The ending point will be the last character immediately preceding the sub string identified by the \ :code:`BEFORE`\ specification. #. If no \ :code:`AFTER`\ is specified, the first character position of the target range will be character position #1 of the inspect subject. #. If no \ :code:`BEFORE`\ is specified, the last character position of the target range will be the last character position of the inspect subject. #. The following points apply to the use of the \ :code:`TALLYING`\ clause: #. While there will typically be only be a single set of counting instructions on an \ :code:`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 \ :code:`INSPECT`\ proceeds forward through the inspect subject, character-by-character. With the above example, if the inspect subject were \ :code:`--ABCDEF----BCDEF--`\ , the final result of the counting would be that \ :code:`C-ABC`\ would be incremented by 1 while \ :code:`C-BCDE`\ would be incremented only once; although the human eye clearly sees two '\ :code:`BCDE`\ ' sequences, the \ :code:`INSPECT ... TALLYING`\ would only "see" the second --- the first would have been processed by the first (higher-priority) counting instruction. #. Each set of counting instructions contains the following information: #. A target range, specified by the presence of an \ :code:`AFTER INITIAL`\ and/or \ :code:`BEFORE INITIAL`\ clause; the rules for specifying target ranges were covered previously. #. 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 ('\ :code:`1`\ ') character. The keywords before the literal or identifier control how many target sub strings could be identified from that replacement instruction, as follows: \ :code:`ALL`\ --- identifies every possible target sub string that occurs within the target range. There are three occurrences of \ :code:`ALL 'XX'`\ found in \ :code:`aXXabbXXccXXdd`\ . \ :code:`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 \ :code:`LEADING 'XX'`\ found in \ :code:`aXXabbXXccXXdd`\ , but there is one occurrence of \ :code:`LEADING 'a'`\ (the first character). \ :code:`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 \ :code:`LEADING 'XX'`\ found in \ :code:`aXXabbXXccXXdd`\ , but there are two occurrences of \ :code:`TRAILING 'd'`\ . The \ :code:`CHARACTERS`\ option will match any one single character, regardless of what that character is. #. will be incremented by 1 each time the target sub string is found within the target range of the inspect subject. The \ :code:`INSPECT`\ statement \ *will not*\ zero-out at the start of execution of the \ :code:`INSPECT`\ --- it is the programmer's responsibility to ensure that all data items are properly initialized to the desired starting values prior to execution of the \ :code:`INSPECT`\ . #. The following points apply to the use of the \ :code:`REPLACING`\ clause: #. While there will typically be only be a single set of replacement instructions on an \ :code:`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 \ :code:`INSPECT`\ proceeds forward through the inspect subject, character-by-character. With the above example, if the inspect subject were \ :code:`--ABCDEF----BCDEF--`\ , the final result of the replacement would be \ :code:`--DEFDEF----WXYZF--`\ . #. Each set of replacement instructions contains the following information: #. A target range, specified by the presence of an \ :code:`AFTER INITIAL`\ and/or \ :code:`BEFORE INITIAL`\ clause; the rules for specifying target ranges were covered previously. #. 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 \ :code:`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 ('\ :code:`1`\ ') character. The keywords before the literal or identifier control how many target sub strings could be identified from that replacement instruction, as follows: \ :code:`ALL`\ --- identifies every possible target sub string that occurs within the target range. There are three occurrences of \ :code:`ALL 'XX'`\ found in \ :code:`aXXabbXXccXXdd`\ . \ :code:`FIRST`\ --- the first occurrence of the target sub string found within the target range. The \ :code:`FIRST 'XX'`\ found in \ :code:`aXXabbXXccXXdd`\ would be the one found between the '\ :code:`a`\ ' and '\ :code:`b`\ ' characters. \ :code:`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 \ :code:`LEADING 'XX'`\ found in \ :code:`aXXabbXXccXXdd`\ , but there is one occurrence of \ :code:`LEADING 'a'`\ (the first character). \ :code:`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 \ :code:`LEADING 'XX'`\ found in \ :code:`aXXabbXXccXXdd`\ , but there are two occurrences of \ :code:`TRAILING 'd'`\ . The \ :code:`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. #. A Replacement Sub string --- this is the sequence of characters that should replace the target sub string. Replacement sub strings are specified after the \ :code:`BY`\ keyword. They too may be specified as a literal, either with or without an \ :code:`ALL`\ prefix (again, figurative constants are allowed) or the value of an identifier. If a figurative constant is coded, the \ :code:`ALL`\ keyword will be assumed, even if it wasn't specified. Literals without \ :code:`ALL`\ will either be truncated or padded with spaces on the right to match the length of the target sub string. Literals with \ :code:`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. #. When both \ :code:`REPLACING`\ and \ :code:`TALLYING`\ are specified: #. The \ :code:`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. #. At any point in time, there may well be multiple \ :code:`REPLACING`\ and/or \ :code:`TALLYING`\ operational instructions active. Only one of the \ :code:`TALLYING`\ and one of the \ :code:`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. #. When both a \ :code:`TALLYING`\ and a \ :code:`REPLACING`\ instruction have been selected for execution, the \ :code:`TALLYING`\ instruction will be executed first. This guarantees that \ :code:`TALLYING`\ will compute occurrences based upon the \ *initial*\ value of the inspect subject before any replacements occur. #. The following points apply to the use of the \ :code:`CONVERTING`\ clause: #. A \ :code:`CONVERTING`\ clause performs a series of single-character substitutions against a data item in much the same manner as is possible with the \ :code:`TRANSFORM`\ statement ( :ref:`TRANSFORM`). #. Unlike the \ :code:`TALLYING`\ and \ :code:`REPLACING`\ clauses, both of which may have multiple operations specified, there may be only one \ :code:`CONVERTING`\ operation per \ :code:`INSPECT`\ . #. If the length of or (the "from" string) \ *exceeds*\ the length of or (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. #. 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. #. 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. .. index:: single:MERGE .. _MERGE: 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... } { ~~~~~~ } .. index:: single:DUPLICATES The \ \ :code:`DUPLICATES`\ clause is syntactically recognized but is otherwise non-functional. The \ :code:`MERGE`\ statement merges the contents of two or more files that have each been pre-sorted on a set of specified identical keys. #. The reserved words \ :code:`IN`\ , \ :code:`IS`\ , \ :code:`KEY`\ , \ :code:`ON`\ , \ :code:`ORDER`\ , \ :code:`SEQUENCE`\ and \ :code:`WITH`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The reserved words \ :code:`THRU`\ and \ :code:`THROUGH`\ are interchangeable. #. GnuCOBOL always behaves as if the \ :code:`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. #. The named on the \ :code:`MERGE`\ statement must be defined using a sort description (\ :code:`SD`\ ( :ref:`FileASort-Description`)). This file is referred to in the remainder of this discussion as the \ *merge work file*\ . #. Each , and (if specified) must reference \ :code:`ORGANIZATION LINE SEQUENTIAL`\ ( :ref:`ORGANIZATIONALINEASEQUENTIAL`) or \ :code:`ORGANIZATION SEQUENTIAL`\ ( :ref:`ORGANIZATIONASEQUENTIAL`) files. These files must be defined using a file description (\ :code:`FD`\ ( :ref:`FileASort-Description`)). #. The ... field(s) must be defined as field(s) within a record of . #. The record descriptions of , , (if any) and 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, \ :code:`PICTURE`\ ( :ref:`PICTURE`) of fields, \ :code:`USAGE`\ ( :ref:`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 \ :code:`KEY`\ fields are concerned. #. A common programming technique when using the \ :code:`MERGE`\ statement is to define the records of all files involved as simple elementary items of the form \ :code:`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 . #. The following rules apply to the files named on the \ :code:`USING`\ clause: #. None of them may be open at the time the \ :code:`MERGE`\ is executed. .. index:: single:KEY #. Each of those files is assumed to be already sorted according to the specifications set forth on the \ :code:`MERGE`\ statement's \ \ :code:`KEY`\ clause. #. No two of those files may be referenced on a \ :code:`SAME RECORD AREA`\ ( :ref:`SAMEARECORDAAREA`), \ :code:`SAME SORT AREA`\ or \ :code:`SAME SORT-MERGE AREA`\ statement. #. The merging process is as follows: .. index:: single:USING #. As the \ :code:`MERGE`\ statement begins execution, the first record in each of the \ \ :code:`USING`\ files is read automatically. .. index:: single:COLLATING SEQUENCE #. As the \ :code:`MERGE`\ statement executes, the current record from each of the \ :code:`USING`\ files is examined and compared to each other according to the rules set forth by the \ :code:`KEY`\ clause and the alphabet ( :ref:`Alphabet-Name-Clause`) specified on the \ \ :code:`COLLATING SEQUENCE`\ clause. The record that should be next in sequence will be written to the merge work file and the \ :code:`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 \ :code:`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. .. index:: single:OUTPUT PROCEDURE .. index:: single:GIVING #. After the merge work file has been populated, the merged data will be written to each if the \ \ :code:`GIVING`\ clause was specified, or will be processed by utilizing an \ \ :code:`OUTPUT PROCEDURE`\ . #. When \ :code:`GIVING`\ is specified, none of the files can be open at the time the \ :code:`MERGE`\ statement is executed. #. When an output procedure is used, the procedure(s) specified on the \ :code:`OUTPUT PROCEDURE`\ clause will be invoked as if by a procedural \ :code:`PERFORM`\ ( :ref:`ProceduralAPERFORM`) statement with no \ :code:`VARYING`\ , \ :code:`TIMES`\ or \ :code:`UNTIL`\ options specified. Merged records may be read from the merge work file --- one at a time --- within the output procedure using the \ :code:`RETURN`\ ( :ref:`RETURN`) statement. A \ :code:`GO TO`\ statement ( :ref:`GOATO`) that transfers control out of the output procedure will terminate the \ :code:`MERGE`\ statement but allows the program to continue executing from the point where the \ :code:`GO TO`\ statement transferred control to. Once an output procedure has been "aborted" using a \ :code:`GO TO`\ it cannot be resumed, and the contents of the merge work file are lost. You may, however, re-execute the \ :code:`MERGE`\ statement itself. \ *Using a*\ \ :code:`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 \ :code:`PERFORM`\ statement would be. Usually, this action will be taken once the \ :code:`RETURN`\ statement indicates that all records in the merge work file have been processed, but termination could occur at \ *any*\ time --- via an \ :code:`EXIT`\ statement ( :ref:`EXIT`) --- if required. Neither a file-based \ :code:`SORT`\ statement ( :ref:`File-BasedASORT`) nor another \ :code:`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. #. Once the output procedure terminates, or the last file has been populated with merged data, the output phase --- and the \ :code:`MERGE`\ statement itself --- is complete. .. index:: single:MOVE .. _MOVE: 7.8.28 MOVE ~~~~~~~~~~~ .. index:: single:Simple MOVE .. _SimpleAMOVE: 7.8.28.1 Simple MOVE ^^^^^^^^^^^^^^^^^^^^ Simple MOVE Syntax :: MOVE { literal-1 } TO identifier-2... ~~~~ { identifier-1 } ~~ The Simple \ :code:`MOVE`\ statement moves a specific value to one or more receiving data items. #. The \ :code:`MOVE`\ statement will replace the contents of one or more receiving data items () with a new value --- the one specified by or . #. Only numeric data can be moved to a numeric or numeric-edited . A \ :code:`MOVE`\ involving numeric data will perform any necessary format conversions that might be necessary due to differing \ :code:`USAGE`\ ( :ref:`USAGE`) specifications. #. The contents of the data item will not be changed, unless that same data item appears as an . Note that such situations will cause a warning message to be issued by the compiler, if warning messages are enabled. .. index:: single:MOVE CORRESPONDING .. _MOVEACORRESPONDING: 7.8.28.2 MOVE CORRESPONDING ^^^^^^^^^^^^^^^^^^^^^^^^^^^ MOVE CORRESPONDING Syntax :: MOVE CORRESPONDING identifier-1 TO identifier-2... ~~~~ ~~~~ ~~ The \ :code:`MOVE CORRESPONDING`\ statement similarly-named items from one group item to another. #. The reserved word \ :code:`CORRESPONDING`\ may be abbreviated as \ :code:`CORR`\ . #. Both and must be group items. #. :ref:`CORRESPONDING`, for a discussion of how corresponding matches between two group items are established. #. When corresponding matches are established, the effect of a \ :code:`MOVE CORRESPONDING`\ on those matches will be as if a series of individual \ :code:`MOVE`\ s were done --- one for each match. .. index:: single:MULTIPLY .. _MULTIPLY: 7.8.29 MULTIPLY ~~~~~~~~~~~~~~~ .. index:: single:MULTIPLY BY .. _MULTIPLYABY: 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 \ :code:`MULTIPLY BY`\ statement computes the product of one or more data items () and either a numeric literal or another data item. #. The reserved words \ :code:`IS`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. Both and must be numeric un-edited data items; must be a numeric literal. #. The product of or and each , in turn, will be computed and moved to each of the data items, replacing the prior contents. #. The value of is not altered, unless that same data item appears as an . #. The optional \ :code:`ROUNDED`\ ( :ref:`ROUNDED`) clause available to each will control how non-integer results will be saved. #. The optional \ :code:`ON SIZE ERROR`\ and \ :code:`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 with an insufficient number of digit positions available to the left of any implied decimal point. :ref:`ONASIZEAERRORAAANOTAONASIZEAERROR`, for additional information. .. index:: single:MULTIPLY GIVING .. _MULTIPLYAGIVING: 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 \ :code:`MULTIPLY GIVING`\ statement computes the product of two literals and/or data items and saves that result in one or more other data items. #. The reserved words \ :code:`IS`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. Both and must be numeric un-edited data items; and must be numeric literals. #. The product of or and or will be computed and moved to each of the data items, replacing their old contents. #. Neither the value of nor will be altered, unless either appears as an . #. The optional \ :code:`ROUNDED`\ ( :ref:`ROUNDED`) clause available to each will control how non-integer results will be saved. #. The optional \ :code:`ON SIZE ERROR`\ and \ :code:`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 with an insufficient number of digit positions available to the left of any implied decimal point. :ref:`ONASIZEAERRORAAANOTAONASIZEAERROR`, for additional information. .. index:: single:OPEN .. _OPEN: 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 } } ~~~~ .. index:: single:REVERSED .. index:: single:NO REWIND The \ \ :code:`NO REWIND`\ , and \ \ :code:`REVERSED`\ clauses are syntactically recognized but are otherwise non-functional. The \ :code:`OPEN`\ statement makes one or more files described in your program available for use. #. The reserved words \ :code:`OTHER`\ and \ :code:`WITH`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The \ :code:`SHARING`\ and \ :code:`WITH LOCK`\ clauses may not both be specified in the same \ :code:`OPEN`\ statement. #. Any file defined in a GnuCOBOL program must be successfully opened before it or any of its record descriptions may be referenced on: A \ :code:`CLOSE`\ statement ( :ref:`CLOSE`) A \ :code:`DELETE`\ statement ( :ref:`DELETE`) A \ :code:`READ`\ statement ( :ref:`READ`) A \ :code:`REWRITE`\ statement ( :ref:`REWRITE`) A \ :code:`START`\ statement ( :ref:`START`) An \ :code:`UNLOCK`\ statement ( :ref:`UNLOCK`) A \ :code:`WRITE`\ statement ( :ref:`WRITE`) #. Any attempt to open a file that is already open will fail with a file status of 41 ( :ref:`File Status Codes `). #. Any open failure (including status 41) may be trapped using \ :code:`DECLARATIVES`\ ( :ref:`DECLARATIVES`) or an error procedure established using the \ :code:`CBL_ERROR_PROC`\ built-in system subroutine ( :ref:`CBLAERRORAPROC`) 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. .. index:: single:EXTEND .. index:: single:I-O .. index:: single:OUTPUT .. index:: single:INPUT .. index:: single:File OPEN Modes .. _FileAOPENAModes: #. \ The \ \ :code:`INPUT`\ , \ \ :code:`OUTPUT`\ , \ \ :code:`I-O`\ and \ \ :code:`EXTEND`\ open modes inform GnuCOBOL of the manner in which you wish to use the file, as follows: * \ :code:`INPUT`\ You may only read the existing contents of the file --- only the \ :code:`CLOSE`\ , \ :code:`READ`\ , \ :code:`START`\ and \ :code:`UNLOCK`\ statements will be allowed. This enforcement takes place at execution time, not compilation time. * \ :code:`OUTPUT`\ You may only write new content (which will completely replace any previous file contents) to the file --- only the \ :code:`CLOSE`\ , \ :code:`UNLOCK`\ and \ :code:`WRITE`\ statements will be allowed. This enforcement takes place at execution time, not compilation time. * \ :code:`I-O`\ You may perform any operation you wish against the file --- all file I/O statements will be allowed. * \ :code:`EXTEND`\ You may only write new content (which will be appended after the previously existing file contents) to the file --- only the \ :code:`CLOSE`\ , \ :code:`UNLOCK`\ and \ :code:`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. .. index:: single:SHARING #. The \ \ :code:`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. :ref:`FileASharing`, for an explanation of the \ :code:`SHARING`\ clause. .. index:: single:WITH LOCK #. The \ \ :code:`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 \ :code:`fcntl`\ primitive doesn't exist in those environments. GnuCOBOL built for Cygwin or Unix will. .. index:: single:PERFORM .. _PERFORM: 7.8.31 PERFORM ~~~~~~~~~~~~~~ .. index:: single:Procedural PERFORM .. _ProceduralAPERFORM: 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 \ :code:`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 \ :code:`TRUE`\ or forever (with some way of breaking out of the control of the \ :code:`PERFORM`\ or of halting program execution within the procedure(s)). #. The reserved word \ :code:`WITH`\ is optional and may be omitted. The presence or absence of this word has no effect upon the program. #. The reserved words \ :code:`THRU`\ and \ :code:`THROUGH`\ are interchangeable. #. The reserved word and phrase \ :code:`FOREVER`\ and \ :code:`UNTIL EXIT`\ are interchangeable. #. Both and must be procedure division sections or paragraphs defined in the same program as the \ :code:`PERFORM`\ statement. If is specified, it must follow in the program's source code. .. index:: single:perform scope #. The \ \ *perform scope*\ is defined as being the statements within , the statements within and all statements in all procedures defined between them. #. 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. #. must be an elementary un-edited numeric data item with an integer value greater than zero. .. index:: single:FOREVER .. index:: single:TIMES .. index:: single:UNTIL EXIT .. index:: single:UNTIL #. Without the \ \ :code:`UNTIL`\ , \ \ :code:`UNTIL EXIT`\ , \ \ :code:`TIMES`\ , \ *VARYING-Clause*\ ( :ref:`VARYING`) or \ \ :code:`FOREVER`\ clauses, the code within the perform scope will be executed once, after which control will return to the statement following the \ :code:`PERFORM`\ . #. The \ :code:`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 \ :code:`EXIT SECTION`\ statement ( :ref:`EXIT`) or \ :code:`EXIT PARAGRAPH`\ statement within the procedure(s) being performed that will break out of the loop. #. The \ :code:`TIMES`\ option will repeat the execution of the code within the perform scope a fixed number of times. When the \ :code:`PERFORM`\ statement begins execution, an internal repeat counter (not accessible to the programmer) will be set to the value of or the value within . If the counter has a value greater than zero, the statement(s) within the \ :code:`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 \ :code:`PERFORM`\ . If the option was used, altering the value of that data item within the perform scope will \ *not*\ affect the repetition count. #. The \ :code:`UNTIL `\ option will repeat the code within the perform scope until the specified conditional expression evaluates to a \ :code:`TRUE`\ value. .. index:: single:AFTER .. index:: single:WITH TEST #. The optional \ \ :code:`WITH TEST`\ clause will control whether \ :code:`UNTIL`\ testing occurs \ :code:`BEFORE`\ the statements within the perform scope are executed on each iteration (creating the possibility --- if is initially \ :code:`TRUE`\ --- that the statements within the perform scope will never be executed) or \ \ :code:`AFTER`\ (guaranteeing the statements within the perform scope will be executed at least once). The default, if this clause is absent, is \ :code:`WITH TEST BEFORE`\ . This clause may not be coded when the \ :code:`TIMES`\ clause is used. #. The optional \ :code:``\ 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 \ :code:`UNTIL`\ clause. :ref:`VARYING`, for the details. .. index:: single:Inline PERFORM .. _InlineAPERFORM: 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 \ :code:`PERFORM`\ statement is identical in operation to the procedural \ :code:`PERFORM`\ , except for the fact that the statement(s) comprising the perform scope () ( :ref:`Imperative Statement `) are now specified in-line with the \ :code:`PERFORM`\ code rather than in procedures located elsewhere within the program. .. index:: single:VARYING .. _VARYING: 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 \ :code:`VARYING`\ clause, available on both formats of the \ :code:`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. #. All identifiers used in a must be elementary, un-edited numeric data items. All literals must be numeric literals. #. The following points describe the sequence of events that take place as a result of the \ :code:`VARYING`\ portion of the clause: #. When the \ :code:`PERFORM`\ begins execution, the \ :code:`FROM`\ value will be moved to . #. If the \ :code:`PERFORM`\ specifies or implies \ :code:`WITH TEST BEFORE`\ , will be evaluated and processing of the \ :code:`PERFORM`\ will halt if the expression evaluates to \ :code:`TRUE`\ . If \ :code:`WITH TEST BEFORE`\ was \ *not*\ specified or implied, or if the conditional expression evaluated to \ :code:`FALSE`\ , processing proceeds with step C. #. The statements within the perform scope will be executed. If a \ :code:`GO TO`\ executed within the perform scope transfers control to a point outside the perform scope, processing of the \ :code:`PERFORM`\ will halt. #. 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 \ :code:`EXIT PERFORM CYCLE`\ statement ( :ref:`EXIT`) * executing an \ :code:`EXIT PARAGRAPH`\ statement or \ :code:`EXIT SECTION`\ statement when there is only one paragraph (or section) in the perform scope ( this option only applies to a procedural \ :code:`PERFORM`\ ) If \ :code:`WITH TEST AFTER`\ was specified, control will return back to the \ :code:`PERFORM`\ , where will be evaluated, and processing of the \ :code:`PERFORM`\ will halt if the expression evaluates to \ :code:`TRUE`\ . If \ :code:`WITH TEST AFTER`\ was \ *not*\ specified, or if the conditional expression evaluated to \ :code:`FALSE`\ , processing continues with the next step. #. The \ :code:`BY`\ value, if any, will be added to . If no \ :code:`BY`\ is specified, it will be treated as if \ :code:`BY 1`\ had been specified. #. Return to step C. #. Most \ :code:``\ s have no \ :code:`AFTER`\ specified. Those that do, however, are establishing a loop-within-a-loop situation where the process described above in steps ('\ :code:`A`\ ') through ('\ :code:`F`\ ') will take place from the \ :code:`AFTER`\ , and those six processing steps actually replace step C of the \ :code:`VARYING`\ . This "nesting" process can continue indefinitely, with each additional \ :code:`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 \ :code:`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 \ :code:`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 \ :code:`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 \ :code:`WITH TEST`\ clause, the statement is now assuming \ :code:`WITH TEST BEFORE`\ . Since testing now happens \ *before*\ the \ :code:`DISPLAY`\ statement gets executed, when PD-Row-No is 3 and PD-Col-No is 4 the \ :code:`DISPLAY`\ statement won't be executed. Most COBOL programmers, when using \ :code:`WITH TEST BEFORE`\ explicitly or implicitly have developed the habit of using '\ :code:`>`\ ' rather than '\ :code:`=`\ ' on \ :code:`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, \ :code:`ABCDEFGHIJKL`\ is once again displayed. .. index:: single:READ .. _READ: 7.8.32 READ ~~~~~~~~~~~ .. index:: single:Sequential READ .. _SequentialAREAD: 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 \ :code:`READ`\ statement retrieves the next (or previous) record from a file. #. The reserved words \ :code:`AT`\ , \ :code:`RECORD`\ and \ :code:`WITH`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The file \ *must*\ have been defined via an \ :code:`FD`\ ( :ref:`FileASort-Description`), not an \ :code:`SD`\ . #. The file must currently be open for \ :code:`INPUT`\ ( :ref:`File OPEN Modes `) or \ :code:`I-O`\ . #. If is an \ :code:`ORGANIZATION RELATIVE`\ ( :ref:`ORGANIZATIONARELATIVE`) or \ :code:`ORGANIZATION INDEXED`\ ( :ref:`ORGANIZATIONAINDEXED`) file with an \ :code:`ACCESS MODE RANDOM`\ , this statement cannot be used. #. If was specified as \ :code:`ACCESS MODE SEQUENTIAL`\ , this is the \ *only*\ format of the \ :code:`READ`\ statement that is available. #. If is an \ :code:`ORGANIZATION RELATIVE`\ ( :ref:`ORGANIZATIONARELATIVE`) or \ :code:`ORGANIZATION INDEXED`\ ( :ref:`ORGANIZATIONAINDEXED`) file with \ :code:`ACCESS MODE DYNAMIC`\ , this statement as well as a random \ :code:`READ`\ ( :ref:`RandomAREAD`) may be used. .. index:: single:PREVIOUS .. index:: single:NEXT #. The keywords \ \ :code:`NEXT`\ and \ \ :code:`PREVIOUS`\ specify what "direction of travel" the reading process will take through the file. If neither is specified, \ :code:`NEXT`\ is assumed. #. The \ :code:`PREVIOUS`\ option is available only for \ :code:`ORGANIZATION INDEXED`\ files. #. 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. #. The minimal statement \ :code:`READ `\ is perfectly legal according to \ *both*\ READ formats. For that reason, when \ :code:`ACCESS MODE DYNAMIC`\ has been specified and you want to tell the GnuCOBOL compiler that this minimal statement should be treated as a \ *sequential*\ \ :code:`READ`\ , you must add either \ :code:`NEXT`\ or \ :code:`PREVIOUS`\ to the statement (otherwise it will be treated as a random \ :code:`READ`\ ). .. index:: single:INTO #. A successful sequential READ will retrieve the next available record from , in either a "next" or "previous" direction from the most-recently-read record, depending upon the use of the \ :code:`NEXT`\ or \ :code:`PREVIOUS`\ option. The newly-retrieved record data will be saved into the 01-level record structure(s) that immediately follow the file's \ :code:`FD`\ . If the optional \ \ :code:`INTO`\ clause is present, a copy of the just-retrieved record will be automatically moved to . #. When an \ :code:`ORGANIZATION RELATIVE`\ file has been successfully read, the file's \ :code:`RELATIVE KEY`\ ( :ref:`ORGANIZATIONARELATIVE`) field will be automatically populated with the relative record number (ordinal occurrence number) of the record in the file. #. The optional \ :code:`LOCK`\ options may be used to manually control access to the retrieved record by other programs while this program is running. :ref:`RecordALocking`, to review the various record locking behaviours. #. The optional \ :code:`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. #. The optional \ :code:`NOT AT END`\ clause, if coded, will check for a file status value of 00. :ref:`File Status Codes `, for additional information. .. index:: single:Random READ .. _RandomAREAD: 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 \ :code:`READ`\ statement retrieves an arbitrary record from an \ :code:`ORGANIZATION RELATIVE`\ ( :ref:`ORGANIZATIONARELATIVE`) or \ :code:`ORGANIZATION INDEXED`\ ( :ref:`ORGANIZATIONAINDEXED`) file. #. The reserved words \ :code:`IS`\ , \ :code:`KEY`\ (on the \ :code:`INVALID`\ and \ :code:`NOT INVALID`\ clauses), \ :code:`RECORD`\ and \ :code:`WITH`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The file \ *must*\ have been defined via an \ :code:`FD`\ ( :ref:`FileASort-Description`), not an \ :code:`SD`\ . #. The file must currently be open for \ :code:`INPUT`\ ( :ref:`File OPEN Modes `) or \ :code:`I-O`\ . #. If the \ :code:`ACCESS MODE`\ of is \ :code:`SEQUENTIAL`\ , or the \ :code:`ORGANIZATION`\ of the file is any form of sequential, this format of the \ :code:`READ`\ statement cannot be used. #. If the \ :code:`ACCESS MODE`\ of is \ :code:`RANDOM`\ , this is the \ *only*\ format of the \ :code:`READ`\ statement that is available. #. If is an \ :code:`ORGANIZATION RELATIVE`\ ( :ref:`ORGANIZATIONARELATIVE`) or \ :code:`ORGANIZATION INDEXED`\ ( :ref:`ORGANIZATIONAINDEXED`) file with \ :code:`ACCESS MODE DYNAMIC`\ , this statement as well as a sequential \ :code:`READ`\ ( :ref:`SequentialAREAD`) may be used. #. The minimal statement \ :code:`READ `\ is perfectly legal according to \ *both*\ READ formats. For that reason, when \ :code:`ACCESS MODE DYNAMIC`\ has been specified and you want to tell the GnuCOBOL compiler that this minimal statement should be treated as a \ *random*\ \ :code:`READ`\ , you must omit the \ :code:`NEXT`\ or \ :code:`PREVIOUS`\ available to the sequential format of the \ :code:`READ`\ statement to ensure the statement \ *will*\ be treated as a random \ :code:`READ`\ . .. index:: single:KEY #. The optional \ \ :code:`KEY`\ clause tells the compiler how a record is to be located in the file. If the \ :code:`KEY`\ clause is absent, and the file is * \ :code:`ORGANIZATION RELATIVE`\ the contents of the field declared as the file's \ :code:`RELATIVE KEY`\ will be used to identify a record * \ :code:`ORGANIZATION INDEXED`\ the contents of the field declared as the file's \ :code:`RECORD KEY`\ will be used to identify a record. If the \ :code:`KEY`\ clause \ *is*\ specified, and the file is * \ :code:`ORGANIZATION RELATIVE`\ the contents of will be used as the relative record number of the record to be accessed. need not be the \ :code:`RELATIVE KEY`\ ( :ref:`ORGANIZATIONARELATIVE`) field of the file (although it could be if you wish). * \ :code:`ORGANIZATION INDEXED`\ \ *must*\ be the \ :code:`RECORD KEY`\ ( :ref:`ORGANIZATIONAINDEXED`) or one of the file's \ :code:`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. .. index:: single:INTO #. 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 \ :code:`FD`\ . If the optional \ \ :code:`INTO`\ clause is present, a copy of the just-retrieved record will be automatically moved to . #. When an \ :code:`ORGANIZATION RELATIVE`\ file has been successfully read, the file's \ :code:`RELATIVE KEY`\ ( :ref:`ORGANIZATIONARELATIVE`) field will be automatically populated with the relative record number (ordinal occurrence number) of the record in the file. #. The optional \ :code:`LOCK`\ options may be used to manually control access to the retrieved record by other programs while this program is running. :ref:`RecordALocking`, to review the various record locking behaviours. #. The optional \ :code:`INVALID KEY`\ and \ :code:`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. :ref:`File Status Codes `, for additional information. .. index:: single:READY TRACE .. _READYATRACE: 7.8.33 READY TRACE ~~~~~~~~~~~~~~~~~~ READY TRACE Syntax :: READY TRACE ~~~~~ ~~~~~ The \ :code:`READY TRACE`\ statement turns procedure or procedure-and-statement tracing on. .. index:: single:-ftrace Compiler Switch .. index:: single:Compiler Switches, -ftrace #. In order for this statement to be functional, tracing code must have been generated into the compiled program using either the \ \ \ :code:`-ftrace`\ switch (procedures only) or \ :code:`-ftraceall`\ switch (procedures and statements). #. Tracing may be turned off at any point by executing the \ :code:`RESET TRACE`\ statement ( :ref:`RESETATRACE`). .. index:: single:Environment Variables, COB_SET_TRACE .. index:: single:COB_SET_TRACE Environment Variable #. The \ \ run-time environment variable ( :ref:`RunATimeAEnvironmentAVariables`) provides another way to control tracing. If this environment variable is set to a value of '\ :code:`Y`\ ' prior to the start of program execution, tracing starts at the point the program begins execution, as if \ :code:`READY TRACE`\ were the first executed statement. .. index:: single:RELEASE .. _RELEASE: 7.8.34 RELEASE ~~~~~~~~~~~~~~ RELEASE Syntax :: RELEASE record-name-1 [ FROM { literal-1 } ] ~~~~~~~ ~~~~ { identifier-1 } The \ :code:`RELEASE`\ statement adds a new record to a sort work file. #. This statement is valid only within the \ :code:`INPUT PROCEDURE`\ of a file-based \ :code:`SORT`\ statement ( :ref:`File-BasedASORT`). #. The specified must be a record defined to the sort description (\ :code:`SD`\ ( :ref:`FileASort-Description`)) of the sort work file being processed by the current sort. .. index:: single:FROM #. The optional \ \ :code:`FROM`\ clause will cause or to be automatically moved into prior to writing 's contents to the . If this clause is not specified, it is the programmer's responsibility to populate with the desired data prior to executing the \ :code:`RELEASE`\ . .. index:: single:RESET TRACE .. _RESETATRACE: 7.8.35 RESET TRACE ~~~~~~~~~~~~~~~~~~ RESET TRACE Syntax :: RESET TRACE ~~~~~ ~~~~~ The \ :code:`RESET TRACE`\ statement turns procedure or procedure-and-statement tracing off. #. By default, procedure and procedure-and-statement tracing is off as programs begin execution. The \ :code:`READY TRACE`\ statement ( :ref:`READYATRACE`) can be used to turn tracing on. .. index:: single:-ftraceall Compiler Switch .. index:: single:Compiler Switches, -ftraceall .. index:: single:-ftrace Compiler Switch .. index:: single:Compiler Switches, -ftrace #. In order for this statement to be functional, tracing code must have been generated into the compiled program using either the \ \ \ :code:`-ftrace`\ switch (procedures only) or \ \ \ :code:`-ftraceall`\ switch (procedures and statements). .. index:: single:Environment Variables, COB_SET_TRACE .. index:: single:COB_SET_TRACE Environment Variable #. The \ \ run-time environment variable ( :ref:`RunATimeAEnvironmentAVariables`) provides another way to control tracing. If this environment variable is set to a value of '\ :code:`Y`\ ' prior to the start of program execution, tracing started at the point the program begins execution, as if \ :code:`READY TRACE`\ were the first executed statement. The \ :code:`RESET TRACE`\ statement, if executed, will then turn off tracing. .. index:: single:RETURN .. _RETURN: 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 \ :code:`RETURN`\ statement reads a record from a sort or merge work file. #. The reserved words \ :code:`AT`\ and \ :code:`RECORD`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The \ :code:`RETURN`\ statement is valid only within the \ :code:`OUTPUT PROCEDURE`\ of a file-based \ :code:`SORT`\ ( :ref:`File-BasedASORT`) or a \ :code:`MERGE`\ statement ( :ref:`MERGE`) statement. #. The file must be a sort- or merge work file defined with a \ :code:`SD`\ ( :ref:`FileASort-Description`), not an \ :code:`FD`\ . .. index:: single:INTO #. A successful \ :code:`RETURN`\ will retrieve the next available record from . 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 \ \ :code:`INTO`\ clause is present, a copy of the just-retrieved record will be automatically moved to . #. The mandatory \ :code:`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. #. The optional \ :code:`NOT AT END`\ clause, if coded, will check checking for a file status value of 00. :ref:`File Status Codes `, for additional information. .. index:: single:REWRITE .. _REWRITE: 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 \ :code:`REWRITE`\ statement replaces a logical record on a disk file. #. The reserved words \ :code:`KEY`\ and \ :code:`WITH`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The specified on the statement must be defined as an 01-level record subordinate to the File Description (\ :code:`FD`\ ( :ref:`FileASort-Description`)) of a file that is currently open for \ :code:`I-O`\ ( :ref:`File OPEN Modes `). .. index:: single:FROM #. The optional \ \ :code:`FROM`\ clause will cause or to be automatically moved into prior to writing 's contents to the . If this clause is not specified, it is the programmer's responsibility to populate with the desired data prior to executing the \ :code:`REWRITE`\ . #. This statement may not be used with \ :code:`ORGANIZATION LINE SEQUENTIAL`\ ( :ref:`ORGANIZATIONALINEASEQUENTIAL`) files. #. 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 \ :code:`COMMIT`\ ( :ref:`COMMIT`) or \ :code:`UNLOCK`\ statement ( :ref:`UNLOCK`) is issued or that file is closed. #. If the file has \ :code:`ORGANIZATION SEQUENTIAL`\ ( :ref:`ORGANIZATIONASEQUENTIAL`): #. The record to be rewritten will be the one retrieved by the most-recently executed \ :code:`READ`\ ( :ref:`READ`) of the file. #. If the \ :code:`FD`\ of the file contains the \ :code:`RECORD CONTAINS`\ or \ :code:`RECORD IS VARYING`\ clause, and that clause allows the record size to vary, the size of cannot be altered. #. If the file has \ :code:`ORGANIZATION RELATIVE`\ ( :ref:`ORGANIZATIONARELATIVE`) or \ :code:`ORGANIZATION INDEXED`\ ( :ref:`ORGANIZATIONAINDEXED`): #. If the file has \ :code:`ACCESS MODE SEQUENTIAL`\ , the record to be rewritten will be the one retrieved by the most-recently executed \ :code:`READ`\ of the file. If the file has \ :code:`ACCESS MODE RANDOM`\ or \ :code:`ACCESS MODE DYNAMIC`\ , no \ :code:`READ`\ is required before a record may be rewritten --- the \ :code:`RELATIVE KEY`\ or \ :code:`RECORD KEY`\ definition for the file, respectively, will specify the record to be updated. #. If the \ :code:`FD`\ of the file contains the \ :code:`RECORD CONTAINS`\ or \ :code:`RECORD IS VARYING`\ clause, and that clause allows the record size to vary, the size \ *can*\ be altered. #. The optional \ :code:`LOCK`\ options may be used to manually control access to the re-written record by other programs while this program is running. :ref:`RecordALocking`, to review the various record locking behaviours. #. The optional \ :code:`INVALID KEY`\ and \ :code:`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. :ref:`File Status Codes `, for additional information. .. index:: single:ROLLBACK .. _ROLLBACK: 7.8.38 ROLLBACK ~~~~~~~~~~~~~~~ ROLLBACK Syntax :: ROLLBACK ~~~~~~~~ The \ :code:`ROLLBACK`\ statement has the same effect as if an \ :code:`UNLOCK`\ statement ( :ref:`UNLOCK`) were executed against every open file in the program. #. All locks currently being held for all open files will be released. #. :ref:`RecordALocking`, to review the various record locking behaviours. .. index:: single:SEARCH .. _SEARCH: 7.8.39 SEARCH ~~~~~~~~~~~~~ SEARCH Syntax :: SEARCH table-name-1 ~~~~~~ [ VARYING index-name-1 ] ~~~~~~~ [ AT END imperative-statement-1 ] ~~~ { WHEN conditional-expression-1 imperative-statement-2 }... ~~~~ [ END-SEARCH ] ~~~~~~~~~~ The \ :code:`SEARCH`\ statement is used to sequentially search a table, stopping either once a specific value is located within the table or when the table has been completely searched. #. The reserved word \ :code:`AT`\ is optional and may be omitted. The presence or absence of this word has no effect upon the program. .. index:: single:VARYING .. index:: single:Search Index #. The searching process will be controlled through a \ \ *Search Index*\ --- a data item with a \ :code:`USAGE`\ ( :ref:`USAGE`) of \ :code:`INDEX`\ . The search index is either the identifier specified on the \ \ :code:`VARYING`\ clause or --- if no \ :code:`VARYING`\ is specified --- the \ :code:`USAGE INDEX`\ data item implicitly created by an \ :code:`INDEXED BY`\ ( :ref:`OCCURS`) clause in the table's definition. #. At the time the \ :code:`SEARCH`\ statement is executed, the current value of the search index data item will define the starting position in the table where the searching process will begin. Typically, one initializes that index to a value of 1 before starting the \ :code:`SEARCH`\ via \ :code:`SET TO 1`\ . #. Each of the s on the \ :code:`WHEN`\ clause(s) should involve a data element within the table, subscripted using the search index. #. The searching process is as follows: #. Each will be evaluated, in turn, until either one evaluates to a value of \ :code:`TRUE`\ or all have evaluated to \ :code:`FALSE`\ . #. The ( :ref:`Imperative Statement `) specified on the \ :code:`WHEN`\ clause whose evaluated to \ :code:`TRUE`\ will be executed; after that, the search will be considered complete and control will fall into the first executable statement following the \ :code:`SEARCH`\ . #. If all s evaluated to FALSE: * The search index will be incremented by 1 .. index:: single:AT END * If the search index now has a value greater than the number of entries in the table, the search is considered to have failed and the on the optional \ \ :code:`AT END`\ clause, if any, will be executed. After that, control will fall into the first executable statement following the \ :code:`SEARCH`\ . * If the search index now has a value less than or equal to the number of entries in the table, search processing returns back to step A. .. index:: single:SEARCH ALL .. _SEARCHAALL: 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 \ :code:`SEARCH ALL`\ statement performs a binary, or half-interval, search against a sorted table. This is generally \ *significantly*\ faster than performing a sequential \ :code:`SEARCH`\ of a table, especially if the table contains a large number of entries. #. The reserved word \ :code:`AT`\ is optional and may be omitted. The presence or absence of this word has no effect upon the program. #. To be eligible for searching via \ :code:`SEARCH ALL`\ : #. The \ :code:`OCCURS`\ clause of must contain the following elements: .. index:: single:INDEXED BY * An \ \ :code:`INDEXED BY`\ entry to define an implicit search index data item with a \ :code:`USAGE`\ ( :ref:`USAGE`) of \ :code:`INDEX`\ . .. index:: single:DESCENDING KEY .. index:: single:ASCENDING KEY * An \ \ :code:`ASCENDING KEY`\ or \ \ :code:`DESCENDING KEY`\ clause to specify the field within the table by which all entries in the table are sorted. #. Just because the table has one or more \ :code:`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 \ :code:`SORT`\ ( :ref:`TableASORT`) can prove very useful in this regard. #. No two records in the table may have the same \ :code:`KEY`\ field values. If the table has multiple \ :code:`KEY`\ definitions, then no two records in the table may have the same \ *combination*\ of \ :code:`KEY`\ field values. #. If rule \ *A*\ is violated, the compiler will reject the \ :code:`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 \ :code:`SEARCH ALL`\ against the table will probably be incorrect. #. The should involve the \ :code:`KEY`\ field(s), using the search index (the table's \ :code:`INDEXED BY`\ index name) as a subscript. .. index:: single:WHEN #. The function of the single, mandatory, \ \ :code:`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 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. #. The internal processing of the SEARCH ALL statement begins by setting internal "first" and "last" pointers to the 1\ :sup:`st`\ and last entry locations of the table. Processing then proceeds as follows: #. 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 . #. The 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, ( :ref:`Imperative Statement `) is executed, after which control falls through into the next statement following the \ :code:`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). #. 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. #. 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; is executed, after which control falls through into the next statement following the \ :code:`SEARCH ALL`\ . If there is no \ :code:`AT END`\ clause coded, control simply falls into the next statement following the \ :code:`SEARCH ALL`\ . #. 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. #. Computer scientists will compare the two techniques implemented by the \ :code:`SEARCH`\ and \ :code:`SEARCH ALL`\ statements as follows: #. 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. #. 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! .. index:: single:SET .. _SET: 7.8.41 SET ~~~~~~~~~~ .. index:: single:SET ENVIRONMENT .. _SETAENVIRONMENT: 7.8.41.1 SET ENVIRONMENT ^^^^^^^^^^^^^^^^^^^^^^^^ SET ENVIRONMENT Syntax :: SET ENVIRONMENT { literal-1 } TO { literal-2 } ~~~ ~~~~~~~~~~~ { identifier-1 } ~~ { identifier-2 } The \ :code:`SET ENVIRONMENT`\ statement provides a straight-forward means of setting environment values from within a program. #. The value of or specifies the name of the environment variable to set. #. The value of or specifies the value to be assigned to the environment variable. #. Environment variables created or changed from within GnuCOBOL programs will be available to any sub-shell processes spawned by that program (i.e. \ :code:`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 \ :code:`DISPLAY UPON ENVIRONMENT-NAME`\ statement ( :ref:`DISPLAYAUPONAENVIRONMENT-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" .. index:: single:SET Program-Pointer .. _SETAProgram-Pointer: 7.8.41.2 SET Program-Pointer ^^^^^^^^^^^^^^^^^^^^^^^^^^^^ SET Program-Pointer Syntax :: SET program-pointer-1 TO ENTRY { literal-1 } ~~~ ~~ ~~~~~ { identifier-1 } The \ :code:`SET `\ statement allows you to retrieve the address of a procedure division code module --- specifically the \ :code:`PROGRAM-ID`\ , \ :code:`FUNCTION-ID`\ or an entry-point established via the \ :code:`ENTRY`\ statement ( :ref:`ENTRY`). #. The \ :code:`USAGE`\ ( :ref:`USAGE`) of must be \ :code:`PROGRAM-POINTER`\ . #. The or value specified must name a primary entry-point name (\ :code:`PROGRAM-ID`\ of a subroutine or \ :code:`FUNCTION-ID`\ of a user-defined function) or an alternate entry-point defined via an \ :code:`ENTRY`\ statement within a subprogram. #. 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 \ :code:`PROGRAM-POINTER`\ s at work, see the discussions of the \ :code:`CBL_ERROR_PROC`\ built-in system subroutine ( :ref:`CBLAERRORAPROC`) and \ :code:`CBL_EXIT_PROC`\ built-in system subroutine ( :ref:`CBLAEXITAPROC`). .. index:: single:SET ADDRESS .. _SETAADDRESS: 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 \ :code:`SET ADDRESS`\ statement can be used to work with the addresses of data items rather than their contents. .. index:: single:ADDRESS OF #. When the \ \ :code:`ADDRESS OF`\ clause is used \ *before*\ the \ :code:`TO`\ you will be using this statement to alter the address of a linkage section or \ :code:`BASED`\ ( :ref:`BASED`) data item. Without that clause you will be assigning an address to one or more data items whose \ :code:`USAGE`\ ( :ref:`USAGE`) is \ :code:`POINTER`\ . #. When the \ :code:`ADDRESS OF`\ clause is used \ *after*\ the \ :code:`TO`\ , this statement will be identifying the address of as the address to be assigned to or stored in . #. If the \ :code:`ADDRESS OF`\ clause is absent after the \ :code:`TO`\ , the contents of will serve as the address to be assigned. .. index:: single:SET Index .. _SETAIndex: 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 \ :code:`USAGE INDEX`\ data item. #. Either the \ :code:`USAGE`\ ( :ref:`USAGE`) of should be \ :code:`INDEX`\ , or must be identified in a table \ :code:`INDEXED BY`\ clause. .. index:: single:SET UP/DOWN .. _SETAUPADOWN: 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. #. The \ :code:`USAGE`\ ( :ref:`USAGE`) of must be \ :code:`INDEX`\ , \ :code:`POINTER`\ or \ :code:`PROGRAM-POINTER`\ . #. The typical usage when is a \ :code:`USAGE INDEX`\ data item is to increment its value \ :code:`UP`\ or \ :code:`DOWN`\ by 1, since an index is usually being used to sequentially walk through the elements of a table. .. index:: single:SET Condition Name .. _SETAConditionAName: 7.8.41.6 SET Condition Name ^^^^^^^^^^^^^^^^^^^^^^^^^^^ SET Condition Name Syntax :: SET condition-name-1... TO { TRUE } ~~~ ~~ { ~~~~ } { FALSE } ~~~~~ The \ :code:`SET `\ statement provides one method of specifying the \ :code:`TRUE`\ / \ :code:`FALSE`\ value of a level-88 condition name. #. By setting the specified (s) to a \ :code:`TRUE`\ or \ :code:`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. #. When specifying \ :code:`TRUE`\ , the value assigned to each parent data item will be the first value specified on the condition name's \ :code:`VALUE`\ clause. #. When specifying \ :code:`FALSE`\ , the value assigned to each parent data item will be the value specified for the \ :code:`FALSE`\ clause of the condition name's definition; if any occurrence lacks a \ :code:`FALSE`\ clause, the \ :code:`SET`\ statement will be rejected by the compiler. .. index:: single:SET Switch .. _SETASwitch: 7.8.41.7 SET Switch ^^^^^^^^^^^^^^^^^^^ SET Switch Syntax :: SET mnemonic-name-1... TO { ON } ~~~ ~~ { ~~ } { OFF } ~~~ This form of the \ :code:`SET`\ statement is used to turn switches on or off. #. Switches are defined using the \ :code:`SPECIAL-NAMES`\ ( :ref:`SPECIAL-NAMES`) paragraph. #. Switches may be tested via the \ :code:`IF`\ statement ( :ref:`IF`) and a Switch-Status Condition. :ref:`Switch-StatusAConditions`, for more information. .. index:: single:SET ATTRIBUTE .. _SETAATTRIBUTE: 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 \ :code:`SET ATTRIBUTE`\ statement may be used to modify one or more attributes of a screen section data item at run-time. #. When making an attribute change to , the change will not become visible on the screen until the screen section data item containing is next accepted (if is an input field) or is next displayed (if is not an input field). #. The attributes shown in the syntax diagram are the only ones that may be altered by this statement. :ref:`DataADescriptionAClauses`, for information on their usage. .. index:: single:SET LAST EXCEPTION .. _SETALASTAEXCEPTION: 7.8.41.9 SET LAST EXCEPTION ^^^^^^^^^^^^^^^^^^^^^^^^^^^ SET ATTRIBUTE Syntax :: SET LAST EXCEPTION TO { OFF } ~~~ ~~~~ ~~~~~~~~~ ~~ ~~~ The \ :code:`SET LAST EXCEPTION`\ statement will set the last program exception status to indicate no exception. #. The predefined object reference EXCEPTION-OBJECT is set to null, and the last exception status is set to indicate no exception. #. 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. .. index:: single:SORT .. _SORT: 7.8.42 SORT ~~~~~~~~~~~ .. index:: single:File-Based SORT .. _File-BasedASORT: 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... } ~~~~~~ .. index:: single:DUPLICATES The \ \ :code:`DUPLICATES`\ clause is syntactically recognized but is otherwise non-functional. This format of the \ :code:`SORT`\ statement is designed to sort large volumes of data according to one or more key fields. #. The reserved words \ :code:`IN`\ , \ :code:`IS`\ , \ :code:`KEY`\ , \ :code:`ON`\ , \ :code:`ORDER`\ , \ :code:`SEQUENCE`\ and \ :code:`WITH`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The reserved words \ :code:`THRU`\ and \ :code:`THROUGH`\ are interchangeable. #. GnuCOBOL always behaves as if the \ :code:`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. #. The named on the \ :code:`SORT`\ statement must be defined using a sort description (\ :code:`SD`\ ( :ref:`FileASort-Description`)). This file is referred to in the remainder of this discussion as the \ *sort work file*\ . #. If specified, and must reference \ :code:`ORGANIZATION LINE SEQUENTIAL`\ ( :ref:`ORGANIZATIONALINEASEQUENTIAL`) or \ :code:`ORGANIZATION SEQUENTIAL`\ ( :ref:`ORGANIZATIONASEQUENTIAL`) files. These files must be defined using a file description (\ :code:`FD`\ ( :ref:`FileASort-Description`)). The same file(s) may be used for and . #. The ... field(s) must be defined as field(s) within a record of . #. A sort work file is never opened or closed. #. The sorting process works in three stages --- the Input Stage, the Sort Stage and the Output Stage. #. The following points pertain to the Input Stage: #. 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 \ :code:`USING`\ clause (done automatically by the sort) or by utilizing an input procedure. .. index:: single:USING #. When \ \ :code:`USING`\ is specified, none of the files may be open at the time the \ :code:`SORT`\ statement is executed. .. index:: single:INPUT PROCEDURE #. When an input procedure is used, the procedure(s) specified on the \ \ :code:`INPUT PROCEDURE`\ clause will be invoked as if by a procedural \ :code:`PERFORM`\ statement ( :ref:`ProceduralAPERFORM`) with no \ :code:`VARYING`\ , \ :code:`TIMES`\ or \ :code:`UNTIL`\ options specified. Records will be loaded into the sort work file --- one at a time --- within the input procedure using the \ :code:`RELEASE`\ statement ( :ref:`RELEASE`). This, by the way, is how you could sort the contents of relative or indexed files. A \ :code:`GO TO`\ statement ( :ref:`GOATO`) that transfers control out of the input procedure will terminate the \ :code:`SORT`\ statement but allows the program to continue executing from the point where the \ :code:`GO TO`\ statement transferred control to. Once an input procedure has been "aborted" using a \ :code:`GO TO`\ it cannot be resumed, and the contents of the sort work file are lost. You may, however, re-execute the \ :code:`SORT`\ statement itself. [#]_ An input procedure should be terminated in the same way a procedural \ :code:`PERFORM`\ statement would be. Neither a another file-based \ :code:`SORT`\ statement nor a \ :code:`MERGE`\ statement may be executed within the input procedure unless those statements utilize a different sort or merge work file. #. Once the input procedure terminates, the input phase is complete. .. index:: single:Environment Variables, COB_SORT_MEMORY .. index:: single:COB_SORT_MEMORY Environment Variable #. 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 ( :ref:`RunATimeAEnvironmentAVariables`) that you may use to allocate more or less memory to the sorting process. #. The following points pertain to the Sort Stage: #. The sort will take place by arranging the data records in the sequence defined by the \ :code:`KEY`\ specification(s) on the \ :code:`SORT`\ statement according to the \ :code:`COLLATING SEQUENCE`\ specified on the \ :code:`SORT`\ (if any) or --- if none was defined --- the \ :code:`PROGRAM COLLATING SEQUENCE`\ ( :ref:`OBJECT-COMPUTER`). Keys may be any supported data type and \ :code:`USAGE`\ ( :ref:`USAGE`) except for level-78 or level-88 data items. #. 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 31\ :sup:`st`\ of August 2009, those transactions will be retained in the order in which they were loaded into the sort work file. .. index:: single:Environment Variables, TEMP .. index:: single:TEMP Environment Variable .. index:: single:Environment Variables, TMP .. index:: single:TMP Environment Variable .. index:: single:Environment Variables, TMPDIR .. index:: single:TMPDIR Environment Variable #. 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 ( :ref:`RunATimeAEnvironmentAVariables`) (checked for existence in that sequence). These disk files will be automatically purged upon \ :code:`SORT`\ termination or program execution termination (normal or otherwise). #. The following points pertain to the Output Stage: .. index:: single:GIVING #. Once the sort stage is complete, a copy of the sorted data will be written to each if the \ \ :code:`GIVING`\ clause was specified. None of the files can be open at the time the sort is executed. .. index:: single:OUTPUT PROCEDURE #. When an output procedure is used, the procedure(s) specified on the \ \ :code:`OUTPUT PROCEDURE`\ clause will be invoked as if by a procedural \ :code:`PERFORM`\ statement ( :ref:`ProceduralAPERFORM`) with no \ :code:`VARYING`\ , \ :code:`TIMES`\ or \ :code:`UNTIL`\ options specified. Records will be retrieved from the sort work file --- one at a time --- within the output procedure using the \ :code:`RETURN`\ statement ( :ref:`RETURN`). A \ :code:`GO TO`\ statement ( :ref:`GOATO`) that transfers control out of the output procedure will terminate the \ :code:`SORT`\ statement but allows the program to continue executing from the point where the \ :code:`GO TO`\ statement transferred control to. Once an output procedure has been "aborted" using a \ :code:`GO TO`\ it cannot be resumed, and the contents of the sort work file are lost. You may, however, re-execute the \ :code:`SORT`\ statement itself. USING A \ :code:`GO TO`\ statement [#]_ An output procedure should be terminated in the same way a procedural \ :code:`PERFORM`\ statement would be. Neither a another file-based \ :code:`SORT`\ statement nor a \ :code:`MERGE`\ statement may be executed within the output procedure unless those statements utilize a different sort or merge work file. #. Once the output procedure terminates, the sort is complete. .. index:: single:Table SORT .. _TableASORT: 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 ] ~~~~~~~~~ .. index:: single:DUPLICATES The \ \ :code:`DUPLICATES`\ clause is syntactically recognized but is otherwise non-functional. This format of the \ :code:`SORT`\ statement sorts relatively small quantities of data --- namely data contained in a data division table --- according to one or more key fields. #. The reserved words \ :code:`IN`\ , \ :code:`IS`\ , \ :code:`KEY`\ , \ :code:`ON`\ , \ :code:`ORDER`\ , \ :code:`SEQUENCE`\ and \ :code:`WITH`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. GnuCOBOL always behaves as if the \ :code:`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. #. The data item must be a table defined in any data division section \ *except*\ the report or screen sections. #. The data within will be sorted in-place (i.e. no sort file is required). #. The sort will take place by rearranging the data in into the sequence defined by the \ :code:`KEY`\ specification(s) on the \ :code:`SORT`\ statement, according to the \ :code:`COLLATING SEQUENCE`\ specified on the \ :code:`SORT`\ (if any) or --- if none was defined --- the \ :code:`PROGRAM COLLATING SEQUENCE`\ ( :ref:`OBJECT-COMPUTER`). Keys may be any supported data type and \ :code:`USAGE`\ ( :ref:`USAGE`) except for level-78 or level-88 data items. #. If you are sorting for the purpose of preparing the table for use with a \ :code:`SEARCH ALL`\ statement ( :ref:`SEARCHAALL`), care must be taken that the \ :code:`KEY`\ specifications on the \ :code:`SORT`\ agree with those in the table's definition. #. Although the specification of one or more \ :code:`KEY`\ clauses is optional, currently, a table sort with no \ :code:`KEY`\ specification(s) made on the \ :code:`SORT`\ statement is unsupported by GnuCOBOL and will be rejected by the compiler. .. index:: single:START .. _START: 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 \ :code:`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. #. The reserved words \ :code:`IS`\ , \ :code:`THAN`\ and \ :code:`TO`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. To use this statement, must be an \ :code:`ORGANIZATION RELATIVE`\ ( :ref:`ORGANIZATIONARELATIVE`) or \ :code:`ORGANIZATION INDEXED`\ ( :ref:`ORGANIZATIONAINDEXED`) file that must have been defined with an \ :code:`ACCESS MODE DYNAMIC`\ or \ :code:`ACCESS MODE SEQUENTIAL`\ in its \ :code:`SELECT`\ statement ( :ref:`SELECT`). #. At the time this statement is executed, must be open in either \ :code:`INPUT`\ or \ :code:`I-O`\ ( :ref:`File OPEN Modes `) mode. #. If is a relative file, must be the defined \ :code:`RELATIVE KEY`\ of the file. #. If is an indexed file, must be the defined \ :code:`RECORD KEY`\ of the file or any of the \ :code:`ALTERNATE RECORD KEY`\ fields for the file. #. If no \ :code:`FIRST`\ , \ :code:`LAST`\ or \ :code:`KEY`\ clause is specified, \ :code:`KEY IS EQUAL TO `\ will be assumed, where \ :code:``\ is the defined \ :code:`RELATIVE KEY`\ of (if is a relative file) or the defined \ :code:`RECORD KEY`\ (if is an indexed file). #. After successful execution of a \ :code:`START`\ statement, the internal logical record pointer into the data will be positioned to the record which satisfied the actual or implied \ :code:`FIRST`\ , \ :code:`LAST`\ or \ :code:`KEY`\ clause specification, as follows: * \ :code:`FIRST`\ the logical record pointer will point to the first record in the file. * \ :code:`LAST`\ the logical record pointer will point to the last record in the file. * \ :code:`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. * \ :code:`SIZE`\ WITH \ :code:`SIZE`\ or \ :code:`LENGTH`\ arithmetic-expression specifies the number of characters in the key to be used in the positioning process. * \ :code:`LENGTH`\ WITH \ :code:`LENGTH`\ or \ :code:`SIZE`\ arithmetic-expression specifies the number of characters in the key to be used in the positioning process. \ :code:`SIZE`\ and \ :code:`LENGTH`\ are interchangeable and mean exactly the same. * \ :code:`EQUAL TO`\ , \ :code:`GREATER THAN`\ or \ :code:`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 \ :code:`KEY`\ clause), provided the relation is * \ :code:`LESS THAN`\ , \ :code:`LESS THAN OR EQUAL TO`\ or \ :code:`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 \ :code:`KEY`\ clause) The next sequential \ :code:`READ`\ statement will read the record that is pointed to by the logical record pointer. #. The optional \ :code:`INVALID KEY`\ and \ :code:`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. :ref:`File Status Codes `, for additional information. .. index:: single:STOP .. _STOP: 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 \ :code:`STOP`\ statement suspends program execution. Some options will allow program execution to resume while others return control to the operating system. #. The reserved words \ :code:`STATUS`\ and \ :code:`WITH`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. .. index:: single:GIVING .. index:: single:RETURNING #. The reserved words \ \ :code:`RETURNING`\ and \ \ :code:`GIVING`\ are interchangeable. .. index:: single:RUN #. The \ \ :code:`RUN`\ clause halts the program without displaying any special message to that effect. #. The clause displays the specified text on the \ :code:`SYSOUT`\ /\ :code:`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. #. The optional \ :code:`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 \ :code:`%ERRORLEVEL%`\ to query the exit status while Unix shells such as sh, bash and ksh can query the exit status as \ :code:`$?`\ . Other Unix shells may have different ways to access return code values. .. index:: single:STATUS #. The \ \ :code:`STATUS`\ clause provides another means of returning an exit status. Using the \ :code:`STATUS`\ clause is functionally equivalent to using the \ :code:`RETURNING`\ clause. .. index:: single:ERROR .. index:: single:NORMAL #. Using the \ :code:`STATUS`\ clause without a or will return an exit status of 0 if the \ \ :code:`NORMAL`\ keyword is used or a 1 if \ \ :code:`ERROR`\ was specified. .. index:: single:Special Registers, RETURN-CODE .. index:: single:RETURN-CODE Special Register #. Your program will \ *always*\ return an exit status, even if no \ :code:`RETURNING`\ or \ :code:`STATUS`\ clause is specified. In the absence of the use of these clauses, the value in the \ \ \ :code:`RETURN-CODE`\ special register ( :ref:`SpecialARegisters`) at the time the \ :code:`STOP`\ statement is executed will be used as the exit status. #. Any programmer-defined exit procedure (established via the \ :code:`CBL_EXIT_PROC`\ built-in system subroutine ( :ref:`CBLAEXITAPROC`)) will be executed by \ :code:`STOP RUN`\ , but not by \ :code:`STOP `\ . #. Valid return code values can be in the range -2147483648 to +2147483647. #. 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. #. :: STOP RUN RETURNING 16 #. :: MOVE 16 TO RETURN-CODE STOP RUN #. :: STOP RUN WITH ERROR STATUS 16 .. index:: single:STRING .. _STRING: 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 \ :code:`STRING`\ statement is used to concatenate all or a part of one or more strings together, forming a new string. #. The reserved words \ :code:`BY`\ , \ :code:`ON`\ and \ :code:`WITH`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. All literals and identifiers (except for ) must be explicitly or implicitly defined with a \ :code:`USAGE`\ ( :ref:`USAGE`) of \ :code:`DISPLAY`\ . Any of the identifiers may be group items. .. index:: single:POINTER #. The \ \ :code:`POINTER`\ data item --- --- must be a non-edited elementary integer numeric data item with a value greater than zero. #. Each / will be referred to as a source item. The receiving data item is . .. index:: single:current character pointer #. The \ :code:`STRING`\ statement's processing is based upon a \ \ *current character pointer*\ . The initial value of the current character pointer will be the value of at the time the \ :code:`STRING`\ statement began execution. If no \ :code:`POINTER`\ clause is coded, a value of 1 (meaning "the 1\ :sup:`st`\ character position") will be assumed for the current character pointer's initial value. #. For each source item, the contents of the sending item will be copied --- character-by-character --- into 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 where the \ *next*\ character should be copied. .. index:: single:DELIMITED BY #. The \ \ :code:`DELIMITED BY`\ clause specifies how much of each source item will be copied into . \ :code:`DELIMITED BY SIZE`\ (the default if no \ :code:`DELIMITED BY`\ clause is specified) causes the \ *entire*\ contents of the source item to be copied into . #. Using \ :code:`DELIMITED BY `\ or \ :code:`DELIMITED BY `\ 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. #. \ :code:`STRING`\ processing will cease when one of the following occurs: #. The initial value of the current character pointer is less than 1 or greater than the number of characters in , or... #. The value of the current character pointer exceeds the size of at the point the STRING statement wants to copy a character into , or... #. All sending items have been fully processed #. If event \ *A*\ occurs, will remain unchanged. .. index:: single:overflow condition #. The occurrence of either event \ *A*\ or \ *B*\ triggers what is referred to as an \ \ *overflow condition*\ . #. The ) is neither automatically initialized (to spaces or any other value) at the start of a \ :code:`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 yourself via the \ :code:`INITIALIZE`\ ( :ref:`INITIALIZE`) or \ :code:`MOVE`\ ( :ref:`MOVE`) statements before executing the \ :code:`STRING`\ if you wish. #. The optional \ :code:`ON OVERFLOW`\ and \ :code:`NOT ON OVERFLOW`\ clauses may be used to detect and react to the occurrence or not, respectively, of an overflow condition. :ref:`ONAOVERFLOWAAANOTAONAOVERFLOW`, for additional information. .. index:: single:SUBTRACT .. _SUBTRACT: 7.8.46 SUBTRACT ~~~~~~~~~~~~~~~ .. index:: single:SUBTRACT FROM .. _SUBTRACTAFROM: 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 \ :code:`SUBTRACT`\ statement generates the arithmetic sum of all arguments that appear before the \ :code:`FROM`\ ( or ) and subtracts that sum from each . #. The reserved words \ :code:`IS`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. Both and must be numeric unedited data items. #. must be a numeric literal. #. The optional \ :code:`ROUNDED`\ ( :ref:`ROUNDED`) clause available to each will control how non-integer results will be saved. #. The optional \ :code:`ON SIZE ERROR`\ and \ :code:`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 with an insufficient number of digit positions available to the left of any implied decimal point. :ref:`ONASIZEAERRORAAANOTAONASIZEAERROR`, for additional information. .. index:: single:SUBTRACT GIVING .. _SUBTRACTAGIVING: 7.8.46.2 SUBTRACT GIVING ^^^^^^^^^^^^^^^^^^^^^^^^ .. index:: single: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 \ :code:`SUBTRACT GIVING`\ statement generates the arithmetic sum of all arguments that appear before the \ :code:`FROM`\ ( or ), subtracts that sum from the contents of and then replaces the contents of the identifiers listed after the \ \ :code:`GIVING`\ () with that result. #. The reserved words \ :code:`IS`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. Both and must be numeric unedited data items. #. must be a numeric literal. #. must be a numeric (edited or unedited) data item. #. The optional \ :code:`ROUNDED`\ ( :ref:`ROUNDED`) clause available to each will control how non-integer results will be saved. #. The optional \ :code:`ON SIZE ERROR`\ and \ :code:`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 with an insufficient number of digit positions available to the left of any implied decimal point. :ref:`ONASIZEAERRORAAANOTAONASIZEAERROR`, for additional information. .. index:: single:SUBTRACT CORRESPONDING .. _SUBTRACTACORRESPONDING: 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 \ :code:`SUBTRACT CORRESPONDING`\ statement generates code equivalent to individual \ :code:`SUBTRACT FROM`\ statements for corresponding matches of data items found subordinate to the two identifiers. #. The reserved words \ :code:`IS`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. Both and must be group items. #. :ref:`CORRESPONDING`, for information on how corresponding matches will be found between and . #. The optional \ :code:`ROUNDED`\ ( :ref:`ROUNDED`) clause available to each will control how non-integer results will be saved. #. The optional \ :code:`ON SIZE ERROR`\ and \ :code:`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 with an insufficient number of digit positions available to the left of any implied decimal point. :ref:`ONASIZEAERRORAAANOTAONASIZEAERROR`, for additional information. .. index:: single:SUPPRESS .. _SUPPRESS: 7.8.47 SUPPRESS ~~~~~~~~~~~~~~~ SUPPRESS Syntax :: SUPPRESS PRINTING ~~~~~~~~ The \ :code:`SUPPRESS`\ statement causes the presentation of a report group to be suppressed. #. The reserved word \ :code:`PRINTING`\ is optional and may be omitted. The presence or absence of this word has no effect upon the program. #. This statement may only appear within a \ :code:`USE BEFORE REPORTING`\ procedure (in \ :code:`DECLARATIVES`\ ( :ref:`DECLARATIVES`)). #. \ :code:`SUPPRESS`\ only prevents the presentation of the report group within whose \ :code:`USE BEFORE REPORTING`\ procedure the statement occurs. #. This statement must be executed each time presentation of the report group is to be suppressed. #. When a report group's presentation is suppressed, none of the following operations for the report will take place: #. Actual presentation of the report group in question. #. Processing of any \ :code:`LINE`\ ( :ref:`LINE`) clauses within the report group in question. #. Processing of the \ :code:`NEXT GROUP`\ ( :ref:`NEXTAGROUP`) clause (if any) within the report group in question. .. index:: single:Special Registers, LINE-COUNTER .. index:: single:LINE-COUNTER Special Register #. Any modification to the \ \ \ :code:`LINE-COUNTER`\ special register ( :ref:`SpecialARegisters`). .. index:: single:Special Registers, PAGE-COUNTER .. index:: single:PAGE-COUNTER Special Register #. Any modification to the \ \ \ :code:`PAGE-COUNTER`\ special register. .. index:: single:TERMINATE .. _TERMINATE: 7.8.48 TERMINATE ~~~~~~~~~~~~~~~~ TERMINATE Syntax :: TERMINATE report-name-1... ~~~~~~~~~ The \ :code:`TERMINATE`\ statement causes the processing of the specified report(s) to be completed. #. Each must be the name of a report having an \ :code:`RD`\ ( :ref:`REPORTASECTION`) defined for it. #. The specified report name(s) must be currently initiated (via \ :code:`INITIATE`\ ( :ref:`INITIATE`)) and cannot yet have been terminated. #. The \ :code:`TERMINATE`\ statement will present each \ :code:`CONTROL FOOTING`\ (if any), in reverse sequence of the control hierarchy, starting with the most minor up to \ :code:`FINAL`\ (if any). During the presentation of these groups and the processing of any \ :code:`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. #. During the presentation of the \ :code:`CONTROL FOOTING`\ groups, any necessary \ :code:`PAGE FOOTING`\ and \ :code:`PAGE HEADING`\ groups will be presented as well. #. Finally,the \ :code:`REPORT FOOTING`\ group, if any, will be presented. #. If an \ :code:`INITIATE`\ is followed by a \ :code:`TERMINATE`\ with no intervening \ :code:`GENERATE`\ ( :ref:`GENERATE`) statements (all pertaining to the same report, of course), no report groups will be presented to the output file. .. index:: single:TRANSFORM .. _TRANSFORM: 7.8.49 TRANSFORM ~~~~~~~~~~~~~~~~ TRANSFORM Syntax :: TRANSFORM identifier-1 CHARACTERS FROM { literal-1 } TO { literal-2 } ~~~~~~~~~ ~~~~ { identifier-2 } ~~ { identifier-3 } The \ :code:`TRANSFORM`\ statement scans a data item performing a series of mono-alphabetic substitutions, defined by the arguments before and after the \ :code:`TO`\ clause. #. Both and/or must be alphanumeric literals. #. All of , and must either be group items or alphanumeric data items. Numeric data items with a \ :code:`USAGE`\ ( :ref:`USAGE`) of \ :code:`DISPLAY`\ are accepted, but will generate warning messages from the compiler. #. The \ :code:`TRANSFORM`\ statement will replace characters within that are found in the string specified \ *before*\ the \ :code:`TO`\ keyword with the corresponding characters from the string specified \ *after*\ the \ :code:`TO`\ keyword. #. Usage of word CHARACTERS has no effect on operations other than for appearance. #. This statement exists within GnuCOBOL to provide compatibility with COBOL programs written to pre-1985 standards. The \ :code:`TRANSFORM`\ statement was made obsolete in the 1985 standard of COBOL, having been replaced by the \ :code:`CONVERTING`\ clause of the \ :code:`INSPECT`\ statement ( :ref:`INSPECT`). New programs should be coded to use \ :code:`INSPECT CONVERTING`\ rather than \ :code:`TRANSFORM`\ . .. index:: single:UNLOCK .. _UNLOCK: 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 . #. The reserved words \ :code:`RECORD`\ and \ :code:`RECORDS`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. If is a Sort/Merge work file, no action will be taken. #. 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. #. 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. #. 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). #. 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. #. :ref:`RecordALocking`, for additional information on record locking. .. index:: single:UNSTRING .. _UNSTRING: 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 \ :code:`UNSTRING`\ statement parses a string, extracting any number of sub strings from it. #. The reserved words \ :code:`BY`\ , \ :code:`IN`\ and \ :code:`ON`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. through must be explicitly or implicitly defined with a \ :code:`USAGE`\ ( :ref:`USAGE`) of \ :code:`DISPLAY`\ . Any of those identifiers may be group items. #. Both and must be alphanumeric literals. #. Each of , and must be elementary non-edited integer numeric items. #. At the time the \ :code:`UNSTRING`\ statement begins execution, must have a value greater than 0. #. will be referred to as the \ *source string*\ and each will be referred to as a \ *destination field*\ in the following discussions. #. The \ :code:`UNSTRING`\ statement's processing is based upon a \ *current character pointer*\ , the initial value of which will be the value of at the time the \ :code:`UNSTRING`\ statement began execution. If no \ :code:`POINTER`\ clause is coded, a value of 1 (meaning "the 1\ :sup:`st`\ character position") will be assumed for the current character pointer's initial value. .. index:: single:DELIMITED BY #. 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 \ \ :code:`DELIMITED BY`\ clause as inter-sub string separators. .. index:: single:ALL #. Using the \ \ :code:`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. #. Two consecutive delimiter sequences will identify a null sub string. #. 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 \ :code:`JUSTIFIED`\ ( :ref:`JUSTIFIED`) clause on the destination field. .. index:: single:DELIMITER #. Each destination field may have an optional \ \ :code:`DELIMITER`\ clause. If a \ :code:`DELIMITER`\ clause is specified, 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), for that destination field will also be unchanged. .. index:: single:COUNT #. Each destination field may have an optional \ \ :code:`COUNT`\ clause. If a \ :code:`COUNT`\ clause is specified, 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), for that destination field will also be unchanged. #. If a \ :code:`TALLYING`\ clause is coded, will be incremented by 1 each time a destination field is populated. #. None of , , , or are initialized by the \ :code:`UNSTRING`\ statement. You need to do that yourself via a \ :code:`MOVE`\ ( :ref:`MOVE`) or \ :code:`INITIALIZE`\ statement ( :ref:`INITIALIZE`). #. \ :code:`UNSTRING`\ processing will cease when one of the following occurs: #. The initial value of the current character pointer is less than 1 or greater than the number of character positions in , or... #. All destination fields have been fully processed #. If event \ *A*\ occurs, none of the destination field contents (or the contents of their \ :code:`DELIMITER`\ or identifiers) will be changed. #. An \ *overflow*\ condition exists if either event \ *A*\ occurs, or if event \ *B*\ occurs with at least one character position in not having been processed. #. The optional \ :code:`ON OVERFLOW`\ and \ :code:`NOT ON OVERFLOW`\ clauses may be used to detect and react to the occurrence or not, respectively, of an overflow condition. :ref:`ONAOVERFLOWAAANOTAONAOVERFLOW`, for additional information. The following sample program illustrates the \ :code:`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! .. index:: single:WRITE .. _WRITE: 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 \ :code:`WRITE`\ statement writes a new record to an open file. #. The reserved words \ :code:`ADVANCING`\ , \ :code:`AT`\ , \ :code:`KEY`\ , \ :code:`LINE`\ , \ :code:`LINES`\ and \ :code:`WITH`\ are optional and may be omitted. The presence or absence of these words has no effect upon the program. #. The reserved words \ :code:`END-OF-PAGE`\ and \ :code:`EOP`\ are interchangeable. #. The specified on the statement must be defined as an 01-level record subordinate to the File Description (\ :code:`FD`\ ( :ref:`FileASort-Description`)) of a file that is currently open for \ :code:`OUTPUT`\ ( :ref:`File OPEN Modes `), \ :code:`EXTEND`\ or \ :code:`I-O`\ . .. index:: single:FROM #. The optional \ \ :code:`FROM`\ clause will cause or to be automatically moved into prior to writing 's contents to the appropriate file. If this clause is not specified, it is the programmer's responsibility to populate with the desired data prior to executing the \ :code:`WRITE`\ . #. The optional \ :code:`LOCK`\ options may be used to manually control access to the just-written record by other programs while this program is running. :ref:`RecordALocking`, to review the various record locking behaviour. #. The optional \ :code:`INVALID KEY`\ and \ :code:`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. :ref:`File Status Codes `, for additional information. #. When \ :code:`WRITE`\ is used against an \ :code:`ORGANIZATION LINE SEQUENTIAL`\ ( :ref:`ORGANIZATIONALINEASEQUENTIAL`) file, with or without the \ :code:`LINE ADVANCING`\ ( :ref:`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 (\ :code:`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 (\ :code:`X'0A'`\ ) if you are running a Cygwin, Linux, Unix or OSX build of GnuCOBOL #. The following points pertain to the use (or not) of the \ :code:`ADVANCING`\ clause: #. Using this clause with any organization other than \ :code:`ORGANIZATION LINE SEQUENTIAL`\ will either be rejected outright by the compiler (relative or indexed files) or may introduce unwanted characters into the file (\ :code:`ORGANIZATION SEQUENTIAL`\ ( :ref:`ORGANIZATIONASEQUENTIAL`)). #. If no \ :code:`ADVANCING`\ clause is specified on a \ :code:`WRITE`\ to a line-advancing file, \ :code:`AFTER ADVANCING 1 LINE`\ will be assumed; on other than line-advancing files, \ :code:`BEFORE ADVANCING 1 LINE`\ will be assumed. .. index:: single:BEFORE ADVANCING #. When \ \ :code:`BEFORE ADVANCING`\ is used (or implied), the record is written to the file before the \ :code:`ADVANCING`\ action writes line-terminator characters to the file. .. index:: single:AFTER ADVANCING #. If \ \ :code:`AFTER ADVANCING`\ is used (or implied), the \ :code:`ADVANCING`\ action writes line-terminator characters to the file and then the record data is written to the file. #. The \ :code:`ADVANCING n LINES`\ clause will introduce the specified number of line-terminator character sequences into the file either before the written record (\ :code:`AFTER ADVANCING`\ ) or after the written record (\ :code:`BEFORE ADVANCING`\ ). #. If the \ :code:`LINAGE`\ ( :ref:`FileASort-Description`) clause is \ *absent*\ from the file's \ :code:`FD`\ : .. index:: single:ADVANCING PAGE #. The \ \ :code:`ADVANCING PAGE`\ clause will introduce an ASCII formfeed character into the file either before the written record (\ :code:`AFTER PAGE`\ ) or after the written record (\ :code:`BEFORE PAGE`\ ). #. 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. #. If the LINAGE clause is \ *present*\ in the file's \ :code:`FD`\ : #. The \ :code:`ADVANCING PAGE`\ clause will introduce the appropriate number of line-terminator character sequences into the file either before the written record (\ :code:`AFTER ADVANCING`\ ) or after the written record (\ :code:`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 \ :code:`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 \ :code:`LINAGE`\ clause. .. index:: single:END-OF-PAGE .. index:: single:Special Registers, LINAGE-COUNTER .. index:: single:LINAGE-COUNTER Special Register #. 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 \ \ \ :code:`LINAGE-COUNTER`\ special register ( :ref:`SpecialARegisters`) and the \ \ :code:`END-OF-PAGE`\ clause to deal with page formatting issues. #. The \ :code:`AT END-OF-PAGE`\ clause will be triggered, thus executing ( :ref:`Imperative Statement `), if the \ :code:`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 \ :code:`LINAGE`\ clause. The \ :code:`NOT AT END-OF-PAGE`\ clause will be triggered (thus executing ) if no end-of-page condition occurred during the \ :code:`WRITE`\ . .. [#] Using a \ :code:`GO TO`\ statement to prematurely terminate a sort, or re-starting a previously-cancelled sort is not considered good programming style and should be avoided. .. [#] To prematurely terminate a sort, or re-starting a previously-cancelled sort is not considered good programming style and should be avoided.