Adding Copybooks to COBOL Programs

To enable you to call Application Engine programs from COBOL programs, include the copybook called PTCCBLAE.CBL with your COBOL programs. This copybook is located in PS_HOME\src\cbl\base.

The following is the PTCCBLAE.CBL copybook:

*01  CBLAE.

NOCLN      02  CBLAE-PRCSNAME          PIC X(12)   VALUE SPACE.

NOCLN      02  CBLAE-COMMIT-FLAG       PIC X(1)    VALUE SPACE.

               88 AE-COMMITS-SUCCESS               VALUE 'B'.

               88 AE-COMMITS-ALL                   VALUE 'C'.

           02  CBLAE-PARMS.

               03  CBLAE-PARM-CNT      PIC 9(4)                COMP.

               03  CBLAE-PARM-ENT      OCCURS 500 TIMES.

                   05 CBLAE-STATEREC   PIC X(15).

                   05 CBLAE-FIELDNM    PIC X(18).

                   05 CBLAE-DATA-PTR               POINTER.

                   05 CBLAE-LENGTH     PIC 9999                COMP.

                   05 CBLAE-SCALE      PIC 99                  COMP.

NOCLN              05 CBLAE-TYPE       PIC X.

                       88  CBLAE-TYPE-CHAR         VALUE 'C'.

                       88  CBLAE-TYPE-SMALLINT     VALUE 'S'.

                       88  CBLAE-TYPE-INT          VALUE 'I'.

                       88  CBLAE-TYPE-DEC          VALUE 'P'.

                       88  CBLAE-TYPE-DATE         VALUE 'D'.

                       88  CBLAE-TYPE-TIME         VALUE 'T'.

                       88  CBLAE-TYPE-TIMEONLY     VALUE 'V'.

                       88  CBLAE-TYPE-NUMERIC      VALUE 'S' 'I' 'P'.

Data Transfer Process Between COBOL Programs and Application Engine Programs

To interface between COBOL programs and Application Engine programs, the process uses a file to pass parameters from COBOL to the Application Engine program. This file is owned by the process and has the prm extension. The location of the file is determined by the following:

  • If an application server root directory is defined, then the file resides in the output directory of that particular process instance.

  • If the output directory on the application server is not defined, then the file resides in the default output directory of the Process Scheduler domain.

  • If neither of the above is defined, then the file is written to the default temp directory.