Compaq COBOL
User Manual


Previous Contents Index

1.4.2 Program Logic Errors

When checking your program for logic errors, first examine your program for some of the more obvious bugs, such as the following:

1.4.3 Run-Time Input/Output Errors

An input/output error is a condition that causes an I/O statement to fail. These I/O errors are detected at run time by the I/O system. Each time an I/O operation occurs, the I/O system generates a two-character file status value. One way to determine the nature of an I/O error is to check a file's I/O status by using file status data items. (Refer to the Compaq COBOL Reference Manual for a list of file status values.) See Chapter 7, Handling Input/Output Exception Conditions for additional information about I/O exception condition handling.

Checking a file's I/O status within a Declarative USE procedure or in an INVALID KEY imperative condition can help you determine the nature of an I/O error. For example:


FD  INDEXED-MASTER 
    ACCESS MODE IS DYNAMIC 
    FILE STATUS IS MASTER-STATUS 
    RECORD KEY IN IND-KEY. 
  . 
  . 
  . 
WORKING-STORAGE SECTION. 
01  MASTER-STATUS      PIC XX  VALUE SPACES. 
  . 
  . 
  . 
PROCEDURE DIVISION. 
  . 
  .                                                     
  . 
050-READ-MASTER. 
    READ INDEXED-MASTER 
      INVALID KEY PERFORM 100-CHECK-STATUS 
      GO TO 200-INVALID-READ. 
      . 
      . 
      . 
100-CHECK-STATUS. 
    IF MASTER-STATUS = "23" 
       DISPLAY "RECORD NOT IN FILE". 
    IF MASTER-STATUS = "24" 
       DISPLAY "BOUNDARY VIOLATION OR RELATIVE RECORD 
       NUMBER TOO LARGE". 
      . 
      . 
      . 

If your program contains a Declarative USE procedure for a file and an I/O operation for that file fails, the I/O system performs the USE procedure, but does not display an error message.

A Declarative USE procedure can sometimes avoid program termination. For example, File Status 91 indicates that the file is locked by another program; rather than terminate your program, you can perform other procedures and then try reopening the file. If program continuation is not desirable, the Declarative USE procedure can perform housekeeping functions, such as saving data or displaying program-generated diagnostic messages.

If you specify an INVALID KEY phrase for a file and the I/O operation causes an INVALID KEY condition, the I/O system performs the associated imperative statement and no other file processing for the current statement. The Declarative USE procedure (if any) is not performed. The INVALID KEY phrase processes I/O errors due to invalid key conditions only.

If you do not specify an INVALID KEY phrase but declare a Declarative USE procedure for the file, the I/O system performs the Declarative USE procedure and returns control to the program.

If a severe error occurs and you do not have a Declarative Use procedure, your program will terminate abruptly with a run-time diagnostic. For example, given a program that looks for AFILE.DAT and that file is missing:


cobrtl: severe: file AFILE.DAT not found 

In this case, program run ends because you have not handled the error with a Declarative Use procedure.

1.4.4 I/O Errors and RMS (OpenVMS)

I/O errors are detected by the I/O system, which (for OpenVMS systems) consists of Record Management Services (RMS) and the Run-Time Library (RTL). You can use the RMS special registers, which contain the primary and secondary RMS completion codes of an I/O operation, to detect errors. The RMS special registers are as follows:

RMS-STS
RMS-STV
RMS-FILENAME
RMS-CURRENT-STS
RMS-CURRENT-STV
RMS-CURRENT-FILENAME

Refer to the Compaq COBOL Reference Manual and the OpenVMS Record Management Services Reference Manual for more information about RMS special registers.

Examples 1-7 and 1-8 show how you can use RMS special registers to detect errors.

Example 1-7 Using RMS Special Registers to Detect Errors (OpenVMS)

IDENTIFICATION DIVISION. 
PROGRAM-ID. RMSSPECREGS. 
* 
* This program demonstrates the use of RMS special registers to 
* implement a different recovery for each of several errors with RMS files. 
* 
ENVIRONMENT DIVISION. 
INPUT-OUTPUT SECTION. 
FILE-CONTROL. 
    SELECT OPTIONAL EMP-FILE ASSIGN "SYS$DISK:ART.DAT". 
    SELECT REPORT-FILE       ASSIGN "SYS$OUTPUT". 
