The DAY-TO-YYYYDDD function converts a date specified with argument-1 from the Julian date format with a 2-digit year into the Julian date format with a 4-digit year. The end of the 100-year interval in which the year specified in argument-1 falls is determined by adding argument-2 to the current year (the year in which the function is executed) ("floating window").
The type of this function is integer.
Format
FUNCTION DAY-TO-YYYYDDD (argument-1 [argument-2])
Arguments
argument-1 must be a positive number less than 100000.
argument-2, if specified, must be an integer.
If argument-2 is not specified, the value 50 is taken for the second argument.
The sum of the current year and argument-2 must be less than 10000 and greater than 1699.
No check is run to verify whether argument-1 is a valid date. This means that the values 0 and 99999 are also valid arguments for the DAY-TO-YYYYDDD function if a check of the arguments is required by one of the options CHECK-FUNCTION-ARGUMENTS = YES or SET-FUNCTION-ERROR-DEFAULT = YES.
Returned values
The returned value is the date specified in argument-1 with a 4-digit year. For an argument of the form YYDDD, the returned value is defined by:
FUNCTION YEAR-TO-YYYY (YY, argument-2) * 1000 + DDDThe error default value is 0.
See also: DATE-TO-YYYYMMDD, YEAR-TO-YYYY
Example 9-13
... DATA DIVISION. WORKING-STORAGE SECTION. 01 A-DATE PIC 9(7). PROCEDURE DIVISION. P1 SECTION. MAIN. COMPUTE A-DATE = FUNCTION DAY-TO-YYYYDDD (59001). DISPLAY A-DATE UPON T. (1) COMPUTE A-DATE = FUNCTION DAY-TO-YYYYDDD (47365 -50). DISPLAY A-DATE UPON T. (2) STOP RUN.
A more detailed example is provided with the description of the YEAR-TO-YYYY function.
Result:
In the year 1996 the program returns the following results:
(1) 1959001
(2) 1847365
In the year 2009 the program returns the following results:
(1) 2059001
(2) 1947365