Friday, February 19, 2021

How to pass more than 100 bytes of data from JCL to COBOL?

There is a famous interview question one can expect in COBOL interviews.

How many ways you can pass data from JCL to COBOL program? 

If your answer is 3 (via SYSIN, via PARM and File Input), this blog post is for you as it's time 🕐 to update your answer. Let's begin..

I have prepared the following COBOL Program:
 =COLS> ---1----+----2----+----3----+----4----+----5----+----6----+----7--     
 ****** ***************************** Top of Data ******************************  
 000100 ID DIVISION.                                
 000200 PROGRAM-ID. CBL3.                             
 000210 AUTHOR. SRINIVASAN.                            
 000220 DATA DIVISION.                               
 000230 WORKING-STORAGE SECTION.                          
 000240 01 WS-DISPLAY           PIC X(10).               
 000241 01 WS-LENGTH            PIC S9(4) SIGN LEADING         
 000242                   SEPARATE.                
 000250 LINKAGE SECTION.                              
 000260 01 WS-PARM-GROUP.                             
 000270   05 WS-PARM-LEN         PIC S9(4) COMP.             
 000280   05 WS-PARM-DATA         PIC X(100).               
 000290 PROCEDURE DIVISION USING WS-PARM-GROUP.                  
 000300   ADD WS-PARM-LEN TO ZERO GIVING WS-LENGTH.               
 000400   MOVE WS-PARM-DATA(91:10) TO WS-DISPLAY.                
 000410   DISPLAY 'PARM LEN  :' WS-LENGTH.                   
 000420   DISPLAY 'WS-DISPLAY :' WS-DISPLAY.                   
 000500   STOP RUN.                               
 ****** **************************** Bottom of Data ****************************  
Pretty simple program. I've defined 2 data items in the LINKAGE SECTION to handle the PARM data passed from JCL to COBOL program. The first data item (WS-PARM-LEN) holds the length of the data passed from the JCL and the second data item (WS-PARM-DATA) holds the data itself. 

In the PROCEDURE DIVISION, I'm simply displaying the length of data passed and a portion of the data i.e., 10 bytes starting from 91st position. 

One important thing that you should note here in the program is the order of the data items defined in the LINKAGE SECTION. The data field is always preceeded by a two-byte length field defined in binary format. 

Let's take a look at the JCL now. 
 =COLS> ----+----1----+----2----+----3----+----4----+----5----+----6----+----7--  
 ****** ***************************** Top of Data ******************************  
 000001 //Z01071C  JOB 1,NOTIFY=&SYSUID                       
 000002 //***************************************************/           
 000003 //* COBOL COMPILE AND LINK EDIT                       
 000004 //COBRUN  EXEC IGYWCL                            
 000005 //COBOL.SYSIN  DD DSN=&SYSUID..PDS(CBL3),DISP=SHR              
 000006 //LKED.SYSLMOD DD DSN=&SYSUID..LOAD(CBL3),DISP=SHR             
 000007 //***************************************************/           
 000008 // IF RC = 0 THEN                              
 000009 //***************************************************/           
 000010 //RUN     EXEC PGM=CBL3,PARM='12345678901234567890123456789012345678901   
 000011 //             23456789012345678901234567890123456789012345678901234567   
 000012 //             890'                             
 000013 //STEPLIB   DD DSN=&SYSUID..LOAD,DISP=SHR                  
 000014 //SYSOUT    DD SYSOUT=*,OUTLIM=15000                    
 000015 //CEEDUMP   DD DUMMY                            
 000016 //SYSUDUMP  DD DUMMY                            
 000017 //***************************************************/           
 000018 // ELSE                                   
 000019 // ENDIF                                  
 ****** **************************** Bottom of Data ****************************  
The first step is a PROC which is for COBOL program compilation and Link Edit. The second step (RUN 🏃) will run if the return code from the first step is 0. 

