Calls to CEECBLDY in COBOL

This example shows converting a 2-digit input date to a COBOL Integer date, adding 90 days to the Integer date, and converting the Integer format date back to a 4-digit year format using COBOL intrinsic functions.
       CBL QUOTE
      *************************************************
      *Module/File Name: CBLDAYS
      *************************************************
      **                                             **
      ** Function: Invoke CEECBLDY callable service  **
      ** to convert date to COBOL Lilian format.     **
      ** This service is used when using the         **
      ** Language Environment Century Window         **
      ** mixed with COBOL Intrinsic Functions.       **
      **                                             **
      *************************************************
       IDENTIFICATION DIVISION.
       PROGRAM-ID. CBLDAYS.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01  CHRDATE.
           05  CHRDATE-LENGTH      PIC  9(2) BINARY.
           05  CHRDATE-STRING      PIC X(50).
       01  PICSTR.
           05  PICSTR-LENGTH       PIC S9(4) BINARY.
           05  PICSTR-STRING       PIC X(50).
       01  COBINT                  PIC S9(9) BINARY.
       01  NEWDATE                 PIC 9(8).
       01   FC                     PIC X(12).
       PROCEDURE DIVISION.
      *************************************************
      ** Specify input date and length               **
      *************************************************
           MOVE "1 January 00" to CHRDATE-STRING.
           MOVE 25 TO CHRDATE-LENGTH.
      *************************************************
      ** Specify a picture string that describes     **
      ** input date, and the picture string"s length.**
      *************************************************
           MOVE "ZD Mmmmmmmmmmmmmmz YY"
                                TO PICSTR-STRING.
           MOVE 23 TO PICSTR-LENGTH.

      *************************************************
      ** Call CEECBLDY to convert input date to a    **
      ** COBOL integer date                          **
      *************************************************
           CALL "CEECBLDY" USING CHRDATE, PICSTR,
                                 COBINT, FC.

      *************************************************
      ** If CEECBLDY runs successfully, then compute **
      ** the date of the 90th day after the          **
      ** input date using Intrinsic Functions        **
      *************************************************
           IF (FC = LOW-VALUE) THEN
               COMPUTE COBINT = COBINT + 90
               COMPUTE NEWDATE = FUNCTION
                              DATE-OF-INTEGER (COBINT)
               DISPLAY NEWDATE " is COBOL integer day: " COBINT
           ELSE
               CONTINUE
           END-IF.

           GOBACK.