Вы находитесь на странице: 1из 63

12

IBM OS/JCL: DD Statements

//TPEIN //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP)

The DD Statement: Defines a data set to the operating system. Notifies the operating system that a data set is to be either accessed or created. Identifies the device requirements of the data set: Type of I/O unit required. Specific volumes to be mounted on the unit.

//TPEIN //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP)

The DD Statement: Further defines characteristics of the data set


The length of each record; The format of the record; Whether the data set already exists or is to be created during the job step.

Specifies what is to be done with the data set when the

job completes.

Tape DD Statement

//TPEIN //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP)

DDNAME - one to eight alphanumeric characters. The first character must be alphabetic. The DDNAME comes from the External Reference name in the SELECT Clause of the ENVIRONMENT DIVISION of a COBOL program.

INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CARD-FILE ASSIGN UR-2540R-S-CARDIN. SELECT PRINT-FILE ASSIGN UR-3203-S-PRTFLE. SELECT TAPE-IN ASSIGN UT-3420-S-TPEIN. SELECT TAPE-OUT ASSIGN UT-3420-S-TPEOUT. SELECT DISK-IN ASSIGN DA-3375-S-DSKIN. SELECT DISK-OUT ASSIGN DA-3375-S-DSKOUT. DATA DIVISION. 01 CARD-FILE. 05 EMP-NO PIC X(5) 05 EMP-NAME. 10 EMP-LAST PIC X(25). 10 EMP-FIRST PIC X(25). 10 EMP-MIDDLE PIC X.

//TPEIN //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP)

DD Operation - Data Definition

//TPEIN //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP)

UNIT - Identifies the data set as a tape file

//TPEIN //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP)

DSN (DSNAME) Data Set Name Identifies the name of the file as recorded in the header label when the file was created.

Fig. 12.4: The UNIT parameter specifies a physical device.


UNIT=device

select from unit or device address (channel/device address). device type (2501, 3330, etc.) group name (READER, PRINTER, etc.)

//TPEIN // //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP), VOL=SER=2992

DISP - Identifies the status of the data set:


Subparameter 1 - at the beginning of the job step; Subparameter 2 - If the job step terminates normally; Subparameter 3 - If the job step terminates abnormally.

Fig. 12.6: The disposition (DISP) parameter specifies the files status.
DISP=(a,b,c) file status following abnormal job step termination file status following successful job step termination file status at start of job step

Start of step dispositions NEW OLD SHR MOD

End of step dispositions KEEP PASS DELETE CATLG UNCATLG

//TPEIN // //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP), VOL=SER=2992

DISP - Identifies the status of the data set:

Subparameter 1 - at the beginning of the job step;

//TPEIN //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP) NEW,DELETE,DELETE SHR , PASS,CATLG ,CATLG,UNCATLG ,UNCATLG,


- The data set was created in an earlier job or job step. - The data set is being created in the current job step.

OLD

NEW

//TPEIN // //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP), VOL=SER=2992

DISP - Identifies the status of the data set:

Subparameter 2 - If the job step terminates normally;

//TPEIN //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP) NEW,DELETE,DELETE SHR , PASS,CATLG ,CATLG,UNCATLG ,UNCATLG,


- The data set is to be saved for future use. - The data set is scratched. - The data set will remain mounted. - The data set cataloged to the Tape Library. - The data set is uncataloged from the Tape Library.

KEEP DELETE PASS CATLG UNCATLG

//TPEIN // //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP), VOL=SER=2992

DISP - Identifies the status of the data set:

Subparameter 3 - If the job step terminates abnormally.

//TPEIN //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP) NEW,DELETE,DELETE SHR , PASS,CATLG ,CATLG,UNCATLG ,UNCATLG,


- The data set is to be saved for future use. - The data set is scratched. - The data set cataloged to the Tape Library. - The data set is uncataloged from the Tape Library.

KEEP DELETE CATLG UNCATLG

Common sense dictates:

//TPEIN //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP)

Common sense dictates:

//TPEIN //

DD UNIT=TAPE,DSN=PR.FLE, DISP=(NEW,CATLG,DELETE)

//TPEIN // //

DD

UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP), VOL=SER=2992

21

//TPEIN DD UNIT=TAPE,DSN=PR.FLE, // DISP=(OLD,KEEP,KEEP), // DCB=(RECFM=FB,LRECL=300,BLKSIZE=600)

DCB Parameter - supplies data set characteristics to be included in the data control block.
RECFM Record Format LRECL Logical Record Length BLKSIZE Block Size

22

