Pages

Saturday, June 14, 2014

REXX - Count records in PDS in Mainframe



This REXX code is to count the record in the PDS in Mainframe, just copy paste it into the pds and execute it



/*Rexx                                                                */
/*~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~*/
/* Runs ICETOOL to count records                                      */
/* */
/*                                                                    */
/*~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~*/
/* get dataset name                                                   */
/*_ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ */
/*                                                                    */

TRACE o
X = MSG("Off")

arg count_dsn
if length(search_dsn)=0 then do
   say "Dataset name required"
   say "Enter dataset name or press enter to quit"
   pull count_dsn
   if length(count_dsn)=0 then exit
   end

count_dsn = strip(count_dsn,b,"'")

/*                                                                    */
/*~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~*/
/* check dsorg of dataset and determine type of record count          */
/* to perform.                                                        */
/*_ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ */
/*                                                                    */

x = LISTDSI("'"count_dsn"'" directory smsinfo)

Select
When SYSDSORG = PO Then
   Do
   Say "Sorry, this function does not work for libraries"
   Exit 4
   End
When SYSUNIT ^= 3390 Then
   Do
   Say "Sorry, this function only works for files on disk"
   Exit 4
   End
When SYSDSORG = VS Then Call VCount
OTHERWISE
   Call DCount


Exit Return_Code

/*                                                                    */
/*~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~*/
/*                                                                    */
/*_ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ */
/*                                 */
DCOUNT:

/*~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~*/
/* Count DD                        */
/*_ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _*/
/*                                 */

"FREE  da('"count_dsn"')"

"ALLOC File(countdd) da('"count_dsn"') shr"

/*~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~*/
/* Toolin                          */
/*_ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _*/
/*                                 */

  toolin = 'ttlu.BASE.cntl(icecount)'

"FREE FILE(TOOLIN)"
"FREE  da('"TOOLIN"')"

"ALLOC  F(toolIN) da('"TOOLIN"')"

/*~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~*/
/* Toolmsg                         */
/*_ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _*/
/*                                 */

  tmsgdsn = 'TTLU.']]SYSVAR("SYSUID")]]'.toolmsg'

"FREE FILE(TOOLMSG)"
"FREE  da('"TMSGDSN"')"


"DELETE '"tmsgdsn"'"
"ALLOC F(toolmsg) DA('"tmsgdsn"')
 NEW CYLINDERS CATALOG SPACE(1,1)
 UNIT(SYSDA)
 BLKSIZE(0) RECFM(F,B,A) LRECL(133)"

/*~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~*/
/* DFSMsg                          */
/*_ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _*/
/*                                 */

dmsgdsn = 'TTLU.']]SYSVAR("SYSUID")]]'.dfsmsg'

"FREE FILE(DFSMSG)"
"FREE  da('"DMSGDSN"')"

"DELETE '"dMsgdsn"'"
"ALLOC F(dfsmsg) DA('"dMsgdsn"')
 NEW CYLINDERS CATALOG SPACE(1,1)
 UNIT(SYSDA)
 BLKSIZE(0) RECFM(F,B,A) LRECL(133)"

/*~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~*/
/* Run                             */
/*_ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _*/
/*                                 */

/* "ICETOOL"     */

ADDRESS LINKMVS ICETOOL
Retcd = RC
If Retcd ^= 0 Then Say 'Return code is ' RC

/*~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~*/
/* Free datasets                   */
/*_ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _*/
/*                                 */
Address TSO

  "FREE FILE(toolin)"
  "FREE FILE(toolmsg)"
  "FREE FILE(dfsmsg)"

/*~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~*/
/* Dig out the record count from   */
/* the Toolmsg file                */
/*_ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _*/
/*                                 */

  "FREE FILE(INDD)"
  "ALLOC FILE(INDD) DA('"tmsgdsn"') SHR",

  eof = 'no'                            /* initialize end-of-file  */
  hit_count=0
  x t_count=0

