Your Browser is not longer supported

Please use Google Chrome, Mozilla Firefox or Microsoft Edge to view the page correctly
Loading...

{{viewport.spaceProperty.prod}}

DATE-TO-YYYYMMDD - year conversion

The DATE-TO-YYYYMMDD function converts a date specified with argument-1 from the standard date format with a 2-digit year into the standard 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 DATE-TO-YYYYMMD (argument-1 [argument-2])


Arguments

  1. argument-1 must be a positive number less than 1000000.

  2. argument-2, if specified, must be an integer.

  3. If argument-2 is not specified, the value 50 is taken for the second argument.

  4. The sum of the current year and argument-2 must be less than 10000 and greater than 1699.

  5. No check is run to verify whether argument-1 is a valid date. This means that the values 0 and 999999 are also valid arguments for the DATE-TO-YYYYMMDD 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

  1. The returned value is the date specified in argument-1 with a 4-digit year. For an argument of the form YYMMDD, the returned value is defined by:
    FUNCTION YEAR-TO-YYYY (YY, argument-2) * 10000 + MMDD

  2. The error default value is 0.


See also:
DAY-TO-YYYYDDD, YEAR-TO-YYYY

Example 9-11

...
DATA DIVISION.
WORKING-STORAGE SECTION.
01  A-DATE         PIC 9(8).
PROCEDURE DIVISION.
P1 SECTION.
MAIN.   
    COMPUTE A-DATE = FUNCTION DATE-TO-YYYYMMDD (590123).   
    DISPLAY A-DATE UPON T.                                           (1)   
    COMPUTE A-DATE = FUNCTION DATE-TO-YYYYMMDD (470101 -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) 19590123
(2) 18470101

In the year 2009 the program returns the following results:
(1) 20590123
(2) 19470101