Fig. 12.5: The DCB parameter. The DSORG, MACRF, and DDNAME must be coded in the program DCB.
DCB=(list of parameters) Typical parameters include: LRECL=n logical record length BLKSIZE=n block size RECFM=x record format, where x is one or more of: F fixed length V variable length B blocked A ASA characters Parentheses are required if more than one DCB parameter is coded

Disk DD Statement

//DISKIN DD UNIT=DISK,DSN=PR.FLE, SYSDA

//DISKIN DD UNIT=DISK,DSN=PR.FLE, SYSDA

UNIT - Identifies the data set as a disk file

//DISKIN DD UNIT=DISK,DSN=PR.FLE, SYSDA &&PR.FLE

DSN (DSNAME)
Data Set Name
Identifies the name of the file as recorded in the header

label when the file was created. && used to indicate a temporary data set

Fig. 12.7: The SPACE parameter.


SPACE=(type,(primary,secondary,index),RLSE,CONTIG) contiguous space return (release) any unused space to the system when the job step ends units of space to hold an ISAM index, or blocks of space to hold a library directory secondary space allocation primary space allocation type of space allocation in cylinders (CYL), tracks (TRK), or blocks

//DISKOUT DD UNIT=DISK,DSN=PR.FLE, SYSDA // SPACE=(TRK,(10,10),RLSE,CONTIG), CYL, BLKSIZE, // DISP=(NEW,CATLG,DELETE)

Type of space allocation Primary Allocation Secondary Allocation Release Any Unused Space All Space Must Be Contiguous

//DISKIN DD UNIT=DISK,DSN=PR.FLE, // DISP=(OLD,KEEP,KEEP) NEW,DELETE,DELETE SHR , PASS,CATLG ,CATLG,UNCATLG ,UNCATLG,

OLD

NEW
SHR

- The data set was created in an earlier job or job step. - The data set is being created in the current job step. - The input data set will be shared by another job.

//SYSIN

DD *

Allows a file to be inputted via the systems default input device.


The asterisk indicates that the data follows this DD statement.

31

//SYSOUT

DD SYSOUT=A

Allows a file to be outputted to the systems default output device. Normally implies printer output. The value of SYSOUT is dependent upon your installation.

32

//DISKIN

DD DUMMY

Allows a file to be ignored, or dummyed out. This process will be allowed as long as the logic of the program will allow the file to be dummyed out.

33

//DISKIN //

DD UNIT=DISK,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP),

34

CONCATENATING DATA SETS


// INDATA DD DSN=CURORDR,UNIT=TAPE, // VOL=SER=K90221, // DISP=(OLD,KEEP,KEEP) // DD DSN=PREVORDR,UNIT=AFF=INDATA, // VOL=SER=14552,DISP=(OLD,KEEP,KEEP) // DD DSN=INV,UNIT=AFF=INDATA, // VOL=SER=866221,DISP=(OLD,KEEP,KEEP)

Data Control Block Table

As the Job Stream JCL is checked, the information in the DD statements is used to create an entry for the data sets in the DCB Table.

Once the DCB Table is completed, the JCL is then checked for accuracy and validity. If any errors are discovered, they are documented on the JCL Listing (MSGLEVEL parameter) and the job is not run.

Backward References

Using the DCB Table entries, Backward References (Refer Backs) can take place.

Backward References
//OSJCL // // //STEP1 //DD1 // //DD2 // //DD3 //
38

JOB

(OSJCL,04/03/98),M. R. IZZO, CLASS =T,MSGLEVEL=(1,1), MSGCLASS =A EXEC PGM=CALC DD UNIT=TAPE,DSN=FILE1, DISP=(OLD,KEEP,KEEP) DD UNIT=TAPE,DSN=FILE2, DISP=(OLD,KEEP,KEEP) DD UNIT=TAPE,DSN=FILE3, DISP=(NEW,PASS,DELETE)

//REPORT DD SYSOUT=A //SYSUDUMP DD SYSOUT=J //CRDIN DD * * Card Input * /* //STEP2 EXEC PGM=CALC2 //DD4 DD UNIT=TAPE,DSN=*.STEP1.DD3, // DISP=(OLD,KEEP,KEEP) //REPORT2 DD SYSOUT=A //SYSUDUMP DD SYSOUT=J //

DCB Table
STEP NAME STEP 1 DD Name DD1 DD2 DD3 REPORT SYSUDUMP CRDIN STEP2 DD4
*.STEP1.DD3

DSN FILE1 FILE2 FILE3

UNIT TAPE TAPE TAPE SYSOUT=A SYOUT=J * TAPE

RECFMT

DISP Old, Keep Keep Old Keep Keep New Pass Delete

