Language elements that are not supported

Enterprise COBOL does not support the following OS/VS COBOL language elements. When upgrading to Enterprise COBOL, you must either remove or alter these items as indicated in the following descriptions:
ASSIGN . . . OR
OS/VS COBOL accepted the ASSIGN ... OR clause. To use this clause under Enterprise COBOL, you must remove the OR.
ASSIGN TO integer system-name
OS/VS COBOL accepted the ASSIGN TO integer system-name clause. To use this clause under Enterprise COBOL, you must remove the integer.
ASSIGN . . . FOR MULTIPLE REEL/UNIT
OS/VS COBOL accepted the ASSIGN ... FOR MULTIPLE REEL/UNIT phrase, and treated it as documentation. Enterprise COBOL does not support this phrase.
CLOSE statement: WITH POSITIONING, DISP phrases
OS/VS COBOL accepted the WITH POSITIONING and DISP phrases of the CLOSE statement provided as IBM® extensions in OS/VS COBOL. In Enterprise COBOL, these phrases are not accepted.
CURRENT-DATE special register
OS/VS COBOL accepted the CURRENT-DATE special register. It is valid only as the sending field in a MOVE statement. CURRENT-DATE has the 8-byte alphanumeric format:
MM/DD/YY  (month, day, year)
Enterprise COBOL supports the DATE special register. It is valid only as the sending field in an ACCEPT statement. DATE has the 6-byte alphanumeric format:
YYMMDD  (year, month, day)
Therefore, you must change an OS/VS COBOL program with statements similar to the following one:
77  DATE-IN-PROGRAM  PICTURE X(8).
    . . .
    MOVE CURRENT-DATE TO DATE-IN-PROGRAM.
An example of one way to change it, keeping the two-digit year format, is as follows:
01  DATE-IN-PROGRAM.
    02 MONTH-OF-YEAR     PIC X(02).
    02 FILLER            PIC X(01)  VALUE "/".
    02 DAY-OF-MONTH      PIC X(02).
    02 FILLER            PIC X(01)  VALUE "/".
    02 YEAR              PIC X(02).

01  ACCEPT-DATE.
    02 YEAR              PIC X(02).
    02 MONTH-OF-YEAR     PIC X(02).
    02 DAY-OF-MONTH      PIC X(02).
    . . .
    ACCEPT ACCEPT-DATE FROM DATE.
    MOVE  CORRESPONDING ACCEPT-DATE TO DATE-IN-PROGRAM.
An example of how to change it and specify a four-digit year is as follows:
01  DATE-IN-PROGRAM.
    02 MONTH-OF-YEAR     PIC X(02).
    02 FILLER            PIC X(01)  VALUE "/".
    02 DAY-OF-MONTH      PIC X(02).
    02 FILLER            PIC X(01)  VALUE "/".
    02 YEAR              PIC X(04).

01  CURRENT-DATE.
    02 YEAR              PIC X(04).
    02 MONTH-OF-YEAR     PIC X(02).
    02 DAY-OF-MONTH      PIC X(02).
    . . .
    MOVE FUNCTION CURRENT-DATE(1:8) TO CURRENT-DATE.
    MOVE CORRESPONDING CURRENT-DATE TO DATE-IN-PROGRAM.
EXAMINE statement
OS/VS COBOL accepted the EXAMINE statement; Enterprise COBOL does not.
Therefore, if your OS/VS COBOL program contains coding similar to the following one:
EXAMINE DATA-LENGTH TALLYING UNTIL FIRST " "
Replace it in Enterprise COBOL with:
MOVE 0 TO TALLY
INSPECT DATA-LENGTH TALLYING TALLY FOR CHARACTERS BEFORE " "

You can continue to use the TALLY special register wherever you can specify a WORKING-STORAGE elementary data item of integer value.

EXHIBIT statement
OS/VS COBOL accepted the EXHIBIT statement; Enterprise COBOL does not.

With Enterprise COBOL, you can use DISPLAY statements to replace EXHIBIT statements. However, the DISPLAY statement does not perform all the functions of the EXHIBIT statement.