"EXECIO * DISKR Indd (STEM Irec." /* READ A LINE             */

DO x = 1 TO Irec.0

/*      Say 'Checking line ' Irec.x  */

        If substr(Irec.x,2,22) = 'ICE628I 0 RECORD COUNT' Then
           Do
           Count = substr(Irec.x,27,15)
           If count = 000000000000000 Then
              Count = 0
           Else
           Count = strip(substr(Irec.x,27,15),l,'0')

Say 'The Record Count for dataset ' Count_dsn ' = ' count

        "FREE FILE(indd)"
        "FREE FILE(toolin)"
        "FREE FILE(toolmsg)"
        "FREE FILE(dfsmsg)"
        "FREE FILE(Countdd)"
           Exit
           End
     End
  End
        "FREE FILE(indd)"
        "FREE FILE(toolin)"
        "FREE FILE(toolmsg)"
        "FREE FILE(dfsmsg)"
        "FREE FILE(Countdd)"
Return
/*~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~*/
/* VCOUNT                                                             */
/*                                                                    */
/*~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~*/
VCount:

X = OUTTRAP(Irec.)
ADDRESS TSO
"LISTC ENT('"Count_DSN"') ALL"

/*~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~*/
/* Analyze outtrap & extract the   */
/* relevant parameters             */
/*_ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _*/
/*                                 */


DO x = 1 TO Irec.0

/* Say "Rec number is " x                     */
/* Say "Record being checked is " Irec.x      */

   If substr(Irec.x,8,9) = 'REC-TOTAL' Then
      Do
      Count  = strip(substr(Irec.x,17,15),l,'-')
      Say 'The Record Count for dataset ' Count_dsn ' = ' count
      Exit 0
      End
End


Return

REXX Basics

What is REXX?

•REstructered eXtended eXecutor language
•Developed by M.F.Cowlishaw of IBM U.K.
•Introduced in 1983
•Highly versatile programming language
•Can  be intermixed with commands to different host environments

Setting up to Execute REXX Programs on TSO/ISPF

This is what you can do so that you will be able to execute your REXX program on MVS TSO/ISPF.

There are several ways that this can be done. 

1. The simpliest of them all, dumb way. 

If you do it this way, you can’t create and use REXX external subroutines. 
Briefly: no setup is done. 
You just put your REXX program in a PDS member or even in a sequential file. 
Then execute it this way from the command line of any ISPF panel: 

TSO EXEC 'the-name-of-the-PDS(member-name)' EXEC

2. The "Ideal way" from the point of view of the person executing the program. 
not so ideal for the technical support personnel.

Your REXX program is a member in a PDS that everyone has read access to. 
This PDS name is specified in the TSO Logon Procedure that is executed everytime you and everyone logs on. 
This is a part of it.

//TSOSTEP EXEC PGM=IKJEFT01
//SYSTSPRT DD TERM=TS 
//SYSEXEC DD DSN=the-name-of-the-pds,DISP=SHR
// DD DSN=name-of-another-pds,DISP=SHR


3. You wait till you get into ISPF. Then you type in the following in option 6, or on the ISPF panel command line, preceded by the word TSO:


ALTLIB DEACTIVATE APPL(EXEC) 
ALTLIB ACTIVATE APPL(EXEC) DA('name-of-your-REXX-PDS')

You have to do this on both halves of a split screen and every time you log on. 
A suggested way of doing this is to put the above command in a CLIST or REXX program, then execute the program. 
This example shows a CLIST.

ALTLIB DEACTIVATE APPL(EXEC) 
ALTLIB ACTIVATE APPL(EXEC) DA('name-of-your-REXX-PDS') 
This example shows a REXX program.

/* REXX */ 
"ALTLIB DEACTIVATE APPL(EXEC)" 
"ALTLIB ACTIVATE APPL(EXEC) DA('name-of-your-REXX-PDS')"

REXX - HELLO WORLD

Let try out our first REXX module and enjoy.

