Jcl
Introduction to JCL Jcl coding sheet JOB Statement Exec statement DD Statement Concatenating Datasets Referback in JCL Special DD statements Utility Programs Utility program IEBGENER Utility programs IEBCOPY and IEBCOMPR DFSort DFSort reformat dataset DFSort INCLUDE OMIT COND Procedures generation data group (GDG) JCL quick study JCL Interview questionsDFSort Conditions
While using DFSort to sort records we can specify conditions to select specific records by using INCLUDE COND or OMIT COND. You can specify either an INCLUDE statement or an OMIT statement in the same DFSORT run, but not both as they are mutually exclusive.
Use an INCLUDE statement if you want only certain records to appear in the output data set. The INCLUDE statement selects the records you want to include.
Use an OMIT statement if you want exclude certain records fromn the output data set. The OMIT statement excludes the records you want to omit.
Syntax:
INCLUDE COND =(Start-byte,Length,Format,relational operator,Constant)
OMIT COND =(Start-byte,Length,Format,relational operator,Constant)
Start-byte | Starting position of the field |
Length | Length of the field |
Format | CH (EBCDIC character), AC (ASCII character), FS (Signed numeric character), D1 (User-defined data type) |
Relational operator | GT Greater than EQ Equal to LT Less than GE Greater than or equal to NE Not equal to LE Less than or equal to |
Constant | Decimal constant 12,-16,222,46 Hexadecimal “ X’nnnn…nn’ Character “ C’character-literals’ |
The INCLUDE COND or OMIT COND should be coded before Sort Fields and Inrec Fields in the SYSIN parameters.
Lets consider the following example with the file structure:
01 WS-DATE-RNAME.
05 EMPID PIC 9(05).
05 EMPLOYEENAME PIC A(25).
05 PROJECT PIC X(15).
05 SALARY PIC 9(09).
05 FILLER PIC x(26).
The example Input file is PS with fixed length
- EMPID starting at absolute byte 1, for 5 bytes long
- EMPLOYEENAME at absolute byte 6, for 25 bytes long
- PROJECT at absolute byte 31, for 15 bytes long
- SALARY at byte 46, for 9 bytes long
To select employees getting a salary of 25000 and sort in ascending order of employee number
//PROGPUBA JOB NOTIFY=PROGPUB
//STEP010 EXEC PGM=SORT
//SYSPRINT DD SYSOUT=*
//SYSOUT DD SYSOUT=*
//SORTIN DD DSN=
//SORTOUT DD DSN=
//SYSIN DD *
INCLUDE COND=(46,9,CH,GT,C’25000)
SORT FIELDS=(1,3,CH,A)
/*
We can also use OMIT COND to exclude employees with salary greater than 25000
//PROGPUBA JOB NOTIFY=PROGPUB
//STEP010 EXEC PGM=SORT
//SYSPRINT DD SYSOUT=*
//SYSOUT DD SYSOUT=*
//SORTIN DD DSN=
//SORTOUT DD DSN=
//SYSIN DD *
OMIT COND=(46,9,CH,GT,C’25000)
SORT FIELDS=(1,3,CH,A)
/*
/*
Can use connect operators AND and OR to form several logical conditions and here is an example
//PROGPUBA JOB NOTIFY=PROGPUB
//STEP010 EXEC PGM=SORT
//SYSPRINT DD SYSOUT=*
//SYSOUT DD SYSOUT=*
//SORTIN DD DSN=
//SORTOUT DD DSN=
//SYSIN DD *
INCLUDE COND=(1,2,CH,EQ,C'AB',OR,1,2,CH,EQ,C'CD',
OR,1,2,CH,EQ,C'EF') OR
INCLUDE COND=(1,2,CH,EQ,L(C'AC',C'AJ',C'CY'))
SORT FIELDS=(1,3,CH,A)
/*
/*
To COPY dataset
We can use DFSORT to copy a dataset with other control cards like INCLUDE COND, OMIT COND, INREC FIELDS and OUTREC FIELDS.
//PROGPUBA JOB NOTIFY=PROGPUB
//STEP010 EXEC PGM=SORT
//SYSPRINT DD SYSOUT=*
//SYSOUT DD SYSOUT=*
//SORTIN DD DSN=
//SORTOUT DD DSN=
//SYSIN DD *
OMIT COND=(46,5,CH,EQ,C’1000)
SORT FIELDS=(1,3,CH,A)
OUTREC FIELDS=(1,5,46,5)
/*
/*
To concatenate datasets & sort
The SORT program can be used to concatenate two or more datasets and merge into one dataset. An example JCL is
//PROGPUBA JOB NOTIFY=PROGPUB
//STEP010 EXEC PGM=SORT
//SYSPRINT DD SYSOUT=*
//SYSOUT DD SYSOUT=*
//SORTIN DD DSN=
// DD DSN=
//SORTOUT DD DSN=
//SYSIN DD *
SORT FIELDS=(1,5,CH,A)
/*
/*
Datasets can be merged using MERGE FIELDS instead SORT FIELDS. If the MERGE FIELDS is used to merge data the only condition is dataset should be SORTED before merging. This is an example JCL
//PROGPUBA JOB NOTIFY=PROGPUB
//STEP010 EXEC PGM=SORT
//SYSPRINT DD SYSOUT=*
//SYSOUT DD SYSOUT=*
//SORTIN01 DD DSN=
//SORTIN02 DD DSN=
//SORTOUT DD DSN=
//SYSIN DD *
MERGE FIELDS=(1,5,CH,A)
/*
//
The merging of fixed length dataset will work like a charm but if the dataset is of different LRECL, then we can concatenate different LRECL datasets as long as the highest LRECL is coded first. THe output dataset will have the the highest LRECL.
Example JCLs:
JCL to sort a file with an include condition and to remove duplicates.
File Edit Edit_Settings Menu Utilities Compilers Test Help
-------------------------------------------------------------------------------
EDIT PROGPUB.AA.SOURCE(SRTJCL) - 01.13 Member SRTJCL saved
****** ***************************** Top of Data ******************************
==MSG> -Warning- The UNDO command is not available until you change
==MSG> your edit profile using the command RECOVERY ON.
000001 //PROGPUBC JOB NOTIFY=PROGPUB
000002 //S1 EXEC PGM=SORT
000003 //SYSPRINT DD SYSOUT=*
000004 //SYSOUT DD SYSOUT=*
000005 //SORTIN DD DSN=PROGPUB.AA.A1,DISP=SHR
000006 //SORTOUT DD DSN=PROGPUB.AA.A2,DISP=SHR
000007 //SYSIN DD *
000008 SORT FIELDS=(1,3,CH,A,11,2,CH,A)
000009 INCLUDE COND=(1,1,CH,EQ,C'A')
000010 SUM FIELDS=NONE
000011 /*
000012 //
****** **************************** Bottom of Data ****************************
JCL to sort a file with omit condition and to remove duplicates.
File Edit Edit_Settings Menu Utilities Compilers Test Help
-------------------------------------------------------------------------------
EDIT PROGPUB.AA.SOURCE(SRTJCL) - 01.13 Columns 00001 00072
****** ***************************** Top of Data ******************************
==MSG> -Warning- The UNDO command is not available until you change
==MSG> your edit profile using the command RECOVERY ON.
000001 //PROGPUBC JOB NOTIFY=PROGPUB
000002 //S1 EXEC PGM=SORT
000003 //SYSPRINT DD SYSOUT=*
000004 //SYSOUT DD SYSOUT=*
000005 //SORTIN DD DSN=PROGPUB.AA.A1,DISP=SHR
000006 //SORTOUT DD DSN=PROGPUB.AA.A2,DISP=SHR
000007 //SYSIN DD *
000008 SORT FIELDS=(1,3,CH,A,11,2,CH,A)
000009 OMIT COND=(1,1,CH,EQ,C'A')
000010 SUM FIELDS=NONE
000011 /*
000012 //
****** **************************** Bottom of Data ****************************