Top
NetCOBOL V11.0 Syntax Samples
FUJITSU Software

1.47 INTEGER-OF-DATE and DATE-OF-INTEGER Functions

The INTEGER-OF-DATE function accepts a date in the format YYYYMMDD and returns the number of days since January 1, 1601. The converse function, DATE-OF-INTEGER accepts an integer argument and converts it to a date in the format YYYYMMDD, where the integer argument is the number of days since January 1, 1601.

000010 @OPTIONS MAIN
000020*----------------------------------------------------------------------
000030* In this sample, the INTEGER-OF-DATE and DATE-OF-INTEGER functions are 
000040* used to obtain the date after the specified number of days has
000045* elapsed.
000050*----------------------------------------------------------------------
000060 IDENTIFICATION   DIVISION.
000070 PROGRAM-ID.      SAMPLE.
000080 DATA             DIVISION.
000090 WORKING-STORAGE  SECTION.
000100 01 TODAY.
000110    02 YYYYMMDD   PIC 9(8).
000120 01 OTHER-DAY1    PIC S9(9) BINARY.
000130 01 OTHER-DAY2    PIC 9(8).
000140 01 DAYS          PIC S9(4) BINARY.
000150 PROCEDURE        DIVISION.
000160     MOVE FUNCTION CURRENT-DATE TO TODAY.
000170     DISPLAY "Today is " TODAY ".".
000180     DISPLAY "Obtain the date after how many days? >> " WITH NO 
000185             ADVANCING.
000190     ACCEPT DAYS.
000200*----------------------------------------------------------------------
000210* The date after the specified number of days has elapsed is obtained 
000215* by calculating the number of days from January 1, 1601 and adding the 
000216* days entered by the user.
000220*----------------------------------------------------------------------
000230     COMPUTE OTHER-DAY1 = FUNCTION INTEGER-OF-DATE (YYYYMMDD) + DAYS.
000240*----------------------------------------------------------------------
000250* To display the date, the newly computed number of days is converted 
000255* to standard format (YYYYMMDD).
000260*----------------------------------------------------------------------
000270     COMPUTE OTHER-DAY2 = FUNCTION DATE-OF-INTEGER (OTHER-DAY1).
000280*----------------------------------------------------------------------
000290     DISPLAY " ".
000300     DISPLAY "The date after " DAYS " days from " TODAY " is " 
000305             OTHER-DAY2 ".".
000310 END PROGRAM SAMPLE.