Friday, December 2, 2011

How to Fix “GDG Generation Not Found JCL Error”

Here is the snippet to avoid JCL error due to NO GDG Generations are found on SMS.

You know that the only possible way to avoid DATASET NOT FOUND JCL Error is “Create datasets or use Dummy” here is a method to handle the errors in JCL itself.

You can have IDCAMS to issue LISTCAT LVL to list all the generations for the GDG and the move the out put to an input file, then use SORT utility to Check the resultant file for the .G and V00 characters on the file. If no GDG generations found set Return code of the step to 4 (it can be anything). then setup COND parameter for an IEFBR step in such a way that if the CONDCODE matches 4 (“COND=(4,NE)”), create the versions :)

JCL.

//R0318BMJ  JOB 'GDG VER FINDER',NOTIFY=R0318B               
//IDCAMS   EXEC PGM=IDCAMS                                   
//SYSPRINT DD DSN=&&TEMP,DISP=(,PASS)                        
//SYSIN    DD *                                              
LISTCAT LVL('TSHRCI.PATMAN.REPORT.GROUP') ALL               
/*                                                           
//*                                                          
//GETPOS   EXEC PGM=SORT                                     
//SYSOUT   DD SYSOUT=*                                       
//SORTIN   DD DSN=&&TEMP,DISP=SHR                            
//SORTOUT  DD SYSOUT=*                                       
//SYSIN    DD *                                              
OPTION    NULLOUT=RC4,VLSCMP                                
SORT      FIELDS=COPY                                       
 INCLUDE   COND=(48,2,CH,EQ,C'.G',AND,54,3,CH,EQ,C'V00')     
/*                                                           
//MODEL    EXEC PGM=IEFBR14,COND=(4,NE,GETPOS)               
//GDGMODEL DD   DSN=TSHRCI.PATMAN.REPORT.GROUP(+1),          
//         DISP=(NEW,CATLG,DELETE),                          
//         UNIT=SYSDA,                                       
//         SPACE=(TRK,(1,1),RLSE),                           
//         DCB=(LRECL=80,RECFM=FB,BLKSIZE=800,DSORG=PS)      
//SYSPRINT DD   SYSOUT=*                                     
//SYSIN    DD DUMMY
                                          

INCLUDE   COND=(48,2,CH,EQ,C'.G',AND,54,3,CH,EQ,C'V00') 

Once you executed IDCAMS step the messages from LISTCAT will be moved to &&TEMP dataset, then using the above CONDITION statement SORT utility will check for .G and V00 characters on the TEMPDATASET, if found SOR will skip the step else if set RETURN CODE 4.

The TEMP Dataset is FBA, so you need to add 4 bytes to the actual position of the characters on TEMP dataset. 44 and 50 are the Character positions of .G & V00 on my TEMPDATASET, after adding 4 it will become 48 and 54.  To find the positions of your characters replace TEMP with a dataset on your system then, check the file. “Don’t forget to add 4 bytes”

//MODEL    EXEC PGM=IEFBR14,COND=(4,NE,GETPOS)

This will execute only if the GETPOS step returned a return code of 4.

Let me know if you have any concerns on the JCL. and Like it/rate it/Comment on it you like the post.

Thanks

-Shibu-

Saturday, October 29, 2011

Programming a CICS-DPL-COBOL application & setting up the region.

DPL (Distributed Program Link) enables a Local CICS program to issue a EXEC CICS LINK to a program in the remote CICS region which return control to the calling program. DPL provides the below advantages for a CICS application.

  1. It allows a non OS390/zOS application to use DL/I, SQL, BDAM and VSAM files owned by a zOS/os390 system.
  2. Allows CICS programmer to use LU 6.2 link Protocol without knowing the protocol.
Restrictions of DPL.

You cannot use the below CICS services on the remote application.

  1. You cannot issue any terminal control commands. e.g. SEND, RECEIVE.
  2. No BMS commands.
  3. No security commands like SIGNON or SIGNOFF.

If you are receiving any abends on the remote application and it didn’t handle the abend by itself then, abend code will returned to the Main program.

Defining and installing CICS entries.

Assume that you have a Mainframe connectivity like below.

image

Here I have 2 TSO sessions, 8 CICS regions, 2 IMS, 1 CICSPlex/SM and few Session manager setups and Misce sessions.

I am using the CICSA and CICSB regions, I.e my Main program is in CICSA and it then calling the program on CICSB using a COMMAREA, second program will write the message passed in commarea into a VSAM file, set a message onto COMMAREA and returns into CICSA region.

Before you are getting started with your program, make sure that MRO/ISC is configured in your Mainframe, you can contact you system Admin or follow my instructions below.

  1. Go to your CICS region batch job in spool.
  2. Open the JESYSMSG and Check for ISC and IRCSTRT init parms are setup to YES.
  3. IF the above initparms are not setup to YES then you need to ask your sysadmin to set this up before you continue with DPL program.
Usually SYSADMIN do the below steps to setup ISC or IRCSTRT.
  1. Bring down CICS region using master console or Perform SHUTDOWN using CEMT.
  2. Find SIP parameter for the region.
  3. Go to SYSIN PDS of the Installed CICS TS.
  4. Find the DFH$SIP<SIP PARM> member and add the ISC and IRCSTRT parms.
  5. Restart CICS region.

You can also issue a CEMT I IRC to check whether IRC is setup for the region.

image

Steps to create CICS table entries for a DPL program.

  1. Define and Install the main program on LOCAL CICS region as usual.
  2. Define and install Mirror Entries of remote CICS transaction and program on LOCAL CIS region. Set the remote Attributes (Remote System as the 4 digit remote CICS region ID, and program name) You can see the remote system ID on SYSID field once you issue a CEMT/CEDA command (See below screenshots).
  3. Go to Remote CICS region and define and Install only remote Program and Transaction.
  4. Compile CICS programs and move Load module to the respective libraries of local and Remote CICS regions.
  5. Perform New copy for the Local program on Local CICS region and Remote program on remote region.
  6. Invoke the Local CICS program using the defined Transaction on Local CICS region.
DPL Sample program

Main program.

IDENTIFICATION DIVISION.
PROGRAM-ID. CDPL01A.
AUTHOR.     SHIBU.T.
*
DATA DIVISION.
WORKING-STORAGE SECTION.
77  WS-MSG-1                    PIC X(100).
77  WS-MSG-LEN                  PIC S9(4) COMP.
*
01  WS-COMMAREA.
     02  WS-RECID                PIC X(10).
     02  WS-MSG                  PIC X(40).
     02  WS-PROG-ID              PIC X(08).
LINKAGE SECTION.
01  DFHCOMMAREA.
     02  LS-COMMAREA.
         03  LS-RECID            PIC X(10).
         03  LS-MSG              PIC X(40).
         03  LS-PROG-ID          PIC X(08).
PROCEDURE DIVISION.
A0001-MAIN-PARA.
     MOVE SPACES                 TO WS-COMMAREA WS-MSG-1.
     IF EIBCALEN = 0 THEN
        PERFORM A00150-INITIALIZE
     ELSE
        PERFORM A00200-LINK
     END-IF.

*
A00150-INITIALIZE.
     MOVE 'PROGRAM ON CICSAOR1 REGION'
                                 TO WS-MSG.
     MOVE '1000000123'           TO WS-RECID.
     MOVE 'CDPL01A'              TO WS-PROG-ID.
     MOVE 'WS-MSG BEFORE DPL: '  TO WS-MSG-1(1:20).
     MOVE WS-MSG                 TO WS-MSG-1(21:26).
     MOVE '* PROGRAM-ID: '       TO WS-MSG-1(47:14).
     MOVE WS-PROG-ID             TO WS-MSG-1(61:08).
     EXEC CICS SEND TEXT
         FROM(WS-MSG-1)
         ERASE
     END-EXEC.
     EXEC CICS RETURN
         TRANSID('AA05')
         COMMAREA(WS-COMMAREA)
     END-EXEC.

*
A00200-LINK.
     MOVE LS-COMMAREA            TO WS-COMMAREA.
     EXEC CICS LINK
         PROGRAM('CDPL01B')
         COMMAREA(WS-COMMAREA)
     END-EXEC.

     MOVE SPACES                 TO WS-MSG-1.
     MOVE 'WS-MSG AFTER  DPL: '  TO WS-MSG-1(1:20).
     MOVE WS-MSG                 TO WS-MSG-1(21:26).
     MOVE '* PROGRAM-ID: '       TO WS-MSG-1(47:14).
     MOVE WS-PROG-ID             TO WS-MSG-1(61:08).
     EXEC CICS SEND TEXT
         FROM(WS-MSG-1)
         ERASE
     END-EXEC.
     EXEC CICS RETURN
     END-EXEC.

Sub Program on Remote region.

IDENTIFICATION DIVISION.
PROGRAM-ID. CDPL01B.
AUTHOR.     SHIBU.T.
*
DATA DIVISION.
WORKING-STORAGE SECTION.
77  WS-MSG-1                    PIC X(100).
77  WS-MSG-LEN                  PIC S9(4) COMP.
01  WS-FILE-DT.
     02  WS-DAT.
         03  WS-KEY              PIC X(10).
         03  WS-DAT1             PIC X(40) VALUE SPACES.
         03                      PIC X(60) VALUE SPACES.
*
01  WS-COMMAREA.
     02  WS-RECID                PIC X(10) VALUE SPACES.
     02  WS-MSG                  PIC X(40).
     02  WS-PROG-ID              PIC X(08).
LINKAGE SECTION.
01  DFHCOMMAREA.
     02  LS-COMMAREA.
         03  LS-RECID            PIC X(10).
         03  LS-MSG              PIC X(40).
         03  LS-PROG-ID          PIC X(08).
PROCEDURE DIVISION USING DFHCOMMAREA.
A0001-MAIN-PARA.
*    MOVE SPACES                 TO WS-COMMAREA WS-MSG-1.
     MOVE LS-RECID               TO WS-KEY.
     MOVE LS-MSG                 TO WS-DAT1.
     EXEC CICS WRITE
          DATASET('VFILE1')
          FROM(WS-DAT)
          LENGTH(LENGTH OF WS-DAT)
          RIDFLD(WS-KEY)
     END-EXEC.
     MOVE 'PROGRAM ON CICSAORB REGION'
                                 TO WS-MSG.
     MOVE 'CDPL01B'              TO WS-PROG-ID.
     MOVE WS-COMMAREA            TO LS-COMMAREA.
     EXEC CICS RETURN
     END-EXEC.

Compile aCICS programs and Move load modules to respective LOAD LIBS of CICS regions.

Please refer to http://mainframegeek.wordpress.com/2011/10/11/prepare-compile-define-install-execute-a-cics-cobol-program/ for more info on how to prepare compile a COBOL-CICS program, how to find LOAD LIB od CICS region and move the Load module.

Defining and Installing Resources to CICS.
On CICS REGION CICSA

Step 1 Create and Install Program entries for the Main program on CICSA, defining is similar to a normal CICS program.

clip_image002[12]

Step 2 Install the program.

clip_image002[32]

Step 3 Define Transaction Entry for Main program on CICSA, you need to mention main program name (CDPL01A) while defining Transaction entry.

clip_image002[8]

Step 4  Install the transaction.

clip_image002[10]

Step 5 Define Mirror Program.

clip_image002[14]

clip_image002[16]

clip_image002[18]

Step 6 Define and Install Mirror Transaction.

clip_image002[22]

clip_image002[24]

clip_image002[26]

on remote region

Step 7 Define, Install Program and Transaction entries .

image

clip_image002[6]

clip_image002[28]

clip_image002[30]

Step 9 Execute Program.

Issue AA05 on CICSA to execute program, do a cedf if you want to see what is exactly happening in the program. This is a pseudo-conversation program, it displays commarea content before links to the remote app. Press enter to issue LINK.

clip_image002[34]

clip_image002[36]

Control came back from Remote app, you can see the commarea contents which set up by remote app.

You can also open the file to ensure that Remote app is getitng COMMAREA conts correctly ( Remote app will write the commarea contents to VSAM file). Look for th last line, that is the message passed on commarea.

clip_image002[38]

Tuesday, October 11, 2011

Prepare, Compile, Define, Install, Execute a CICS (COBOL) program

Here I’m trying to cover the necessary steps to Prepare, Compile, Define and Execute a CICS COBOL program, Technically there no difference in Link edit, Define, Install and Execute a COBOL program and the programs prepared in any other languages such as Assembler, C/C++, PL\1. But yes there is difference in compiling object codes.

 

                    cics-lifecycle

Step 1. Compile/Link edit a CICS COBOL Program.

IBM has supplied a standard procedure for Compile and link edit CICS-COBOL code. The pre-compile ( Translating ) will comment all the CICS commands from the source code and then replace them with specific COBOL call statements. This translated source code then passed to Compile step, which will compile the source code and create the object code. The Cobol compilation is done with IGYCRCTL compiler program. The object code then given as input to the IBM linkedit program. you can use HEWL or IEWL for this purpose, you can find this program in CEE.SCEELKED or CEE.SCEECICS this may be different in your system. The IBM supplied standard procedure name is DFHEITVL. You can find this proc in SDFHPROC,of the CICS base location. for me it was CICSTS42.CICS.SDFHPROC.  And of course you can see a lot of other procs in the CICS proclib, some of them can be used for CICS-DB2-COBOL, CICS-Assempler, CICS-C/C++, CICS-PL\1 or compile and link edit BMS Maps etc. you can then use the below jcl for precompile, Compile and Link edit your program.

//DDS1764J   JOB 'SHIBU THANNIKKUNNATH',NOTIFY=&SYSUID  
//IBMLIB     JCLLIB ORDER=CICSTS42.CICS.SDFHPROC               
//CPLSTP     EXEC DFHEITVL                               
//TRN.SYSIN  DD DSN=TSHRCI.PGMG.CICOB(PGM1),DISP=SHR    
//LKED.SYSIN DD *                                       
   NAME PGM1(R)                                         
//

make sure that the PROGLIB in the DFHEITVL is pointed to your CICS loadlib. If you are not sure about this you can go to The JESJCL of the job for your CICS region in Spool and check for DFHRPL dd statement.

Step 2. DEFINE and INSTALL PROGRAM and TRANSACTION Entries.

You should have Administration privileges to do the below steps.

Define Program Entries.

To define a CICS prog entry, you can issue CEDA  DEF  PROG( Program ID) GROUP(group ID). If the group doesn’t exist in the system them CICS will create a new group for you. If your program lies in the same CICS region itself then the mandatory values are Program Id and Group name. If your program is a Remote program , lies in a different CICS region then you need to have the destination CICS region ID and remote Program ID in addition to the program Id and group ID.

image

Install the Program ID

You can issue a CEDA INS PROG(Program id) GROUP(Group ID). the group and program are must be defined in the system.

image

Define Transaction ID

You can Issue a CEDA DEF TRANS(transaction id) group(group id) for this. If the group is not existing in the system then group will be created by CICS. You must Give Program ID (associated with the trans-id) while defining Transaction. Again if your transaction is for a remote program then you must provide the destination CICS region ID and destination transaction name.

image

Then Issue CEDA INS TRANS(Transaction ID) GROUP( Group ID) to install the transaction id.

image

Step 3. Run The Program

You can just enter the transaction Id associated with the program to execute it. You can also use CEDF for debugging mode, in CEDF you can see the step by step execution of CICS commands in your program, you can also see the working storage section, EIB Fields values and lot mode when you use CEDF.

Executing with CEDF

image

image

 

Execution without CEDF

image

here is my CICS-COBOL Source code.. This is a Link program, but I’m not giving my second program’s source code, please comment in this post if you guys want me to post my second program.

 Identification division.                                     
Program-id.    pgm1.                                         
author.        shibu.t.                                      
data division.                                               
working-storage section.                                     
77  msg-len                     pic s9(4) comp.              
77  msg-out                     pic x(30).                   
01  ws-commarea.                                             
     05  ws-pgm1                 pic x(8).                    
     05  ws-pgm2                 pic x(8).                    
77  temp-data                   pic x(10).                   
linkage section.                                             
01  dfhcommarea.                                             
     02  ls-commarea.                                         
         05  ls-pgm1             pic x(8).                    
         05  ls-pgm2             pic x(8).                    
Procedure division.                                          
     Move 'PGM1:YES' to ws-pgm1.                              
     Move 'PGM2:NO ' to ws-pgm2.                              
     Move 16 to msg-len.                                      
     exec cics send                                           
       from(ws-commarea)                                      
       length(msg-len)                                        
       erase                                                  
     end-exec.                                                
     exec cics LINK                                           
       program('PGM2')                                        
       commarea(ws-commarea)                                  
     end-exec.                                                
*    move ls-commarea            to ws-commarea.              
*    move ls-commarea            to temp-data.                
*    move 10                     to msg-len.                  
     exec cics send                                           
       from(ws-commarea)                                      
       length(msg-len)                                        

       erase                                                   
     end-exec.                                                 
     Exec cics return                                          
     end-exec.                                                 
     goback.
                                                   

Tuesday, September 13, 2011

DSNTIAR & DSNTIAC–SQLCA formatter for Batch & CICS

We must check for the SQLCODE before we issue commit on a table in DB2, handle the errors- Display description or whatever. handling/remembering reason for each and every sqlcode every time is a time pressing task always. There is DSNTIAR and DSNTIAC comes in picture. DSNTIAR and DSNTIAC are two assembler routine which helps to get a formatted version of SQLCA and the text message based on the sqlcode in the SQLCA.

DSNTIAR takes data from SQLCA formats and puts into a data area provided by the calling program. DSNTIAR will overwrite the contents of the data area before it moves the data.

DSTIAR expects the SQLCA in its original for, so before you call DSNTIAR/DSNTIAC make sure that you haven’t modified SQLCA.

Defining Message output Data name

Calling program must allocate output message data name and pass it,

make sure:

1. First 2 bytes are length – a pic s9(4) comp will be ideal for the purpose.

2.You must define enough space for the message in character type, data should be minimum of 10 lines of 72 bytes. A  PIC x(72)  occurs 10 times. will  be quite enough for the message.

e.g.

01  ERROR-MESSAGE.                                
        02  ERROR-LEN   PIC S9(4)  COMP VALUE +720.
        02  ERROR-TEXT  PIC X(72)  OCCURS 10 TIMES.

keep the length in another variable.

77  ERROR-TEXT-LEN      PIC S9(9)  COMP VALUE +72.

Once we executed a SQL statement, we are ready to issue a call to DSNTIAR,

CALL 'DSNTIAR' USING SQLCA ERROR-MESSAGE ERROR-TEXT-LEN

display the resultant message by displaying “ ERROR-TEXT() “ table.

Possible return codes for DSNTIAR/DSNTIAC
0 Successful execution.
4 More data available than could fit into the provided message area.
8 Error record length is not between 72 & 240
12 Message area is not large enough,  we need to provide more space needs to be defined and must be passed.
16 Error in message routine.

 

Sample program

IDENTIFICATION DIVISION.                                        
PROGRAM-ID. DBPGM01.                                            
AUTHOR    . SHIBU.T.                                            
*                                                                
DATA DIVISION.                                                  
WORKING-STORAGE SECTION.                                        
     EXEC SQL                                                    
         INCLUDE MYNAM                                           
     END-EXEC.                                                   
     EXEC SQL                                                    
         INCLUDE SQLCA                                           
     END-EXEC.                                                   
                                                                 
01  ERROR-MESSAGE.                                              
         02  ERROR-LEN   PIC S9(4)  COMP VALUE +720.             
         02  ERROR-TEXT  PIC X(72)  OCCURS 10 TIMES.             
77  ERROR-TEXT-LEN      PIC S9(9)  COMP VALUE +72.              
                                                                 
01  WS-TEMP-VAR.                                                
     05  TEMP                    PIC X(30).                      
     05  TEMP-MSG                PIC X(60).                      
     05  WS-IND                  PIC X VALUE 'Y'.                
01  WS-TBLE-DTA.                                                
     05  WS-SEQ                  PIC X(3).                       
     05  WS-SEQ-TMP              PIC X(3).                       
     05  WS-NAME                 PIC X(15).                      
                                                                 
77  WS-I                        PIC S9(4) COMP.                 
                                                                 
01  WS-SQLCODE                  PIC ------9.                    
*                                                                
PROCEDURE DIVISION.                                             
     PERFORM A00100-READ-PARA.                                   
                                                                 
Z00100-EXIT-PARA.                                               
     STOP RUN.                                                   
A00100-READ-PARA.                                               
     DISPLAY '         A00100-READ-PARA.           '             
     EXEC SQL                                                   
         DECLARE CURREAD1 CURSOR FOR                            
             SELECT NAME,SEQ FROM IBMGRP.MYNAM                  
     END-EXEC.                                                  
     EXEC SQL                                                   
        OPEN CURREAD1                                           
     END-EXEC.                                                  
     EVALUATE TRUE                                              
     WHEN SQLCODE = 0                                           
      PERFORM A00150-READ-PARA                                  
     WHEN SQLCODE > 0                                           
      DISPLAY 'FETCH WAS SUCCESS WITH A WARNING'                
      CALL 'DSNTIAR' USING SQLCA ERROR-MESSAGE ERROR-TEXT-LEN   
      PERFORM VARYING WS-I FROM 1 BY 1 UNTIL WS-I = 10          
        DISPLAY ERROR-TEXT(WS-I)                                
      END-PERFORM                                               
     WHEN OTHER                                                 
      CALL 'DSNTIAR' USING SQLCA ERROR-MESSAGE ERROR-TEXT-LEN   
      PERFORM VARYING WS-I FROM 1 BY 1 UNTIL WS-I = 10          
        DISPLAY ERROR-TEXT(WS-I)                                
      END-PERFORM                                               
      PERFORM Z00100-EXIT-PARA                                  
     END-EVALUATE.                                              
     MOVE SQLCODE             TO WS-SQLCODE.                    
     DISPLAY 'SQLCODE OPEN  ' WS-SQLCODE.                       
A00150-READ-PARA.                                              
     DISPLAY '****DATA FROM TABLE***'                           
     PERFORM UNTIL SQLCODE = 100                                
        EXEC SQL                                                
           FETCH CURREAD1 INTO :WS-NAME,:WS-SEQ                 
        END-EXEC                                                
        MOVE SQLCODE             TO WS-SQLCODE                  
        EVALUATE TRUE                                           
        WHEN SQLCODE = 0                                        
         MOVE SPACES TO TEMP-MSG                                
         STRING                                                 
         'NAME: ' DELIMITED BY SPACE ' ' DELIMITED BY SIZE      
         WS-NAME DELIMITED BY SPACE ',' DELIMITED BY SIZE       
         'SEQ#' DELIMITED BY SPACE ' ' DELIMITED BY SIZE        
         WS-SEQ DELIMITED BY SIZE INTO TEMP-MSG                 
         DISPLAY TEMP-MSG                                       
        WHEN  SQLCODE > 0                                       
         DISPLAY 'FETCH WAS SUCCESS WITH A WARNING'             
         CALL 'DSNTIAR' USING SQLCA ERROR-MESSAGE ERROR-TEXT-LEN
         PERFORM VARYING WS-I FROM 1 BY 1 UNTIL WS-I = 10       
         DISPLAY ERROR-TEXT(WS-I)                               
      END-PERFORM                                               
        WHEN OTHER                                              
         CALL 'DSNTIAR' USING SQLCA ERROR-MESSAGE ERROR-TEXT-LEN
         PERFORM VARYING WS-I FROM 1 BY 1 UNTIL WS-I = 10       
           DISPLAY ERROR-TEXT(WS-I)                             
         END-PERFORM                                            
         PERFORM Z00100-EXIT-PARA                               
        END-EVALUATE                                            
     END-PERFORM.                                               
     DISPLAY '****END OF TABLE DATA****'                        
     EXEC SQL                                                   
        CLOSE CURREAD1                                          
     END-EXEC.                                                  
     MOVE SQLCODE             TO WS-SQLCODE.                    
     DISPLAY 'SQLCODE CLOSE ' WS-SQLCODE.                       
     EXIT                                                       
     .                                                          

Compiling and link editing.

remember you must concatenate <HLQ>.SDSNLOAD of DB2 installed in your host mainframe to the STEPLIB of compile step, otherwise it will result in DSNTIAR module not found error while compiling. Read http://mainframegeek.wordpress.com/2011/05/12/steps-in-a-cobol-db2-program/ for the jcl for compile, link edit and exec ut the DB2 cobol program. Don’t forget to change the JCL as mentioned below.

e.g.

//DB2COBA JOB (12345678),MSGCLASS=H,REGION=4M,                        
//        MSGLEVEL=(1,1),CLASS=A,NOTIFY=&SYSUID                       
//*                                                                   
//JOBLIB    DD DSN=DSN910.DB9G.SDSNEXIT,DISP=SHR                      
//          DD DSN=DSN910.SDSNLOAD,DISP=SHR                           
//*****************************************************************   
//* SQL PREPROC AND COBOL COMPILATION:                                
//*****************************************************************   
//*-NB---SQL PREPROC NOW IS NOW DONE BY THE COBOL COMPILER:           
//*****************************************************************   
//COB     EXEC  PGM=IGYCRCTL,                                         
//            PARM=(SQL,LIB,NOTERM,NOSEQUENCE,LIB,XREF,DYN,'')        
//STEPLIB   DD DSN=IGY410.SIGYCOMP,DISP=SHR                           
//          DD DSN=DSN910.SDSNLOAD,DISP=SHR                           
//DBRMLIB   DD DSN=TSHRCI.PGMG.DBRM(DBPGM02),DISP=SHR                 
//SYSIN     DD DSN=TSHRCI.PGMG.COBOL1(DBPGM02),DISP=SHR               
//SYSLIB    DD DSN=TSHRCI.PGMG.COBOL1,DISP=SHR                        
//SYSLIN    DD DSN=&&LOADSET,DISP=(MOD,PASS),UNIT=SYSDA,              
//             SPACE=(800,(500,500))                                  
//SYSPRINT  DD SYSOUT=*                                               
//SYSUDUMP  DD SYSOUT=*                                               
//SYSUT1    DD SPACE=(800,(500,500),,,ROUND),UNIT=SYSDA               
//SYSUT2    DD SPACE=(800,(500,500),,,ROUND),UNIT=SYSDA               
//SYSUT3    DD SPACE=(800,(500,500),,,ROUND),UNIT=SYSDA               
//SYSUT4    DD SPACE=(800,(500,500),,,ROUND),UNIT=SYSDA               
//SYSUT5    DD SPACE=(800,(500,500),,,ROUND),UNIT=SYSDA               
//SYSUT6    DD SPACE=(800,(500,500),,,ROUND),UNIT=SYSDA               
//SYSUT7    DD SPACE=(800,(500,500),,,ROUND),UNIT=SYSDA               
//*****************************************************************
   

Outputs.

image

Thursday, August 18, 2011

Submitting Batch JOB( JCL) from CICS Online program.

How do we submit JCL's from CICS Online program?, we can use a TDQ or CICS SPOOL Verbs. So how these CICS SPOOL Verbs differs  from  TDQ?. The problem with TDQ is that in most of the sites, application developers are not authorized to create TDQ (its sysadmin task ) , not that much flexible, and we are responsible to read TDQ sequentially . So thats how CICS JES  commands  comes into picture. We can read the Spool data and write into spool. today we are gonna look only submitting the jobs.

The JES-CICS interface is totally depends on SPOOL initialization parm of CICS TS, check with your sysadmin guys whether CICS SPOOL parm is YES or NO. To use JES-CICS, SPOOL keyword must be YES.

Submitting a batch job has 3 steps

1. SPOOLOPEN OUTPUT

We are opening SPOOL for submitting JCL, we need to provide USERID and need to store TOKEN for the connection. We must use the same token till we close the spool. The userId is not RACF ID it must be INTRDR (Internal reader), the token is a 8 bit alphanumeric dataname (PIC x(8).

Snippet.

EXEC CICS SPOOLOPEN OUTPUT 
   NODE('LOCAL')           
   USERID('INTRDR')        
   TOKEN(WS-TOKEN)         
   RESP(WS-RESP)           
END-EXEC.                

2. SPOOLWRITE

Is for writing the lines of JCL statements into spool with INTRDR. we should define the data name which holds the JCL statements as a 80 bit length Alpha numeric field (PIC X(80). we must provide the length in FLENGTH of SPOOLWRITE. we must provide the token which we got when we opened spool.

Snippet.

EXEC CICS SPOOLWRITE                   
     FROM(WS-LINE(WS-CNTR))            
     FLENGTH(LENGTH OF WS-LINE(WS-CNTR))
     RESP(WS-RESP)                     
     TOKEN(WS-TOKEN)                   
END-EXEC                             

3. SPOOLCLOSE

Okay, we have written our jcl statements to JES; now we need to close the spool connection so the JCL will get submitted. we must provide the token which we got when we opened spool.

Snippet.

EXEC CICS SPOOLCLOSE
   RESP(WS-RESP)   
   TOKEN(WS-TOKEN) 
END-EXEC.        

Common Abends/Errors.
1. ALLOCERROR

occurs when Dynamic allocation rejected request to allocate input dataset.

2. INVREQ

Can occur if any of the following happens. Unsupported function, Unsupported language, From dataname is missing etc.

3. SPOLBUSY

JES interface is used by another task.

4. LENGERR

Happens when the from dataname contents and FLENGTH value are mismatching, we can always make use of  'LENGTH OF' keyword to avoid this.

5. NOTOPEN

Spool report has not been opened.

finally

6 NOSPOOL

this happens when we have no JES subsystem.

Sample program for Submitting JCL from CICS

IDENTIFICATION DIVISION.                                    
PROGRAM-ID. SPOOL01.                                        
AUTHOR.     SHIBU.T.                                        
*                                                            
DATA DIVISION.                                              
WORKING-STORAGE SECTION.                                    
01  WS-JCL.                                                 
     05  WS-LINE                 PIC X(80) OCCURS 13 TIMES.  
01  WS-TEMP.                                                
     05  WS-MSG                  PIC X(40).                  
     05  WS-RESP                 PIC S9(8) COMP.             
     05  WS-CNTR                 PIC S9(4) COMP.             
     05  WS-TOKEN                PIC X(8).                   
COPY DFHAID.                                                
*                                                            
PROCEDURE DIVISION.                                         
A00100-MAIN-PARA.                                           
     MOVE LOW-VALUES             TO WS-JCL.                  
     MOVE 'TEST MESSAGE'         TO WS-MSG.                  
     MOVE '//R0318BJJ  JOB REGION=0M'                        
                                 TO WS-LINE(1).              
     MOVE '//MODEL    EXEC PGM=IEFBR14'                      
                                 TO WS-LINE(2).              
     MOVE '//JPAYSLP DD DSN=TSHRCI.PAYROLL.PAYSLIP.GROUP(+1),'
                                 TO WS-LINE(4).              
     MOVE '//            DISP=(NEW,CATLG,DELETE),'           
                                 TO WS-LINE(5).              
     MOVE '//            SPACE=(TRK,5),'                     
                                 TO WS-LINE(6).              
     MOVE '//            DCB=TSHRCI.PAYROLL.PAYSLIP.MODEL,'  
                                 TO WS-LINE(7).              
     MOVE '//*           VOL=SER=ETRU04,'                    
                                 TO WS-LINE(8).              
     MOVE '//            UNIT=SYSDA'                         
                                 TO WS-LINE(9).              
     MOVE '//SYSIN     DD   *'   TO WS-LINE(10).             
     MOVE '//SYSPRINT DD   SYSOUT=*'                         
                                 TO WS-LINE(11).         
     MOVE '/*'                   TO WS-LINE(12).         
     MOVE '//'                   TO WS-LINE(13).         
     EXEC CICS SEND                                      
        FROM(WS-MSG)                                     
        LENGTH(LENGTH OF WS-MSG)                         
     END-EXEC.                                           
* OPEN SPOOL.                                            
     EXEC CICS SPOOLOPEN OUTPUT                          
        NODE('LOCAL')                                    
        USERID('INTRDR')                                 
        TOKEN(WS-TOKEN)                                  
        RESP(WS-RESP)                                    
     END-EXEC.                                           
     IF WS-RESP NOT = DFHRESP(NORMAL)                    
        MOVE SPACES              TO WS-MSG               
        MOVE '* OPEN SPOOL.'     TO WS-MSG               
        EXEC CICS SEND                                   
        ERASE                                            
           FROM(WS-MSG)                                  
           LENGTH(LENGTH OF WS-MSG)                      
        END-EXEC                                         
        PERFORM Z00100-EXIT-PARA                         
     END-IF.                                             
* WRITE RECORDS INTO SPOOL                               
     PERFORM VARYING WS-CNTR FROM 1 BY 1 UNTIL           
             WS-CNTR = 14                                
        EXEC CICS SPOOLWRITE                             
             FROM(WS-LINE(WS-CNTR))                      
             FLENGTH(LENGTH OF WS-LINE(WS-CNTR))         
             RESP(WS-RESP)                               
             TOKEN(WS-TOKEN)                             
        END-EXEC                                         
     END-PERFORM.                                        
     IF WS-RESP NOT = DFHRESP(NORMAL)                    
        MOVE SPACES              TO WS-MSG               
        MOVE '* WRITE JCL '      TO WS-MSG               
        EXEC CICS SEND                                   
        ERASE                                           
           FROM(WS-MSG)                                 
           LENGTH(LENGTH OF WS-MSG)                     
        END-EXEC                                        
        PERFORM Z00100-EXIT-PARA                        
     END-IF.                                            
* CLOSE SPOOL                                           
     EXEC CICS SPOOLCLOSE                               
        RESP(WS-RESP)                                   
        TOKEN(WS-TOKEN)                                 
     END-EXEC.                                          
     IF WS-RESP NOT = DFHRESP(NORMAL)                   
        MOVE SPACES              TO WS-MSG              
        MOVE '* CLOSE SPOOL'     TO WS-MSG              
        EXEC CICS SEND                                  
        ERASE                                           
           FROM(WS-MSG)                                 
           LENGTH(LENGTH OF WS-MSG)                     
        END-EXEC                                        
     END-IF.                                            
        PERFORM Z00100-EXIT-PARA.                       
*                                                       
Z00100-EXIT-PARA.                                      
     EXEC CICS RETURN                                   
     END-EXEC.    

When the application finished the execution you can see the job in SPOOL ( with SDSF or whatever).

image