INCLUDE: Alphanumeric Tests


  • INCLUDE can be used to perform arithmetic tests during sorting.

Syntax -


INCLUDE COND=(Field1 starting position, Field1 Length, Field1 format,
		 Relational Operator,alphanumeric_char)
Field1 starting position Starting position of field1 to be compared
Field1 Length Length of the field1 to be compared
Field1 format_type Specifies the format of the field1.Use BI for Alphanumeric tests
Relation operator Relational operators like GT, EQ, NE, LT etc,.
EQ 		Equal to
NE 		Not equal to
GT 		Greater than
GE 		Greater than or equal to
LT 		Less than
LE 		Less than or equal to
alphanumeric_char Specifies the alphanumeric character typeThe set of alphanumeric characters are provided below:
UC: Uppercase characters (A-Z)
LC: Lowercase characters (a-z)
MC: Mixed case characters (A-Z, a-z)
UN: Uppercase and numeric characters (A-Z, 0-9)
LN: Lowercase and numeric characters (a-z, 0-9)
MN: Mixed case and numeric characters (A-Z, a-z, 0-9)

Example -


Scenario - From the below data, filter the records having the ID is alphanumeric and only numeric. The ID starts from 1st and ends at 5th column in the file.

Input File - MTH.SORT.INPUT

----+----1----+----2----+----3----+----4----+----5---+---6---+---7---+---8
********************************* Top of Data *****************************
00002     Srinivas            Employee                          
test3     test3               test3
test      test                test
00001     Pawan kumar         Student                                   
******************************** Bottom of Data ***************************

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----+----6----+----7--
***************************** Top of Data ******************************
//Job-card
//*                                                     
//*****************************************************************
//*                                           
//* SORT TO WRITE ALPHANUMERIC TEST IN INCLUDE CONDITION FOR MIXED
//* NUMERIC CASE                             
//*                                                  
//*****************************************************************
//STEP01   EXEC PGM=SORT           
//SORTIN   DD DSN=MTH.SORT.INPUT,DISP=SHR
//SORTOUT  DD SYSOUT=*  
//SYSOUT   DD SYSOUT=*
//SYSIN    DD *
     INCLUDE COND=(1,05,BI,EQ,MN)                        
     SORT FIELDS=COPY                                       
/*                                                        
**************************** Bottom of Data ***********************

Output -

---+---1---+---2----+---3----+----4---+---5---+---6----+----7---+---8
********************************* TOP OF DATA ******************************
00002     Srinivas            Employee                           
test3     test3               test3
00001     pawan kumar         student                            
******************************** BOTTOM OF DATA ****************************

Explaining Example -

  1. As a first step, need to get the position of the ID in the file.
  2. The names starting from 1st position and ends at 5th position as per the input record layout provided. So the length of ID field is 5.
  3. As a Second step, need to get the type of the ID.
  4. From the Input record layout declaration, ID field is alpha-numeric. For alpha-numeric test, use BI instead of the actual field type.
  5. Lastly, the job requirement is to filter the data with the ID having alphanumeric and only numeric. So the keyword MN should use to match the condition.
  6. The INCLUDE condition for the above requirement with all the data gathered is
    INCLUDE COND=(1,05,BI,EQ,MN) 
  7. The above condition specifies that include the records where the ID having alphanumeric and only numeric.
  8. The output would have the records where the IDs are alphanumeric and only numeric at first 5 positions.