/* REXX */
SAY 'HELLO WORLD'

Put this in a PDS member (ideally, create one like Letmetry.REXX.EXEC).

Now, there are various ways by which you can invoke a REXX program.


1. From ISPF main panel, run the command

TSO EX 'Letmetry.REXX.EXEC(HELLO)' EX


2. From READY Prompt, run the command,

EX 'Letmetry.REXX.EXEC(HELLO)' EX



3. Using 3.4, browse to the PDS Letmetry.REXX.EXEC.
Before the member HELLO, enter EX and press enter.



4. You can also run the REXX program through a JCL. The following is the JCL step that you need.


//REXXBTCH EXEC PGM=IKJEFT01
//SYSEXEC DD DSN=MYHQL.REXX.EXEC,DISP=SHR
//SYSTSPRT DD SYSOUT=*
//SYSTSIN DD *
%HELLO
/*

The above are the manual ways. Below are the advanced methods which needs special privileges

IF you have added the PDS to SYSEXEC then we can execute even by below commands. This needs admin access, Just execute this once and using the below methods you can easily execute them

/* rexx */
/* Rexx lib */
DSNAME = 'BNKSPS.TSO.CMD'
DDNAME = 'SYSPROC'
 /* To get all DSNs already associated to SYSPROC    */
ADDRESS ISPEXEC "QBASELIB" DDNAME "ID(DSLIST)"
 /* ADDRESS ISPEXEC "GETPROF DSLIST" */
say DSLIST;
 /* to allocate DSNs already allocated to SYSPROC plus my DSN */
"ALLOC F("DDNAME") DA("DSLIST",'"DSNAME"') SHR REUSE"
RETURN


1. You just need to execute command from ISPF,

TSO HELLO


2. From READY prompt, just enter


HELLO

Tuesday, March 12, 2013

JCL Utility programs


Sample codes


IEBGENER
1. IEBGENER to copy a PS file --> (  Click me to copy )
//*IEBGENER TO COPY A SEQUENTIAL FILE
//*-------------------------------------
//STEP1 EXEC PGM=IEBGENER
//SYSPRINT DD SYSOUT=A
//SYSUT1 DD DISP=SHR,DSN=ICAMBV1.INPUT.PS1
//SYSUT2 DD DSN=ICAMBV1.OUTPUT.PS1,SPACE=(TRK,(1,1)),
// DISP=(MOD,CATLG)
//SYSIN DD DUMMY

2. IEBGENER to print a PS file--> (  Click me to copy )
//*IEBGENER TO PRINT A PS FILE
//*-------------------------------------
//STEP1 EXEC PGM=IEBGENER
//SYSPRINT DD SYSOUT=A
//SYSUT1 DD DISP=SHR,DSN=ICAMBV1.INPUT.PS1
//SYSUT2 DD SYSOUT=*
//SYSIN DD DUMMY

