Archive for the ‘SPOOL CLOSE’ Tag

Submitting Batch JOB( JCL) from CICS Online program.   Leave a comment


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