Calls to CEESECS in COBOL

CBL LIB,QUOTE
      *Module/File Name: IGZTDT1
      ********************************************************
      **                                                    **
      ** CEE78DAT - Call CEESECS to convert timestamp to    **
      **            seconds                                 **
      **                                                    **
      ** This example calls the LE CEESECS callable         **
      **  service to compute the number of hours between    **
      **  the timestamps 11/02/92 05:22 and 11/02/92 17:22. **
      **  The program responds that 36 hours has elapsed.   **
      **                                                    **
      ********************************************************
       IDENTIFICATION DIVISION.
       PROGRAM-ID. CE78DAT.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
      *  Double precision is needed for the seconds results
       01  START-SECS              COMP-2.
       01  END-SECS                COMP-2.
       01  EOF-SWITCH              PIC X VALUE "N".
           88  EOF                 VALUE "Y".
       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  START-TIME.
           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 START-TIME.
       01  END-TIME.
           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 END-TIME.
       01  INPUT-VARIABLES.
           05  ELAPSED-TIME        PIC S9(5)V99 PACKED-DECIMAL.
           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 START-TIME.
           MOVE "11/02/92 05:22" TO Vstring-text of START-TIME.
           MOVE  14 TO Vstring-length of END-TIME.
           MOVE "11/03/92 17:22" TO Vstring-text of END-TIME.
      *    *********************************************************
      *    * CEESECS takes the timestamp START-TIME and returns a  *
      *    * double-precision Lilian seconds tally in START-SECS.  *
      *    *********************************************************
           CALL "CEESECS" USING START-TIME, PICSTR, START-SECS, FC
           IF CEE000 of FC THEN
      *        *******************************************************
      *        * CEESECS takes the timestamp END-TIME and returns a  *
      *        * double-precision Lilian seconds tally in END-SECS.  *
      *        *******************************************************
               CALL "CEESECS" USING END-TIME, PICSTR, END-SECS, FC
               IF CEE000 of FC THEN
                   COMPUTE ELAPSED-TIME = (END-SECS - START-SECS) / 3600
                   MOVE ELAPSED-TIME TO ELAPSED-TIME-OUT
                   DISPLAY ELAPSED-TIME-OUT
                       " hours have elapsed between "
                       Vstring-text of START-TIME
                       " and " Vstring-text of END-TIME
               ELSE
                   DISPLAY "Error " Msg-No of FC
                       " converting ending date to Lilian date"
                   STOP RUN
               END-IF
           ELSE
               DISPLAY "Error " Msg-No of FC
                   " converting starting date to Lilian date"
               STOP RUN
           END-IF

           GOBACK.