Corrective action for EXHIBIT NAMED
You can replace the EXHIBIT NAMED statement directly with a DISPLAY statement:
    OS/VS COBOL                          Enterprise COBOL 

WORKING-STORAGE SECTION.        WORKING-STORAGE SECTION.
77  DAT-1 PIC X(8).             77  DAT-1 PIC X(8).
77  DAT-2 PIC X(8).             77  DAT-2 PIC X(8).
        . . .                          . . .
    EXHIBIT NAMED DAT-1 DAT-2       DISPLAY "DAT-1 = " DAT-1
                                        "DAT-2 = " DAT-2
Corrective action for EXHIBIT CHANGED
You can replace the EXHIBIT CHANGED statement with IF and DISPLAY statements, as follows:
  1. Specify an IF statement to discover if the new value of the data item is different from the old.
  2. Specify a DISPLAY statement as the statement-1 of the IF statement.
This change displays the value of the specified data item only if the new value is different from the old:
    OS/VS COBOL                          Enterprise COBOL 

WORKING-STORAGE SECTION.        WORKING-STORAGE SECTION.
77  DAT-1 PIC X(8).             77  DAT-1 PIC X(8).
77  DAT-2 PIC X(8).             77  DAT-2 PIC X(8).
                                77  DAT1-CMP PIC X(8).
                                77  DAT2-CMP PIC X(8).
        . . .                           . . .
 EXHIBIT CHANGED DAT-1 DAT-2    IF DAT-1 NOT EQUAL TO DAT1-CMP
                                  DISPLAY DAT-1
                                END-IF
                                IF DAT-2 NOT EQUAL TO DAT2-CMP
                                  DISPLAY DAT-2
                                END-IF
                                MOVE DAT-1 TO DAT1-CMP
                                MOVE DAT-2 TO DAT2-CMP
Corrective action for EXHIBIT CHANGED NAMED
You can replace the EXHIBIT CHANGED NAMED statement with IF and DISPLAY statements, as follows:
  1. Specify an IF statement to discover if the new value of the data item is different from the old.
  2. Specify a DISPLAY statement as the statement-1 of the IF statement.
This change displays the value of the specified data item only if the new value is different from the old:
    OS/VS COBOL                          Enterprise COBOL 

WORKING-STORAGE SECTION.        WORKING-STORAGE SECTION.
77  DAT-1 PIC X(8).             77  DAT-1    PIC X(8).
77  DAT-2 PIC X(8).             77  DAT-2    PIC X(8).
                                77  DAT1-CMP PIC X(8).
                                77  DAT2-CMP PIC X(8).
        . . .                           . . .
  EXHIBIT CHANGED NAMED          IF DAT-1 NOT EQUAL TO DAT1-CMP
      DAT-1 DAT-2                    DISPLAY "DAT-1 = " DAT-1
                                 END-IF
                                 IF DAT-2 NOT EQUAL TO DAT2-CMP
                                     DISPLAY "DAT-2 = " DAT-2
                                 END-IF
                                 MOVE DAT-1 TO DAT1-CMP
                                 MOVE DAT-2 TO DAT2-CMP
FILE-LIMIT clause of the FILE-CONTROL paragraph
OS/VS COBOL accepted the FILE-LIMIT clause and treats it as a comment; Enterprise COBOL does not. Therefore, you must remove any occurrences of the FILE-LIMIT clause.
GIVING phrase of USE AFTER STANDARD ERROR declarative
In OS/VS COBOL, you could specify the GIVING phrase of the USE AFTER STANDARD ERROR declarative. Enterprise COBOL does not support this phrase. Therefore, you must remove any occurrences of the GIVING phrase of the USE AFTER STANDARD ERROR declarative.

Use the FILE-CONTROL FILE STATUS clause to replace the GIVING phrase. The FILE STATUS clause gives you information after each I/O request, rather than only after an error occurs.