DCB Table
STEP NAME STEP 1 DD Name DD1 DD2 DD3 REPORT SYSUDUMP CRDIN STEP2 DD4 FILE3 TAPE DSN FILE1 FILE2 FILE3 UNIT TAPE TAPE TAPE SYSOUT=A SYOUT=J * New Pass Delete RECFMT DISP Old, Keep Keep Old Keep Keep New Pass Delete

DCB Table
STEP NAME STEP 1 DD Name DD1 DD2 DD3 REPORT SYSUDUMP CRDIN STEP2 DD4 FILE3 TAPE DSN FILE1 FILE2 FILE3 UNIT TAPE TAPE TAPE SYSOUT=A SYOUT=J *
OLD,KEEP,KEEP

RECFMT

DISP Old, Keep Keep Old Keep Keep New Pass Delete

DCB Table
STEP NAME STEP 1 DD Name DD1 DD2 DD3 REPORT SYSUDUMP CRDIN STEP2 DD4 REPORT2 SYSUDUMP FILE3 TAPE SYSOUT=A SYSOUT=J DSN FILE1 FILE2 FILE3 UNIT TAPE TAPE TAPE SYSOUT=A SYSOUT=J * New Keep Keep RECFMT DISP Old, Keep Keep Old Keep Keep New Pass Delete

DCB Table
STEP NAME STEP 1 DD Name DD1 DD2 DD3 REPORT SYSUDUMP CRDIN STEP2 DD4 REPORT2 SYSUDUMP FILE3 TAPE SYSOUT=A SYSOUT=J DSN FILE1 FILE2 FILE3 UNIT TAPE TAPE TAPE SYSOUT=A SYSOUT=J * Old Keep Keep RECFMT DISP Old, Keep Keep Old Keep Keep New Pass Delete

Compiler Return Codes


Level W - Warning - Return Code 4


Level C - Condition - Return Code 8 Level E - Errors Level F - Fatal
45

- Return Code 12 - Return Code 16

Compile, Link, & Execute


//OSJCL JOB // // //COB EXEC //SYSPRINT DD //SYSUT1 DD // //SYSUT2 DD //
46

(OSJCL,04/03/98),M.R.IZZO, CLASS=T,MSGLEVEL=(1,1), MSGCLASS=A PGM=IKFCBL00,PARM=LOAD SYSOUT=A UNIT=SYSDA, SPACE=(460,(700,100)) UNIT=SYSDA, SPACE=(460,(700,100))

//SYSUT3 DD UNIT=SYSDA, // SPACE=(460,(700,100)) //SYSUT4 DD UNIT=SYSDA, // SPACE=(460,(700,100)) //SYSLIN DD DSNAME=&&LOADSET, // DISP=(MOD,PASS,DELETE), // UNIT=SYSDA,SPACE=(80,(500,100)) //SYSIN DD * * * Source Input /*

47

//LKED EXEC PGM=IEWL, // PARM=(LIST,XREF,LET), // COND=(5,LT,COB) //SYSLIN DD DSN=&&LOADSET, // DISP=(OLD,DELETE,KEEP) //SYSLMOD DD DSN=&&GOSET(GO), // DISP=(NEW,PASS,DELETE), // UNIT=SYSDA, // SPACE=(1024,(50,20,1)) //SYSUT1 DD UNIT=SYSDA, // SPACE=(1028,(50,20)) //SYSPRINT DD SYSOUT=A
48

//GO EXEC // //TPEIN DD // // // // //TPEOUT DD // // //

PGM=*.LKED.SYSLMOD, COND=((5,LT,COB),(5,LT,LKED)) UNIT=TAPE,DSN=PR.FLE, DISP=(OLD,KEEP,KEEP), DCB=(RECFM=FB,LRECL=150), DCB=(BLKSIZE=300), VOL=SER=00978 UNIT=TAPE,DSN=PR.FLE, DISP=(NEW,CATLG,DELETE), DCB=(RECFM=FB,LRECL=150), DCB=(BLKSIZE=300)

49

//DSKIN DD UNIT=DISK,DSN=PR.TRANS, // DISP=(OLD,KEEP,KEEP), // DCB=(RECFM=FB,LRECL=200), // DCB=(BLKSIZE=400) //DSKOUT DD UNIT=DISK,DSN=ED.PR.TRANS, // DISP=(NEW,CATLG,DELETE), // SPACE=(TRK,(10,5),RLSE) //PRT DD SYSOUT=A //SYSUDUMP DD SYSOUT=A //CRDIN DD * * * Card Input /* //
50

