COBOL II and LE COBOL exit parameter record
The following is a COBOL II and LE COBOL exit parameter record:
01 LOAD-EXIT-PARMS.
05 FIXED-PARM-VALUES.
10 EXIT-JOBNAME PIC X(8).
10 EXIT-STEPNAME PIC X(8).
10 EXIT-DBNAME PIC X(8).
10 EXIT-TSNAME PIC X(8).
10 EXIT-RESUME PIC X(1).
10 EXIT-REPLACE PIC X(1).
10 EXIT-FILLER1 PIC X(2).
10 EXIT-USERID PIC X(8).
10 EXIT-DB2-SSID PIC X(4).
10 EXIT-DATE.
15 EXIT-MM PIC 9(2).
15 EXIT-DD PIC 9(2).
15 EXIT-YY PIC 9(2).
10 EXIT-TIME PIC X(6).
10 EXIT-UTILID-PARM PIC X(16).
10 FILLER REDEFINES EXIT-UTILID-PARM.
15 EXIT-PREFIX PIC X(8).
15 EXIT-SUFFIX PIC X(8).
10 EXIT-DATE8.
15 EXIT-DATE8-MM PIC 9(2).
15 EXIT-DATE8-DD PIC 9(2).
15 EXIT-DATE8-YEAR PIC 9(4).
15 FILLER REDEFINES EXIT-DATE8-YEAR.
20 EXIT-DATE8-CC PIC 9(2).
20 EXIT-DATE8-YY PIC 9(2).
10 EXIT-GRPNM PIC X(4).
10 EXIT-VCAT PIC X(8).
10 EXIT-DATEJ.
15 EXIT-DATEJ-YEAR PIC 9(4).
15 FILLER REDEFINES EXIT-DATEJ-YEAR.
20 EXIT-DATEJ-CC PIC 9(2).
20 EXIT-DATEJ-CC PIC 9(2).
15 EXIT-DATEJ-DDD PIC 9(3).
10 EXIT-FILLER2 PIC X(13).
05 WORK-AREA-ADDRESSES.
10 WORK-AREA-1 PIC 9(4).
10 WORK-AREA-2 PIC 9(4).
10 WORK-AREA-3 PIC 9(4).
10 WORK-AREA-4 PIC 9(4).
10 WORK-AREA-5 PIC 9(4).
10 WORK-AREA-6 PIC 9(4).
10 WORK-AREA-7 PIC 9(4).
10 WORK-AREA-8 PIC 9(4).
The following table describes the COBOL user exit parameter record fields:
Field | Description |
---|---|
EXIT-JOBNAME | Contains the job name, up to 8 bytes |
EXIT-STEPNAME | Contains the step name, up to 8 bytes |
EXIT-DBNAME | Contains the database name, up to 8 bytes |
EXIT-TSNAME | Contains the name of the table space or index space from the LOAD command, up to 8 bytes |
EXIT-RESUME | Indicates whether a LOAD RESUME is being performed: Y (yes) or N (no) |
EXIT-REPLACE | Indicates whether a LOAD REPLACE is being performed: Y (yes) or N (no) |
EXIT-USERID | Contains the user ID of the user running the LOADPLUS utility, up to 8 bytes |
EXIT-DB2-SSID | Contains the Db2 subsystem ID, 4 bytes |
EXIT-DATE | Contains the date of the execution of the utility, in the format MMDDYY, 6 bytes |
EXIT-TIME | Contains the time of the execution of the utility, in the format HHMMSS, 6 bytes |
EXIT-UTILID-PARM | Contains the utility ID, up to 16 bytes |
EXIT-DATE8 | Contains the date of the execution of the utility, in the format MMDDYYYY, 8 bytes |
EXIT-GRPNM | Contains the Db2 data sharing group name In a non-data-sharing environment, the field contains the Db2 subsystem ID. |
EXIT-VCAT | Contains the VCATNAME specified in the Db2 catalog for the table space being loaded, or for the first partition if the table space is partitioned |
EXIT-DATEJ | Contains the Julian date of the execution of the utility, in the format CCYYDDD, 7 bytes |
WORK-AREA-1...WORK-AREA-8 | Provides work space, 8 parameters, up to 4 bytes each |