TSO-ISPF JCL COBOL VSAM DB2 CICS IMS-DB Tools Articles Forum Quiz Interview Q&A

JCL - Compile and Execute COBOL Program


Compiling COBOL Programs:

In order to execute a COBOL program in batch mode using JCL, the program needs to be compiled and a load module is created with all the sub-programs. The JCL uses the load module and not the actual program at the time of execution. The load libraries are concatenated and given to the JCL at the time of execution using JCLLIB or STEPLIB.

There are many mainframe compiler utilities available to compile a COBOL program. Some corporate companies use Change Management tools like CHANGEMAN, Endevor, which compiles and stores every version of the program. This is useful in tracking the changes made to the program.

Writing JCL to compile programs

//JOBIBMKS  JOB (123),'IBMMAINFRAMER',CLASS=C,MSGCLASS=S,MSGLEVEL=(1,1),
//       NOTIFY=&SYSUID                       ---> JOBIBMKS is the name of the job.
//STEP1    EXEC PGM=IGYCRCTL,PARM='OBJECT'    ---> STEP1 is the name of the sole job step in the job.
//STEPLIB  DD   DSNAME=IGY.V4R2M0.SIGYCOMP,DISP=SHR          The EXEC statement also specifies that the generated object
//SYSUT1   DD   UNIT=SYSDA,SPACE=(CYL,(1,1))                 code should be placed on disk or tape (to be used as input to the link step).
//SYSUT2   DD   UNIT=SYSDA,SPACE=(CYL,(1,1))
//SYSUT3   DD   UNIT=SYSDA,SPACE=(CYL,(1,1))
//SYSUT4   DD   UNIT=SYSDA,SPACE=(CYL,(1,1))
//SYSUT5   DD   UNIT=SYSDA,SPACE=(CYL,(1,1))
//SYSUT6   DD   UNIT=SYSDA,SPACE=(CYL,(1,1))
//SYSUT7   DD   UNIT=SYSDA,SPACE=(CYL,(1,1))
//SYSPRINT DD   SYSOUT=A
//SYSLIN   DD   DSNAME=userid.IBMMF.COPYLIB,UNIT=SYSDA,
//              DISP=(MOD,PASS),SPACE=(TRK,(3,3))
//SYSIN    DD   *               ---> The asterisk indicates that the input data set follows in the input stream.
000100 IDENTIFICATION DIVISION.
000200 PROGRAM ID. MYPROGRM
. . .
/*                              ---> The delimiter statement /* separates data from subsequent control statements in the input stream.

IGYCRCTL is an IBM COBOL compiler utility. The compiler options are passed using PARM parameter. In the above example, RMODE instructs the compiler to use relative addressing mode in the program. The COBOL program is passed using SYSIN parameter and the copybook is the library used by the program in SYSLIB.

This JCL produces the load module of the program as output which is used as the input to the execution JCL.


Running COBOL Programs:

Below JCL example where the simple COBOL program MYPROGRM is executed.

//JOBIBMKS  JOB (123),'IBMMAINFRAMER',CLASS=C,MSGCLASS=S,MSGLEVEL=(1,1),
//       NOTIFY=&SYSUID
//STEP001   EXEC PGM=MYPROGRM,PARM=TOT9999
//STEPLIB   DD DSN=userid.IBMMF.LOADLIB,DISP=SHR
//INPUT1    DD DSN=userid.IBMMF.INPUT,DISP=SHR
//SYSABEND  DD SYSOUT=*
//SYSOUT    DD SYSOUT=*
//SYSIN     DD *
KALAIA    1000
SRINIV    2000
/*

The load module of MYPROGRM is located in userid.IBMMF.LOADLIB. This is important to note that the above JCL can be used for a non-DB2 COBOL module only.

Passing Data to COBOL Programs:

Data input to COBOL batch program can be through files, PARAM parameter and SYSIN DD statement. In the above example:

  1. Data records are passed to MYPROGRM through file userid.IBMMF.INPUT. This file will be referred in the program using the DD name INPUT1. The file can be opened, read and closed in the program.

  2. The PARM parameter data TOT9999 is received in the LINKAGE section of the program MYPROGRM in a variable defined within that section.

  3. The data in the SYSIN statement is received through ACCEPT statement in the PROCEDURE division of the program. Every ACCEPT statement reads one whole record (i.e., KALAIA 1000) into a working storage variable defined in the program.


Running a COBOL-DB2 program

For running COBOL DB2 program, specialised IBM utility is used in the JCL and program. DB2 region and required parameters are passed as input to the utility.

The below steps are followed in running a COBOL-DB2 program:

When a COBOL-DB2 program is compiled, a DBRM (Database Request Module) is created along with the load module. The DBRM contains the SQL statements of the COBOL programs with its syntax checked to be correct.

The DBRM is bound to the DB2 region (environment) in which the COBOL will run. This can be done using the IKJEFT01 utility in a JCL.

After the bind step, the COBOL-DB2 program is run using IKJEFT01 (again) with the load library and DBRM library as the input to the JCL.

//JOBIBMKS  JOB (123),'IBMMAINFRAMER',CLASS=C,MSGCLASS=S,MSGLEVEL=(1,1),
//       NOTIFY=&SYSUID
//STEP001  EXEC PGM=IKJEFT01
//*
//STEPLIB  DD DSN=userid.IBMMF.DBRMLIB,DISP=SHR
//*
//input files
//output files
//SYSPRINT DD SYSOUT=*
//SYSABOUT DD SYSOUT=*
//SYSDBOUT DD SYSOUT=*
//SYSUDUMP DD SYSOUT=*
//DISPLAY  DD SYSOUT=*
//SYSOUT   DD SYSOUT=*
//SYSTSPRT DD SYSOUT=*
//SYSTSIN  DD *
    DSN SYSTEM(SSID)
    RUN PROGRAM(MYDB2PGM) PLAN(PLANNAME) PARM(parameters to cobol program) -
    LIB('userid.IBMMF.LOADLIB')
    END
/*

In the above example, MYDB2PGM is the COBOL-DB2 program run using IKJEFT01. Please note that the program name, DB2 Sub-System Id (SSID), DB2 Plan name are passed within the SYSTSIN DD statement. The DBRM library is specified in the STEPLIB.


If you have any doubts or queries related to this chapter, get them clarified from our Mainframe experts on ibmmainframer Community!

Are you looking for Job Change? Job Portal