INCLUDE Numeric Tests Example


Scenario - Filter the records having the ID is numeric. The ID starts from 1st and ends at 5th column in the file.

Input File - MATEPK.SORT.INPUT

----+----1----+---2----+----3----+---4----+---5----+---6----+---7---+---8
00002     Srinivas            Employee             
test	  test                test
00001     pawan kumar         student

Input Record Layout -

01 INPUT-REC.
	05 ID			PIC X(05).
	05 FILLER		PIC X(05).
	05 NAME			PIC X(15).
	05 FILLER		PIC X(05).
	05 OCCUPATION 		PIC X(10).
	05 FILLER		PIC X(40).

JCL -

----+----1----+----2----+----3----+----4----+----5----+
//MATEPKD  JOB (123),'MTH',NOTIFY=&SYSUID
//*
//STEP01   EXEC PGM=SORT
//SORTIN   DD DSN=MATEPK.SORT.INPUT,DISP=SHR
//SORTOUT   DD DSN=MATEPK.MERGE.OUTPUT,
//            DISP=(NEW,CATLG,DELETE),UNIT=SYSDA,
//            SPACE=(CYL,(1,4),RLSE),
//            DCB=(RECFM=FB,LRECL=80,BLKSIZE=0)
//SYSOUT   DD SYSOUT=*
//SYSIN    DD *
     INCLUDE COND=(1,05,FS,EQ,NUM)
     SORT FIELDS=COPY 
/* 

Output -

----+----1----+----2---+---3---+----4---+----5---+----6---+---7----+---8
00002     Srinivas            Employee 
00001     pawan kumar         student

Explaining Example -

  1. As a first step, we need to get the position of the ID in the file. The ID starting from 1st position and ends at 5th position as per the input record layout provided. So the length of ID field is 5.
  2. As a second step, we need to get the type of the ID. From the Input record layout declaration, ID field is alpha-numeric. But we need only numeric data from it. So the type is FS.
  3. Lastly, the job requirement is to filter the data with the ID as numeric. So the keyword NUM should use to match the condition.
  4. INCLUDE COND=(1,05,FS,EQ,NUM)
    - The output would have the records where the IDs are numeric at first 5 positions.