CICS ILC application

The following examples illustrate how you can use ILC under CICS®. A COBOL main program, COBCICS, dynamically CALLs a PL/I routine, PLICICS, which does the following:
  • Writes a message to the operator
  • Establishes a ZERODIVIDE ON-unit
  • Generates a divide-by-zero
  • Writes another message to the operator
  • Returns to the COBOL main program
COBCICS then calls CUCICS, a statically linked C routine, and passes a message character string and a length field to the subroutine. This routine then calls the Language Environment service CEEMOUT to write the message to the CESE transient data queue.
Figure 1. COBOL CICS main program that calls C and PL/I subroutines
        CBL  XOPTS(COBOL2),LIB,APOST                                 
       *Module/File Name: IGZTCICS                                   
       ******************************************************        
       *  TRANSACTION: COBC.                                *
       *  FUNCTION:                                         *
       *                                                    *
       *       A CICS COBOL main dynamically calls a PL/I   *
       *       subroutine, and statically calls a C         *
       *       subroutine. COBCICS passes a message to      *
       *       the C subroutine to output to the            *
       *       transient data queue.                        *
       *                                                    *
       ******************************************************        
        IDENTIFICATION DIVISION.                                     
        PROGRAM-ID. COBCICS.                                         
        ENVIRONMENT DIVISION.                                        
        DATA DIVISION.                                               
        WORKING-STORAGE SECTION.                                     
        77  STARTMSG     PIC X(16) VALUE 'STARTING COBCICS'.         
        77  DTVAL        PIC X(14) VALUE 'ENDING COBCICS'.           
        77  RUNNING      PIC X(80) VALUE 'STARTING CUCICS'.          
        77  RUNLENGTH    PIC S9(4) BINARY VALUE 15.                  
        77  PLISUBR      PIC X(8) VALUE 'PLISUBR'.                   
                                                                     
        PROCEDURE DIVISION.                                          
                                                                     
                                                                     
            EXEC CICS SEND FROM(STARTMSG) ERASE END-EXEC.            
            CALL PLISUBR USING DFHEIBLK DFHCOMMAREA.                 
            CALL 'CUCICS'  USING RUNLENGTH  RUNNING.                 
                                                                     
                                                                     
            EXEC CICS SEND FROM(DTVAL) ERASE END-EXEC.               
                                                                         
            EXEC CICS RETURN END-EXEC.                                   
Figure 2. PL/I routine called by COBOL CICS main program
   /*module/file name: ibmcics                        */                  
   /***************************************************/                  
   /**                                                *
   /**  function:                                     *
   /**                                                *
   /**  plicics is a pl/i cics subroutine that is     *
   /**  called from a cobol main program, cobcics.    *
   /**  plicics writes a startup message to the       *
   /**  terminal operator and establishes a           *
   /**  zerodivide on-unit. a zerodivide is           *
   /**  generated and the zerodivide on-unit is       *
   /**  called to notify the terminal operator. the   *
   /**  zerodivide performs a normal return to the    *
   /**  program and the control returns to cobol.     *
   /**                                                *
   /***************************************************/                  
                                                                          
   plicics : procedure(dfheiptr) options(fetchable);                      
                                                                          
    dcl  running  char(20) init ( 'plicics entered' ) ;                   
    dcl  msg  char(30);                                                   
                                                                          
    msg = 'plicics entered';                                              
    exec cics send from(msg) length(15) erase;                            
    on zdiv begin;                                                        
      msg = 'inside of zdiv on unit';                                     
      put skip list(msg);                                                 
      exec cics send from(msg) length(30) erase;                          
    end;                                                                  
    a = 10;                                                               
    a = a/0;                                                              
                                                                         
  end plicics;                                                           
Figure 3. C routine called by COBOL CICS main program
  /*Module/File Name: EDCCICS                                          */  
  /*********************************************************************/  
  /**                                                                  */
  /**Function: CEEMOUT: write message to transient data queue.         */
  /*                                                                   */
  /*  This example illustrates a C CICS subroutine that is             */
  /*  statically linked to a COBOL main routine, COBCICS. COBCICS      */
  /*  passes a message character string and a length field to the      */
  /*  subroutine.  This routine then calls the CEEMOUT service         */
  /*  to write the message to the transient data queue, CESE.          */
  /*                                                                   */
  /*********************************************************************/  
 #ifndef __cplusplus                                                       
 #pragma linkage(CUCICS,COBOL)                                             
 #else                                                                     
  extern "COBOL" void CUCICS(unsigned short *len, char (* running) 80 );
 #endif                                                                    
 #include <stdio.h>
 #include <stdlib.h>
 #include <string.h>
 #include <leawi.h>
 #include <ceeedcct.h>

   _VSTRING message;                                                       
   _INT4 dest;                                                             
   _CHAR80 msgarea;                                                        
   _FEEDBACK fc;                                                           
  /*                                                                */     
  /*  mainline.                                                     */     
  /*                                                                */     
 void CUCICS(unsigned short *len, char (* running) 80  )
 {                                                                         
   /* Send a message to the CICS terminal operator.                 */     
   char * startmsg = "CUCICS STARTED\n";                                   
   unsigned short I1;                                                      
   I1 = strlen(startmsg);                                                  
   EXEC CICS SEND FROM(startmsg) LENGTH(I1) ERASE;                         
                                                                           
   /* set output area to nulls                   */                        
   memset(message.string,'\0',sizeof(_CHAR80) );                           
   if (*len >= sizeof(_CHAR80) )                                           
       *len  = sizeof(_CHAR80)-1 ;                                         
                                                                           
   /* copy message to output area */                                       
   memcpy(message.string, running,(unsigned int) *len);                    
                                                                           
   message.length = (unsigned int) *len;                                   
   dest = 2;                                                               
   /*************************************************************          
    *   Call CEEMOUT to place copy of operator message in       *
    *   transient data queue CESE.                              *
    *************************************************************
   CEEMOUT(&message,&dest,&fc);
                                                                           
   if ( _FBCHECK (fc , CEE000) != 0 ) {                                    
      /* put the message if CEEMOUT failed */                              
      dest = 2;                                                            
      CEEMSG(&fc,&dest,NULL);
      exit(2999);                                                          
   }                                                                       
 }