Calls to CEE3CTY, CEEFMDT, and CEEDATM in COBOL

the following example illustrates how you would query the default country code (CEE3CTY), change it to another country code (CEE3CTY), get the default date and time in the new country code (CEEFMDT), and convert the seconds to a timestamp (CEEDATM).
CBL LIB,QUOTE,RENT,OPTIMIZE
      *Module/file name: IGZTNLS
      ************************************************************
      **                                                        **
      **  CESCNLS - Call the following LE services:             **
      **                                                        **
      **               CEE3CTY  :  query default country        **
      **               CEEFMDT  :  obtain the default date and  **
      **                           time format                  **
      **               CEEDATM  :  convert seconds to timestamp **
      **                                                        **
      ** This example shows how to use several of the LE        **
      ** national language support callable services in a       **
      ** COBOL program.  The current country is queried, saved, **
      ** and then changed to Germany. The default date and time **
      ** for Germany is obtained. CEEDATM is called to          **
      ** convert a large numeric value in seconds to the        **
      ** timestamp 16.05.1988 19:01:01 (May 16, 1988 7:01PM.)   **
      **                                                        **
      ************************************************************
       IDENTIFICATION DIVISION.
       PROGRAM-ID. CESCNLS.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01  SECONDS                 COMP-2.
       01  FUNCTN                  PIC S9(9) BINARY.
       01  COUNTRY                 PIC X(2).
       01  GERMANY                 PIC X(2) VALUE "DE".
       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  TIMESTP                 PIC X(80).
       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  QUERY-COUNTRY-SETTING   PIC S9(9) BINARY VALUE 2.
       01  SET-COUNTRY-SETTING     PIC S9(9) BINARY VALUE 3.
       01  COUNTRY-PIC-STR         PIC X(80).

       PROCEDURE DIVISION.

       0001-BEGIN-PROCESSING.
           DISPLAY "**************************************".
           DISPLAY "CESCNLS COBOL example is now in motion. ".
           DISPLAY "**************************************".

      ************************************************************
      *      Query Country Setting                               *
      ************************************************************
           MOVE QUERY-COUNTRY-SETTING TO FUNCTN.
           CALL "CEE3CTY" USING FUNCTN, COUNTRY, FC.
           IF NOT CEE000 of FC THEN
               DISPLAY "Error " Msg-No of FC
                   " in query of country setting"
           ELSE
      ************************************************************
      *        Call CEE3CTY to set country to Germany            *
      ************************************************************
               MOVE SET-COUNTRY-SETTING TO FUNCTN
               MOVE GERMANY TO COUNTRY
               CALL "CEE3CTY" USING FUNCTN, COUNTRY, FC
               IF NOT CEE000 of FC THEN
                   DISPLAY "Error " Msg-No of FC
                       " in setting country"
               ELSE
      ************************************************************
      *            Call CEEFMDT to get default date/time         *
      *            format for Germany and verify format          *
      *            against the published value.                  *
      ************************************************************
                   MOVE SPACE TO COUNTRY
                   CALL "CEEFMDT" USING COUNTRY, COUNTRY-PIC-STR, FC
                   IF NOT CEE000 of FC THEN
                       DISPLAY "Error getting default date/time"
                               " format for Germany."
                   ELSE
      ************************************************************
      *                Call CEEDATM to convert the number of     *
      *                seconds from October 14, 1582 12:00AM     *
      *                to 16 May 1988 7:01PM to character format.*
      *                The default date and time matches         *
      *                that of the default country, Germany.     *
      ************************************************************
                       MOVE 12799191661.986 TO SECONDS
                       COMPUTE Vstring-length OF PICSTR =
                         FUNCTION MIN( LENGTH OF COUNTRY-PIC-STR, 256 )
                       MOVE COUNTRY-PIC-STR TO Vstring-text of PICSTR
                       CALL "CEEDATM" USING SECONDS, PICSTR,
                                            TIMESTP, FC
                       IF CEE000 of FC THEN
                           DISPLAY "Generated timestamp is: " TIMESTP
                       ELSE
                           DISPLAY "Error " Msg-No of FC
                               " generating timestamp"
                       END-IF
                   END-IF
                   DISPLAY "***********************"
                   DISPLAY "COBOL NLS example ended"
                   DISPLAY "***********************"
               END-IF
           END-IF.

           GOBACK.