Calls to CEESECS, CEESECI, CEEISEC, and CEEDATM in COBOL

CBL LIB,QUOTE
      *Module/File Name: IGZTDT3
      ****************************************************************
      * CE81DATA - Call the following LE service routines:           *
      *           : CEESECS - convert timestamp to seconds           *
      *           : CEESECI - convert seconds to time components     *
      *           : CEEISEC - convert time components to seconds     *
      *           : CEEDATM - convert seconds to timestamp           *
      *   CEESECS is used to convert the timestamp to seconds        *
      *   CEESECI is used to convert seconds to date/time components.*
      *   32 months is added to the month and year component         *
      *       of date/time.                                          *
      *   CEEISEC is to convert the date/time components with the    *
      *       new months component back to a Lilian seconds tally.   *
      *   CEEDATM is then used to build a new timestamp for          *
      *       the updated number of seconds.                         *
      ****************************************************************
       IDENTIFICATION DIVISION.
       PROGRAM-ID. CE81DAT.
       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).
      *    *********************************************
      *    * These are the date/time variables used by *
      *    * CEEISEC and CEESECI.                      *
      *    *********************************************
       01  DATE-TIME-COMPONENTS BINARY.
           05  YEAR                PIC 9(9).
           05  MONTH               PIC 9(9).
           05  DAYS                PIC 9(9).
           05  HOURS               PIC 9(9).
           05  MINUTES             PIC 9(9).
           05  SECONDS             PIC 9(9).
           05  MILLSEC             PIC 9(9).
       01  FILLER                  PIC X(80).
       01  INPUT-VARIABLES.
           05  MONTHS-TO-DISPLACE  PIC S9(4) BINARY VALUE 32.
           05  DISPLACEMENT-COMP   PIC S9(4) BINARY.
           05  MONTHNUM            PIC 9(9)  BINARY.

       PROCEDURE DIVISION.

       0001-BEGIN-PROCESSING.
           MOVE 14 TO Vstring-length of WS-TIMESTAMP.
           MOVE "11/02/92 05:22" TO Vstring-text of WS-TIMESTAMP.
           MOVE 14 TO Vstring-length of PICSTR.
           MOVE "MM/DD/YY HH:MI" TO Vstring-text of PICSTR.
      *    ***********************************************************
      *    * The timestamp "11/02/92 05:22" is converted to          *
      *    * seconds under the control of the mask PICSTR.  CEESECS  *
      *    * will return a Lilian seconds tally in the double-       *
      *    * precision floating-point variable START-SECS.           *
      *    ***********************************************************
           CALL "CEESECS" USING WS-TIMESTAMP, PICSTR, START-SECS, FC.
           IF CEE000 of FC THEN
      *    ***********************************************************
      *    * The Lilian seconds tally in field START-SECS is mapped  *
      *    * into its date/time components using function CEESECI.   *
      *    ***********************************************************
               CALL "CEESECI" USING START-SECS, YEAR, MONTH, DAYS,
                                   HOURS, MINUTES, SECONDS, MILLSEC, FC
               IF CEE000 of FC THEN
                   MOVE MONTHS-TO-DISPLACE TO DISPLACEMENT-COMP
      *            ****************************************************
      *            * MONTH is converted to month-in-century for the   *
      *            * displacement arithmetic. Then a new month and    *
      *            * year are computed from the new month-in-century  *
      *            * number (in variable MONTHNUM).  The months com-  *
      *            * ponent has an allowed range of between 1 and 12.*
      *            ****************************************************
                   COMPUTE MONTHNUM =
                       YEAR * 12 + MONTH + DISPLACEMENT-COMP - 1
                   DIVIDE MONTHNUM BY 12 GIVING YEAR REMAINDER MONTH
                   ADD 1 TO MONTH
      *            **************************************************
      *            * Now that the MONTH DateTime component has      *
      *            * been shifted forward by 32 months,             *
      *            * we must get a new Lilian seconds tally based   *
      *            * on the new MONTH and YEAR components.  We      *
      *            * do this with a call to the CEEISEC callable    *
      *            * service.  The new Lilian seconds tally is      *
      *            * placed in the double-precision field NEW-TIME. *
      *            **************************************************
                   CALL "CEEISEC" USING YEAR, MONTH, DAYS, HOURS,
                                MINUTES, SECONDS, MILLSEC, NEW-TIME, FC
      *            ******************************************
      *            * CEEDATM is now used to obtain a new    *
      *            * timestamp based on the Lilian seconds  *
      *            * tally in the variable New-time.        *
      *            ******************************************
                   IF CEE000 THEN
                       CALL "CEEDATM" USING NEW-TIME, PICSTR,
                                            NEW-TIMESTAMP, FC
                       IF CEE000 THEN
                           DISPLAY "The time "
                               MONTHS-TO-DISPLACE " months after "
                               Vstring-text of WS-TIMESTAMP
                               " is " NEW-TIMESTAMP
                       ELSE
                           DISPLAY "Error " Msg-No of FC
                               " converting seconds to timestamp."
                       END-IF
                   ELSE
                       DISPLAY "Error " Msg-No of FC
                           " converting components to seconds."
                   END-IF
               ELSE
                   DISPLAY "Error " Msg-No of FC
                       " converting seconds to components."
               END-IF
           ELSE
               DISPLAY "Error " Msg-No of FC
                   " converting timestamp to seconds."
           END-IF

           GOBACK.