Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

INTEGER-OF-DATE - Date conversion

The INTEGER-OF-DATE function converts a date in the Gregorian calendar from standard date form (YYYYMMDD) to integer date form.
This type of this function is integer.

Format


FUNCTION INTEGER-OF-DATE (argument-1)


Argument

  1. argument-1 must be an integer of the form YYYYMMDD, whose value is obtained from the calculation: (YYYY * 10000) + (MM * 100) + DD

    • YYYY represents the year in the Gregorian calendar. It must be an integer greater than 1600.

    • MM represents a month and must be a positive integer less than 13.

    • DD represents a day and must be a positive integer less than 32 provided that it is valid for the specified month and year combination.

Returned values

  1. The returned value is an integer that is the number of days the date represented by argument-1 succeeds December 31, 1600, (on sunday) in the Gregorian calendar.

  2. The error default value is 0.


See also:
        INTEGER-OF-DAY, DATE-OF-INTEGER, DAY-OF-INTEGER, CURRENT-DATE, WHEN-COMPILED

Example 9-17

...
DATA DIVISION.
WORKING-STORAGE SECTION.
01  DAYS PIC 9(8).
PROCEDURE DIVISION.
P1 SECTION.
MAIN.
    COMPUTE DAYS = FUNCTION INTEGER-OF-DATE (19530410).
    DISPLAY DAYS UPON T.
    STOP RUN. 

Result:               00128665
                          10.4.1953 was the 128665th day as of 31.12.1600.