Fig. 12.1: One data control block is coded for each file accessed by a program.
* * SCREEN PRINTER /* //LINE //DATAIN /* // DD DD parameters DATA CONTROL BLOCKS DCB MACRF=GM,DSORG=PS, EODAD=QUIT,DDNAME=DATAIN DCB MACRF=PM,DSORG=PS,DDNAME=LINE

parameters

Load module

Fig. 12.2: The linkage editor adds an access method to the load module.

Object module

SCREEN

DCB

MACRF=GM,DSORG=PS,...

PRINTER DCB

MACRF=PM,DSORG=PS,...

Access method for SCREEN Access method for PRINTER

Other subroutines

Fig. 12.3: The link to a specific physical device is established at OPEN time.

SCREEN

DCB DDNAME=DATAIN,...

OPEN

(SCREEN,INPUT)

//DATAIN DD

parameters

Access methods and other subroutines

Magnetic Disk Parameters

UNIT DCB DISP DSNAME VOLUME SPACE

Fig. 12.8: Some examples.


1. Create a temporary data set on the system work pack. //DISK // // DD DSNAME=&&TEMP,UNIT=SYSDA, DISP=(NEW,PASS),SPACE=(CYL,5), DCB=(LRECL=120,BLKSIZE=2400,RECFM=FB)

2. Create a cataloged data set on a specific volume. //RECS // // // DD DSN=MU.USERDATA.MIS4,UNIT=3330, VOL=SER=MIAMI3,DISP=(NEW,CATLG), SPACE=(TRK,(20,5),RLSE,CONTIG), DCB=(LRECL=155,RECFM=FB,BLKSIZE=1550)

3. Create a kept data set. //KEEPIT // // // DD SPACE=(CYL,(10,2),RLSE), DCB=(RECFM=FB,LRECL=72,BLKSIZE=720), VOL=SER=MYPACK,DISP=(NEW,KEEP), DSNAME=MYDATA,UNIT=3330

Fig. 12.8: Some Examples


4. Retrieve a passed data set. //DATA DD DSNAME=&&TEMP,DISP=(OLD,DELETE)

5. Retrieve a cataloged data set //STUFF DD DSN=MU.USERDATA.SAN4,DISP=OLD

6. Retrieving a kept data set that has not been cataloged requires UNIT and VOLUME parameters in addition to DSNAME and DISP //DDNAME // DD DSNAME=MYDATA,UNIT=3330, VOL=SER=MYPACK,DISP=(OLD,KEEP)

Magnetic Tape Parameters

UNIT DCB DISP DSNAME VOLUME LABEL

System Input and Output

Spooling -- slower devices System input device


//SYSIN DD *

System output device


//SYSOUT DD SYSOUT=A

Fig. 12.9: The DDNAME can be qualified if it is part of a catalogued procedure.


//JOBNAME // //FORT.SYSIN JOB EXEC DD (9824,18),DAVIS,CLASS=A FORTRAN *

FORTRAN source module /* //GO.SYSIN Data /* DD *

Fig. 12.10: Code the library member name as part of the DDNAME.

DSNAME=library(member)

a member name parentheses are required the library name

Fig. 12.11: A complete set of JCL to support an assemble, link edit, and go job. //MU132 JOB 1
2 3 4 5 6 7 8 9 10 // XXASM XXSYSLIB XXSYSUT1 XXSYSUT2 XXSYSUT3 XXSYSPRINT XXSYSPUNCH XXSYSGO XX XX //ASM.SYSIN EXEC EXEC DD DD DD DD DD DD DD DD ASMGCLG PGM=IEUASM DSNAME=SYS1.MACLIB,DISP=SHR SYSOUT=A SYSOUT=B DSNAME=&&LOADSET,DISP=(NEW,PASS), SPACE=(400,(100,20)),UNIT=SYSDA, DCB=(LRECL=80,BLKSIZE=400,RECFM=FB) *

11 12 13

Source code /*

Fig. 12.11: Continued

14 15 16 17

XXLKED XXSYSLIN XX XX XXSYSLMOD XXSYSUT1 XXSYSPRINT /*

EXEC DD DD DD DD DD

PGM=IEWL DSNAME=&&LOADSET, DISP=(OLD,DELETE) DCB=(LRECL=80,BLKSIZE=400,RECFM=FB) DDNAME=SYSIN DSNAME=&&GOSET(GO),DISP=(NEW,PASS), SPACE=(1024,(50,20,1)), UNIT=SYSDA SYSOUT=A

18 19 20

Fig. 12.11: Continued

21 22 23 24 25 26 27

XXGO

EXEC

PGM=*.LKED.SYSLMOD SYSOUT=A Parameters for program disk file *

//GO.OUTPUT DD //GO.DISK DD //GO.SYSIN DD Data /* //

Вам также может понравиться