You are on page 1of 41

***********************************************************************

* *
* ------------------ *
* JCL QUESTIONNAIRE *
* ------------------ *
* *
***********************************************************************

Q1. WHAT IS JCL


JOB CONTROL LANGUAGE:FOR A PGM TO BE EXECUTED ON THE COMPUTER
IT MUST BE PROCESSED BY THE OPERATING SYSTEM. OPERATING SYSTEM
CONSISTS OF A BASIC CONTROL PROGRAM(BCP) & THE JOB ENTRY SUBSYSTEM
(JES2 OR JES3) INSTALLED WITH BCP. A JOB MAY CONSISTS OF ONE OR
MORE TASKS. TASKS WITHIN A JOB ARE CALLED JOBSTEPS. THE TASKS OF A
JOB ARE INFORMED TO OS THRU JCL STATEMENTS. A JOB STEP IS IDENTIFIED
BY AN EXEC STATEMENT. A PROGRAM IS ENTERED INTO OS AS A JOB STEP.
*
Q2. WHAT IS JOB STATEMENT.
A JOB IS A COLLECTION OF RELATED JOB STEPS.IT IS IDENTIFIED BY
THE JOB STATEMENT. A JOB CAN HAVE MAXIMUM OF 255 JOB STEPS.
JOB STMT INDICATES THE BEGINNING OF A JOB & TO TELL THE SYSTEM HOW
TO PROCESS THE JOB. JOB STMT SPECIFIES ACCOUNTING INFORMATION,
PROGRAMMER,STORAGE REQUIRED,PRIORITY,JOBCLASS,CONDITIONAL TESTING
ETC. WHEN JOBS ARE STACKED IN THE INPUT STREAM THE JOB STMT MARKS
THE END OF THE PRECEEDING
*
Q3. WHAT IS EXEC STATEMENT.
EXECUTE STMT DEFINES A JOB STEP & JOB STEP RELATED INFORMATION
LIKE WHAT PROGRAM/PROCEDURE TO EXECUTE, JOB STEP ACCOUNTING INFO
STORAGE REQUIRED, CONDITIONAL EXECUTION OR TESTING,PARAMETERS TO
BE PASSED TO THE PROGRAM.IT MUST BE THE FIRST JCL STATEMENT IN
EACH STEP.
*
Q4. WHAT IS DD STATEMENT.
DATA DEFINITION STATEMENT(DD) :> DEFINES DATA RESOURCE REQUIREMENT
FOR THE JOB STEP TO EXECUTE. IT TELLS THE INITIATOR WHAT TO ALLOC
*
Q5. WHAT IS FORMAT OF JCL STMT.
JCL STMT CONSISTS OF 80 BYTE RECORDS
123456789012345678901234567890
//NAME $ OPERATION $ PARAMETER $ COMMENT
$ INDICATES ONE OR MORE SPACES. COLUMN 72 IS THE CONTINUATION
COLUMN.
NAME FIELD :> MUST BEGIN IN COLUMN 3.
1 THRU 8, ALPHANUMERIC & NATIONAL CHARS MUST BE ALLOWED BY
ATLEAST ONE BLANKS
OPERATION FIELD :> FOLLOW NAME FIELD
MUST BE PRECEDED & FOLLOWED BY ATLEAST ONE BLANK DESIGNATES TYPE
OF CONTROL STMT STANDARD SYNTAX
*
Q6. WHAT IS PARAMETER FIELD. TYPES?
PARAMETER FIELD:>
- CONTROLS PARAMETERS SEPARATED BY COMMAS
- FOLLOWS OPERATION FIELD
- MUST BE PRECEDED & FOLLOWED BY ATLEAST ONE BLANK
PARAMETERS ARE OF TWO TYPES
1.POSITIONAL PARAMETERS
2.KEYWORD PARAMETER
POSITIONAL PARAM:
- SEQUENCE PREDETERMINED
- MUST BE CODED FIRST IN PARAMETER LIST
- PARAMETERS SEPARATELY PASSED
- OMITTED PARAMETERS MUST BE INDICATED BY COMMAS UNLESS
- IT IS THE LAST POSITIONAL
- ALL FOLLOWING POSITIONALS ARE OMMITED
- ALL POSTIONALS ARE OMITTED
- INSTALLATION DEPENDANT
EG.
//NAME OPERATION PARM1, PARM2, PARM3
//JOBNAME JOB (STDC,TRG,TRG001),'RAJAN'
KEYWORD PARAMETERS:>
- PREDETERMINED WORDS ARE REFERRED TO AS KEYWORD PARAMS.
- ANY SEQUENCE IS PERMITTED SEPERATED BY COMMAS
- KEYWORDS ARE FOLLOWED BY = SIGN & A VALUE.
SUBPARAMETER LISTS OF POSITIONAL/KEYWORD PARAMETER FOLLOW THE RULE
-SUBPARAMETERS MAY CONTAIN BOTH KEYWORD & POSITIONAL SUBPARAMS
-ENCLOSE SUBPARAMS LISTS WITHIN PARENTHESES UNLESS IT EXISTS
AS SINGLE KEYWORD PARAM OR SINGLE POSITIONAL WITHIN ANY
OMITTED SUBPARAMS
EG.
//NAME OPERATION POS1, POS2, KEY1=A, KEY2=B
KEY3=C, KEY4=(P1,P2,K1=Q,K2=T)
*
Q7. WHAT ARE JOB STATEMENTS
INDICATES THE BEGINNING OF A JOB IT CONTAINS
JOBNAME,ACCOUNTING INFORMATION,PROGRAMMER NAME,CLASS,TYPRUN
MSGLEVEL,PRTY,NOTIFY
*
Q8. WHAT IS THE MEANING OF JOBNAME
JOBNAME IS USED FOR JOB IDENTIFICATION. CAN BE 1 TO 8 ALPHANUM
OR NATIONAL CHARS. JOBNAME MUST BE UNIQUE.IF MULTIPLE JOBS
WITH SAME NAME RUN TOGETHER & OPERATOR CANCELS ONE OF THEM,
RESULTING UNPREDICTABLE .BOTH JES2 & JES3 ALLOCATES A NO. WHEN
JOB ENTERS THE SYSTEM. THE JOB MAY BE CANCELLED USING THIS
NUMBER.
*
Q9. WHAT IS ACCOUNTING INFORMATION.
A MAX OF 142 CHARS CAN BE USED FOR CODING ACCOUNTING INFO
IF SPECIAL CHARS OTHER THAN COMMAREA IS USED .THE ENTIRE
ACCOUNTING INFO PARAMETER MUST BE ENCLOSED WITHIN PARENTHESIS.
EG.
'768,/A/B,20'
(768,A/B,20)
*
Q10. WHAT IS PROGRAMMER NAME.
MAX OF 20 CHAR ALLOWED. IF SPECIAL CHARACTERS CODED, ENCLOSE
NAME WITHIN APOSTROPHES SPECIAL CHAR(') IS CODED AS (' ')
EG.
//JOB1 JOB (STDC,TRG,3,,,ABCD),'O''NEIL'
//JOB2 JOB (STDC,TRG,3),ROGER
*
Q11. WHAT IS CLASS
PLACES YOUR JOB INTO A JES INPUT QUEUE CLASS. CLASS SPECIFIED IN
A-Z OR 0-9 ONLY. YOU CLASS SHOULD HAVE BEEN DEFINED TO JES AT
THE TIME OF JES INITIALIZATION.IF CLASS PARAMETER OMITTED IN
JOB STMT DEFAULT JES CLASS IS ASSIGNED
*
Q12.EXPLAIN TYPRUN & ITS TYPE
TYPRUN> MODIFIES THE WAY JES PROCESS YOUR JOB.
TYPRUN= SCAN
- JCL IS SCANNED FOR SYNTAX ERROR BUT NOT EXECUTED
TYPRUN= HOLD
- JCL IS HELD IN THE INPUT QUEUE. THE OPERATOR MUST RELEASE
THE JOB TO EXECUTE
TYPRUN= JCLHOLD
- JOB IS HELD IN THE INPUT QUEUE BEFORE PROCEDURE RESOLUTION
WHEN OPERATOR RELEASES THE JOB, ALL THE PROCEDURE LIBRARY
AVILABLE AT THAT TIME WILL BE USED TO RESOLVE PROCEDURES.
TYPRUN=COPY
THE JCL IS COPIED OR SUBMITTED TO THE SYSOUT CLASS SPECIFIED
IN THE MSGCLASS PARAMETER. NO EXECUTION OR SYNTAX CHECKING
TAKES PLACE. THIS IS RARELY USED.
*
Q13.EXPLAIN MSGLEVEL.
MSGLEVEL> CONTROLS WHICH STMT TO BE PRINTED FROM THE JOBLOG SPOOLED IN THE
OUTPUT CLASS SPECIFIED BY MSGCLASS PARAMETER
IT CONSISTS OF TWO POSITIONAL PARAMETRS
MSGLEVEL=(X,Y) WHERE X CONTROLS THE JCL STAMT & THE MESSAGES IN
THE JOBLOG.
TYPES OF MESSAGES CONTROLLED ARE -
JCL MESSAGES
JES MESSAGES
OPERATOR MESSAGES
1. JCL MESSAGE
2. JES MESSAGE> SYSIN/SYSOUT SELECTED
3. OPERATOR MESSAGES> ALL MESSAGES FROM & TO THE OPERATOR REGARD
ING YOUR JOB PLUS ALLOCATION & TERMINATION MESSAGES OF RESOURCES
MSGLEVEL=(X,Y)
X=0 - PRINT ONLY JOB STMT.
X=1 - PRINT ALL JCL INCLUDING PROCEDURE STMT PLUSJES MESSAGES
X=2 - PRINTS ONLY SUBMITTED JCL & JES STMTS.
Y=0 PRINTS ONLY JCL MESSAGES ON NORMAL TERMINATION PRINT ALL
MESSAGES IN CASE OF ABNORMAL TERMINATION.
Y=1 ALL MESSGES ARE PRINTED REGARDLESS OF HOW THE JOB TERMINATES
DEFAULT-AS SPECIFIED BY THE INSTALLATION AT JES INITIALIZATION
TIME.
*
Q14.WHAT IS PRTY & DPRTY
PRTY> THIS IS USED BY JES FOR QUEUING THE JOB IN THE INPUT QUEUE
FOR JES2 MAXIMUM PRTY IS 15 & JES3 IT IS 14.
*
Q15.EXPLAIN EXEC STATEMENT
THIS DEFINES THE BEGINNING OF A STEP IN A JOB.STEPNAME IS OPTIONAL
FORMAT
//STEPNAME EXEC POSITIONAL,KEYWORDS
//STEP1 EXEC PGM=IEFBR14,PARM=88210,ACCT=(378,28,20)
PGM PARAMETER IS POSITIONAL EVEN THOUGH IT IS CODED IN KEYWORD
FORMAT.BY DEFAULT SYS1.LINKLIB IS SEARCHED FOR THE PROGRAM.IF
THE PROGRAM IS NOT FOUND,THE STEP IS ABNORMALLY TERMINATED.
*
Q16.WHAT IS PARM STMT
THIS PARAMETER PASSES INFORMATION TO THE EXECUTING PGM THE
INFORMATION WITHIN PARANTHESES OR APHOSTROPHES IS PASSED IN
UNPACKED EBCDIC FORMAT. A MAXIMUM OF 100 CHARACTERS CAN BE PASSED
*
Q17.WHAT IS COND PARAMETER
THIS PARAMETER IS USED TO CONTROL JOBSTEP EXECUTION
AFTER EXECUTION OF EACH STEP SYSTRERM RETURNS A RETURN CODE
THE COND PARAMETER OFFERS A METHOD OF TESTING THE RETURN CODES
ISSUED BY THE PREVIOUS STEPS TO DETERMINE WHETHER A STEP IS TO
BE EXECUTED
THE FORMAT OF COND = (VALUES,OPERATOR)
WHERE VALUE IS NUMBER BETWEEN 0 & 4095
OPERATOR CAN BE THE FOLLOWING
GT - GREATER THAN
GE - GREATER THAN OR EQUAL TO
EQ - EQUAL TO
NE - NOT EQUAL TO
LT - LESS THAN
LE - LESS THAN EQUAL TO
COND PARAMETR CAUSES THE VALUE YOU ENTER TO BE TESTED AGAINST
THE RETURN CODES FROM THE PREVIOUS STEPS USING THE OPERATOR
IF THE TEST CONDITION IS TRUE, THE STEP IS SKIPPED IF NOT THE
STEP IS EXECUTED
ABNORMAL TERMINATION - EVEN & ONLY
COND = EVEN/ONLY
EVEN CAUSES A STEP TO BE EXECUTED EVEN IF A PREVIOUS STEP ABENDS
ONLY CAUSES A STEP TO BE EXECUTED ONLY IF A PREVIOUS STEPS ABENDS
YOU SHOULD NOT CODE BOTH EVEN & ONLY IN THE SAME COND PARAMETER
EG.
//TRG01 JOB
//STEP1 EXEC PGM=UPDATE
..............
//STEP2 EXEC PGM=BACKOUT,COND=ONLY
..............
//STEP3 EXEC PGM=LIST,COND=EVEN
..............
//
*
Q18.EXPLAIN DD STATEMENT
THE DD (DATA DEFINITION ) STMT IS USED TO DESCRIBE THE DATASET
& TO SPECIFY THE INPUT & OUTPUT RESOURCES NEEDED FOR THE DATASET
PROGRAMS DO NOT REFER DATASETS.DD STMT REFERS TO THE DATASETS
THUS PROGRAMS CAN BE DEVICE INDEPENDENT.THE NAME OF THE DATASET
IS CODED IN THE PROGRAM. WHEN THE DATASET IS OPENED FOR PROCESSING
THE NAME IS USED TO LOCATE THE PROPER DD STMT SO AS TO IDENTIFY
THE ACTUAL DATASET
EG.
COBOL- SELECT <FILENAME> ASSIGN TO DA-3390-XYZ
JCL- //XYZ DD=...
*
Q19.DEFINE DDNAME
DDNAME FOLLOWS THE NAME RULES AS JOBNAME & STEPNAME.DDNAME SHOULD
BE UNIQUE WITHIN THE JOB STEP. IF DUPLICATE DDNAME APPEAR IN A
JOBSTEP(IN A JES2 SYSTEM) THE SYSTEM PERFORMS DEVICE & SPACE
ALLOCATION & DISPOSITION PROCESSING FOR BOTH THE DD STMT
HOWEVER IT DIRECTS ALL REFERENCES TO THE FIRST DD STMT IN THE STEP
AVOID DDNAMES STARTING WITH SYS JOB STEP
DDNAMES USED BY SYSTEMS ARE
SYSPRINT,SYSIN,SYSLMOD,SYSLIN,SYSUT1,SYSUT2,SYSDUMP,SYSMDUMP
SYSABEND,SYSCHK,SYSCHEV,JOBLIB,STEPLIB,JOBCAT,STEPCAT
//DDNAME DD POSITIONAL,KEYWORDS
//XYZ DD UNIT=...,VOL=...,DSN=...,DISP=...,
SPACE=...
*
Q20.DEFINE DSNAME
DSNAME PARAMETER IS USED TO SPECIFY THE NAME OF THE DATASET
A MAXIMUM OF 44 CHARACTERS CAN BE CODED FOR THE DATASET NAME
OFTEN HIGHTEST LEVEL QUALIFIER IS USED FOR CATALOG SEARCHING
RACF PROTECTION ETC.,
DSN=MASTER.PAY22.INPUT
*
Q21.WHAT IS DISP. ITS FIELDS
DISP PARAMETER IS USED TO DESCRIBE THE STATUS OF A DATASET
TO THE SYSTEM & TELL THE SYSTEM WHAT TO DO WITH THE DATASET
AFTER TERMINATION OF THE NORMAL TERMINATION & ANOTHER FOR THE
ABNORMAL TERMINAL
SYNTAX:
DISP=STATUS
DISP=(STATUS) (,NORMAL.TERMINATION-DISP)
(,ABNORMAL-TERMINATION-DISP)
DISP=(NEW,DELETE,DELETE)
(OLD,KEEP,KEEP)
(SHR,PASS,CATLG)
(MOD,CATLG,UNCATLG)
( ,UNCATLG,)
(, )
STATUS SUBPARAMETER
NEW - INDICATES THAT A NEW DATASET IS TO BE CREATED IN THIS STEP
OLD- INDICATES THAT THE DATASET EXISTS BEFORE THIS STEP & THAT
THIS STEP REQUIRES EXCLUSIVE(UNSHARED) USE OF THE DATASET
SHR-INDICATES THAT THE DATASET EXISTS BEFORE THIS STEP &
THAT OTHER JOBS CAN SHARE IT. IE USE IT AT THE SAME TIME
MOD-INDICATES ONE OF THE FOLLOWING
THE DATASET EXISTS RECORDS ARE TO BE ADDED TO THE END OF
THE DATASET. THE DATASET MUST BE SEQUENTIAL
' '- A NEW DATASET IS TO BE CREATED
TERMINATION DISPOSITION SUBPARAMETER
DELETE INDICATES THAT THE DATASET IS TO BE DELETED AT THE END OF
THE JOBSTEP
KEEP- INDICATE STHAT THE DATASET IS TO BE KEPT ON THE VOLUME
PASS- INDICATES THAT DATASET IS TO PASSED FOR THE USE BY A
SUBSEQUENT STEP IN THE SAME JOB
CATLG- INDICATES THAT THE DATASET IS TO BE KEPT & AN ENTRY IS
MADE IN THE CATALOG AT THE END OF THE STEP
UNCATLG-INDICATES THAT THE ENTRY IN THE CATALOG FOR THIS DATASET
IS TO BE DELETED
DEFAULT- DISP=(NEW,DEELTE,DELETE)
IF YOU OMIT THE STATUS SUBPARAMETER, THE DEFAULT IS NEW.IF YOU
OMIT THE NORMAL TERMINATION DISPOSTION SUBPARAMETER THE DEFAULT
IS DELETE FOR A NEW DATASET & KEEP FOR AN EXISTING DATASET
IF YOU OMIT THE ABNORMAL TERMINATION DISPOSITION SUBPARAMETER
THE DEFAULT IS THE DISPOSITION SPECIFIED OR IMPLIED BY THE II
SUBPARAMETER.HOWEVER IF THE II PARAMETER IS PASS THE DEFAULT
ABNORMAL TERMINATION SUBPARAMETER IS DELETE FOR A NEW DATASET &
KEEP FOR AN EXISTING ONE.
*
Q22.WHAT IS UNIT PARAMETER IN JCL
UNIT IDENTIFIES
- THE DEVICE TYPE OR DEVICE ADDRESS WHERE THE VOLUME IS MOUNTED
- THE NUMBER OF DEVICES TO BE ALLOCATED TO THE DATASET WHEN THE
MOUNT MESSAGE IS TO BE SHOWN TO THE OPERATOR
SYNTAX - UNIT =(DEVICENO)(,UNIT-COUNT)(,DEFER)
UNIT=(DEVICE-TYPE)(,P )
UNIT=(DEVICE-TYPE)(,P )
OR
UNIT=AFF=DDNAME
DEVICE NO: IDENTIFIES A PARTICULAR DEVICE
DEVICE-TYPE> IDENTIFIES A DEVICE BY ITS GENERIC NAME.
GROUP-NAME> REQUEST A GROUP OF DEVICES BY A SYMBOLIC NAME
UNIT-COUNT>SPECIFIES A NO OF DEVICES FOR THE DATASET
P> SPECIFIES PARALLEL MOUNTING
DEFER>ASKS THE SYSTEM TO ASSIGN THE DATASET TO DEVICES BUT REQUEST
THAT THE VOLUMES NOT TO BE MOUNTED UNTIL THE DATASET IS OPENED
AFF>REQUESTS THE SYSTEM ALLOCATES DIFFERENT DATASETS RESIDING ON
DIFFERENT REMOVABLE VOLUMES OF THE SAME DEVICE DURING EXECUTION
OF A STEP .THIS REQUEST IS CALLED UNIT AFFINITY
EG. UNIT=SYSDA INDICATES ALL DASD DEVICES
UNIT=3390
*
Q23.WHAT IS VOLUME
VOLUME PARAMETER IS USED TO IDENTIFY THE VOLUMES ON WHICH A DATASET
RESIDES OR RESIDE
SYNTAX:
VOLUME=((PRIVATE)(,RETAIN)(,VOL-SEQ-NO)(,VOL-COUNT)(SER=SER-NO))
VOLUME=REF=REFERENCE
PRIVATE>INDICATES THAT NO OTHER DATASET IS TO BE ALLOCATED THIS
VOLUME UNLESS A SPECIFIC VOLUME REQUEST IS MADE.EVEN NON SPECIFIC
VOLUME REQUESTS FROM THE SYSTEM ARE NOT PERMITTED
RETAIN>USED ONLY FOR TAPE VOLUMES .SPECIFIES THAT THE VOLUMES
SHOULD NOT BE DEMOUNTED AT THE END FO JOB STEP. AVOIDS THE TROUBLE
OF DEMOUNTING & MOUNTING VOLUMES WHICH ARE REFERRED IN SUBSEQUENT
STEPS
VOL-SEQ-NO>PROVIDES WHICH VOLUME OF A MULTIVOLUME DATASET IS TO
BE MOUNTED
EG.
//INPUT DD DSN=NAMEFILE, DISP=OLD,VOL=(,,3)
//OUTPUT DD DSN=NEWFILE, DISP=(NEW,CATLG),UNIT=(TAPE,1),
VOLUME=(,,,5,SER=(T1,T2))
//OUTPUT DD DSN=NEWFILE, DISP=(NEW,CATLG),UNIT=(TAPE,2),
VOLUME=SER=(T1,T2,T3)
*
Q24.EXPLAIN SPACE PARAMETER
SPACE PARAMETER IS USED TO REQUEST SPACE FOR A NEW DATASET ON A
DIRECT ACCESS VOLUME
SYNTAX:
SPACE=(TRK/CYL/BLK-LENGTH,(PRIMARY-QTY(,SEC-QTY)(DIR-BLOCKS))
(,RISE)(,CONTIG/NIXG/AIX)(,ROUND))
THE SYSTEM FIRST ALLOCATES THE PRIMARY QTY ROUNDED TO TRACKS
SECONDARY ALLOCATION TAKES PLACE WHENEVER THE SPACE ALLOCATED
BY THE PRIMARY BECOMES INSUFFICIENT.A TOTAL OF 16 EXTENTS WILL
BE ALLOCATED FOR A NON-VSAM DATASETS WHICH INCLUDED ONE PRIMARY
QTY & 16 SECONDARY ALLOCATION QTY. FOR MULTIVOLUME DATASETS,THE
PRIMARY QTY MUST SATISFY THE FIRST VOLUME .THE SECONDARY REQUEST
MAY BE SATISFIED ON THE I VOLUME OR SUBSEQUENT VOLUMES.
RLSE> TO RELEASE THE UNUSED SPACE
CONTIG>TO ALLOCATE CONTIGOUS SPACE.IT AFFECTS ONLY PRIMARY
ALLOCATION
MIXG>REQUESTS THAT SPACE ALLOCATED TO THE DATASET MUST BE THE
LARGEST AREA OF AVAILABLE CONTIGOUS SPACE ON THE VOLUME & EQUAL
TO OR GREATER THAN THE PRIMARY QUANTITY- THIS SUBPARAMETER AFFECTS
ONLY PRIMARY ALLOCATION.
ALX>REQUESTS THAT UPTO 5 SEPERATE AREAS OF CONTIGOUS SPACE ARE
TO BE ALLOCATED TO THE DATASET & EACH MUST BE EQUAL TO OR GREATER
THAN THE PRIMARY QUANTITY IT AFFECTS ONLY PRIMARY ALLOCATION
ROUND>USED TO ALLOCATE SPACE IN CYLINDERS WHEN SPACE IS REQUESTED
IN BLOCKS.TOTAL BLOCK SIZE IS ROUNDED TO THE NEAREST CYLINDER
EG. SPACE=(TRK,(5,3,10))
SPACE=(CYL,(5,1),RLSE)
SPACE=(800,(500)
*
Q25.WHAT IS DATA CONTROL BLOCK(DCB)
DESCRIBES THE CHARACTERISTICS IN WHICH RECORDS ARE WRITTEN INTO
THE FILE. IT HAS SEVERAL KEYWORD PARAMETERS
RECFM
LRECL
LABEL
BLKSIZE
*
Q26.WHAT ARE RECORD FORMAT (RECFM) SUB PARAMETERS
RECFM=FD - FIXED BLOCKED
RECFM=F - FIXED LENGTH UNBLOCKED
RECFM=VB - VARIABLE LENGTH BLOCKED
RECFM=V - VARIABLE LENGTH UNBLOCKED
RECFM=VBS- VARIABLE LENGTH SPANNED
RECFM=U - UNDEFINED
ADDING 'A' TO THESE RECORD FORMATS(AS IN FBA) INDICATES THAT THE
I BYTES OF THE RECORD CONTAINS A CHARACTER USED TO CONTROL PRINTER
SPACING OR TO SELECT A STACKER FOR A CARD PUNCH
WHEN FIXED LENGTH RECORDS ARE BLOCKED ,BLOCK SIZE MUST BE A
MULTIPLE OF LOGICAL RECORD LENGTH.FOR UNDEFINED FORMAT ONLY BLOCK
SIZE IS REQUIRED. HERE EACH TRACK IS TREATED AS A RECORD & EACH
MAY HAVE VARIABLE SIZE
FOR VARIABLE RECORD LENGTH LRECL CAN BE EQUAL TO A MAXIMUMLENGTH
OF THE RECORD PLUS FOUR BYTES(RECORD DESCRIPTOR WORD) TO SPECIFY
ITS ACTUAL LENGTH
IN CASE OF SPANNED RECORDS RECORD LENGTH CAN BE LARGER THAN THE
BLOCK SIZE.RECORD IS SEGMENTED APPROPRIATELY & THE FIRST SEGMENT
IS PLACED IN THE I BLOCK & II IN THE NEXT BLOCK & SO ON.HERE WE
USE A SEGMENT DESCRIPTOR WORD (SDW) TO DESCRIBE THE SIZE OF THE
SEGMENT TO INDICATE WHETHER THE SEGMENT IS THE I INTERMEDIATE ,
THE LAST OR COMPLETE
*
Q27.WHAT IS LOGICAL RECORD LENGTH
(RECL = LOGICAL RECORD LENGTH IN BYTES
FORMAT LRECL = LENGTH
BLKSIZE - BLOCKSIZE IN BYTES
FORMAT - BLKSIZE = LENGTH
EG.
DCB=(RECFM=FB,LRECL=80,BLKSIZE=8000) OR
RECFM=FB,LRECL=80,BLKSIZE=8000
*
Q28.WHAT IS LABEL PARAM
THIS PARAM CAN SPECIFY THE SEQUENCE OF A TAPEDATA SET ON A VOLUME
THE TYPE OF A LABEL OF THE DATASET,EXPIRATION DATE OF THE DATASET
IT CAN ALSO PROVIDE PASSWORD PROTECTION
SYNTAX>
LABEL=((SEQNO),(,LABELTYPE)(,PASSWORD]]NO PASSWORD)(,IN]OUT)
(,RETPW=NNN]EXPDT=YYDDD))
SEQNO- IDENTIFIES THE RELATIVE POSITION OF THE DATASET ON A TAPE
VOLUME
LABELTYPE- SPECIFIES THE KIND OF LABELS THE DATASET HAS
DASD DATASETS EITHER SHOULD HAVE SL (IBM STANDARD LABELS) OR
SVL(IBM STANDARD & USER LABELS)
DEFAULT =SL
EG. LABEL=(5,,PASSWORD,RETPW=90)
LABEL=EXPDT=90365
*
Q29.WHAT IS FREE PARAMETER
USED TO SPECIFY WHEN THE SYTEM IS TO DEALLOCATE THE RESOURCES
USED FOR THIS DD STATEMENTS DATASET.BY DEFAULT THE DATASET IS
DEALLOCATED BY THE END OF JOB STEP. THSI CAN BE SPECIFICALLY ASKED
FOR CODING FREE=END. YOU MAY ALSO DEALLOCATE WHEN THE DATASET CLOSE
FREE=CLOSE
*
Q30.WHAT IS SYSOUT
USE SYSOUT TO IDENTIFY THIS DATASET AS A SYSTEM OUTPUT DATASET &
ASSIGNS THSI DATASET TO AN OUTPUT CLASS
SYNTAX:
SYSOUT=(CLASS(,PROGRAMNAME)(,FORMNAME))
CLASS- IDENTIFIES THE OUTPUT FOR THE DATASET.CLASS IS ONE CHAR
A-Z 0-9
USUALLY CLASS STANDS FOR PRINTER &
B FOR PUNCH
* INDICATES THAT THE OUTPUT IS DIRECTED TO THEOUTPUT CLASS YOU
SPECIFIED IN THE MSG-CLASS BY THE JOB STMT
PROGRAM NAME- IF YOU WANT THE OUTPUT DATASET WRITTEN BY A PROGRAM
IN THE SYSTEM RATHER THAN JES, YOU CAN SPECIFY THE NAME OF THE
PROGRAM HERE IT IS RARELY USED.
FORM-NAME- IDENTIFIES THE PRITN OR PUNCH FORMS
EG. //REPEAT DD SYSOUT=(C,2)
*
Q31.WHAT IS COPIES PARAMETER
COPIES USED WHEN MULTIPLE COPIES OF A SYSOUT DATASET ARE REQUIRED
SYNTAX:
COPIES=((NUMBER)(,NUM-PER-PAGE))
NUMBER- SPECIFIES THE NUMBER OF COPIES OF DATASET TO THE PRINTED
MAXIMUM OF 255 COPIES CAN BE REQUESTED
*
Q32.WHEN IS DEST PARAMETER USED
TO ROUTE A SYSOUT DATASET TO A REMOTE OR LOCAL DESTINATION IF IT
IS OMITTED THE SYSOUT DATASET WILL BE ROUTED TO THE DEFAULT
DESTINATION OF THE DEVICE USED TO SUBMIT THE JOB
EG.
//ABC DD SYSOUT=A
//XYZ DD SYSOUT=A, DEST=RMT
*
Q33.WHAT IS HOLD ? OUTLIM?OUTPUT?
HOLD IS USED TO HOLD THE DATASET BEING PRINTED UNTIL IT IS
RELEASED BY THE OPERATOR
SYNTAX:
HOLD=(YES/NO)
YES-INDICATES THAT THE SYSOUT DATASET IS TO BE HELD
NO- INDICATES THAT THE SYSOUT DATASET IS TO BE PROCESSED NORMALLY
(DEFAULT)
OUTLIM- USED TO LIMIT NUMBER OF RECORDS (PRINTLINE) OF SYSOUT
DATASET
SYNTAX:
OUTLIM=NUMBER
NUMBER- SPECIFIES THE NUMBER OF LINES THE SYSOUT DATASET IS PERMITT
ED TO OUTPUT FROM 1 TO 1677215
OUTPUT - SPECIFIES THAT THE DATASET IS TO BE PRINTED USING THE
OPTIONS CODED IN AN EARLIER OUTPUT STATEMENT .THIS PARAMETER CAN
REFERENCE A MAXIMUM OF 128 OUTPUT STATEMENTS
SYNTAX:
OUTPUT=(REFERENCE(,REFERENCE),)
//EX1 DD SYSOUT=A,OUTPUT=*.OUT1
*
Q34.WHAT ARE TEMPORARY DATASETS
A TEMPORARY DATASET IS CREATED & DELETED WITHIN A JOB.WHEN DEFINING
A TEMPORARY DATASET,YOU CAN CODE THE DSNAME PARAMETER OR OMIT IT
IF CODED THE NAME CONSISTS OF TWO AMPERSANDS(&&) FOLLOWED BY AN
UNQUALIFIED DATASET NAME. ALSO THE UNIT MUST BE VIRTUAL INPUT/OUTPU
T (VIO) SPECIFIED BY THE INSTALLATION.IF OMITTED THE SYSTEM
GENERATES A NAME FOR THE DATASET DSN=NULLFILE SPECIFIES A DUMMY
DATASET.IT HAS THE SAME EFFECT AS CODING THE
DD DUMMY PARAMETER
*
Q35.WHAT IS DLM PARAMETER
USED TO SPECIFY A DELIMITER TO TERMINATE AN INSTREAM DATA.WHEN THE
DLM PARAM ASSIGNS A DIFFERNT DELIMITER, THE INSTREAM DATA CAN
INCLUDE STANDARD DELIMITER SUCH AS /* & // IN THE DATA. THE DELIM
DATA MUST BE CODED IN COLUMN 1 & 2
*
Q36.WHAT IS JOBLIB?HOW IT USED?
THE JOBLIB DD STATEMENT IDENTIFIES A PRIVATE LIBRARY THAT THE
SYSTEM IS TO SEARCH FOR THE PROGRAM NAMED IN EACH EXEC STMT
PGM PARAM IN THE JOB.IF THE SYSTEM DOES NOT FIND THE PROGRAM
IN PRIVATE LIBRARY ONLY THEN THE SYSTEM SEARCHES THE SYSTEM LIBRARY
THE JOBLIB STMT MUST IMMEDIATELY FOLLOW THE JOB STMT SEVERAL LIB
MAY BE CONCATENATED IN THE JOBLIB
SYNTAX:
//JOBLIB DD PARAMETER(,PARAMETER)....COMMENTS
BY DEFAULT ALL PROGRAMS ARE SEARCHED & TAKEN FROM SYS1.LINKLIB
EG.
//JOB11 JOB....
//JOBLIB DD DSN=MYLIB,DISP=SHR
//STEP1 EXEC PGM=MYPGM1
..........
.........
//STEP2 EXEC PGM=XYZ
..........
.........
//STEP3 EXEC PGM=IEBGENER
//
*
Q37.WHAT IS STEPLIB? EXPLAIN
THE STEPLIB DD STATEMENT IDENTIFIES A PRIVATE LIBRARY AT THE STEP
LEVEL THAT THE SYSTEM IS TO SEARCH FOR THE PROGRAM NAMED IN THE
EXEC STATEMENT.PGM PARAMETER .IF THE SYSTEM DOES NOT RESPOND
THE PROGRAM IN THE PRIVATE LIBRARY ,ONLY THEN THE SYSTEM SEARCH
THE SYSTEM LIBRARY
THE JOBLIB STATEMENT CAN BE PLACED ANYWHERE WITHIN THE JOBSTEP
SEVERAL LIBRARIES MAY BE CONCATENATED IN THE STEPLIB STATEMENT
SYNTAX:
//STEPLIB DD PARAMETER (,PARAM,)...
//JOB11 JOB...
//STEP0 EXEC PGM=ABC
//STEPLIB DD DSN=MYLIB,DISP=SHR
...........
...........
//STEP1 EXEC PGM=MYPGM1
//STEPLIB DD DSN=MY.LIB1,DISP=SHR,
// DD DSN=MY.LIB2,DISP=SHR,
// DD DSN=MY.LIB3,DISP=SHR,
...........
...........
//STEP3 EXEC PGM=IEBGENER
*
Q38.WHAT ARE PROCEDURES.
A PROCEDURE IS A PREPACKAGED JCL ITS AN ADDITION OF JCL STATEMENTS
THAT APPEAR BETWEEN A PROC & PEND STATEMENTS
THERE ARE TWO TYPES OF PROCEDURES NAMELY
INSTREAM PROCEDURE &
CATALOGUED PROCEDURES
IN LISTING OF JCL THE PROCEDURE STMT THAT YOU DID NOT OVERRIDE ARE
IDENTIFIED BY ++ IN COLUMNS 1 & 2 .STMT OVERRIDEN ARE INDICATED
BY +/ IN COLUMN 1 & 2.COMMENT STMT ARE INDICATED AS *** IN
1-3 COLUMN .INVOKING A PROCEDURE
//STEPNAME EXEC PROCNAME OR
//STEPNAME EXEC PROC=PROCNAME
*
Q39.WHAT ARE INSTREAM PROCEDURES.
INSTREAM PROCEDURE IS CONTAINED WITHIN A JOBS INPUT STREAM ITS
AVAILABLE ONLY TO A PARTICULAR JOB.BUT WITHIN THE JOB AN INSTREAM
PROCEDURE CAN BE USED MANY TIMES.THE INSTREAM PROCEDURE CAN BE
PLACED ANYWHERE WITHIN THE JOB,BUT BEFORE THE STEP WHERE IT IS
CALLED UPTO 15 PROCEDURES CAN BE DEFINED IN ONE JOB. THE PROC
STMT INDICATES THE BEGINNING & THE PEND STMT THE END OF THE
INSTREAM PROCEDURE.
FORMAT:
//NAME PROC (PARAM)(,PARM)...
BODY OF THE PROCEDURE
//(NAME) PEND (COMMENTS)
*
Q40.WHAT ARE CATALOGUED PROCEDURES.
A CATALOGUED PROCEDURE IS A MENBER OF A PDS,WHICH IS AFTEN
REFERRED TO AS A PROCEDURE LIBRARY .THE DEFAULT PROCEDURE
LIBRARY IS THE SYS1.PROCLIB.IF YOUR CATALOGUED PROCEDURE IS IN
OTHER LIBRARY YOU HAVE TO GIVE A JCLLIB STMT IN YOUR JOB
PROC STMT INDICATES THE BEGINNING OF THE CATALOGUED PROCEDURE
PEND STATEMENT IS OPTIONAL.
FORMAT :
//NAME PROC (PARAM)(,PARM)...
BODY OF PROCEDURE
//NAME PEND
FORMAT OF JCLLIB
//NAME JCLLIB ORDER=(LIBRARY(,LIBRARY)...)
*
Q41.GIVE ONE EXAMPLE FOR INSTREAM & CATALOGUED PROCEDURE EACH
INSTREAM PROCEDURE-
//GOPAL21 JOB 'J GOPAL'
//CREATE PROC
//STEPA EXEC PGM=IEFBR14
//DDA DD DSN=GOPAL.JCL.MYDS,DISP=(NEW,CATLG),
UNIT=3390,VOL=SER=WORK01,SPACE=(TRK,(1,1,10)),
DCB=(RECFM=FB,LRECL=80,BLKSIZE=8000)
// PEND
//STEPX EXEC CREATE
EG OF CATALOGUED PROCEDURE
//VSUBRAA JOB NOTIFY=VSUBRA
//STEP0 EXEC COB2UCLG
IN THE ABOVE EG, ITS ASSUMED THAT COB2UCLG IS A PROCEDURE AVAILABLE
IN SYS1.PROCLIB
NOW LETS SEE HOW TO INVOKE A PROCEDURE ,NAMELY CREATE,AVAILABLE IN
A PRIVATE PROCEDURE LIBRARY (GOPAL.PROCLIB.CNTL)
//GOPALAA JOB NOTIFY=GOPAL
//JJ JCLLIB ORDER=GOPAL.PROCLIB.CNTL
//STEP0 EXEC CREATE
*
Q42.WHAT IS OVERRIDING PROCEDURES.
IF THE JCL IN THE PROCEDURE IS EXACTLY MATCHING THE USER NEEDS THEN
ONLY THE EXEC STMT IS REQUIRED.OFTEN HOWEVER THE JCL IN THE PROC
MAY NOT COMPLETELY SATISFYTHE USER NEEDS & SOME CHANGES ARE
REQUIRED.THE NON DESTRUCTIVE CHANGES ARE KNOWN AS OVERRIDES
OVERRIDING DOES NOT ALTER PERMANENTLY OR TEMPORARILY, THE CONTENTS
OF A PROCEDURE .AS THE SYSTEM READS THE PROCEDURE IT CHANGES SOME
OF ITS PARAMETERS BASED ON THE USER SUPPLIED OVERRIDES BUT NEVER
WRITES THE CHANGED PROCEDURE BACK
OVERRIDE CAN ADD,REPLACE OR NULLIFY ANY EXEC STMT PARAMETER
EXCEPT PGM
ADD,REPLACE OR NULLIFY ANY DD STAMT PARAMETER.ADD AN ENTIRE DD STMT
TO OVERRIDE A PARAMETER IN THE EXEC STMT YOU HAVE TO CODE
'PARAMETER.STEPNAME=VALUE' IN THE EXEC STMT THAT INVOKE THE PROCS
& TO NULLIFY PARAMETER 'PARAMETER.STEPNAME='. ALL OVERRIDES TO
EXEC PARAMS FOR A STEP MUST BE COMPLETED BEFORE OVERRIDING PARAMS
IN SUBSEQUENT STEPS
*
Q43.WHAT ARE SYMBOLIC PARAMETERS IN PROCEDURES
SYMBOLIC PARAMETERS ARE USED IN PROCEDURES FOR VALUES WHICH ARE
LIKELY TO CHANGE FREQUENTLY SYMBOLIC PARAM NAME CONSISTS OF
1-7 ALPHANUMERIC OR NATIONAL CHARACTERS PRECEDED BY & SYMBOL.THE
I CHARS MUST BE ALPHABETIC OR NATIONAL.EXEC STMT KEYWORD PARAMS
CAN NOT BE USED AS NAME OF A SYMBOLIC VARIABLE .THIS RESTRICTION
DOES NOT EXTEND TO KEYWORD PARAMS OF DD STATEMENT
EG.
//CREATE2 PROC
//LIBMAKE EXEC=IEFBR14
//LIBDD DD DSN=&DSN,DISP=(,CATLG)
// UNIT=3390,VOL=SER=&PACK,
// SPACE=(TRK(&TRKS,&DIRBLKS)),
// DCB=(RECFM=FB,LRECL=80,BLKSIZE=8000)
// PEND
TO EXECUTE CREATE2 PROCEDURE
//GOPAL21 JOB NOTIFY=GOPAL,CLASS=A,MSGLEVEL=(1,1)
//STEPA EXEC CREATE2,DSN='GOPAL.PASS.MYDS',
// PACK=WORK01,TRACKS=5,DIRBLK=10
//
NOTE THAT DSN CONTAINING SPECIAL CHARS ARE ENCLOSED IN APOSTRPHES
WHENEVER PARAMETERS IS CHANGED BY THE VALUE GIVEN IN THE PROCEDURE
CALL, SYSTEM CONVEYS IT THRU A MESSAGE 'SUBSTITUTION JCL'
*
Q44.HOW TO ALLOCATE A DATASET? WHICH UTILITY IS USED
TO ALLOCATE A DATASET IEFBR14 IS A DUMMY UTILITY WHICH JUST RETURNS
THE CONTROL TO THE OPERATING SYSTEM & NOTHING ELSE
//GOPALA JOB NOTIFY=GOPAL,CLASS=A,MSGLEVEL=(1,1)
//STEP0 EXEC PGM=IEFBR14
//ALLOC DD DSN=GOPAL.TEST.DATA,DISP=(,CATLG),UNIT=3390,
// VOL=SER=WORK01,SPACE=(TRK,(1,1,5)),
// DCB=(RECFM=FB,LRECL=80,BLKSIZE=8000)
*
Q45.HOW TO COPY A DATASET? WHAT UTILITY IS USED
TO COPY A DATASET YOU CAN USE THE UTILITY IEBGENER FOR THE SAME
BY DEFAULT SYSUT1 IS THE INPUT & SYSUT2 IS THE OUTPUT DDNAMES.IF
YOU ARE USING ANY OTHER DDNAMES,USE THE CORRESPONDING UTILITY CONTR
OL STATEMENT IS REQUIRED FOR MESSAGES
//GOPALA JOB NOTIFY=GOPAL,CLASS=A,MSGLEVEL=(1,1)
//STEP0 EXEC PGM=IEBGENER
//SYSUT1 DD DSN=GOPAL.INPUT.DATA,DISP=SHR
//SYSUT2 DD DSN=GOPAL.OUTPUT.DATA,DISP=(,CATLG)
// UNIT=3390,VOL=SER=WORK01,
// SPACE=(TRK,(1,1)),
// DCB=(RECFM=FB,LRECL=80,BLKSIZE=8000)
//SYSPRINT DD SYSOUT=*
//SYSIN DD DUMMY
*
Q46.HOW TO INVOKE TSO COMMAND VIA JCL
TO INVOKE TSO COMMANDS VIA JCL
//GOPAL JOB NOTIFY=GOPAL,CLASS=A,MSGLEVEL=(1,1)
//STEP0 EXEC PGM=IEFBR14
//COMMAND 'SEND' 'HELLO' ',USER=(EDM125)'
*
Q47.HOW TO EXECUTE A PROGRAM IN YOUR OWN DATASET
TO EXECUTE A PROGRAM IN YOUR OWN DATASET,THE EXECUTABLE
MODULE MYPROG IS RESIDING IN 'GOPAL.PROG.LOAD
IT IS ASSUMED THAT MYPROG IS JUST DISPLAYING SOME MESSAGES
//GOPAL JOB NOTIFY=GOPAL,CLASS=A,MSGLEVEL=(1,1)
//STEP0 EXEC PGM=MYPROG
//STEPLIB DD DSN=GOPAL.PROG.LOAD,DISP=SHR
//SYSOUT DD SYSOUT=*
//

:: Job Control Language ::


JOB

JCL is not a procedural language. It is a means of communications between a program & the MVS
o/s.
The JOB Statement

// Name Operations Operands Comments


// Jobname JOB Operands Positional / Keyword Parameters Comments

KEYWORD Parameters :
CLASS : To identify characterstics like short-running, heavy resource requirement
(A-Z or 0-9)
PRTY : To assign priority ( 0-14 or 0-15 depending on JES being run at the time.
MSGCLASS : To determine the output device to which system messages & JCL messgaes are
written.
MSGLEVEL : To specify JCL & allocation messages which will be recorded on the output device
specified in MSGCLASS.
MSGLEVEL=(statements,messages)
MSGLEVEL=(,messages)
MSGLEVEL=(statements)

TYPRUN : To specify a special type of job processing (HOLD/SCAN)


NOTIFY : &SYSUID (means it notifies for the user, who submitted the job)
________________________________________________________________________________
____
The EXEC Statement

//stepname EXEC PGM=program-name, keyword parameters

• Stepname is mandatory, if a referback statement is to be used or restart from a specific step is to


be started.
Keyword Parameters :
ACCT=(account-information, ...)
PARAM =value where value is a string from 1 to 100 characters long.
JOBLIB immediately follows the JOB statement & it must precede the EXEC statement
STEPLIB same as JOBLIB, but the statement is coded after the EXEC
ADDRSPC=VIRT or ADDRSPC=REAL
DPRTY=(value1,value2) ; DPRTY= value1*(16) + value2 ( value1 & value2 can be between 0 &
15).
PERFORM=n ; n can be between 0 & 999. To specify performance group.
RD=R RESTART
RD=RNC Restart with No Checkpoint
RD=NR No Automatic Restart
RD=NC No Checkpoint
The DD (Data Definition) Statement

// Name Operation Operation Comments


// ddname DD operands Comments
<positional/keyword params>
JCL Parameters on the DD statement
Rules :
1. The DD statement must immediately follow the EXEC statement.
2. A valid statement must be assigned to each data set used.
3. A DD stetment must exist for each data set used.

1. The DDNAME Parameter


Syntax : //ddname DD
DSN=data_set_name,DISP=(status,normal_disposition,abnormal_disposition)

DDNAMES reserved for system use :

//JOBLIB, //JOBCAT, //SYSABEND, //SYSIN, //SYSCHK //STEPLIB,


//STEPCAT //SYSDUMP, //SYSOUT, //SYSDBOUT

2. The DSN Parameter

Syntax : DSN data_set_name ( which can be qualified or non-qualified)

Temporary Data Sets can be created using && followed by 1 to 8 characters. They are deleted
after a job completion.

3. The DISP keyword parameter.


It is used to instruct the system about the current status of a data set and steps to be taken after
successful or unsuccessful execution of job.

Syntax : DISP=(status,normal-disposition,abnormal-disposition)

DISP=NEW DISP=(,CATLG,DELETE) DISP=(OLD,,DELETE)


DISP=(MOD,CATLG) DISP=SHR DISP=(OLD,DELETE)
DISP=(OLD,KEEP) DISP=(MOD,CATLG)
DISP=(OLD,UNCATLG)
DISP=(NEW,PASS) DISP=(NEW,CATLG,DELETE) DISP=(NEW,CATLG,KEEP)
DISP=(NEW,UNCATLG,CATLG)
DISP=(OLD,CATLG,UNCATLG)
________________________________________________________________________________
____
/* End of input stream
________________________________________________________________________________
____
//
________________________________________________________________________________
____
PROC
________________________________________________________________________________
____
PEND
________________________________________________________________________________
____
INCLUDE
________________________________________________________________________________
____
IF/THEN/ELSE/ENDIF
________________________________________________________________________________
____
JCLLIB
________________________________________________________________________________
____
SET
________________________________________________________________________________
____
OUTPUT
JCL : ADVANCE CONCEPTS

Why special DD statements ?


• There may be need to test the execution of a program without actually resorting the reading or
writing to data sets in the process .
• In the MVS environment, you can read several input data set in sequence. These data sets must
reside on similar device types, but they do not have to reside on the same volume.
• The system can be requested to supply information with reference to the source of errors that
may occur during the execution of the specific job step within a job.
• The system can be requested to supply information relating to its nucleus , if error should occur
during the execution occur during the execution of the job step within a job.
• Information can be directly input to a data set, at the time the job step is executed.
• The end of the input must be specified to the system.
• Output can be directed to a specified pre-defined class
• Output can be directed to a specified in diffrent or remote locations.
• Output can be held over until further notice.
• Output can be limited to a specific number of lines.

The DUMMY parameter


//DATA1 DD DUMMY
//DATA1 DD DSN=NULLFILE

SYSUDUMP SYSABEND SYSIN DATA or SYSIN DLM SYSOUT DEST HOLD


OUTLIM

Concatenating DATA SETS


• Upto 255 data sets can be concatenated together
• Upto 16 partitioned data can be concatenated together
• All data sets concatenated must have the same type of record format.
• All data sets concatenated together must be of the same type( i.e. file organisation)
• If same type data sets are concatenated together, then the block of size of the first data set must
be larger that, or equal to, that of the subsequent data sets.
• It is not possible (alright to concatenate fixed length records with variable length records.

//DATA DD DSN=FILE1
// DD DSN=FILE3
// DD DSN=FILE3

The SYSDUMP DD Statement

It is used to obtain a dump of the contents of various registers and variables in case of abnormal
termination of the job.
//SYSDUMP DD ... Comments
e.g. //SYSDUMP DD DSN=DUMPFILE, UNIT=3390,

The SYSABEND Statement

Same as SYSDUMP statement and also listed to the output device or data set.

//SYSABEND DD ... Comments

e.g. //SYSABEND DD SYSOUT=A

The SYSIN - INPUT STREAM DATA

SYSIN is not a parameter but it is the conventional ddname assigned to input data stream.


//SYSIN DD * //SYSIN DD DATA
<lines of data>
/*

The DLM Parameter

To specify the end of the input data stream.

//SYSIN DD *,DLM=‘xx’
<lines of text>
/* * ‘INPUT’
xx

SYSOUT - Specifying Output Class

//SYSOUT DD SYSOUT=class Comments

//SYSOUT DD SYSOUT=A
//SYSOUT DD SYSOUT=*

The asterisk is assigned to the SYSOUT parameter. Implying that the class is assigned to the
MSGCLASS parameter will also be used for SYSOUT. Thus SYSOUT is assigned to the CLASS
K. (??)

The DEST Parameter to route output to a specific location.

Syntax in JES2 environment

// Name Oparation Operand Comments


// ddname DD DEST comments
DEST=RMTxxxx DEST=RMxxxx DEST=Rxxxx DEST=Uhhh DEST=Nxxxx
DEST=NnnnRyyy DEST=LOCAL DEST=name
R - Remote U - specifies a local terminal, N specifies a node.

Syntax in JES2 environment

DEST=ANYLOCAL DEST=device_name DEST=address DEST=group_name


DEST=Node_name

ANYLOCAL is used to route the output to a local device, device_name is the name of the
destination device which is physical address that was given to the device at the time the system is
generated. The name of the output device to which the output is directed to is group_name. The
name of the remote node is node_name.

The HOLD Parameter :

This parameter is coded on the DD statement to specify whether the output is to be printed
immediately or held till further notice.

// Name Operation Operand Comments


// ddname DD HOLD comments
HOLD=YES HOLD=NO

//DATA1 DD DSN=FILE1,SYSOUT=A,HOLD=YES

The OUTLIM Parameter

This parameter is coded on the DD statement and is used to limit the number of lines that are output
to the destination specified in SYSOUT. It is used to avoid printing excessive amount of data in a
print environment.
//DATA1 DD DSN=FILE1,SYSOUT=A,SYSLIM=1000

JCL Procedures : JCL statements are grouped together into procedures. No more than 255 job
steps can be coded in one procedure.

//PROC1 PROC
//STEP1 EXEC PGM=PROGRAM1
//DD1 DD DSN=FILE1,DISP=SHR
//STEP2 EXEC PGM=PROGRAM2
//DD2 DD DSN=FILE2,DISP=SHR
// PEND

Cataloged Procedures : A catalogued procedure is a set of job control statements that are grouped
together, given a name and than recorded as a member of a partitioned data set. IBM supplies a
utility program called IEBUPDTE which places cataloged procedures into partitioned data sets.
Traditionally, these procedures are placed inside a system library called SYS1.PROCLIB.
//CATALOG1 PROC
//STEP1 EXEC PGM=PROGRAM1
//DD1 DD DSN=FILE1,DISP=SHR
//STEP2 EXEC PGM=PROGRAM2
//DD2 DD DSN=FILE2,DISP=SHR
//

Once the procedure is cataloged using IEBUPDTE, it is executed as follows :

//JOB1 JOB G700,MATLING


//PROCLIB DD DSN=USER.TEST.PROCLIB,DISP=SHR
//JOBLIB DD DSN=USER.TEST.JOBLIB,DISP=SHR
//DATA2 EXEC CATALOG1

PEND must not be coded in CATALOGED Procedures.

IN-STREAM Procedures :

Instream-procedures are similar to cataloged procedures except that they are not the members of
partitioned data sets. They are included in the inputstream of the job itself. The same in-stream
procedure can be invoked more than once within the job.

//JOB1 JOB (A123),DAVID


//INSTREAM PROC
//STEP1 EXEC PGM=PROGRAM1
//DD1 DSN=FILE1,DISP=SHR
//STEP2 EXEC PGM=PROGRAM2
//DD2 DSN=FILE2,DISP=SHR
// PEND
//STEP3 EXEC INSTREAM
Overriding parameters in procedures

One can easily change the parameters in DD statement without actually changing the contents of
the original procedure as follows
//INSTREAM PROC
//STEP1 EXEC PGM=PROGRAM1
//DD1 DSN=FILE1,DISP=SHR
//STEP2 EXEC PGM=PROGRAM2
//DD2 DSN=FILE2,DISP=SHR
// PEND

//JOB1 JOB A123,’H BLAKLEY’


//PROCLIB DD DSN=USER.TEST.LIB1,DISP=SHR
//EXEC1 EXEC PROC1
//STEP1.DD1 DD DSN=FILE1,DISP=OLD
//STEP2.DD2 DD DSN=NEWFILE,DISP=SHR

Overriding parameters, concatenated datasets

//PROC2 PROC
//STEP1 EXEC PGM=PROGRAM2
//DD1 DD DSN=TEST.FILE1,DISP=SHR
// DD DSN=TEST.FILE2,DISP=OLD
// DD DSN=TEST.FILE3,DISP=MOD
// DD DSN=TEST.FILE4,DISP=OLD
// PEND

//JOB1 JOB A123,’H BLACK)


//PROCLIB DD DSN=USER.TEST.LIB1,DISP=SHR
//EXEC1 EXEC PROC2
//STEP.DD1 DD
// DD DSN=PROD,FILE2,DISP=OLD
// DD
// DD DSN=PROD,FILE2,DISP=OLD

SYMBOLIC PARAMETERS :
These are used to override parameters on the DD statement. They can be used both in catalogued &
in-stream procedures. It provides a convenient way of assigning different parameters to commonly
used JCL procedures.

//JOB1 JOB A123,BETTY


//ASSIGN PROC FILE=DATAFILE
//STEP1 EXEC PGM=SYMBOL1
//DATA1 DD DSN=&FILE1

//JOB2 JOB Y1,BETTY


//ASSIGN PROC FILE1=NEWFILE,DISP=SHR,DEVICE=CYL,FORMAT=FB
//STEP1 EXEC PGM=SYMBOL1
//DATA1 DD DSN=$FILE1, UNIT=3390, SPACE=(%DEVICE(1,1)),
B=(RECFM=&FORMAT), // SYSOUT=A,DEST=LOCAL

The DATA statement will look like :


//DATA1 DD DSN=NEWFILE,UNIT=3390,DISP=SHR,SPACE(CYL(1,1)),
// DCB=(RECFM=FB),SYSOUT=A,DEST=LOCAL)

Generation data Group

GDG’s are groups of data sets which are related to each other chronologically & functionally.
Generation can be continued until a specified limit is reached. Once this limit is reached, then the
oldest generation can be deleted.

Creating a Generation Data Set :

//JOB3 EXEC PGM=GDG1


//FILE1 DD DSN=FINANCE,MONTHLY(+1),
DISP=(NEW,KEEP,DELETE),UNIT=SYSDA,SPACE=(TRK,(20,10),RLSE),
DCB=(MODEL.DCB, // RECFM=FB, LRECL=80, BLKSIZE=800)
Modifying Feature of A GDG :

//SYSIN DD *
ALTER gdg-name parameter, parameter, ...
/*
:: Utility Programs ::
Utility helps expediate a task.

IEBGENER Copy sequential files


IEBCOPY Copy/Compress partitioned data sets.
IEHPROGM Catalog/Uncatalog/Rename data sets / Create Generation Data Group
IEBCOMPR Compare seuqntial/partitioned data sets, or code other functions on the DD
statement, without having to execute aprogram
IEFBR14 Create or delete data sets, allocate or deallocate space data sets,

JCL reuired to execute utilities :

//JOBNAME JOB (accounting information), programmer-name


//stepname EXEC PGM=utility-name, PARM=parm-values
//printname DD SYSOUT=print-device-class
//inputfile DD input-file-features
//outputfile DD output-file-features
//workfile DD work-file-features
inputdata DD
<data statement specific to the utility>
/*
//

A piece of work submitted to the operating system for processing is called a job. A job consists of
one or more steps. To describe this job to the MVS operating system, the programmer uses Job
Control Language, or JCL. The JCL tells MVS which program is to be executed at each step,
which inputs each step requires, and which output each step produces.

Three JCL statements are used to communicate this information to MVS.

1. The JOB statement, which makes the beginning of a step, tells which program is to be executed
in that step, and describes certain attributes of the job.

2. The EXEC (execute) statement, which marks the beginning of a step, tells which program is to
be executed in that step, and describes certain attributes of the step.

3. The DD (data definition) statement, which identifies the inputs and outputs for each step

To illustrate how these statements work together, consider a job with just one step. The JCL for
such a job might be constructed like this:
//.....JOB..........................
//.....EXEC........................
//.....DD.............................
//.....DD.............................
//.....DD.............................

The job statement always comes first and is followed by the first(and, in this case, only) EXEC
statement, which tells which program is to be executed. The EXEC statement is followed by the
DD statements, each of which describes a different input file required by the program or an output
file produced by the program. DD statements always follow the EXEC statement for the step to
which they apply.

In a multistep job, each EXEC statement is followed by the DD statements required for that step:

//.....JOB..........................
//.....EXEC........................
//.....DD........step1............
//.....DD.............................
//.....EXEC........................
//.....DD.........step2..........
//.....DD.............................
//.....EXEC........................
//.....DD..........step3.........
//.....DD.............................

When several jobs are submitted as a group, the group of jobs is called a job stream or sometimes
an input stream.
//.....JOB..........................
//.....EXEC........................
job 1-------------- //.....DD.............................
//.....DD.............................

//.....JOB..........................
job 2-------------- //.....EXEC........................
//.....DD.............................

//.....JOB..........................
//.....EXEC........................
job 3-------------- //.....DD.............................
//.....DD.............................
//.....EXEC........................
//.....DD.............................
//.....DD.............................

There is more to JCL than the JOB, EXEC, and DD statements, but you will find that the vast
majority of the JCL you write will consist of just those three statements.
JCL CODING RULES:

JCL isn’t a true programming language, but it does have some coding rules you must obey.
One line of JCL can contain upto 80 characters, although a single statement can run to several lines.
A JCL statement has the following general format:

1. JCL statements must begin with two slashes (//) in position 1 and 2. The slashes identify the
statement as JCL.

2. Every JCL statement has a name, which begins immediately following the //. in position 3. The
name identifies the statement so that it can be referred to by other statements and by MVS itself.
The name can contain from 1 to 8 characters and include alphabetic, numeric and national (#, @, $)
characters. However the first character must be either alphabetic or national.

3. The operation field follows the name and is separated from it by one or more spaces. This field
tells whether the statement is JOB, EXEC, or DD.

4. The parameter list follows the operation field and is separated from it by one or more spaces. The
parameters contain the information about each job, step or dataset that MVS needs to know. The
parameter list can extend through position 72. When the list contains more than one parameter, the
parameters must be separated by commas. Note that there can be no spaces between parameters.

5. Comments follow the parameter list. Comments are documentation indented to clarify the JCL
for a human reader; MVS ignores then. Comments can appear anywhere after the parameter list,
but they must be separated form it by at least one space. They can continue through position 80.

EXAMPLES:

To illustrate these rules, we will first use a JOB statement:

//PAYROLL JOB (A68,XX34,DEV),SATISH,CLASS=A,TIME=5


--------------- === ***********************************
Name Operation Parameter list

The name of this statement is PAYROLL. The statement contains four parameters:
(A68,XX34,DEV)
SATISH
CLASS=A
TIME=5
There are no comments in this job statement.

Here is another example, this time a DD statement:

//PAYIN DD DSN=PAY.MASTER,DISP=SHR *PAYROLL MASTER FILE*


The name of this DD statement is PAYIN. It has a parameter list consisting of tow parameters:
DSN=PAY.MASTER
DISP=SHR

The DD statement also contain some comments:

*PAYROLL MASTER FILE*

Now here’s a JCL statement that contains some errors:

/INPUT-FILE DSN=PAY.MASTER, DISP=SHR

There are number of problems with this statement:

1. A second slash is missing at the beginning of the statement.


2. The name INPUT-FILE is more than eight characters long and contains an invalid character - the
hyphen.
3. No operation is indicated.
4. There is a space between the two parameters.

When JCL is submitted to MVS for execution, the operating system first checks the JCL for proper
syntax. When it detects errors such as the above, the JCL is rejected and must be corrected. The
rejected JCL will be accompanied by messages that will help you find and correct the errors. But of
course, it’s better not to make error in the first place.

Note : Before submitting the job we can check for syntax errors by using command JEM on the
ispf command line.

CONTINUING JCL STATEMENTS

You can continue the parameter list of a JCL statement onto multiple line by following these simple
rules:

1. End the line to be continued with a comma at or before position 72.

2. Begin the next line with a // in positions 1 and 2. omit the name and operation fields, and begin
the next parameter between positions 4 and 16.

Here is the JOB statement you saw above with the parameter list continued over two lines.

//PAYROLL JOB (A68,XX34,DEV),SATISH,


// CLASS=A,TIME=5

Some programmer like to take advantage of the ability to continue statements by placing each
parameter on a different line, like this:

//PAYROLL JOB (A68,XX34,DEV),


// SATISH,
// CLASS=A,
// TIME=5

PARAMETERS:

There’s little mystery to beginning each JCL statement with //, and the name and operation fields
are pretty straightforward. But parameters are another story.

The parameters are divided into to two categories: Positional parameters and Keyword parameters.
Positional parameters are identified by their position in the parameter list; that is, MVS can
tell what a positional parameter is by and where it is. Keyword parameters are identified by the
specific keywords they begin with. When a statement contains both positional and keyword
parameters, the positionals as a group must precede the keywords. Positional parameters must be
coded in a specific sequence, while keyword parameters can be coded in any order.
For example, look at this JOB statement:
//PAYROLL JOB (A68,XX34,DEV),SATISH,CLASS=A,TIME=5
In this statement, (A68,XX34,DEV) represents installation accounting information and SATISH is
the name of the programmer responsible for the job. The accounting information and programmer
name parameters are positional parameters on the JOB statement; if used, they must be the first two
parameters coded on the statement, and they must appear in that order. On the other hand
CLASS=A and TIME=5 are keyword parameters. They must follow the positional parameters, but
their order is not significant. This JOB statement could just as well have been coded as
//PAYROLL JOB (A68,XX34,DEV),SATISH,TIME=5,CLASS=A

All keyword parameters are optional; they can be coded or not as the situation requires. Some
positional parameters are optional as well, but a difficulty arises when an optional positional
parameter is omitted. Here is an example, on the JOB statement, there are two positional
parameters. MVS assumes that the first parameter on the statement is the accounting information
and the second parameter is the programmer name. On the JOB statement

//PAYROLL JOB (A68,XX34,DEV),SATISH,CLASS=A,TIME=10

MVS assumes that (A68,XX34,DEV) is the accounting information and SATISH is the
programmer’s name. If the optional accounting information parameter were omitted and the
statement written as

//PAYROLL JOB ,SATISH,CLASS=A,TIME=10

The comma preceding the programmer name shows that the accounting information has
deliberately been omitted, and there is no chance that MVS will interpret SATISH as accounting
information.

THE NULL STATEMENT:


There is one JCL statement that contradicts almost all the rules we’ve just discussed. The only rule
it obeys is that it begins with two slashes. It has no name, no operation, no parameters-- in fact, it
consists only of the two slashes in position 1 and 2. This special JCL statement is called null
statement, and it has just one purpose: to mark the end of a job or job stream.

The JOB Statement:

Every MVS job begins with a JOB statement. The JOB statement marks the beginning of a job,
names the job, and describes certain characteristics of the job to MVS so that the control program
can handle job properly.
The job name follows two slashes. MVS uses the job name to identify the job and its inputs and
outputs. When the job is submitted for execution MVS assigns a number to it that it uses internally
to identify the job’s components.

Positional JOB Statement Parameters

Most of the JOB statement parameters are keyword parameters. But the first two - ACCOUNTING
INFORMATION and PROGRAMMER NAME are positional. Each parameter on the JOB
statement represents a particular piece of information about your job that is communicated to MVS.

ACCOUNTING INFORMATION: Who pays for the job?

The first positional parameter on the JOB statement is the ACCOUNTING INFORMATION
parameter. It consists of information MVS uses to determine who to charge for the job.
PROGRAMMER NAME: Who is responsible for the job?

The second positional parameter on the JOB statement is called the PROGRAMMER NAME
parameter. However, it does not necessarily have to include the programmer’s name. The
PROGRAMMER NAME parameter consists up to 20 characters of identifying information relating
to the job. It is usually used to identify the programmer responsible for the job, but it could just as
well specify a room number, a department name, or almost anything else.

A Reminder

Remember that both ACCOUNTING INFORMATION and PROGRAMMER NAME are optional
parameters. If you choose to omit one or both of them, you must code a comma to indicate the
missing parameter or parameters.

Keyword JOB Statement Parameters

The remaining parameters that can be coded on the JOB statement are keyword parameters. That
means they can be coded in any order you wish.

CLASS: What kind of job is it?


MVS allows for a maximum of 36 classes. Each class is identified by a single letter or digit and is
specified to MVS via the optional CLASS keyword parameter on the JOB statement. Assume for
example SEALAND INC. has defined the following job classes:

Class Maximum CPU Time


F 10
A 45
H 600
8 1800
L 3600

(The data given above is true data given by SEALAND onsite team for SEALAND TEST system)

MSGCLASS: Where Does the Output Go?

As jobs are processed by the computing system, the control program produces a series of
messages(including the job’s JCL itself) that document the processing that has occurred. But these
system messages are not printed as they are produced. Instead they are stored in a special disk
dataset and printed at a later time.
The various output groupings are called output classes. The class to which a job’s system messages
are routed is determined by the optional MSGCLASS parameter. As with job classes, there are 36
possible output classes, each named by a single letter or digit.
The EXEC Statement

The EXEC statement marks the beginning of a job step and tells MVS which program is to be
executed in that step.
Like the JOB statement the EXEC statement begins with two slashes and a name. However
while MVS requires the job name, step names are optional.
If step name is used it must confirm to the same rules as the job name; that is, it must consist of
from 1 to 8 alphabetic, numeric or national (#, $, @) characters, and the first character must be
alphabetic or national.

The PGM= Parameter:

A number of parameters can be coded on the EXEC statement. One of those parameters are PGM=
parameter. Though it looks like a keyword parameter it is POSITIONAL parameter that names the
program to be executed and it consists of the characters PGM= followed by the program name. For
example, if the payroll program is named PAY you might code

//PAYROLL EXEC PGM=PAY

while for the COBOL compiler named IKFCBL00 would have

//PAYROLL EXEC PGM=IKFCBL00


It is important to note that although PGM= looks like a keyword parameter, it is in fact positional.
It must be the first parameter on the EXEC statement.

The DD Statement:

DD statements tell MVS about the input and output requirements of the program being executed.
Most programs require some input data and produce some output. DD statements tell MVS where
the required input should come from and where the output being produced should go to.

The ddname
Like the JOB and EXEC statements, the DD statement begins with two slashes followed by
a name. The name of the DD statement, usually called a ddname, must follow the same rules as the
other names. It must consist of from one to eight alphabetic, numeric, or national characters, the
first of which must be alphabetic or national. The DD statement provides the connection between
the actual physical data and the description of that data in the program that uses it.

Reserved ddnames

There are several words that are valid ddnames but nevertheless must be used with care
when used for this purpose. This is because DD statements with these names invoke special
facilities within MVS. That is when MVS sees a DD statement with one of these names it expects
the files associated with them to be used for certain specific purposes. Use these names only when
you want to see use the special facilities associated with them. The following are the special
DDNAMES to be avoided while coding usual dataset names....

JOBCAT
STEPCAT
SYSABEND
SYSMDUMP
SYSCKEOV
JOBLIB
STEPLIB
SYSUDUMP
SYSCHK

In-stream Input: The * Parameter

When a DD statement describes an input file, it must contain information that tells MVS where the
data is and how it is stored. The easiest way to deal with the input data is to include it directly in the
job stream with the JCL. Such data is therefore called in-stream data.
When you use in-stream data, the DD statement that describes it must contain a parameter
that tells MVS that the data is present in the job stream. The parameter is a positional parameter,
and it consists of a single character: the asterisk (*). When used, the * must be the first parameter
on the DD statement. Specifically, the * means that the data described by the DD statement is
included in the job stream and begins on the line that immediately follows the DD statement
containing the *.
Here is an example:

Suppose the program GR9203EP prints a list of all the people who own stock in the SEALAND
INC., The program has been written to expect a DD statement named STKHLDRS that defines the
names to be printed. The JCL for executing this program might be coded like this:

//GR9203DXP JOB .......


//STEP1 EXEC PGM=GR9203EP
//STKHLDRS DD *
Hyderabad Satish 43 Charminar Chowrasta
Anakapalli B.S.Rao 109 Edo Addu Roddu
Nuzvidu Anju 6 Mamidi roddu
:
:

The STKHLDRS DD statement specifies in-stream data. The lines immediately following the DD
statement constitute that data. We can tell that those lines contain data rather than more JCL
because they have the following characterstics:
1. The lines immediately follow a DD * statement.
2. None of the “data lines” begins with // as JCL must.

Ending In-stream Data

If the DD * statement marks the beginning of in-stream data, you also need a way to indicate the
end of that data. There are three ways to accomplish this:
* The delimiter statement. This is a special JCL statement whose sole purpose is to mark the
end of in-stream data. The delimiter statement consists of the characters /* in the first two positions
of the line. Notice that the delimiter statement is the only JCL statement that does not begin with //.
Also, delimiter is usually optional.
* The next JCL statement. In the absence of a delimiter, the next JCL statement( the next
statement that begins with //) serves to terminate the in-stream data.
* The end of the job stream. If the in-stream data occupies the last lines in the job stream.
MVS will realize that the end of the job stream is also the end of instream.

Hardcopy Output : The SYSOUT Parameter

If the DD * statement is the easiest JCL statement to code, the DD statement for producing
hardcopy output must be the next easiest.
The MSGCLASS parameter is used on the JOB statement to route system messages to a particular
ouptut class. You can use the SYSOUT parameter on the DD statement to route program output to
one of those same classes.
Suppose you want to test a program that produces an report, that the program has been coded to
expect a DD statement named REP1 to allocate the output file to contain the report and you want
the output report to be printed on output class A. The DD statement for having this report routed to
output class A is

//REP1 DD SYSOUT=A

SYSOUT is a keyword parameter. Thus, when it appears with other parameters, its position in the
parameter list is insignificant. Particularly speaking, however most programmers code the
SYSOUT parameter as the first one on the DD statement on which it appears.

Making MSGCLASS and SYSOUT Work Together

Both MSGCLASS and SYSOUT refer to the same set of output classes. Although they are used on
different JCL statements and affect the routing of different kinds of output (system output for
MSGCLASS and program output for SYSOUT), the two parameters can work together.

Here is the example:

//MYJOB JOB AAAA,SATISH,CLASS=F,MSGCLASS=H


//STEP1 EXEC PGM=PRINTIT
//REP1 DD SYSOUT=*

Look at the parameter SYSOUT=* in the above DD statement. When a SYSOUT parameter
contains an asterisk instead of a job class, it tells MVS to route this output to the same output class
that the system output is going to. If a MSGCLASS has been coded, the class specified in that
parameter is used for the SYSOUT output as well. If no MSGCLASS is coded, SYSOUT output is
routed to the default output class along with the system output.
In other words coding SYSOUT=* is an easy way to keep program and system output
together. In addition, coding SYSOUT=* makes changing your JCL a bit easier.

DATASET NAMES:

You give a dataset a name for the same reason you give a person a name-- so that you will have
some way to refer to it. MVS has a set of rules you must follow when naming a dataset:
1. The name may contain a maximum of 44 characters.
2. The characters can be alphabetic, numeric, or national (@, #, $). Spaces cannot be used.
3. The first character must be alphabetic or national.
4. If the name contains more than eight characters, it must be divided into smaller strings with
periods so that each string is no longer than eight characters.
5. The periods must be counted in the 44 character maximum.
6. When the name is divided into strings, each string must begin with an alphabetic or national
character.
The DSN parameter:

To tell MVS the name of a dataset, you use the DSNAME keyword parameter. To specify a dataset
named CHGMAN.PROD.SOURCE, for example you would code the parameter

DSNAME=CHGMAN.PROD.SOURCE

However MVS allows you to abbreviate the DSNAME parameter to just DSN. Since the DSN
parameter is a keyword parameter you can code the above statement as

DSN=CHGMAN.PROD.SOURCE

and it can appear anywhere in the parameter listof a DD statement. However, when most
programmers use the DSN parameter, they code it as the first one. Thus, we might begin a DD
statement that specifies the creation of a tape dataset something like this:

//OUT1 DD DSN=L1234.USER.TEST.REPORT,......

The DISP Parameter

After identifying the dataset by name, you might tell MVS whether the dataset in question is
existing one to be retrieved or a new one to be created. You do this with the DISP parameter. DISP
stands for disposition, and thus it tells MVS how to dispose of the dataset. DISP is a keyword
parameter, but it has three positional subparameters. The general form of the DISP parameter is
DISP=(status,normal disposition,abnormal disposition)

The first positional subparameter of DISP tells the current status of the dataset. The two options for
this subparameter are:

NEW The dataset does not yet exist but is to be created in the current job step.
OLD The dataset is already exists and is to be retrieved for use in the current job step.

The second positional subparameter of DISP tells MVS what to do with the dataset--how to
dispose of it-if the current job step ends normally. The two options for this subparameter are:

KEEP The dataset should be retained by the system for future use
DELETE The dataset is no longer needed and may be eliminated from the system.

The third positional subparameter of the DISP tells MVS how to dispose of the dataset when the
current step terminates abnormally. The options for this subparameter are identical to those for the
second subparameter--KEEP and DELETE. If the third subparameter is not coded, MVS assumes
as a default value the value of the second subparameter. Thus the parameter

DISP=(NEW,KEEP,KEEP) means exactly the same thing as


DISP=(NEW,KEEP)

By the way, all three subparameters of DISP are optional, and so is the DISP parameter itself. If the
DISP parameter is not coded on a DD statement, MVS assumes that a new dataset is to be created
and deleted in the current step; that is, if DISP is not coded, the default DISP is

DISP=(NEW,DELETE,DELETE)

If the DISP is coded but the first subparameter is omitted, MVS assumes a new dataset is to be
created. Thus ,
DISP=(,KEEP)
is identical to
DISP=(NEW,KEEP)
Note: For rest of information on this disposition parameter please refer to the quick reference in
sealand TSO session using ispf option P.Q.

Apart from above standard statements the following are the special JCL statements used in Job
Control Language....
** The JCLLIB Statement **

JCLLIB is used ONLY on MVS/ESA Version 4 JES2 systems or higher, to


identify a private library or a system library from which INCLUDE
groups and JCL procedures are to be retrieved. The order in which
the library names appear on the JCLLIB statement is the order in
which they are searched for any JCL procedures (PROCs) and INCLUDE
groups referenced by this job. Only one JCLLIB statement is
permitted in a job, and it must appear after the JOB statement and
before the first EXEC statement in the job. The JCLLIB statement
must not appear within an INCLUDE group. You can continue the
JCLLIB statement by ending it with a comma followed by at least one
blank, then starting the next libary name somewhere between columns
4 and 16 on the next statement.

Syntax:

//{name} JCLLIB ORDER=(dsn1{,dsn2}{,dsn3}...) {comments}


You may use the UP or DOWN keys to scroll the text below as needed
Subparameter Definition

{name} - an optional name that must start in column 3 on the JCLLIB


statement, and follows the same rules as names on DD
statements (i.e., 1 through 8 alpanumeric or national
characters, with the first character being non-numeric)
The name chosen should be unique within the job.

dsn1, dsn2, dsn3, etc. - the fully qualified data set name(s) of the
system or user PDS(s) containing the JCL procedures or
INCLUDE groups referenced in this job. The data set name(s)
cannot include a member name specification, and must be
cataloged in a catalog other than a catalog named by a
JOBCAT or STEPCAT statement in the same job. You cannot
name temporary data sets on a JCLLIB statement. The data
sets named must be accessible to this job (i.e., access is
permitted by the security system) and must be online to MVS
on a DASD volume.

The data sets are searched in the order that they are
specified on the JCLLIB statement; if the needed PROCs or
INCLUDE groups are not found in the named data sets, then
the installation-specified default libraries are searched.
The data sets named must be Partitioned Data Sets with an
LRECL of 80 and a RECFM of F or FB; an valid blocksize that
is a multiple of 80 may be used.

If only one data set name is specified, you can omit the
surrounding parentheses used for the ORDER parameter.

comments - comments are optional and should follow the last


subparameter on the JCLLIB statement by at least 1 blank

EXAMPLES:

Example 1: The JCLLIB statement below will cause JES2 to search


TEST.PROCLIB1, TEST.PROCLIB2, and then SYS2.PROCLIB
for any JCL procedures or INCLUDE groups referenced
by this job that contains this statement.

//PROCS JCLLIB ORDER=(TEST.PROCLIB1,TEST.PROBLIB2,


// SYS2.PROCLIB)

Example 2: The JCLLIB statement below causes a search of


SYS1.PROCLIB, SYS3.USER.PROCLIB, then OPS420.JCLLIB
for the ASMHCL procedure and the PRODINC3 INCLUDE
group named by the job the JCLLIB statement appears in.

//PRODJOB1 JOB (S-1233),CLASS=A,TYPRUN=HOLD,MSGLEVEL=(1,1),


// MSGCLASS=T
// JCLLIB ORDER=(SYS1.PROCLIB,
// SYS3.USER.PROCLIB,
// OPS420.JCLLIB)
//JS10 EXEC ASMHCL,COND.L=(0,NE)
//JS20 EXEC PGM=IEBCOPY
//INC$ INCLUDE MEMBER=PRODINC3
//

*** The PROC Statement ***

The PROC statement indicates the beginning of a JCL procedure (i.e.,


the first statement of every JCL procedure must be a PROC statement).
As an option, the PROC statement can assign default values to symbolic
parameters used within the procedure.

Syntax:

//name PROC {parameters {comments}}

As shown above, a PROC statement consists of the characters // in


columns 1 and 2, followed by the name field, followed by one or more
spaces, followed by the operation field (always specified as PROC),
followed by one or more spaces, followed by the optional parameter
field, followed by one or more spaces, followed, finally, by the
optional comments field.
A PROC statement can be continued onto the next line by ending the
current line with a comma after a complete parameter.

The name field is required on a PROC statement in an in-stream


procedure; it is optional on a PROC statement in a cataloged
procedure. Each name specified for an in-stream procedure must be
unique within the JCL job-stream containing that procedure.

The name, if specified, must begin with an alphabetic or national


character ($, #, @) and must consist of 1 to 8 alphanumeric or
national characters. If omitted, column 3 must be blank.

The optional parameter field is used to assign default values to


symbolic parameters used within the procedure. Here are the rules
governing the parameters coded within the parameter field:
-when more than one parameter is specified, separate them with
a comma
-when a parameter value contains special characters, enclose that
value in apostrophes
-when a parameter value contains an apostrophe, code that
apostrophe as two consecutive apostrophes
-when a parameter value is enclosed within a matched pair of
parentheses, the parentheses need not be enclosed in apostrophes

The optional comments field cannot be specified unless the parameter


field is coded.

Examples:

//PROCA PROC PRM1=ABC THIS IS A COMMENT

In this example, the name field is specified as PROCA. The parameter


field is specified as PRM1=ABC (providing a default value for the
single parameter PRM1). The comment field is coded as THIS IS A
COMMENT.

//PROCB PROC PRM1=ABC,PRM2='02-06',PRM3='O''MALLEY',


// PRM4=(TRK,10)
In this example, which illustrates how the PROC statement can be
continued onto the next line, multiple parameters are coded (and
separated by commas). PRM2 shows how apostrophes are used to enclose
a parameter value containing a special character. PRM3 shows how two
apostrophes are used when a parameter value contains an apostrophe.
PRM4 shows that the enclosing apostrophes are not needed if the parm
value is enclosed in matching parentheses.

*** The PEND Statement ***

The PEND statement marks the end of an in-stream procedure (i.e., every
in-stream procedure should have a PEND statement at the end of the
statements that make up the in-stream procedure). A PEND statement can
also appear at the end of a cataloged procedure (but this is not
required).

Syntax:

//{name} PEND {comments}

As shown above, the PEND statement consists of the characters // in


columns 1 and 2, followed by an optional name field starting in column
3, followed by one or more blanks, followed by an operation field
(always specified as PEND), followed by one or more spaces, followed,
finally, by an optional comments field. A PEND statement cannot be
continued onto the next line.

The name, if specified, must begin with an alphabetic or national ($,


#, @) character and consist of 1 to 8 alphanumeric or national
characters. For an in-stream proc, each name must be unique within the
JCL job-stream containing that in-stream procedure. If the name is
omitted, column 3 msut be blank.

Examples:

// PEND THIS IS A COMMENT

This PEND statement contains a comment but no name field.

//PEND1 PEND

This PEND statement contains a name (PEND1) but no comment.

*** The JOBLIB DD Statement **

The JOBLIB DD statement is used to identify a program library to


search first when attempting to locate programs executed during the
job's life. The JOBLIB must be placed after the JOB statement and
before the first EXEC statement in the job. More than one program
library can be concatenated after the first one on a JOBLIB.

If a STEPLIB DD is specified in a job that also has a JOBLIB, the


STEPLIB takes precedence when searching for a program.

If you use a JOBCAT DD statement, it goes after the JOBLIB.

You can nullify a JOBLIB for a job step by adding a STEPLIB to the
step that points to SYS1.LINKLIB.

Syntax:
//JOBLIB DD DISP=SHR,DSN=program-library-name

Program Search Order:

The program search order for MVS uses the following program
libraries in the order given:

1) JOB Pack Area (already loaded programs)


2) Private task library, if specified.
3) STEPLIB library, if specified.
4) JOBLIB library, if specified, AND no STEPLIB is
present for the job step.
5) Link Pack Area (PLPA)
6) System Link List (i.e., SYS1.LINKLIB and the data sets
concatenated to it).

*** The STEPLIB DD Statement **

The STEPLIB DD statement is used to identify a program library to


search first when attempting to locate programs executed during the
job step. The STEPLIB can be placed anywhere in the step's JCL.
More than one program library can be concatenated after the first
one on a STEPLIB.

If a STEPLIB DD is specified in a job that also has a JOBLIB, the


STEPLIB takes precedence when searching for a program.

Syntax:

//STEPLIB DD DISP=SHR,DSN=program-library-name

'program-library-name' is a data set name or a referback of the


form *.stepname.STEPLIB
Program Search Order:

The program search order for MVS uses the following program
libraries in the order given:

1) JOB Pack Area (already loaded programs)


2) Private task library, if specified.
3) STEPLIB library, if specified.
4) JOBLIB library, if specified, AND no STEPLIB is
specified
5) Link Pack Area (PLPA)
6) System Link List (i.e., SYS1.LINKLIB and the data sets
concatenated to it).

*** The SYSOUT Parameter **

The SYSOUT parameter identifies a data set as a "SYStem OUTput" data


set, consisting of printed or punched output that will managed by
JES2 or JES3. The SYSOUT parameter names the output class to which
the printed or punched output belongs. The SYSOUT class supplied
via the SYSOUT parameter is used instead of any SYSOUT class given
by a JCL OUTPUT statement.
Syntax:

SYSOUT=class
or
SYSOUT=(class,{INTRDR}{,form name})
or
SYSOUT=(class,{writer name}{,form name})
or
SYSOUT=(,)
Subparameter Definition

class

The output class to which this output belongs; this can be a


character in the range A through Z or 0 through 9. A '*' or
a '$' for SYSOUT class indicates that the class given by the
MSGCLASS= parameter on the job statement is to be used for
this SYSOUT DD statement, so that all the job's SYSOUT will
go to the same output class.

INTRDR

Indicates that output written to this DD statement is to be


read back into the system through the JES internal reader.
This technique allows you to write JCL to a SYSOUT DD
statement, thus submitting job(s) back into the system.
writer name

The name of the JES external writer that is to process the


output written to this DD statement. Your installation's
operations staff manages the usage of external writers.

form name

Gives the form name of the (usually pre-printed) form that


is to mounted in the printer before this output is printed.

(,)
Indicates a null SYSOUT file; the CLASS parameter on an
OUTPUT JES statement in this job is to be used for the
SYSOUT class.

Example: //DD1 DD SYSOUT=A


//MYOUTJCL DD SYSOUT=(*,INTRDR)
//STDFORMS DD SYSOUT=(D,,STD)

Thanks for going thru the document. Now you can start writing JCL and you can submit it
using the SUB command. ‘Let me know if you can shutdown MVS by submitting a JCL’.
I Wish you good luck.

The following are most frequently used names:

1. System Completion Code


A system completion code is a three-position identifier controlled by MVS. Programs have
no access to it. It is prefaced under MVS with literal ‘S’ in the form of ‘Snnn’. NNN stands for a
three-position hexadecimal number. The error message will print on the JCL in the format of
‘Snnn-rc’. RC stands for the return code associated with the system message which further
describes the error.

2. Operation Exception Error


An operation exception error indicates that an operation code is not assigned or the assigned
operation is not available on a particular computer model. The machine did not recognize the
instruction or operation used. A possible reason is a subscript error.This error could also be caused
by an attempt to read a file that was not opened, a misspelled ddname, or a missing dd statement.
The system completion code is 0C1.

3. Protection Exception Error


A protection exception error occurs when the program is attempting to access a memory
address that is not within the the memory area that the program is authorized to use. Some of the
causes may be a subscript or index that is not initialized or has taken on a value outside the bounds
of the table with which it is associated, an attempt to read an opened file, or an incorrect or missing
DD statement. The system completion code is 0C4.

4. Addressing Exception Error


An addressing exception error occurs when a program is attempting to access a memory
location which is outside the bound of available real storage on the machine. This can be caused by
a dataset not being opened at the time of I/O was directed to it, an attempt to close a dataset a
second time, incorrectly called module parameters or coding, improper exit from a performed
paragraph, or uninitialized subscript or index. The system completion code 0C5.

5. Data Exception Error


A data exception error indicates an attempt to perform an arithmetic operation on
nonnumeric data. It can occur also occur from incorrect input data to a program that is not
performing sufficient numeric testing on it before attempting arithmetic. The system completion
code is 0C7.

6. Return can be produced when the operator cancels a job


There are two returns codes which can be produced when the operator cancels a job. They
are 122 and 222. A 122 indicates the operator cancelled the job without a dump. It is important to
ask the operator cancelled. Some of the reasons this may occur are: the program needed a resource
that was not available; the program appeared to be stalled in a wait state; or the program was in an
apparent loop.

7. Return code is issued if a job or job step exceeded the time limit
The system will issue a system code of 322 when a job or job step has exceeded the time
limit. If the time parameter was used on the JOB or EXEC statement, it may not have allowed
enough time for the job or job step to complete. If the time parameter was not used, then it is
important to check the program for possible logic loops.

8. System Completion Code issued when a program module cannot be found


A system completion code of 806 will be issued when a program module cannot be found.
Some of the causes may be missing the STEPLIB statement from the step or missing the JOBLIB
statement from the job stream. Most likely the program name was misspelled on the EXEC
statement or in a source code CALL.

9 Abend codes generated when not enough disk space is available ...
Some of the abends generated due to a lack of available disk space are:
1. B37-Disk volume out of space, cannot write output. The system gave all the primary space and
as much secondary space as it could.
2. D37-Primary disk space was exceeded and either no secondary space allocation was specified or
it was insufficient. One should increase the primary space as well as provide adequate secondary
space allocation to eliminate this error.
3. E37-There was insufficient space on the volume. One way to solve this problem is to specify
more volumes on the JCL.

The following are the most Frequently Asked Questions (FAQS) :

Q. What is a Generation Data Group (GDG)?


A. A Generation Data Group is a group of chronologically or functionally related datasets. GDGs
are processed periodically, often by adding a new generation, retaining previous generations, and
sometimes discarding the oldest generation.

Q. How is a GDG base created?


A. A GDG base is created in the system catalog and keeps track of the generation numbers used
for datasets in the group. IDCAMS utility is used to define the GDG base.

Q. What is model dataset label(Model DSCB)?


A. A model dataset label is a pattern for the dataset label created for any dataset named as a part of
the GDG group. The system needs an existing dataset to serve as a model to supply the DCB
parameters for the generation data group one wishes to create. The model dataset label must be
cataloged. The model DSCB name is placed on the DCB parameter on the DD statement that
creates the generationdata group.

Q. How are GDGs concatenated?


A. Generation Data Groups are concatenated by specifying each dataset name and the generation
number for all geneations of the generation data group. Otherwise to have all generations of a
generation data group, omit the generation number. The DD statement will refer to all generations.
The result is the same as if all individual datasets wer concatenated. If generations are not on the
same volume, this will not work.

Q. How is a new GDG coded?


A. A new GDG is coded as (+1) after the dataset name as follows:
DSN=JAN.DATA(+1). This will cause all generations to be pushed down one level at the end of
the job.

Q. When should DISP=MOD is used?


A. DISP=MOD is used to either extend an existing sequential dataset or to create a dataset if it does
not exist. If the dataset exists, then records are appended to the dataset at the end of the existing
dataset. If the dataset does not exist, the system treats MOD as if it were NEW, provided that the
volume parameter has not been used. If the volume parameter is used, the system terminates the job
and does not create the new dataset. MOD can be used to add to a dataset that extends onto several
volumes. Always specify a disposition of CATLG with MOD for cataloged datasets, even if they
are already cataloged, so that any additional volume serial numbers will be recorded in the catalog.

Q. How is a dataset passed from one step to another?


A. A dataset is passed from one step to another based on what is coded on the DISP parameter. The
dataset can only be passed to subsequent steps if PASS was used on the disposition parameter.

Q. How are datasets concatenated?


A. Datasets are concatenated by writing a normal DD statement for the first dataset and then adding
a DD statement without a DDNAME for each dataset to be concatenated in the order they are to be
read. The following is an example of three datasets concatenated:
//YEARDAT DD DSN=JAN.DATA,DISP=SHR
// DD DSN=FEB.DATA,DISP=SHR
// DD DSN=MAR.DATA,DISP=SHR

Q. What is the difference between the JOBLIB and the STEPLIB statements?
A. The JOBLIB statement is placed after the JOB statement and is effective for all job steps. It
cannot be placed in a cataloged procedure. The STEPLIB statement is placed after the EXEC
statement and is effective for that job step only. Unlike the JOBLIB statement, the STEPLIB can be
placed in a cataloged procedure.

Q. Name some of the JCL statements that are not allowed in procs.?
A. Some of the JCL statements which are not allowed in procedures are:
1. JOB, Delimiter(/*), or Null statements
2. JOBLIB or JOBCAT DD statements
3. DD * or DATA statements
4. Any JES2 or JES3 control statements

You might also like