Joined: 02 Dec 2002 Posts: 155 Topics: 25 Location: N.Ireland
Posted: Wed Jun 14, 2006 3:00 am Post subject:
I still didn't manage to get the JCL submitted from IMS online. I contacted the sysprogs and they talked to IBM. the answer from IBM is that this may not be possible using API.
Does anyone tried this successfuly ?
Bithead,
PMed you the reply I got from IBM(don't want to put it on the forum). Do the points made by IBM make any sense to you ?
Joined: 02 Dec 2002 Posts: 155 Topics: 25 Location: N.Ireland
Posted: Thu Jun 15, 2006 3:13 am Post subject:
Bithead,
thanks for the reply. I don't have DB2 here. I tried the following code from an IMS transaction and this worked. I was under the impression that it is not possible to use INTRDR in IMS transaction as we do in batch. But look like I was wrong.
01 WS-88-FIELDS.
05 WS-INP-MSG-STS PIC X(01) VALUE SPACES.
88 EOF-INPUT-MSG VALUE 'Y'.
05 WS-ERR-STS PIC X(01) VALUE SPACES.
88 ERROR-FOUND VALUE 'Y'.
05 WS-ISRT-STS PIC X(01) VALUE SPACES.
88 INSERT-TO-MPP-OK VALUE 'Y'.
88 INSERT-TO-MPP-NOT-OK VALUE 'N'.
05 WS-ISRT-STS PIC X(01) VALUE SPACES.
88 CHANGE-OK VALUE 'Y'.
88 CHANGE-NOT-OK VALUE 'N'.
05 WS-SAME-PR-PO-STS PIC X(01) VALUE SPACES.
88 SAME-PR-PO VALUE 'Y'.
88 NOT-SAME-PR-PO VALUE 'N'.
01 WS-OPTIONS.
05 OP-LL PIC S9(4) COMP VALUE 26.
05 OP-ZZ PIC S9(4) COMP VALUE ZEROES.
05 FILLER PIC X(22)
VALUE 'IAFP=M1M,OUTN=PRNTDUMP'.
01 DLI-CALL-FUNCTIONS.
05 GU PIC X(4) VALUE 'GU '.
05 GN PIC X(4) VALUE 'GN '.
05 GNP PIC X(4) VALUE 'GNP '.
05 GHU PIC X(4) VALUE 'GHU '.
05 GHNP PIC X(4) VALUE 'GHNP'.
05 ISRT PIC X(4) VALUE 'ISRT'.
05 DLET PIC X(4) VALUE 'DLET'.
05 REPL PIC X(4) VALUE 'REPL'.
05 CHNG PIC X(4) VALUE 'CHNG'.
05 PURG PIC X(4) VALUE 'PURG'.
01 WS-HOLD-AREA.
05 OM-LL PIC S9(4) COMP VALUE 141.
05 OM-ZZ PIC S9(4) COMP VALUE ZEROES.
05 OM-LL2 PIC S9(4) COMP VALUE 137.
05 OM-ZZ2 PIC S9(4) COMP VALUE ZEROES.
05 WS-JCL-LINE PIC X(80).
01 JCLMOD-PCB.
05 FILLER PIC X(08).
05 FILLER PIC X(02).
05 JCLMOD-STATUS-CODE PIC X(02).
05 FILLER PIC X(20).
*
*=================================================================
* P R O C E D U R E D I V I S I O N *
*=================================================================
*
PROCEDURE DIVISION USING DUMMY-IO-PCB
JCLMOD-PCB.
*
DDECLARATIVES.
DREADY-TRACE SECTION.
D USE DEBUGGING ALL PROCEDURES.
*DSHOW-PROCEDURE-NAME.
D DISPLAY DEBUG-NAME ',' DEBUG-CONTENTS
D .
DEND DECLARATIVES.
DREMAINDER-OF-PROGRAM SECTION.
******************************************************************
* MAIN SECTION *
******************************************************************
0100-MAIN SECTION.
PERFORM 1000-INITIAL-PROCESS
IF CNTRL-NORMAL
PERFORM 2000-PROCESS-RECS
END-IF
PERFORM 7000-FINAL-PROCESS
.
*----------------------------------------------------------------*
* INITIAL PROCESS *
*----------------------------------------------------------------*
1000-INITIAL-PROCESS SECTION.
DISPLAY 'JCL SUBMIT TEST'
CALL 'CBLTDLI' USING GU
DUMMY-IO-PCB
WS-INPUT-MSG
DISPLAY 'JCL SUBMIT'
MOVE +141 TO OM-LL
MOVE +0 TO OM-ZZ
MOVE +137 TO OM-LL2
MOVE +0 TO OM-ZZ2
MOVE +26 TO OP-LL
MOVE +0 TO OP-ZZ
MOVE +48 TO FB-LL
MOVE +0 TO FB-ZZ
All times are GMT - 5 Hours Goto page Previous1, 2
Page 2 of 2
You cannot post new topics in this forum You cannot reply to topics in this forum You cannot edit your posts in this forum You cannot delete your posts in this forum You cannot vote in polls in this forum