Previous Topic: Considerations for Non-Reentrant or Non-LE-Compliant Database ProceduresNext Topic: Allocating and Formatting Files


Database Procedure Example

Using the Employee database, a company uses a database procedure to perform validity checks on employee identification numbers (ID-0415) before EMPLOYEE records are stored in the employee database. A COBOL program CHECKID functions as follows:

Sample Database Procedure

The LINKAGE SECTION describes the five blocks of information that CA IDMS/DB passes to the procedure. ID-0415 (employee ID) is the first four bytes of the record occurrence passed to the procedure. If ID-0415 does not pass the validity check, the error-status indicator in the application control block is set to 99 to prevent execution of the DML command for which the procedure was called.

Sample database procedure

**************************************************************
 IDENTIFICATION DIVISION.
**************************************************************

 PROGRAM-ID.           CHECKID.
 DATE-WRITTEN.         JUNE 15, 1991.
 AUTHOR.               COMMONWEATHER CORP.
 REMARKS.              VALIDATES INCOMING EMPLOYEE NUMBERS.

**************************************************************
 ENVIRONMENT DIVISION.
**************************************************************

**************************************************************
 DATA DIVISION.
**************************************************************

LINKAGE SECTION.

 01  PROC-CTRL.
     02  PC-ENTRY-LEVEL           PIC X(4).
     02  PC-ENTRY-TIME            PIC X(4).
     02  PC-MAJOR-CODE            PIC XX.
     02  PC-IDBMSCOM-CODE         PIC 9(4) COMP.
     02  PC-CANCEL-SWITCH         PIC 9(4) COMP.
     02  FILLER                   PIC XX.
     02  PC-USER-AREA             PIC 9(8) COMP.

 01  APPLIC-CTRL.
     02  SC-SUB-NAME              PIC X(8).
     02  SC-PROG-NAME             PIC X(8).
     02  SC-ERROR-STATUS.
         03  SC-ERR-MAJOR         PIC XX.
         03  SC-ERR-MINOR         PIC XX.
     02  SC-DBKEY                 PIC 9(8) COMP.
     02  SC-REC-NAME              PIC X(18).
     02  SC-AREA-NAME             PIC X(18).
    02 FILLER                    PIC X(18).
     02  SC-ERR-SET-NAME          PIC X(18).
     02  SC-ERR-REC-NAME          PIC X(18).
     02  SC-ERR-AREA-NAME         PIC X(18).
     02  SC-IDBMSCOM              PIC X(100).
     02  SC-DIRECT-DBKEY          PIC 9(8) COMP.

 01  A-P-COMM-DATA                PIC X(4).
 01  REC-CTRL-BLOCK.
     02  RC-REC-NAME              PIC X(18).
     02  RC-AREA-NAME             PIC X(18).
     02  RC-REC-ID                PIC 9(4) COMP.
     02  RC-REC-LENGTH            PIC 9(4) COMP.
     02  RC-REC-CTRL-LEN          PIC 9(4) COMP.
     02  RC-REC-MAX-LEN           PIC 9(4) COMP.
     02  RC-DBKEY                 PIC 9(8) COMP.
     02  RC-LPL                   PIC 9(8) COMP.
     02  RC-HPL                   PIC 9(8) COMP.

 01  EMPLOYEE.
     02  ID-0415                  PIC X(4).
     02  FILLER                   PIC X(103).

**************************************************************
 PROCEDURE DIVISION USING         PROC-CTRL
                                  APPLIC-CTRL
                                  A-P-COMM-DATA
                                  REC-CTRL-BLOCK
                                  EMPLOYEE.
**************************************************************

     IF ID-0415 NOT NUMERIC
     OR ID-0415 LESS THAN '0001'
     OR ID-0415 GREATER THAN '9999'
     THEN MOVE 99 TO SC-ERR-MINOR.
     GOBACK.

Schema Statement

Include the following clauses in the record description for EMPLOYEE in the Employee schema:

CALL CHECKID BEFORE STORE.
CALL CHECKID BEFORE MODIFY.

Any program using a subschema compiled under this schema automatically invokes the database procedure CHECKID before storing or modifying an EMPLOYEE record occurrence.