LABEL declaratives
Beginning with Enterprise COBOL V5, LABEL declaratives are no longer supported:
  • Format 2 declarative syntax: USE...AFTER...LABEL PROCEDURE... is no longer supported.
  • The syntax: GO TO MORE-LABELS is no longer supported.
If your programs have any of these language elements, they must be removed before you can compile and run these programs with Enterprise COBOL 5 and 6.
LABEL RECORDS clause with TOTALING/TOTALED AREA phrases
OS/VS COBOL allowed the TOTALING and TOTALED phrases of the LABEL RECORDS clause.

Enterprise COBOL does not support these phrases. Therefore, you must remove any occurrences of the TOTALING/TOTALED phrases from the LABEL RECORDS clause. Also check the variables associated with these phrases.

NOTE statement
OS/VS COBOL accepted the NOTE statement. Enterprise COBOL does not accept the NOTE statement. Therefore, for Enterprise COBOL delete all NOTE statements and use comment lines instead for the entire NOTE paragraph.
ON statement
OS/VS COBOL accepted the ON statement. Enterprise COBOL does not accept the ON statement.

The ON statement allows selective execution of statements it contains. Similar functions are provided in Enterprise COBOL by the EVALUATE statement and the IF statement.

OPEN statement failing for QSAM files (file status 39)
In OS/VS COBOL, the fixed file attributes for QSAM files did not need to match your COBOL program or JCL for a successful OPEN. In Enterprise COBOL, if the following conditions do not match, an OPEN statement in your program might not run successfully:
  • The fixed file attributes specified in the DD statement or the data set label for a file
  • The attributes specified for that file in the SELECT and FD statements of your COBOL program
Mismatches in the attributes for file organization, record format (fixed or variable), the code set, or record length result in a file status code 39, and the OPEN statement fails.

To prevent common file status 39 problems, see Preventing file status 39 for QSAM files.

OPEN statement failing for VSAM files (file status 39)
In OS/VS COBOL, the RECORDSIZE defined in your VSAM files associated with IDCAMS was not required to match your COBOL program for a successful OPEN. In Enterprise COBOL they must match. The following rules apply to VSAM ESDS, KSDS, and RRDS file definitions:
Table 1. Rules for VSAM file definitions
File type Rules
ESDS and
KSDS VSAM
RECORDSIZE(avg,m) is specified where avg is the average size of the COBOL records, and is strictly less than m; m is greater than or equal to the maximum size of a COBOL record.
RRDS VSAM RECORDSIZE(n,n) is specified where n is greater than or equal to the maximum size of a COBOL record.
OPEN statement with the LEAVE, REREAD, and DISP phrases
OS/VS COBOL allowed the OPEN statement with the LEAVE, REREAD and DISP phrases. Enterprise COBOL does not allow these phrases.

To replace the REREAD function, define a copy of your input records in the WORKING-STORAGE SECTION and move each record into WORKING-STORAGE after it is read or use READ INTO.

READY TRACE and RESET TRACE statements
OS/VS COBOL allowed the READY TRACE and RESET TRACE statements. Enterprise COBOL does not support these statements.

To get function similar to the READY TRACE statement, you can use either Debug Tool, or the COBOL language available in the Enterprise COBOL compiler.

If you use Debug Tool, compile your program with the TEST option and use the following Debug Tool command:
"AT GLOBAL LABEL PERFORM;
 LIST LINES %LINE; GO; END-PERFORM;"

If you use the COBOL language, the Enterprise COBOL USE FOR DEBUGGING ON ALL PROCEDURES declarative can perform functions similar to READY TRACE and RESET TRACE.

For example:
ENVIRONMENT DIVISION.
  CONFIGURATION SECTION.
  SOURCE-COMPUTER. IBM-370 WITH DEBUGGING MODE.
  . . .
DATA DIVISION.
  . . .
  WORKING-STORAGE SECTION.
  01 TRACE-SWITCH        PIC 9 VALUE 0.
     88  READY-TRACE           VALUE 1.
     88  RESET-TRACE           VALUE 0.
  . . .
