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-DAY - Date conversion

The INTEGER-OF-DAY function converts a date in the Gregorian calendar from Julian date form (YYYYDDD) to integer date form.
The type of this function is integer.

Format


FUNCTION INTEGER-OF-DAY (argument-1)


Argument

  1. argument-1 must be an integer of the form YYYYDDD, whose value is obtained from the calculation: (YYYY * 1000) + DDD

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

    • DDD represents the day of the year. It must be a positive integer less than 367 but 366 may only be specified for a leap year.

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, in the Gregorian calendar.

  2. The error default value is 0.


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

Example 9-18

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

Result:              0143474
                         The 299th day of the year 1993 is the 143474th day as of 31.12.1600.