Error Handling in COBOL

Textual error messages associated with each error number may be retrieved using the SQL

statements GET DIAGNOSTICS and GET DIAGNOSTICS EXCEPTION. These can be declared in a subroutine which is called in the event of a non-zero SQLCODE being returned.

The COBOL program must declare a character variable to receive the error text, an integer variable containing the length of the error text, an integer variable containing the total number of error conditions available and an integer variable containing the current error condition. These 4

items must be declared in a DECLARE SECTION which is in scope whenever the above SQL

statements are called.

A programming example using GET DIAGNOSTICS / GET DIAGNOSTICS EXCEPTION looks

like this:

000015 WORKING-STORAGE SECTION.

000016     EXEC SQL BEGIN DECLARE SECTION END-EXEC.

000017* Error Text Buffer

000018 01  ERRBUF             PIC X(512).

000019* Length of Error Text Buffer

000020 01  ERRLEN             PIC 9(9)   COMP   SYNC VALUE 512.

000021* Count of error conditions

000022 01  CONDITIONCOUNT     PIC 9(9)   COMP   SYNC VALUE 0.

000023* Current error condition

000024 01  ERRNUMBER          PIC 9(9)   COMP   SYNC VALUE 0.

000025     EXEC SQL END   DECLARE SECTION END-EXEC.

000030     EXEC SQL INCLUDE SQLCA         END-EXEC.

000045 PROCEDURE DIVISION.

000041     IF SQLCODE NOT = 0

000042* Obtain the count of error conditions to be returned in

000043* CONDITIONCOUNT

000044       EXEC SQL

000045         GET DIAGNOSTICS :CONDITIONCOUNT = NUMBER

000046       END-EXEC

000050       IF CONDITIONCOUNT > 0

000051* Obtain each error condition text CONDITIONCOUNT times

000052* The error condition text will be returned in ERRBUF

000053         PERFORM DOERROR

000054           VARYING ERRNUMBER FROM 1 BY 1

000055             UNTIL ERRNUMBER > CONDITIONCOUNT

000056       END-IF

000057     END-IF

000058*

000070* Subroutine DOERROR

000071*

000072 DOEXCEPTION.

000073     EXEC SQL

000074       GET DIAGNOSTICS EXCEPTION :ERRNUMBER

000075                                 :ERRBUF = MESSAGE_TEXT,

000076                                 :ERRLEN = MESSAGE_LENGTH

000077     END-EXEC

000078     DISPLAY "ERR MSG: " G-ERRBUF

000079     .

where:

CONDITIONCOUNT is the count of error conditions available, returned by GET DIAGNOSTICS

ERRNUMBER      is the current error condition.

ERRBUF         is the target buffer, space filled on return from GET DIAGNOSTICS EXCEPTION

ERRLEN         is the length of the target buffer ERRBUF