This example shows how to access a field value returned from a retrieve API.
Refer to Example in OPM RPG: Accessing a field value (initial library list) for the original example. The following program also works for OPM COBOL.
IDENTIFICATION DIVISION. ***************************************************************** ***************************************************************** * *Program Name: JOBDAPI * *Programming Language: COBOL * *Description: This example shows how to access a * field value returned from a retrieve * API. * *Header Files Included: QUSEC - Error Code Parameter * QWDRJOBD - Retrieve Job Description API * ***************************************************************** ***************************************************************** * PROGRAM-ID. JOBDAPI. * ENVIRONMENT DIVISION. CONFIGURATION SECTION. SOURCE-COMPUTER. IBM-AS400. OBJECT-COMPUTER. IBM-AS400. * DATA DIVISION. WORKING-STORAGE SECTION. * * Error Code parameter include. As this sample program * uses COPY to include the error code structure, only the first * 16 bytes of the error code structure are available. If the * application program needs to access the variable length * exception data for the error, the developer should physically * copy the QSYSINC include and modify the copied include to * define additional storage for the exception data. * COPY QUSEC OF QSYSINC-QLBLSRC. * * Retrieve Job Description API Include * * The header file for the QWDRJOBD API was included in this * program so that the varying length portion of the structure * can be defined as a fixed portion. * *** START HEADER FILE SPECIFICATIONS **************************** * *Header File Name: H/QWDRJOBD * *Descriptive Name: Retrieve Job Description Information API * *5763-SS1 (C) Copyright IBM Corp. 1994,1994 *All rights reserved. *US Government Users Restricted Rights - *Use, duplication or disclosure restricted *by GSA ADP Schedule Contract with IBM Corp. * *Licensed Materials-Property of IBM * * *Description: The Retrieve Job Description Information API * retrieves information from a job description * object and places it into a single variable in the * calling program. * *Header Files Included: None. * *Macros List: None. * *Structure List: Qwd_JOBD0100_t * *Function Prototype List: QWDRJOBD * *Change Activity: * *CFD List: * *FLAG REASON LEVEL DATE PGMR CHANGE DESCRIPTION *---- ------------ ----- ------ --------- ---------------------- *$A0= D2862000 3D10 940424 ROCH: New Include * *End CFD List. * *Additional notes about the Change Activity *End Change Activity. * *** END HEADER FILE SPECIFICATIONS ****************************** ***************************************************************** *Prototype for QWDRJOBD API ***************************************************************** 77 QWDRJOBD PIC X(00010) VALUE "QWDRJOBD". ***************************************************************** *Type Definition for the JOBD0100 format. **** *** *NOTE: The following type definition defines only the fixed * portion of the format. Any varying length field will * have to be defined by the user. ***************************************************************** 01 RECEIVER-VARIABLE PIC X(05000). 01 QWD-JOBD0100 REDEFINES RECEIVER-VARIABLE. 05 BYTES-RETURNED PIC S9(00009) BINARY. 05 BYTES-AVAILABLE PIC S9(00009) BINARY. 05 JOB-DESCRIPTION-NAME PIC X(00010). 05 JOB-DESCRIPTION-LIB-NAME PIC X(00010). 05 USER-NAME PIC X(00010). 05 JOB-DATE PIC X(00008). 05 JOB-SWITCHES PIC X(00008). 05 JOB-QUEUE-NAME PIC X(00010). 05 JOB-QUEUE-LIB-NAME PIC X(00010). 05 JOB-QUEUE-PRIORITY PIC X(00002). 05 HOLD-JOB-QUEUE PIC X(00010). 05 OUTPUT-QUEUE-NAME PIC X(00010). 05 OUTPUT-QUEUE-LIB-NAME PIC X(00010). 05 OUTPUT-QUEUE-PRIORITY PIC X(00002). 05 PRINTER-DEVICE-NAME PIC X(00010). 05 PRINT-TEXT PIC X(00030). 05 SYNTAX-CHECK-SEVERITY PIC S9(00009) BINARY. 05 END-SEVERITY PIC S9(00009) BINARY. 05 MESSAGE-LOG-SEVERITY PIC S9(00009) BINARY. 05 MESSAGE-LOG-LEVEL PIC X(00001). 05 MESSAGE-LOG-TEXT PIC X(00010). 05 LOG-CL-PROGRAMS PIC X(00010). 05 INQUIRY-MESSAGE-REPLY PIC X(00010). 05 DEVICE-RECOVERY-ACTION PIC X(00013). 05 TIME-SLICE-END-POOL PIC X(00010). 05 ACCOUNTING-CODE PIC X(00015). 05 ROUTING-DATA PIC X(00080). 05 TEXT-DESCRIPTION PIC X(00050). 05 RESERVED PIC X(00001). 05 OFFSET-INITIAL-LIB-LIST PIC S9(00009) BINARY. (1) 05 NUMBER-LIBS-IN-LIB-LIST PIC S9(00009) BINARY. (2) 05 OFFSET-REQUEST-DATA PIC S9(00009) BINARY. 05 LENGTH-REQUEST-DATA PIC S9(00009) BINARY. 05 JOB-MESSAGE-QUEUE-MAX-SIZE PIC S9(00009) BINARY. 05 JOB-MESSAGE-QUEUE-FULL-ACTION PIC X(00010). * 05 RESERVED2 PIC X(00001). * * Varying length * 05 INITIAL-LIB-LIST PIC X(00011). * * * Varying length * 05 REQUEST-DATA PIC X(00001). * * Varying length * * Command String Data Structure * 01 COMMAND-STRING. 05 TEXT1 PIC X(22) VALUE 'SNDMSG MSG(''LIBRARY- '. 05 LIB PIC X(10). 05 TEXT2 PIC X(15) VALUE ''') TOUSR(QPGMR)'. * 01 COMMAND-LENGTH PIC S9(10)V99999 COMP-3. 01 RECEIVER-LENGTH PIC S9(9) COMP-4. 01 FORMAT-NAME PIC X(8) VALUE 'JOBD0100'. 01 QCMDEXC PIC X(10) VALUE 'QCMDEXC'. 01 X PIC S9(9) BINARY. * * Job Description and Library Name Structure * 01 JOBD-AND-LIB-NAME. 05 JOB-DESC PIC X(10). 05 JOB-DESC-LIB PIC X(10). * LINKAGE SECTION. * * Two Parameters are being passed into this program. * 01 JOBD PIC X(10). 01 JOBDL PIC X(10). * PROCEDURE DIVISION USING JOBD, JOBDL. MAIN-LINE. * * Beginning of Mainline * * Move the two parameters passed into JOB-DESC and JOB-DESC-LIB. * MOVE JOBD TO JOB-DESC. MOVE JOBDL TO JOB-DESC-LIB. * * Error Code Parameter is set to 100. * MOVE 100 TO BYTES-PROVIDED. * * Receiver Length Set to 5000. * MOVE 5000 TO RECEIVER-LENGTH. * * Call the QWDRJOBD API. * CALL QWDRJOBD USING RECEIVER-VARIABLE, RECEIVER-LENGTH, FORMAT-NAME, JOBD-AND-LIB-NAME, QUS-EC. * * See if any errors were returned in the error code parameter. * PERFORM ERRCOD. * * Add one to the Initial library list offset because COBOL is a * Base 1 language. * MOVE OFFSET-INITIAL-LIB-LIST TO X. ADD 1 TO X. MOVE 47 TO COMMAND-LENGTH. * * Let's tell everyone what the library value was for this job. * PERFORM NUMBER-LIBS-IN-LIB-LIST TIMES MOVE RECEIVER-VARIABLE(X:10) TO LIB, CALL QCMDEXC USING COMMAND-STRING, COMMAND-LENGTH, ADD 11 TO X, PERFORM RECLEN, END-PERFORM. * STOP RUN. * * End of Mainline * * * Subroutine to handle errors returned in the error code * parameter. * ERRCOD. * IF BYTES-AVAILABLE OF QUS-EC > 0 * * Process errors returned from the API. * STOP RUN. * * Subroutine to check to see if there is enough room in the * receiver variable for the next library in the list. * RECLEN. * IF (X + 10) >= RECEIVER-LENGTH STOP RUN.