Top
NetCOBOL V11.0 Syntax Samples
FUJITSU Software

1.44 CURRENT-DATE Function

The CURRENT-DATE function is used to obtain the current date and time.

The FROM phrase of the ACCEPT statement can also be used to obtain the current date and time. However, the ACCEPT statement returns only the two low-order digits of the year. To obtain all four digits of the year, use the CURRENT-DATE function.

000010 @OPTIONS MAIN
000020*----------------------------------------------------------------------
000030* The date, time, day of the week, and time difference with Greenwich 
000040* mean time obtained using the CURRENT-DATE function are displayed.
000050*----------------------------------------------------------------------
000060 IDENTIFICATION   DIVISION.
000070 PROGRAM-ID.      SAMPLE.
000080 DATA             DIVISION.
000090 WORKING-STORAGE  SECTION.
000100 01 TODAY.
000110    02 CR-YEAR      PIC X(4).
000120    02 CR-MON       PIC X(2).
000130    02 CR-DAY       PIC X(2).
000140    02 CR-HOUR      PIC X(2).
000150    02 CR-MIN       PIC X(2).
000160    02 CR-SEC       PIC X(2).
000170    02 CR-MSEC      PIC X(2).
000180    02 LOCAL-TIME.
000190      03 TIME-DIF     PIC X(1).
000200      03 TIME-DIF-H   PIC X(2).
000210      03 TIME-DIF-M   PIC X(2).
000220 01 CR-DOW        PIC 9(1).
000230 CONSTANT         SECTION.
000240 01 DOW-TABLE.
000250    02                PIC X(9) VALUE "Monday".
000260    02                PIC X(9) VALUE "Tuesday".
000270    02                PIC X(9) VALUE "Wednesday".
000280    02                PIC X(9) VALUE "Thursday".
000290    02                PIC X(9) VALUE "Friday".
000300    02                PIC X(9) VALUE "Saturday".
000310    02                PIC X(9) VALUE "Sunday".
000320 01               REDEFINES DOW-TABLE.
000330    02 DOW            OCCURS 7 TIMES PIC X(9).
000340 PROCEDURE        DIVISION.
000350*----------------------------------------------------------------------
000360* The CURRENT-DATE function obtains the current date and time.
000370* Because the CURRENT-DATE function cannot obtain the day of the week, 
000380* use the DAY-OF-WEEK phrase of the ACCEPT statement.
000390*----------------------------------------------------------------------
000400     MOVE FUNCTION CURRENT-DATE TO TODAY.
000410     ACCEPT CR-DOW FROM DAY-OF-WEEK.
000420*----------------------------------------------------------------------
000430     DISPLAY "Date: Year " CR-YEAR  " Month " CR-MON 
000435             " Day " CR-DAY "(" DOW(CR-DOW) ")".
000440     DISPLAY "Time: Hour " CR-HOUR  " Minute " CR-MIN  
000445             " Second " CR-SEC "." CR-MSEC.
000450     IF LOCAL-TIME NOT = 0 THEN
000460       DISPLAY "Time difference with Greenwich mean time for this time 
000465-              "zone: "
000470               TIME-DIF TIME-DIF-H " Hours " TIME-DIF-M " Minutes"
000480     END-IF.
000490 END PROGRAM SAMPLE.