DATA DIVISION. 
FILE SECTION. 
FD  EMP-FILE VALUE OF ID IS VAL-OF-ID. 
01  EMP-RECORD. 
    02 EMP-ID     PIC 9(7). 
    02 EMP-NAME    PIC X(15). 
    02 EMP-ADDRESS PIC X(30). 
FD  REPORT-FILE     REPORT IS RPT. 
WORKING-STORAGE SECTION. 
01  VAL-OF-ID     PIC X(20). 
01  RMS$_EOF     PIC S9(9) COMP VALUE EXTERNAL RMS$_EOF. 
01  SS$_BADFILENAME PIC S9(9) COMP VALUE EXTERNAL SS$_BADFILENAME. 
01  RMS$_FNF     PIC S9(9) COMP VALUE EXTERNAL RMS$_FNF. 
01  RMS$_DNF     PIC S9(9) COMP VALUE EXTERNAL RMS$_DNF. 
01  RMS$_DEV     PIC S9(9) COMP VALUE EXTERNAL RMS$_DEV. 
01  D-DATE     PIC 9(6). 
01  EOF-SW     PIC X. 
    88 E-O-F  VALUE "E". 
    88 NOT-E-O-F VALUE "N". 
01  VAL-OP-SW     PIC X. 
    88 VALID-OP VALUE "V". 
    88 OP-FAILED VALUE "F". 
01  OP      PIC X. 
    88 OP-OPEN  VALUE "O". 
    88 OP-CLOSE VALUE "C". 
    88 OP-READ  VALUE "R". 
REPORT SECTION. 
RD  RPT PAGE 26 LINES HEADING 1 FIRST DETAIL 5. 
01  TYPE IS PAGE HEADING. 
    02 LINE IS PLUS 1. 
 03  COLUMN 1 PIC X(16) VALUE "Emplyee File on". 
 03  COLUMN 18 PIC 99/99/99 SOURCE D-DATE. 
    02 LINE IS PLUS 2. 
 03  COLUMN 2 PIC X(5) VALUE "Empid". 
 03  COLUMN 22 PIC X(4) VALUE "Name". 
 03  COLUMN 43 PIC X(7) VALUE "Address". 
 03  COLUMN 60 PIC X(4) VALUE "Page". 
 03  COLUMN 70 PIC ZZ9  SOURCE PAGE-COUNTER. 
01  REPORT-LINE TYPE IS DETAIL. 
    02 LINE IS PLUS 1. 
 03  COLUMN  IS 1    PIC 9(7) SOURCE EMP-ID. 
 03  COLUMN  IS 20   PIC X(15) SOURCE IS EMP-NAME. 
 03  COLUMN  IS 42   PIC X(30) SOURCE IS EMP-ADDRESS. 
PROCEDURE DIVISION. 
DECLARATIVES. 
USE-SECT SECTION. 
    USE AFTER STANDARD ERROR PROCEDURE ON EMP-FILE. 
CHECK-RMS-SPECIAL-REGISTERS. 
    SET OP-FAILED TO TRUE. 
    EVALUATE RMS-STS OF EMP-FILE TRUE 
 WHEN (RMS$_EOF)   OP-READ 
     SET VALID-OP TO TRUE 
     SET E-O-F TO TRUE 
 WHEN (SS$_BADFILENAME)  OP-OPEN 
 WHEN (RMS$_FNF)   OP-OPEN 
 WHEN (RMS$_DNF)   OP-OPEN 
 WHEN (RMS$_DEV)   OP-OPEN 
     DISPLAY "File cannot be found or file spec is invalid" 
     DISPLAY RMS-FILENAME OF EMP-FILE 
     DISPLAY "Enter corrected file (control-Z to STOP RUN): " 
      WITH NO ADVANCING 
     ACCEPT VAL-OF-ID 
  AT END STOP RUN 
     END-ACCEPT 
 WHEN ANY   OP-CLOSE 
     CONTINUE 
 WHEN ANY   RMS-STS OF EMP-FILE IS SUCCESS 
     SET VALID-OP TO TRUE 
 WHEN OTHER 
     IF RMS-STV OF EMP-FILE NOT = ZERO 
     THEN 
  CALL "LIB$STOP" USING 
      BY VALUE RMS-STS OF EMP-FILE 
     END-IF 
    END-EVALUATE. 
