Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

DAY-OF-INTEGER - Date conversion

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

Format


FUNCTION DAY-OF-INTEGER (argument-1)


Argument

  1. argument-1 is a positive integer that represents a number of days succeeding December 31, 1600, in the Gregorian calendar.

Returned values

  1. The returned value represents the Julian equivalent of the integer specified in argument-1.

  2. YYYY represents a year in the Gregorian calendar, and DDD represents the day of that year.

  3. The error default value is 0.


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

Example 9-12

...
DATA DIVISION.
WORKING-STORAGE SECTION.
01  DAYS PIC 9999 VALUE 5000.
01  A-DATE PIC X(7).
PROCEDURE DIVISION.
P1 SECTION.
MAIN.
    COMPUTE A-DATE = FUNCTION DAY-OF-INTEGER (DAYS)
    DISPLAY A-DATE UPON T.
    STOP RUN. 

Result:               1614252
                          The 5000th day as of 31.12.1600 was the 252nd day of the year 1614.