The YEAR-TO-YYYY function converts a 2-digit year into 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
YEAR-TO-YYYY
(argument-1 [argument-2])
Arguments
argument-1 must be a positive number less than 100.
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.
Returned values
The returned value is the year specified in argument-1 together with the century.
The returned value depends on the intermediate valueL1L2L3L4 = current year +argument-2 (= last year of the 100-year interval).
The century is calculated as follows:100 * L1L2 + YY
if L3L4 >= YY
(YY = argument-1)
100 * (L1L2 - 1) + YY if L3L4 < YY The error default value is 0
See also: DATE-TO-YYYYMMDD, DAY-TO-YYYYDDD
Example 9-49
... DATA DIVISION. WORKING-STORAGE SECTION. 01 A-DATE PIC 9(7). 01 CURRENT-YEAR PIC 9(7). 01 YEAR PIC 9(7). PROCEDURE DIVISION. P1 SECTION. MAIN. * * Calculation of the function with a floating window: * * The 100-year interval in which the calculated year falls is to * include the years (current year -35) through (current year +64): * COMPUTE A-DATE = FUNCTION YEAR-TO-YYYY (59 64). DISPLAY A-DATE UPON T. (1) * * Without 2nd argument (or 2nd argument =50) * The 100-year interval includes the years (current year -49) * through (current year +50): * COMPUTE A-DATE = FUNCTION YEAR-TO-YYYY (0). DISPLAY A-DATE UPON T. (2) * * The 2nd argument can also be negative * The 100-year interval includes the years (current year -109) * through (current year -10): * COMPUTE A-DATE = FUNCTION YEAR-TO-YYYY (96 -10). DISPLAY A-DATE UPON T. (3) * * Calculation of the function with a fixed window * * The 100-year interval in which the calculated year falls is to * include the years 1950 through 2049: * * Calculation of the last year of the 100-year interval * relative to the current year * MOVE FUNCTION CURRENT-DATE(1:4) TO CURRENT-YEAR. COMPUTE YEAR = 2049 - CURRENT-YEAR. * Calculation of the function values COMPUTE A-DATE = FUNCTION YEAR-TO-YYYY (50 YEAR). DISPLAY A-DATE UPON T. (4) COMPUTE A-DATE = FUNCTION YEAR-TO-YYYY (1 YEAR). DISPLAY A-DATE UPON T. (5) * * The 100-year interval in which the calculated year falls is to * include the years 1890 through 1989: * * Calculation of the last year of the 100-year interval * relative to the current year * MOVE FUNCTION CURRENT-DATE(1:4) TO CURRENT-YEAR. COMPUTE YEAR = 1989 - CURRENT-YEAR. * Calculation of the function values COMPUTE A-DATE = FUNCTION YEAR-TO-YYYY (89 YEAR). DISPLAY A-DATE UPON T. (6) COMPUTE A-DATE = FUNCTION YEAR-TO-YYYY (90 YEAR). DISPLAY A-DATE UPON T. (7) STOP RUN.
In the year 1996 the program returns the following results:
(1) 2059
(2) 2000
(3) 1896
(4) 1950
(5) 2001
(6) 1989
(7) 1890
In the year 2050 the program returns the following results:
(1) 2059
(2) 2100
(3) 1996
(4) 1950
(5) 2001
(6) 1989
(7) 1890