END DECLARATIVES. 
MAIN-PROG SECTION. 
000-DRIVER. 
    PERFORM 100-INITIALIZE. 
    PERFORM WITH TEST AFTER UNTIL E-O-F 
 GENERATE REPORT-LINE 
 READ EMP-FILE 
    END-PERFORM. 
    PERFORM 200-CLEANUP. 
    STOP RUN. 
100-INITIALIZE. 
    ACCEPT D-DATE FROM DATE. 
    DISPLAY "Enter file spec of employee file: " WITH NO ADVANCING. 
    ACCEPT VAL-OF-ID. 
    PERFORM WITH TEST AFTER UNTIL VALID-OP 
 SET VALID-OP TO TRUE 
 SET OP-OPEN TO TRUE 
 OPEN INPUT EMP-FILE 
 IF OP-FAILED 
 THEN 
     SET OP-CLOSE TO TRUE 
     CLOSE EMP-FILE 
 END-IF 
    END-PERFORM. 
    OPEN OUTPUT REPORT-FILE. 
    INITIATE RPT. 
    SET NOT-E-O-F TO TRUE. 
    SET OP-READ TO TRUE. 
    READ EMP-FILE. 
200-CLEANUP. 
    TERMINATE RPT. 
    SET OP-CLOSE TO TRUE. 
    CLOSE EMP-FILE REPORT-FILE. 
END PROGRAM RMSSPECREGS. 

Example 1-8 Using RMS-CURRENT Special Registers to Detect Errors (OpenVMS)

IDENTIFICATION DIVISION. 
PROGRAM ID. RMS-CURRENT-SPEC-REGISTERS. 
* 
* This program demonstrates the use of RMS-CURRENT special registers 
* to implement a single recovery for RMS file errors with multiple files. 
* 
ENVIRONMENT DIVISION. 
INPUT-OUTPUT SECTION. 
FILE-CONTROL. 
SELECT FILE-1 
        ASSIGN TO "SYS$DISK:ART_1.DAT". 
SELECT FILE-2 
        ASSIGN TO "SYS$DISK:ART_2.DAT". 
SELECT FILE-3 
        ASSIGN TO "SYS$DISK:ART_3.DAT". 
DATA DIVISION. 
FILE SECTION. 
FD      FILE-1. 
01      FILE-1-REC. 
        02      F1-REC-FIELD    PIC 9(9). 
FD      FILE-2. 
01      FILE-2-REC. 
        02      F2-REC-FIELD    PIC 9(9). 
FD      FILE-3. 
01      FILE-3-REC. 
        02      F3-REC-FIELD    PIC 9(9). 
PROCEDURE DIVISION. 
DECLARATIVES. 
USE-SECT SECTION. 
        USE AFTER STANDARD EXCEPTION PROCEDURE ON INPUT. 
CHECK-RMS-CURRENT-REGISTERS. 
        DISPLAY "************** ERROR **************". 
        DISPLAY "Error on file: " RMS-CURRENT-FILENAME. 
        DISPLAY "Status Values:". 
        DISPLAY "      RMS-STS = " RMS-CURRENT-STS WITH CONVERSION. 
        DISPLAY "      RMS-STV = " RMS-CURRENT-STV WITH CONVERSION. 
        DISPLAY "***********************************". 
END DECLARATIVES. 
MAIN-PROG SECTION. 
MAIN-PARA. 
        OPEN INPUT FILE-1. 
        OPEN INPUT FILE-2. 
        OPEN INPUT FILE-3. 
        . 
        . 
        . 
        CLOSE FILE-1. 
        CLOSE FILE-2. 
        CLOSE FILE-3. 
        STOP RUN. 
END-PROGRAM RMS-CURRENT-SPEC-REGISTERS.                          <>

