Calls to CEESECS and CEEDATM in COBOL

CBL LIB,QUOTE
      *Module/File Name: IGZTDT2
      ************************************************************
      **                                                        **
      ** CEE80DAT - Call CEESECS to convert timestamp to seconds**
      **            and CEEDATM to convert seconds to timestamp **
      **                                                        **
      **  CEESECS is used to convert a timestamp to seconds.    **
      **  24 hours in seconds is subtracted from                **
      **  the number of seconds in the original timestamp.      **
      **  CEEDATM is then used to build a new timestamp for     **
      **  the updated number of seconds.                        **
      **                                                        **
      ************************************************************
       IDENTIFICATION DIVISION.
       PROGRAM-ID. CE80DAT.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
      *  Double precision needed for the seconds results
       01  START-SECS              COMP-2.
       01  NEW-TIME                COMP-2.
       01  FC.
           02  Condition-Token-Value.
           COPY  CEEIGZCT.
               03  Case-1-Condition-ID.
                   04  Severity        PIC S9(4) BINARY.
                   04  Msg-No          PIC S9(4) BINARY.
               03  Case-2-Condition-ID
                         REDEFINES Case-1-Condition-ID.
                   04  Class-Code      PIC S9(4) BINARY.
                   04  Cause-Code      PIC S9(4) BINARY.
               03  Case-Sev-Ctl    PIC X.
               03  Facility-ID     PIC XXX.
           02  I-S-Info        PIC S9(9) BINARY.
       01  PICSTR.
           02  Vstring-length      PIC S9(4) BINARY.
           02  Vstring-text.
               03  Vstring-char        PIC X
                           OCCURS 0 TO 256 TIMES
                           DEPENDING ON Vstring-length
                              of PICSTR.
       01  WS-TIMESTAMP.
           02  Vstring-length      PIC S9(4) BINARY.
           02  Vstring-text.
               03  Vstring-char        PIC X
                           OCCURS 0 TO 256 TIMES
                           DEPENDING ON Vstring-length
                              of WS-TIMESTAMP.
       01  NEW-TIMESTAMP           PIC X(80).
       01  INPUT-VARIABLES.
           05  SECONDS-DISPLACED   PIC S9(9) BINARY.
           05  ELAPSED-TIME-OUT    PIC +Z(4)9.99.

       PROCEDURE DIVISION.
       0001-BEGIN-PROCESSING.
           MOVE  14 TO Vstring-length of PICSTR.
           MOVE "MM/DD/YY HH:MI" TO Vstring-text of PICSTR.
           MOVE 14 TO Vstring-length of WS-TIMESTAMP.
           MOVE "11/02/92 05:22" TO Vstring-text of WS-TIMESTAMP.
      *    **********************************************************
      *    * CEESECS is invoked to obtain the Lilian seconds tally  *
      *    * corresponding to the timestamp 11/02/92 05:22.         *
      *    * The Lilian seconds tally is returned in the double-    *
      *    * precision floating-point field START-SECS.             *
      *    **********************************************************
           CALL "CEESECS" USING WS-TIMESTAMP, PICSTR, START-SECS, FC.
           IF CEE000 of FC THEN
      *        **********************************************
      *        * The Lilian seconds tally in START-SECS is  *
      *        * decremented by 24 hours worth of seconds.. *
      *        **********************************************
               COMPUTE NEW-TIME = START-SECS - 24 * 3600
      *        **************************************************
      *        * CEEDATM is invoked to obtain a new timestamp   *
      *        * based on the new Lilian seconds tally.         *
      *        **************************************************
               CALL "CEEDATM" USING NEW-TIME, PICSTR, NEW-TIMESTAMP, FC
               IF CEE000 of FC THEN
                   DISPLAY "The time  24 hours before "
                       Vstring-text of WS-TIMESTAMP
                       " is " NEW-TIMESTAMP
               ELSE
                   DISPLAY "Error converting seconds to timestamp."
                   STOP RUN
               END-IF
           ELSE
               DISPLAY "Error converting timestamp to seconds."
               STOP RUN
           END-IF

           GOBACK.