PROCEDURE DIVISION.
  DECLARATIVES.
  COBOL-II-DEBUG SECTION.
    USE FOR DEBUGGING ON ALL PROCEDURES.
  COBOL-II-DEBUG-PARA.
    IF READY-TRACE THEN
        DISPLAY DEBUG-NAME
    END-IF.
  END DECLARATIVES.
  MAIN-PROCESSING SECTION.
  . . .
  PARAGRAPH-3.
  . . .
    SET READY-TRACE TO TRUE.
  PARAGRAPH-4.
  . . .
  PARAGRAPH-6.
  . . .
    SET RESET-TRACE TO TRUE.
  PARAGRAPH-7.
where DEBUG-NAME is a field of the DEBUG-ITEM special register that displays the procedure-name causing execution of the debugging procedure. (In this example, the object program displays the names of procedures PARAGRAPH-4 through PARAGRAPH-6 as control reaches each procedure within the range.)

At run time, you must specify PARM=/DEBUG in your EXEC statement to activate this debugging procedure. In this way, you have no need to recompile the program to activate or deactivate the debugging declarative.

REMARKS paragraph
OS/VS COBOL accepted the REMARKS paragraph.

Enterprise COBOL does not accept the REMARKS paragraph. As a replacement, use comment lines beginning with an * in column 7 or use the floating comment indicator *>.

START . . . USING KEY statement
OS/VS COBOL allowed the START statement with the USING KEY phrase; Enterprise COBOL does not. In Enterprise COBOL, you can specify the START statement with the KEY IS phrase.
THEN as a statement connector
OS/VS COBOL accepted the use of THEN as a statement connector.
The following example shows the OS/VS COBOL usage:
MOVE A TO B THEN ADD C TO D
Enterprise COBOL does not support the use of THEN as a statement connector. Therefore, in Enterprise COBOL change it to:
MOVE A TO B
ADD C TO D
TIME-OF-DAY special register
OS/VS COBOL supported the TIME-OF-DAY special register. It was valid only as the sending field in a MOVE statement. TIME-OF-DAY had the following 6-byte external decimal format:
HHMMSS (hour, minute, second)

Enterprise COBOL does not support the TIME-OF-DAY special register.

Therefore, you must change an OS/VS COBOL program with statements similar to the following one:
77  TIME-IN-PROGRAM   PICTURE  X(6).
. . .
    MOVE TIME-OF-DAY TO TIME-IN-PROGRAM.
An example of one way to change it is as follows:
MOVE FUNCTION CURRENT-DATE (9:6) TO TIME-IN-PROGRAM
TRANSFORM statement
OS/VS COBOL supported the TRANSFORM statement. Enterprise COBOL does not support the TRANSFORM statement, but it does support the INSPECT statement. Therefore, any TRANSFORM statements in your OS/VS COBOL program must be replaced by INSPECT CONVERTING statements.
For example, in the following OS/VS COBOL TRANSFORM statement:
77  DATA-T     PICTURE X(9) VALUE "ABCXYZCCC"
  . . .
    TRANSFORM DATA-T FROM "ABC" TO "CAT"
TRANSFORM evaluates each character, changing each A to C, each B to A, and each C to T.

After the TRANSFORM statement is executed. DATA-T contains "CATXYZTTT".

For example, in the following INSPECT CONVERTING statement (valid only in Enterprise COBOL):
77  DATA-T     PICTURE X(9) VALUE "ABCXYZCCC"
  . . .
    INSPECT DATA-T
        CONVERTING "ABC" TO "CAT"
INSPECT CONVERTING evaluates each character just as TRANSFORM does, changing each A to C, each B to A, and each C to T.

After the INSPECT CONVERTING statement is executed. DATA-T contains "CATXYZTTT:.

USE BEFORE STANDARD LABEL
OS/VS COBOL accepted the USE BEFORE STANDARD LABEL statement; Enterprise COBOL does not.

Therefore, you must remove any occurrences of the USE BEFORE STANDARD LABEL statement. Enterprise COBOL does not support nonstandard labels, so you cannot process nonstandard labeled files with Enterprise COBOL.