1.5 Using Program Switches

You can control program execution by defining switches in your Compaq COBOL program and setting them internally (from within the image) or externally (from outside the image). Switches exist as the environment variable COBOL_SWITCHES (on the Tru64 UNIX operating system) or the logical name COB$SWITCHES (on the OpenVMS operating system).

On OpenVMS systems, switches can be defined for the image, process, group, or system. <>

On Tru64 UNIX systems, switches can be defined for the image or process. <>

1.5.1 Setting and Controlling Switches Internally

To set switches from within the image, define them in the SPECIAL-NAMES paragraph of the ENVIRONMENT DIVISION and use the SET statement in the PROCEDURE DIVISION to specify switches ON or OFF, as in the following example:


ENVIRONMENT DIVISION. 
CONFIGURATION SECTION. 
SPECIAL-NAMES. 
    SWITCH 10 IS MY-SWITCH       
      ON IS SWITCH-ON       
      OFF IS SWITCH-OFF.   
    .     
    .     
    . 
PROCEDURE DIVISION. 
000-SET-SWITCH.     
    SET MY-SWITCH TO ON. 
    IF SWITCH-ON 
       THEN 
    DISPLAY "Switch 10 is on". 
    .     
    .     
    . 

To change the status of internal switches during execution, turn them on or off from within your program. However, be aware that this information is not saved between runs of the program.

Refer to the Compaq COBOL Reference Manual for more information about setting internal switches.

1.5.2 Setting and Controlling Switches Externally

Switches that are set externally are handled differently on Tru64 UNIX and OpenVMS, as described in this section.

Switches on Tru64 UNIX

On Tru64 UNIX systems, to set switches from outside the image, use the SETENV command to change the status of program switches, as follows:


% setenv COBOL_SWITCHES "switch-list"

To remove switch settings:


% unsetenv COBOL_SWITCHES                             

To check switch settings, enter this command:


% printenv COBOL_SWITCHES          Shows switch settings.   
 

The switch-list can contain up to 16 switches separated by commas. To set a switch on, specify it in the switch-list. A switch is off (the default) if you do not specify it in the switch-list.

For example:


% setenv COBOL_SWITCHES "1,5,13"   Sets switches 1, 5, and 13 ON. 
 
% setenv COBOL_SWITCHES "9,11,16"  Sets switches 9, 11, and 16 ON. 
 
% setenv COBOL_SWITCHES " "        Sets all switches OFF.  
 