In the second step, PARM parameter is used (in line #10) to pass 100 bytes of data. Note that we can type the PARM data till 71st postion in the JCL and if it is to be continued on the next line, we can start anywhere from column 4 thru 16. 

After submitting this job, we get the following output written in SYSOUT
 ********************************* TOP OF DATA **********************************  
 PARM LEN   :+0100                                  
 WS-DISPLAY :1234567890                               
 ******************************** BOTTOM OF DATA ********************************  

Now, let's see what happens if we try to pass PARM data with 101 bytes (I've added one additional byte in line #12). 
 =COLS> ----+----1----+----2----+----3----+----4----+----5----+----6----+----7--  
 ****** ***************************** Top of Data ******************************  
 000001 //Z01071C  JOB 1,NOTIFY=&SYSUID                       
 000002 //***************************************************/           
 000003 //* COBOL COMPILE AND LINK EDIT                       
 000004 //COBRUN  EXEC IGYWCL                            
 000005 //COBOL.SYSIN  DD DSN=&SYSUID..PDS(CBL3),DISP=SHR              
 000006 //LKED.SYSLMOD DD DSN=&SYSUID..LOAD(CBL3),DISP=SHR             
 000007 //***************************************************/           
 000008 // IF RC = 0 THEN                              
 000009 //***************************************************/           
 000010 //RUN     EXEC PGM=CBL3,PARM='12345678901234567890123456789012345678901   
 000011 //             23456789012345678901234567890123456789012345678901234567   
 000012 //             8901'                             
 000013 //STEPLIB   DD DSN=&SYSUID..LOAD,DISP=SHR                  
 000014 //SYSOUT    DD SYSOUT=*,OUTLIM=15000                    
 000015 //CEEDUMP   DD DUMMY                            
 000016 //SYSUDUMP  DD DUMMY                            
 000017 //***************************************************/           
 000018 // ELSE                                   
 000019 // ENDIF                                  
 ****** **************************** Bottom of Data ****************************  
After submitting the job, it is found that the job has failed with JCL error.
  
IEF642I EXCESSIVE PARAMETER LENGTH IN THE PARM FIELD

The maximum number of bytes that we can pass from JCL to COBOL, using PARM parameter, is 100.

How to pass more than 100 bytes of data from JCL to COBOL? 🤔




We can make use of PARMDD parameter to pass more than 100 bytes of data from JCL to COBOL. The best way to understand PARMDD is by looking at an example.
Note that PARMDD and PARM parameters are mutually exclusive.
I've just modified the previous JCL by replacing the PARM parameter with PARMDD. There are no changes made to the COBOL program and it remain as it is. Hence, RESTART=RUN is coded in the JOB statement.   
 ****** ***************************** Top of Data ******************************  
 000001 //Z01071C  JOB 1,NOTIFY=&SYSUID,RESTART=RUN                 
 000002 //***************************************************/           
 000003 //* COBOL COMPILE AND LINK EDIT                       
 000004 //COBRUN  EXEC IGYWCL                            
 000005 //COBOL.SYSIN DD DSN=&SYSUID..PDS(CBL3),DISP=SHR              
 000006 //LKED.SYSLMOD DD DSN=&SYSUID..LOAD(CBL3),DISP=SHR             
 000007 //***************************************************/           
 000008 // IF RC = 0 THEN                              
 000009 //***************************************************/           
 000010 //RUN     EXEC PGM=CBL3,PARMDD=MYDD                     
 000011 //STEPLIB   DD DSN=&SYSUID..LOAD,DISP=SHR                  
 000012 //MYDD      DD DISP=SHR,DSN=Z01071.PARMDD.INPUT.PS             
 000013 //SYSOUT    DD SYSOUT=*,OUTLIM=15000                    
 000014 //CEEDUMP   DD DUMMY                            
 000015 //SYSUDUMP  DD DUMMY                            
 000016 //***************************************************/           
 000017 // ELSE                                   
 000018 // ENDIF                                  
 ****** **************************** Bottom of Data ****************************  
Make a note of the things that are in bold. The PARMDD parameter must be used in conjunction with a DD statement. 

Here, the PARMDD keyword specifies a DD name, MYDD, which is then coded on a DD statement (in line #12) that specifies a dataset, Z01071.PARMDD.INPUT.PS, whose record length is 130. There is one record in this dataset which is 125 bytes long. 

After submitting this JCL, we get the following output. 
 ********************************* TOP OF DATA **********************************  
 PARM LEN  :+0125                                  
 WS-DISPLAY :1234567890                               
 ******************************** BOTTOM OF DATA ********************************  

The COBOL program doesn't have any File definitions. Rather, it contain instructions to handle information retrieved from PARM. We are making use of the same instructions/defintions (coded within the LINKAGE SECTION) for PARMDD as well. 
PARMDD is different from File input way of passing data. Both involve datasets but the definitions coded within the program to handle the file differs.
We are passing 125 bytes of data with PARMDD but the WS-PARM-DATA field in the program is declared only with 100 bytes. So, the last 25 bytes will be truncated. Hence, it is imperative that we code proper definitions in the program to handle data passed by PARMDD parameter.  

We've reached the bottom of the post. So, if someone asks you how many ways you can pass data from JCL to COBOL, answer them 4
  1. File Input
  2. via SYSIN
  3. via PARM
  4. and via PARMDD
Hope this helps. Should have any questions/suggestions, please post it in the Comments section of this post. Thx.


12 comments:

  1. Excellent explanation Thanks for sharing this one 👏

    ReplyDelete
  2. Thanks for sharing!

    ReplyDelete
  3. Nice Information. Thanks for Sharing. :)

    ReplyDelete
  4. Thanks for sharing this information

    ReplyDelete
  5. Thank you for sharing. Keep it coming.

    ReplyDelete
  6. Best explanation seen so far. Just one question -
    If we pass a file through PARM parameter, you mean to say we can pass more than 100 bytes of data through that way. Right ? Correct me if my understanding is wrong.

    ReplyDelete
    Replies
    1. Hi Deepa, Glad that you liked it. Use PARMDD parameter along with a DD statement to pass more than 100 bytes of data to COBOL program. The DD statement must point to a dataset that has got the data to be passed to the program.

      Hope this helps!

      Delete
  7. Excellent information sir.. I learn a new thing today. Thanks

    ReplyDelete
  8. Thanks for sharing this. Really appreciate your post , it is very nicely explained.

    ReplyDelete