OUTREC: Date Operations


Converting date -


OUTREC statement can be used for converting date formats of a date field while sorting.

Syntax -


OUTREC BUILD=(Starting position of field1, Length of field1,
		existing date field1 format(Y2X/Y4X), 
		Conversion operator=Target date field1 formats(Y2X/Y4X),….. )
Starting position of field1Specifies field1 starting position in the input file after sorting.
Length of feild1Field1 physical length in input file.
Existing date field1 formatSpecifies source n-digit year date field formats.
  • Y4W and Y4T are two of DFSORT's 4-digit year date field formats.
  • Y4W indicates adate value with the year (ccyy) last such as 'mmddccyy' or 'dddccyy'.
  • Y4T indicates a date value with the year first such as 'ccyymmdd' or 'ccyyddd'.
  • Y2W and Y2T are two of DFSORT's 2-digit year date field formats.
  • Y2W indicates adate value with the year (yy) last such as 'mmddyy' or 'dddyy'.
  • Y2T indicates a date value with the year first such as 'yymmdd' or 'yyddd'.
  • The two formats can be represented in common as Y2X, Y4X.
  • X should be either W or T.
Conversion operator Specifies the keyword for target format operator. The below are the list of format operators -
  • TOJUL=YnX - converts to a julian date without a separator.
  • TOJUL=YnX(s) - converts to a julian date with a separator.
  • TOGREG=YnX - converts to a gregorian date without separators.
  • TOGREG=YnX(s) - converts to a gregorian date with separators.
  • WEEKDAY=CHAR3 - converts to a 3 character day of the week.
  • WEEKDAY=CHAR9 - converts to a 9 character day of the week.
  • WEEKDAY=DIGIT1 - converts to a 1 digit indicator for the day of the week.
Target date field1 formatsSpecifies the target n-digit year date field formats.

Example -


Scenario - Convert the date from mmddccyy to ccyymmm(juliyan date). New ouput layout would be

01 OUTPUT-REC.
  	05 STD-ID			PIC X(05).
	05 FILLER			PIC X(05).
	05 STD-NAME			PIC X(15).
	05 FILLER			PIC X(05).
	05 STD-DEPT	 		PIC X(10).
	05 FILLER			PIC X(05).
	05 STD-MARKS		PIC 9(03).
	05 FILLER			PIC X(07).
	05 STD-JDATE		PIC X(07).    
	05 FILLER			PIC X(18).

Input File - MTHUSER.SORT.INPUT01 - FB file of 80 length

----+----1----+----2----+----3----+----4----+----5----+----6----+----7----+----8
********************************* Top of Data **********************************
00001     student1           dept1          560       01012015                  
00003     student3           dept2          520       03032015                  
00004     student4           dept1          540       06022015                  
00005     student5           dept2          500       09202015                  
00002     student2           dept3          510       05182015                  
******************************** Bottom of Data ********************************

Input Record Layout -

01 INPUT-REC.
  	05 STD-ID			PIC X(05).
	05 FILLER			PIC X(05).
	05 STD-NAME			PIC X(15).
	05 FILLER			PIC X(05).
	05 STD-DEPT	 		PIC X(10).
	05 FILLER			PIC X(05).
	05 STD-MARKS			PIC 9(03).
	05 FILLER			PIC X(07).
	05 STD-DATE			PIC X(08).    
	05 FILLER			PIC X(17).

JCL -

----+----1----+----2----+----3----+----4----+----5----+----6----+----7--
***************************** Top of Data ******************************
//Job-card 
//*                                                                     
//**********************************************************************
//*                                                                     
//* SORT FOR OUTREC STATEMENT                                           
//*                                                                     
//**********************************************************************
//STEP01   EXEC PGM=SORT                                                
//SORTIN   DD DSN=MTHUSER.SORT.INPUT01,DISP=SHR                    
//SORTOUT  DD SYSOUT=*                                                  
//SYSOUT   DD SYSOUT=*                                                  
//SYSIN    DD *                                                         
     SORT FIELDS=(1,5,CH,A)                                             
     OUTREC FIELDS=(1,54,55,8,Y4W,TOJUL=Y4T)                            