Following is a simple program that displays a message depending on the state of the environment variable COBOL_SWITCHES (on Tru64 UNIX systems:


IDENTIFICATION DIVISION. 
PROGRAM-ID. TSW. 
 
ENVIRONMENT DIVISION. 
CONFIGURATION SECTION. 
SPECIAL-NAMES. 
    SWITCH 12 IS SW12 ON IS SW12-ON OFF IS SW12-OFF. 
 
PROCEDURE DIVISION. 
01-S. 
    DISPLAY "**TEST SWITCHES**". 
    IF SW12-ON 
       DISPLAY "SWITCH 12 IS ON". 
    IF SW12-OFF 
       DISPLAY "SWITCH 12 IS OFF". 
 
    DISPLAY "**END**". 
    STOP RUN. 
END PROGRAM TSW. 

To test this program on a Tru64 UNIX system, compile and link it and then type the following:


% setenv COBOL_SWITCHES 12
% tsw

The output is as follows:


**TEST SWITCHES** 
SWITCH 12 IS ON 
**END**        <>                                                  

Switches on OpenVMS

On OpenVMS systems, to set switches from outside the image or for a process, use the DCL DEFINE or ASSIGN command to change the status of program switches as follows:


$ DEFINE COB$SWITCHES "switch-list"

The switch-list can contain up to 16 switches separated by commas. To set a switch ON, specify it in the switch-list. A switch is OFF (the default) if you do not specify it in the switch-list.

For example:


$ DEFINE COB$SWITCHES "1,5,13"   Sets switches 1, 5, and 13 ON. 
 
$ DEFINE COB$SWITCHES "9,11,16"  Sets switches 9, 11, and 16 ON. 
 
$ DEFINE COB$SWITCHES " "        Sets all switches OFF.

The order of evaluation for logical name assignments is image, process, group, system. System and group assignments (including Compaq COBOL program switch settings) continue until they are changed or deassigned. Process assignments continue until they are changed, deassigned, or until the process ends. Image assignments end when they are changed or when the image ends.

You should know the system and group assignments for COB$SWITCHES unless you have defined them for your process or image. To check switch settings, enter this command:


$ SHOW LOGICAL COB$SWITCHES 

Use the DCL DEASSIGN command to remove the switch-setting logical name from your process and reactivate the group or system logical name (if any):


$ DEASSIGN COB$SWITCHES 

To change the status of external switches during execution, follow these steps:

  1. Interrupt the image with a STOP (literal-string) COBOL statement. (Refer to the Compaq COBOL Reference Manual for more information.)
  2. Use the DCL DEFINE command to change switch settings.
  3. Continue execution with the DCL CONTINUE command. Be sure not to force the interrupted image to exit by entering a command that executes another image.

For information about these DCL commands, refer to the OpenVMS DCL Dictionary.

Following is a simple program that displays a message depending on the state of the logical name COB$SWITCHES (on OpenVMS systems):


IDENTIFICATION DIVISION. 
PROGRAM-ID. TSW. 
 
ENVIRONMENT DIVISION. 
CONFIGURATION SECTION. 
SPECIAL-NAMES. 
    SWITCH 12 IS SW12 ON IS SW12-ON OFF IS SW12-OFF. 
 
PROCEDURE DIVISION. 
01-S. 
    DISPLAY "**TEST SWITCHES**". 
    IF SW12-ON 
       DISPLAY "SWITCH 12 IS ON". 
    IF SW12-OFF 
       DISPLAY "SWITCH 12 IS OFF". 
 
    DISPLAY "**END**". 
    STOP RUN. 
END PROGRAM TSW. 

On OpenVMS, to test the previous program, compile and link it and then type the following:


$ DEFINE COB$SWITCHES 12
$ RUN TSW

The output is as follows:


**TEST SWITCHES** 
SWITCH 12 IS ON 
**END**        <>

1.6 Special Information for Year 2000 Programming

Even subsequent to the turn of the millennium, there still exist potential disruptions in previously problem-free software where there are instances of a two-digit year field that should be a four-digit field. Programmers need to correct all such fields, as Compaq cannot prevent problems that originate in application code.

Two-digit year formats used in controlling fields, or as keys in indexed files, can cause program logic to become ambiguous. It is a fundamental rule to use four-digit years instead of two-digit years in areas where sequential operations are driven from these values or for comparison of these values.

Compaq COBOL provides programmer access to four-digit and two-digit year formats:
4-digit FUNCTION CURRENT-DATE
4-digit FUNCTION DATE-OF-INTEGER
4-digit FUNCTION DATE-TO-YYYYMMDD
4-digit FUNCTION DAY-OF-INTEGER
4-digit FUNCTION DAY-TO-YYYYDDD
4-digit FUNCTION INTEGER-OF-DATE
4-digit FUNCTION INTEGER-OF-DAY
4-digit FUNCTION TEST-DATE-YYYYMMDD
4-digit FUNCTION TEST-DAY-YYYYDDD
4-digit FUNCTION WHEN-COMPILED
4-digit FUNCTION YEAR-TO-YYYY
   
2-digit ACCEPT FROM DATE
2-digit ACCEPT FROM DAY
4-digit ACCEPT FROM DATE YYYYMMDD
4-digit ACCEPT FROM DAY YYYYDDD

Compaq COBOL offers date functions that can be used in program logic that makes decisions about year order. The full four-digit year handled by the six functions listed should be used in internal program logic decisions that are based on years. External displays of year information can continue to use two-digit formats when that is appropriate.

You should check program logic in code that uses ACCEPT, to verify that millennium transition dates are properly handled.

The use of two-digit years in applications does not automatically create a problem, but a problem could exist. Programmers need to inspect each of their applications for two-digit year dependencies and change any such instances to check the full four-digit year value.


Previous Next Contents Index