RAMESH KRISHNA REDDY mainframe discussion forum - cobol, db2,cics,jcl,file-aid,changeman,... interview questions, quizs
Online Tutorials   | PREV  | TOP  | NEXT



DRONA SERIES
CICS TUTORIAL / STUDY MATERIAL


CHAPTER - 3


Sample CICS Program



   
 

INTRODUCTION






Writing CICS programs --------------------- We write CICS program in much the same way as you write any other program. You can use COBOL, OO COBOL, C, C++, PL/I, or assembler language to write CICS application programs. Most of the processing logic is expressed in standard language statements, but you use CICS commands for some functions. Now, Let us write simple CICS program Requirement : Task 1 - CICS program to accept input from terminal Task 2 - prefix string 'OUTPUT : ' to the input data send it back to the modified data to terminal Program :

  IDENTIFICATION DIVISION.
  PROGRAM-ID.    SAMCICS.
 *
  ENVIRONMENT DIVISION.
  DATA DIVISION.
  WORKING-STORAGE DIVISION.
 * 
  01  WS-INPUT.
      05 WS-TRAN-ID               PIC  X(4).
      05 WS-MESSAGE-I             PIC  X(70).
 *
  01  WS-OUTPUT.
      05 WS-TEXT                  PIC  X(8).
      05 WS-MESSAGE-O             PIC  X(70).
 *
  01  WS-MSG-LENGTH               PIC  S9(4)  COMP.
 *
  PROCEDURE DIVISION.
 *

      MOVE  74        TO   WS-MSG-LENGTH.               -------  (1)
 *
      EXEC CICS RECEIVE 				-------  (2)
                INTO(WS-INPUT)
                LENGTH(WS-MSG-LENGTH)
      END-EXEC.       
 *
      MOVE WS-MESSAGE-I    TO  WS-MESSAGE-O.            -------  (3)
      MOVE 'OUTPUT: '      TO  WS-TEXT.                 -------  (4)
      MOVE 78              TO  WS-MSG-LENGTH.           -------  (5)  
 *
      EXEC CICS SEND                                    -------  (6)
                FROM(WS-OUTPUT)
                LENGTH(WS-MSG-LENGTH)
                ERASE
      END-EXEC.
 *
      EXEC CICS RETURN                                  -------  (7)
      END-EXEC.
 *
      GOBACK.                                           -------  (8)
 *

 © www.mainframegurukul.com 

Explanination - (1) Moving 74 to WS-MSG-LENGTH, ie., we are expecting 74 bytes of input data from the terminal (2) All CICS commands embedded in COBOL program must be between EXEC CICS & END-EXECtags. Observe the RECEIVE command started with EXEC CICS & ended with END-EXEC tag. Using this RECEIVE CICS command, program can able to get the data passed from terminal. There are two options used in this command. a) INTO - received data will be placed into WS-INPUT variable b) LENGTH - length of the data we are expecting to receive (3) Moving input data to part of output variable. if you observe one thing here, we are not move WS-INPUT to WS-OUPUT, Why because, In WS-INPUT, first 4 bytes is transactionID, which is used by CICS to identify our program to execute. Rest of the data we are passing to second part of output variable, first part of output variable contains the value "OUTPUT:" in it. (4) Now our task is to add 'OUTPUT:' string to received data. for that we are moving 'OUPUT:' string to WS-TEXT which is part of output variable WS-OUTPUT. (5) Since WS-OUTPUT variable size is 78, we are move 78 to WS-MSG-LENGTH (6) Now in step 6, we are using SEND command to send the the data in WS-OUPUT variable to terminal. There are two options used in this command. a) FROM - specifing data location to be send to terminal b) LENGTH - specifing length of data being passed to terminal c) ERASE - instructing to erase data on the screen, before printing data that is being send. (7) RETURN command terminates current transaction. (8) GOBACK statement returns control to CICS. EXECUTING CICS PROGRAM ---------------------- To execute above CICS program in CICS region, programmer should follow these steps (1) Compile the program (2) Move the load module to CICS load libraries. (3) Define the Transaction identifier ( 1 to 4 bytes ) in PCT (Program control table ) along with program name. (4) Define program name in PPT (Processing Program Table ) (5) Login into CICS region (6) Enter transaction identifier defined in PCT.. It will execute your program and return the results.
    

NEXT CHAPTER TOPIC : Resource Definition


                                   




Home | Donations | Online Tutorials | Books | Entertainment | Contactme | privacy |  sql tutorial | jcl interview questions | JCL Tutorial | JCL Tutorial - chapter1 | JCL Tutorial - chapter2 | JCL Tutorial - chapter3 | JCL Tutorial - chapter4 | JCL Tutorial - chapter5 | JCL Tutorial - chapter6 | JCL Tutorial - chapter7 | JCL Tutorial - chapter8 | JCL Tutorial - chapter9 | JCL Tutorial - chapter10 | JCL Tutorial - chapter11