Examples: Using ILE Common Execution Environment APIs

These ILE COBOL and ILE RPG programs call the ILE Common Execution Environment (CEE) APIs for date conversions.

Note: By using the code examples, you agree to the terms of the Code license and disclaimer information.

Example in ILE COBOL

       PROCESS NOMONOPRC.
      ************************************************************
      *
      * This sample ILE COBOL program demonstrates how to call the
      * Common Execution Environment (CEE) Date APIs.  The program
      * accepts two parameters.  The first is the date in character
      * form and the second the format of the date.  For instance
      * CALL CEEDATES ('10131955' 'MMDDYYYY') causes the program
      * to treat the date as October 13 1955).
      *
      * The program then displays on the console the numeric day of
      * the week for that date (Sunday = 1) and the named day of
      * week for that date.
      *
      ************************************************************
       IDENTIFICATION DIVISION.
       PROGRAM-ID. CEEDATES.
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
         SPECIAL-NAMES.
         LINKAGE TYPE PROCEDURE FOR "CEEDAYS" USING ALL DESCRIBED,
         LINKAGE TYPE PROCEDURE FOR "CEEDYWK" USING ALL DESCRIBED,
         LINKAGE TYPE PROCEDURE FOR "CEEDATE" USING ALL DESCRIBED.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01  Lilian-Date         PIC S9(9)  BINARY.
       01  Day-of-Week-Numeric PIC S9(9)  BINARY.
       01  Day-of-Week-Alpha   PIC X(10).
       01  Day-of-Week-Format  PIC X(10)         VALUE "Wwwwwwwwwz".
       LINKAGE SECTION.
       01  Sample-Date         PIC X(8).
       01  Date-Format         PIC X(8).
       PROCEDURE DIVISION USING Sample-Date, Date-Format.
       SAMPLE.
      *
      * Convert formatted date to Lilian date
      *
           CALL "CEEDAYS" USING Sample-Date
                                Date-Format
                                Lilian-Date
                                OMITTED.
      *
      * Get numeric day of week from Lilian date
      *
           CALL "CEEDYWK" USING Lilian-Date
                                Day-of-Week-Numeric
                                OMITTED.
      *
      * Get day of week from Lilian date
      *
           CALL "CEEDATE" USING Lilian-Date
                                Day-of-Week-Format
                                Day-of-Week-Alpha
                                OMITTED.
           DISPLAY "Day of week = " Day-of-Week-Numeric UPON CONSOLE.
           DISPLAY "Day of week = " Day-of-Week-Alpha UPON CONSOLE.
           STOP RUN.

Example in ILE RPG

     D************************************************************
     D*
     D* This sample ILE RPG program demonstrates how to call the
     D* Common Execution Environment (CEE) Date APIs.  The program
     D* accepts two parameters.  The first is the date in character
     D* form and the second the format of the date.  For instance
     D* CALL CEEDATES ('10131955' 'MMDDYYYY') causes the program
     D* to treat the date as October 13 1955).
     D*
     D* The program must be compiled with DFTACTGRP(*NO)
     D*
     D* The program then displays on the console the numeric day of
     D* the week for that date (Sunday = 1) and the named day of
     D* week for that date.
     D*
     D************************************************************
     DLilianDate       s             10i 0
     DDayOfWkN         s             10i 0
     DDayOfWkA         s             10
     DDayOfWkFmt       s             10    inz('Wwwwwwwwwz')
     C     *entry        plist
     C                   parm                    SampleDate        8
     C                   parm                    DateFormat        8
     C*
     C* Convert formatted date to Lilian date
     C*
     C                   callb(d)  'CEEDAYS'
     C                   parm                    SampleDate
     C                   parm                    DateFormat
     C                   parm                    LilianDate
     C                   parm                    *OMIT
     C*
     C* Get numeric day of week from Lilian date
     C*
     C                   callb(d)  'CEEDYWK'
     C                   parm                    LilianDate
     C                   parm                    DayOfWkN
     C                   parm                    *OMIT
     C*
     C* Get day of week from Lilian date
     C*
     C                   callb(d)  'CEEDATE'
     C                   parm                    LilianDate
     C                   parm                    DayOfWkFmt
     C                   parm                    DayOfWkA
     C                   parm                    *OMIT
     C*
     C     DayOfWkN      dsply
     C     DayOfWkA      dsply
     C                   eval      *inlr = '1'
     C                   return