3. IEBGENER to copy a sequential file with reformatting --> (  Click me to copy )
//*IEBGENER TO CREATE AN EDITED COPY OF A PS FILE
//*-------------------------------------
//STEP1 EXEC PGM=IEBGENER
//SYSPRINT DD SYSOUT=A
//SYSUT1 DD DISP=SHR,DSN=ICAMBV1.INPUT.PS1
//SYSUT2 DD DSN=ICAMBV1.OUTPUT.PS1,SPACE=(TRK,(1,1)),
// DISP=(NEW,CATLG,DELETE),
// DCB=(RECFM=FB,LRECL=80)
//SYSIN DD *
GENERATE MAXFLDS=2,MAXLITS=5
RECORD FIELD=(10,10,,1),FIELD=(5,'IBM ',,15)
/*


IEBCOPY

4. IEBCOPY to Copy a PDS to another existing PDS  --> (  Click me to copy )
//*IEBCOPY TO COPY A PDS TO ANOTHER EXISTING PDS
//*-------------------------------------
//STEP1 EXEC PGM=IEBCOPY
//SYSPRINT DD SYSOUT=A
//INFILE DD DSN=ICAMBV1.INPUT.PDS1,DISP=SHR
//OUTFILE DD DSN=ICAMBV1.OUTPUT.PDS1,DISP=OLD
//SYSIN DD *
COPY OUTDD=OUTFILE,INDD=INFILE
/*

5. IEBCOPY to merge 2 PDS  --> (  Click me to copy )
//*IEBCOPY TO MERGE 2 PDS
//*-------------------------------------
//STEP1 EXEC PGM=IEBCOPY
//SYSPRINT DD SYSOUT=A
//DDIN DD DSN=ICAMBV1.INPUT.PDS1,DISP=OLD
//DDOUT DD DSN=ICAMBV1.INPUT.PDS2,DISP=OLD
//SYSIN DD *
COPY OUTDD=DDOUT,INDD=DDIN
/*

6. IEBCOPY to copy members of 2 PDS to another PDS  --> (  Click me to copy )
//*IEBCOPY TO COPY CONTENTS OF 2 PDS TO ANOTHER PDS
//*------------------------------------------------
//STEP1 EXEC PGM=IEBCOPY
//SYSPRINT DD SYSOUT=A
//INFILE DD DSN=ICAMBV1.INPUT.PDS1,DISP=SHR
//INFILE2 DD DSN=ICAMBV1.INPUT.PDS2,DISP=SHR
//OUTFILE DD DSN=ICAMBV1.OUTPUT.PDS1,DISP=(SHR,CATLG,)
//SYSIN DD *
COPY OUTDD=OUTFILE,INDD=INFILE,INFILE2
/*

IDCAMS

7. IDCAMS to copy selected number of records   --> (  Click me to copy )
//* IDCAMS to copy selected number of records
//COPY EXEC PGM=IDCAMS
//SYSPRINT DD SYSOUT=A
//INDD DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//OUTDD DD DSNAME=ICAMBV1.OUTPUT.PS6,DISP=(NEW,CATLG),
// SPACE=(TRK,(10,10)),LRECL=80,RECFM=FB
//* SPACE=(TRK,(10,10)),LRECL=800,RECFM=VB,DSORG=PS
//SYSIN DD *
REPRO INFILE(INDD) -
OUTFILE(OUTDD) -
SKIP(5) -
COUNT(5)
/*

8. IDCAMS to define a KSDS file  --> (  Click me to copy )
//* IDCAMS to copy selected number of records
//COPY EXEC PGM=IDCAMS
//SYSPRINT DD SYSOUT=A
//INDD DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//OUTDD DD DSNAME=ICAMBV1.OUTPUT.PS6,DISP=(NEW,CATLG),
// SPACE=(TRK,(10,10)),LRECL=80,RECFM=FB
//* SPACE=(TRK,(10,10)),LRECL=800,RECFM=VB,DSORG=PS
//SYSIN DD *
REPRO INFILE(INDD) -
OUTFILE(OUTDD) -
SKIP(5) -
COUNT(5)
/*

9. IDCAMS to load a KSDS file from a PS file   --> (  Click me to copy )
//* IDCAMS TO LOAD A KSDS FILE FROM A PS FILE
//STEP1 EXEC PGM=IDCAMS
//SEQFILE DD DSN='ICAMBV1.INPUT.PS1',DISP=SHR
//SYSPRINT DD SYSOUT=A
//SYSIN DD *
REPRO INFILE(SEQFILE) -
OUTDATASET('ICAMBV1.VSAM.KSDS1') -
REPLACE
/*

10. IDCAMS to print the contents of a KSDS file   --> (  Click me to copy )
//* IDCAMS TO PRINT THE CONTENT OF KSDS FILE
//STEP1 EXEC PGM=IDCAMS,REGION=4096K
//SYSPRINT DD SYSOUT=A
//INPUT DD DSN='ICAMBV1.VSAM.KSDS1.DATA',DISP=OLD
//SYSIN DD *
PRINT INFILE(INPUT) -
CHAR
/*



DFSORT
DFSORT is a sort, merge, copy, analysis, and reporting utility for Mainframe environment.
DFSORT can sort, copy or merge fixed-length or variable-length records.
Sorting Data Sets
DFSORT can be used to arrange records in either ascending or descending order within a file.
You can sort data in different formats like Character(CH),Zoned Decimal(ZD), Packed
Decimal(PD), Binary(BI) etc.
//SYSOUT DD Defines the data set in which DFSORT messages and control statements are
listed.
//SORTIN DD Defines the input data set or concatenated input data sets.
//SORTWKdd DD Defines a work data set for a sort. Typically not needed, because DFSORT can
allocate work data sets for a sort dynamically.
//SORTOUT DD Defines the output data set.
//SYSIN DD contains the program control statements.
SORTFIELDS=(Start,Length,DataType,Order)



11. DFSORT to sort a PS file   --> (  Click me to copy )
//* DFSORT TO SEQUENCE A PS FILE
//* CHARACTER :CH, ZONED DECIMAL:ZD,PACKED DECIMAL PD, BINARY :BI
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//SORTOUT DD DSNAME=ICAMBV1.OUTPUT.PS41,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SORTWK01 DD SPACE=(TRK,(1,1))
//SYSIN DD *
SORT FIELDS=(10,10,CH,A)
/*

12. DFSORT to sort a PS file (Using FORMAT=field type)  --> (  Click me to copy )
//* DFSORT TO SEQUENCE A PS FILE
//* SPECIFY FORMAT=TYPE FOR SAME TYPE OF FIELD
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//SORTOUT DD DSNAME=ICAMBV1.OUTPUT.PS42,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SYSIN DD *
SORT FIELDS=(10,10,D,20,10,D),FORMAT=CH
/*


Copying Data Sets
DFSORT can be used to copy data sets without any sorting or merging actions.

13. DFSORT to copy a PS file to a new PS file  --> (  Click me to copy )
//* DFSORT TO COPY A PS FILE TO A NEW PS FILE
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//SORTOUT DD DSNAME=ICAMBV1.OUTPUT.PS43,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SYSIN DD *
SORT FIELDS=COPY
/*

14. Sort a PS file and remove duplicate records  --> (  Click me to copy )
//* DFSORT TO SEQUENCE A PS FILE AND REMOVE DUPLICATES
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS11,DISP=SHR
//SORTOUT DD DSNAME=ICAMBV1.OUTPUT.PS45,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SYSIN DD *
SORT FIELDS=(10,10,CH,A)
SUM FIELDS=NONE
/*


Merging Data Sets
DFSORT can merge two or more files of sorted records and create a single data set of sorted
records. The data sets you merge must be previously sorted into the same order.

15. Merge 2 PS files and create an output PS file  --> (  Click me to copy )
//* DFSORT TO MERGE 2 PS FILES AND CREATE A NEW PS FILE
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN01 DD DSNAME=ICAMBV1.INPUT.PS41,DISP=SHR
//SORTIN02 DD DSNAME=ICAMBV1.INPUT.PS42,DISP=SHR
//SORTOUT DD DSNAME=ICAMBV1.OUTPUT.PS45,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SYSIN DD *
MERGE FIELDS=(1,9,CH,A)
SUM FIELDS=NONE
/*
Select a subset of records
You can include or omit records from the input file that meets a specified criteria using INCLUDE
and OMIT statements.

16. Select needed records using INCLUDE and OMIT statements   --> (  Click me to copy )
//* DFSORT TO SELECT needed RECORDS ONLY
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//SORTOUT DD DSNAME=ICAMBV1.OUTPUT.PS46,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SYSIN DD *
INCLUDE COND=((10,1,CH,NE,C'A'),AND,(1,2,ZD,LT,8))
SORT FIELDS=COPY
/*

17. Reformat using INREC and OUTREC  --> (  Click me to copy )
//* DFSORT TO REFORMAT USING INREC & OUTREC
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//SORTOUT DD DSNAME=ICAMBV1.OUTPUT.PS47,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SYSIN DD *
INREC FIELDS=(10,20)
SORT FIELDS=(1,10,CH,D)
OUTREC FIELDS=(10,10)
/*

18. Insert a text in the output file using OUTREC  --> (  Click me to copy )
//* DFSORT TO INSERT A TEXT IN THE OUTPUT FILE OUTREC
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//SORTOUT DD DSNAME=ICAMBV1.OUTPUT.PS48,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SYSIN DD *
SORT FIELDS=(10,10,CH,A)
OUTREC FIELDS=(C'EmplId of ',10,10,C' is ',30,10)
/*

19. Sort records into different files using OUTFIL  --> (  Click me to copy )
//* DFSORT TO sort records into different files
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//OUTPUT1 DD DSNAME=ICAMBV1.OUTPUT.PS491,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//OUTPUT2 DD DSNAME=ICAMBV1.OUTPUT.PS492,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SYSIN DD *
SORT FIELDS=(10,10,CH,A)
OUTFIL FNAMES=OUTPUT1, X
INCLUDE=(10,1,CH,EQ,C'A')
OUTFIL FNAMES=OUTPUT2, X
INCLUDE=(10,1,CH,NE,C'A')
/*


20. Create a report using OUTFIL  --> (  Click me to copy )
//* DFSORT TO create a report using OUTFIL
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS4,DISP=SHR
//SORTOUT DD DSNAME=ICAMBV1.OUTPUT.PS410,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SYSIN DD *
SORT FIELDS=(10,10,CH,A)
OUTFIL HEADER1=(20:'Sample Report',8X,&DATE=(DM4/),8X,'PAGE: ',&PAGE),x
HEADER2=(10:'Employee Details',30X,'PAGE: ',&PAGE,/, x
5:'sl',9X,'Name1',9X,'Name2',9X,'EmpID'), x
OUTREC=(5:1,9,3X,10,10,3X,20,10,3X,30,10,20X), x
TRAILER1=(15:'TOTAL NO OF RECORDS IS ',COUNT,/, x
20:'***** END OF REPORT *****')
/*


21. DFSORT to display only the total count using OUTFIL  --> (  Click me to copy )
//* DFSORT to display only the total count using OUTFIL
//STEP1 EXEC PGM=SORT
JCL Utility Programs
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS4,DISP=SHR
//SORTOUT DD DSNAME=ICAMBV1.OUTPUT.PS411,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SYSIN DD *
SORT FIELDS=(10,10,CH,A)
OUTFIL TRAILER1=(15:'TOTAL NO OF RECORDS IS ',COUNT),NODETAIL
/*


22. DFSORT to create a SUMMARY report  --> (  Click me to copy )
//* DFSORT to create a SUMMARY report
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//SORTOUT DD DSNAME=ICAMBV1.OUTPUT.PS121,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SYSIN DD *
SORT FIELDS=(70,5,CH,A)
SUM FIELDS=(60,10,ZD)
OUTREC FIELDS=(C'Total Salary of Employees in ',70,5,C' is ',60,10)
/*


23. DFSORT: Using Symbols for Fields in DFSORT Statements   --> (  Click me to copy )
//*DFSORT: Using Symbols for Fields in DFSORT Statements
//* SYMNAMES dataset contains the symbol info
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//SORTOUT DD DSNAME=ICAMBV1.OUTPUT.PS131,DISP=(NEW,CATLG,CATLG),
// SPACE=(TRK,(1,1))
//SYMNAMES DD DSN=ICAMBV1.INPUT.SYMBOL,DISP=SHR
//SYSIN DD *
INCLUDE COND=(Project,EQ,C'Italy')
SORT FIELDS=(LName,D)
/*


SPLIT
SPLIT is the easiest way to split up a data set. It can be used to split the records as evenly as
possible among the output data sets. SPLIT writes one record to each output data set in rotation.
Here's an example of SPLIT for an input data set with 14 records.
The first sorted record is written to the OUT1 data set, the second sorted record is written to the
OUT2 data set, the third sorted record is written to the OUT3 data set, the fourth sorted record is
written to the OUT1 data set, and so on in rotation.
14. DFSORT: To SPLIT a PS file into multiple PS files
//*DFSORT: To split a PS file into multiple PS files
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//OUT1 DD DSNAME=ICAMBV1.OUTPUT.PS141,DISP=(NEW,CATLG,DELETE),
JCL Utility Programs
// SPACE=(TRK,(1,1))
//OUT2 DD DSNAME=ICAMBV1.OUTPUT.PS142,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//OUT3 DD DSNAME=ICAMBV1.OUTPUT.PS143,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SYSIN DD *
SORT FIELDS=(10,10,CH,A)
OUTFIL FNAMES=(OUT1,OUT2,OUT3),SPLIT
/*
INCLUDE/OMIT and SAVE
INCLUDE/OMIT and SAVE can be used to select specific records to be included in each output
data set. The INCLUDE and OMIT operands provide all of the capabilities of the INCLUDE and
OMIT statements including substring search and bit logic. SAVE can be used to select the
records that are not selected for any other subset, eliminating the need to specify complex
conditions.


24. DFSORT: To select specific records using INCLUDE/OMIT and SAVE   --> (  Click me to copy )
//*DFSORT: To select specific records using INCLUDE/OMIT and SAVE
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//OUT1 DD DSNAME=ICAMBV1.OUTPUT.PS151,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//OUT2 DD DSNAME=ICAMBV1.OUTPUT.PS152,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//OUT3 DD DSNAME=ICAMBV1.OUTPUT.PS153,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SYSIN DD *
OPTION COPY
OUTFIL INCLUDE=(70,10,CH,EQ,C'Italy'),FNAMES=OUT1
OUTFIL INCLUDE=(70,10,CH,EQ,C'UK'),FNAMES=OUT2
OUTFIL SAVE,FNAMES=OUT3
/*

STOPAFT/SKIPREC
STOPAFT and SKIPREC options can be used to reduce the number of input records. Use
STOPAFT to specify the maximum number of records to be accepted for sorting or copying. Use
SKIPREC to specify the number of records to be skipped before sorting or copying begins.


25. DFSORT: To eliminate records with STOPAFT and SKIPREC   --> (  Click me to copy )
//*DFSORT: To eliminate records with STOPAFT and SKIPREC
//STEP1 EXEC PGM=SORT
//SYSOUT DD SYSOUT=A
//SORTIN DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//SORTOUT DD DSNAME=ICAMBV1.OUTPUT.PS161,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//SYSIN DD *
OPTION COPY,
SKIPREC=10,
STOPAFT=5
/*



ICETOOL
ICETOOL is a multipurpose DFSORT utility that uses the capabilities of DFSORT to perform
multiple operations on one or more data sets in a single step.
TOOLMSG - ICETOOL message data set.
This data set has the same attributes as the DFSORT SYSOUT data set.
DFSMSG - DFSORT message data set.
This data set has the same attributes as the DFSORT SYSOUT data set.
TOOLIN - ICETOOL statements.
This data set has the same attributes as the DFSORT SYSIN data set.
Comment statements start with an asterisk (*) in column 1 and are printed along with the
ICETOOL operator statements.
STATS Operator
STATS operator can be used to find the minimum, maximum, average, and total values of up to
10 specific numeric fields.
STATS FROM(DDNAME) ON(start ,length ,type) ON(start, length, type)


26.ICETOOL to print statistics for numeric field   --> (  Click me to copy )
//* ICETOOL to print statistics for numeric field
//STEP1 EXEC PGM=ICETOOL
//TOOLMSG DD SYSOUT=A
//DFSMSG DD SYSOUT=A
//INDD DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//TOOLIN DD *
STATS FROM(INDD) ON(60,10,ZD)
/*

SORT Operator
SORT operator can be used to sort a data set to one or more output data sets.
SORT FROM (INDDname)TO(OUTDDname1,OUTDDname2)USING(Control file)
USING specifies the first four characters of the ddname for the data set containing the DFSORT
control statements. The last four characters of the ddname are always CNTL.


27) ICETOOL to create identical sorted data sets  --> (  Click me to copy )
//* ICETOOL to create identical sorted data sets
//STEP1 EXEC PGM=ICETOOL
//TOOLMSG DD SYSOUT=A
//DFSMSG DD SYSOUT=A
//INDD DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//OUTDD1 DD DSNAME=ICAMBV1.OUTPUT.PS51,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//OUTDD2 DD DSNAME=ICAMBV1.OUTPUT.PS52,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
JCL Utility Programs
//TOOLIN DD *
* Sort records by name and write to multiple output files
SORT FROM(INDD) TO(OUTDD1,OUTDD2) USING(SAMP)
/*
//SAMPCNTL DD *
SORT FIELDS=(10,10,CH,D)
* substring search can be used in include statement
INCLUDE COND=(70,5,SS,EQ,C'Italy,UK ')
/*


28) ICETOOL to create different subsets of a sorted dataset   --> (  Click me to copy )
//* ICETOOL to create different subsets of a sorted dataset
//STEP1 EXEC PGM=ICETOOL
//TOOLMSG DD SYSOUT=A
//DFSMSG DD SYSOUT=A
//INDD DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//OUTDD1 DD DSNAME=ICAMBV1.OUTPUT.PS531,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//OUTDD2 DD DSNAME=ICAMBV1.OUTPUT.PS532,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//TOOLIN DD *
* Sort records by name and write to multiple output files
SORT FROM(INDD) USING(SAMP)
/*
//SAMPCNTL DD *
SORT FIELDS=(10,10,CH,A)
OUTFIL INCLUDE=(70,5,CH,EQ,C'Italy'),FNAMES=(OUTDD1)
OUTFIL INCLUDE=(70,5,CH,EQ,C'UK'),FNAMES=(OUTDD2)
/*



COPY Operator
COPY operator can be used to create one or more copies of an input data set.
The COPY operator does not require any DFSORT statements. However, you can supply
DFSORT statements (for example, INCLUDE, OMIT, INREC, OUTREC, or OUTFIL) if
appropriate.
Because copying is more efficient than sorting, you should use the COPY operator rather than
the SORT operator when possible.


29) ICETOOL to create multiple unsorted datasets   --> (  Click me to copy )
//* ICETOOL to create multiple unsorted datasets
//STEP1 EXEC PGM=ICETOOL
//TOOLMSG DD SYSOUT=A
//DFSMSG DD SYSOUT=A
//INDD DD DSNAME=ICAMBV1.INPUT.PS1,DISP=SHR
//OUTDD1 DD DSNAME=ICAMBV1.OUTPUT.PS541,DISP=(NEW,CATLG,DELETE),
// SPACE=(TRK,(1,1))
//OUTDD2 DD DSNAME=ICAMBV1.OUTPUT.PS542,DISP=(NEW,CATLG,DELETE),
JCL Utility Programs
// SPACE=(TRK,(1,1))
//OUTDD3 DD SYSOUT=A
//TOOLIN DD *
* Sort records by name and write to multiple output files
COPY FROM(INDD) TO(OUTDD1,OUTDD2)
COPY FROM(INDD) TO(OUTDD3) USING(SAMP)
/*
//SAMPCNTL DD *
INCLUDE COND=(70,5,CH,EQ,C'UK')
/*


THX
JGR