/*                                                                      
**************************** Bottom of Data ****************************

Output -

----+----1----+----2----+----3----+----4----+----5----+----6----+----7----+----8
********************************* TOP OF DATA **********************************
00001     student1           dept1          560       2015001                   
00002     student2           dept3          510       2015138                   
00003     student3           dept2          520       2015062                   
00004     student4           dept1          540       2015153                   
00005     student5           dept2          500       2015263                   
******************************** BOTTOM OF DATA ********************************

Explaining Example -

  1. OUTREC FIELDS=(1,54,..) copies first 54 bytes of input file data to output as it is.
  2. OUTREC FIELDS=(..,55,8,Y4W,TOJUL=Y4T)- data from 55th byte of length 8 will be converted to Y4T Julian date format.

Input date 01012015 will be converted as 2015001.

Arithmetic operations on date -


OUTREC statement can be used for arithmetic data operations on the date field while sorting.

Syntax -


OUTREC BUILD=(Starting position of field1, Length of field1,
		existing date field1 format(Y2X/Y4X), Arithmetic operator, +n/-n,…)
Starting position of field1Specifies field1 starting position in the input file after sorting.
Length of feild1Field1 physical length in input file.
Existing date field1 formatSpecifies source n-digit year date field formats.
  • Y4W and Y4T are two of DFSORT's 4-digit year date field formats.
  • Y4W indicates adate value with the year (ccyy) last such as 'mmddccyy' or 'dddccyy'.
  • Y4T indicates a date value with the year first such as'ccyymmdd' or 'ccyyddd'.
  • Y2W and Y2T are two of DFSORT's 2-digit year date field formats.
  • Y2W indicates adate value with the year (yy) last such as 'mmddyy' or 'dddyy'.
  • Y2T indicates a date value with the year first such as 'yymmdd' or 'yyddd'.
  • The two formats can be represented in common as Y2X, Y4X.
  • X should be either W or T.
Arithmetic operator Arithmetic operation to perform The below are list of Arithmetic operations used -
  • ADDDAYS, ADDMONS and ADDYEARS can be used to add days, months or years to a date field.
  • SUBDAYS, SUBMONS and SUBYEARS can be used to subtract days, months or years from a date field.
  • DATEDIFF can be used to calculate the number of days between two date fields.
  • NEXTDday can be used to calculate the next specified day of the week for a date field.
  • PREVDday can be used to calculate the previous specified day of the week for a date.
  • LASTDAYW, LASTDAYM, LASTDAYQ and LASTDAYY can be used to calculate the last day of the week, month, quarter or year for a date field.
+n/-n Specifies the number days/months/years used to perform an arithmetic operation

Example -


Scenario - Add two days, two years to the date in the input file. The new output record layout should be

01 OUTPUT-REC.
  	05 STD-ID			PIC X(05).
	05 FILLER			PIC X(05).
	05 STD-NAME			PIC X(15).
	05 FILLER			PIC X(04).
	05 STD-DEPT	 		PIC X(10).
	05 FILLER			PIC X(05).
	05 STD-MARKS			PIC 9(03).
	05 FILLER			PIC X(07).
	05 STD-DATE			PIC X(08).    
	05 FILLER			PIC X(05).
	05 STD-DATE			PIC X(08).    
	05 FILLER			PIC X(05).

Input File - MTHUSER.SORT.INPUT01 - FB file of 80 length

----+----1----+----2----+----3----+----4----+----5----+----6----+----7----+----8
********************************* Top of Data **********************************
00001     student1           dept1          560       01012015                  
00003     student3           dept2          520       03032015                  
00004     student4           dept1          540       06022015                  
00005     student5           dept2          500       09202015                  
00002     student2           dept3          510       05182015                  
******************************** Bottom of Data ********************************

Input Record Layout -

01 INPUT-REC.
  	05 STD-ID			PIC X(05).
	05 FILLER			PIC X(05).
	05 STD-NAME			PIC X(15).
	05 FILLER			PIC X(04).
	05 STD-DEPT	 		PIC X(10).
	05 FILLER			PIC X(05).
	05 STD-MARKS			PIC 9(03).
	05 FILLER			PIC X(07).
	05 STD-DATE			PIC X(08).    
	05 FILLER			PIC X(17).

JCL -

----+----1----+----2----+----3----+----4----+----5----+----6----+----7--
***************************** Top of Data ******************************
//Job-card 
//*                                                                     
//**********************************************************************
//*                                                                     
//* SORT FOR OUTREC STATEMENT                                           
//*                                                                     
//**********************************************************************
//STEP01   EXEC PGM=SORT                                                
//SORTIN   DD DSN=MTHUSER.SORT.INPUT01,DISP=SHR                    
//SORTOUT  DD SYSOUT=*                                                  
//SYSOUT   DD SYSOUT=*                                                  
//SYSIN    DD *                                                         
     SORT FIELDS=(1,5,CH,A)                                             
     OUTREC FIELDS=(1,54,55,8,Y4W,ADDDAYS,+2,TOJUL=Y4T(/),              
                      5X,55,8,Y4W,ADDYEARS,+2,TOJUL=Y4T(/))             
/*                                                                      
**************************** Bottom of Data ****************************

Output -

----+----1----+----2----+----3----+----4----+----5----+----6----+----7----+----8
********************************* TOP OF DATA **********************************
00001     student1           dept1          560       2015/003     2017/001     
00002     student2           dept3          510       2015/140     2017/138     
00003     student3           dept2          520       2015/064     2017/062     
00004     student4           dept1          540       2015/155     2017/153     
00005     student5           dept2          500       2015/265     2017/263     
******************************** BOTTOM OF DATA ********************************

Explaining Example -

  1. OUTREC FIELDS=(1,54,..) copies the first 54 bytes from the input file to output as it is.
  2. OUTREC FIELDS=(..,55,8,Y4W,ADDDAYS,+2,TOJUL=Y4T(/),..) – adds +2 days to the date in the input file and converts it to Julian date before writing it to output file from 55th position.
  3. OUTREC FIELDS=(..,5X,..) - adds 5 spaces from 63rd position
  4. OUTREC FIELDS=(..,55,8,Y4W,ADDYEARS,+2,TOJUL=Y4T(/)) - adds +2 years to the date in the input file and converts it to Julian date before writing it to output file from 68th position.