CICS Translation Process Demystified

 

In this article we will try to explore the steps involved in compiling a CICS program and the transformation it undergoes. The compilation of a CICS program is three step process with an additional translation step being included before the Compile and Linkedit steps.

 

Screen Shot 2015-05-14 at 11.21.46 PM

CICS Program Compilation

The CICS translator reads the COBOL code with embedded CICS commands and check the validity of CICS command syntax, any errors and listed in the output listing created by this step. The translator then converts the CICS commands to equivalent MOVE and CALL statements. It does this by commenting out the CICS statements and by inserting CALL and MOVE statements which will achieve the desired function. This modified code is then fed as input to the traditional COBOL complier which compiles the code as a normal COBOL program because the CICS commands are all commented. The object module created by the complier is then linked edited by the linkage editor to create the load module for your program.

 

CICS Translator

We mentioned above that the CICS commands are replaced with MOVE and CALL statements by the translator , this is actually an oversimplification and the translator actually does a lot more than just that . Lets try to understand this with an example. This is a simple CICS program with just a return command , the DHFCOMMAREA is just added for consistency and is not actually used.

Sample Source Code

IDENTIFICATION DIVISION.
PROGRAM-ID TEST.
DATA DIVISION.
WORKING STORAGE SECTION.
LINKAGE SECTION.
01 DHFCOMMAREA PIC X(1).

PROCEDURE DIVISION.
  EXEC CICS 
       RETURN
  END-EXEC.

 

Modified Program After Translation

IDENTIFICATION DIVISION.
PROGRAM-ID TEST.
DATA DIVISION.

WORKING STORAGE SECTION.
01 DFHLDVER PIC X(22).
01 DFHEIDO  PIC S9(7) COMP-3 VALUE ZERO.
01 DFHEIBO  PIC S9(7) COMP-3 VALUE ZERO.
01 DFHEICB  PIC X(8)
01 DFHB0041 COMP PIC  S9(8).
01 DFHB0042 COMP PIC  S9(8).
01 DFHB0043 COMP PIC  S9(8).
01 DFHB0044 COMP PIC  S9(8).
01 DFHB0045 COMP PIC  S9(8).
01 DFHB0046 COMP PIC  S9(8).
01 DFHB0047 COMP PIC  S9(8).
01 DFHB0048 COMP PIC  S9(8).
01 DFHEIV11 COMP PIC S9(4).
01 DFHEIV12 COMP PIC S9(4).
01 DFHEIV13 COMP PIC S9(4).
01 DFHEIV14 COMP PIC S9(4).
01 DFHEIV15 COMP PIC S9(4).
01 DFHB0025 COMP PIC  S9(4).
01 DFHEIV5  PIC  X(4).
01 DFHEIV6  PIC  X(4).
01 DFHEIV17 PIC X(4).
01 DFHEIV18 PIC X(4).
01 DFHEIV19 PIC X(4).
01 DFHEIV1  PIC X(8).
01 DFHEIV2  PIC X(8).
01 DFHEIV3  PIC X(8).
01 DFHEIV20 PIC X(8).
01 DFHCC0084 PIC X(8).
01 DFHCC0085 PIC X(8).
01 DFHC0320  PIX X(32).
01 DFHEIV7 COMP PIC X(2).
01 DFHEIV8 COMP PIC X(2).
01 DFHC0022 PIC X(2).
01 DFHC0023 PIC X(2).
01 DFHEIV10 PIC S9(7) COMP-3.
01 DFHEIV9  PIC X(1).
01 DFHC0011 PIC X(1).
01 DHFEIV4  PIC X(6).
01 DFHC0070 PIC X(7)
01 DFHC0071 PIC X(7)
01 DFHC0440 PIC X(44)
01 DFHDUMMMY COMP PIC S9(4).
01 DFHEIVO  PIC X(29).
LINKAGE SECTION.
01 DFHEIBLK.
  02  EIBTIME  COMP-3 PIC S9(7).
  02  EIBDATE  COMP-3 PIC S9(7).
  02  EIBTRNID PIC X(4).
  02  EIBTASKN COMP-3 PIC S9(7).
  02  EIBTRMID PIC X(4).
  02  DFHEIGDI COMP PIC S9(4).
  02  EIBCPOSN COMP PIC S9(4).
  02  EIBCALEN COMP PIC S9(4).
  02  EIBAID   PIC X(1).
  02  EIBFN    PIC X(2).
  02  EIBRCODE PIC X(6).
  02  EIBDS    PIC X(8).
  02  EIBREQID PIC X(8).
  02  EIBRSRCE PIC X(8).
  02  EIBSYNC  PIC X(1).
  02  EIBFREE  PIC X(1).
  02  EIBRECV  PIC X(1).
  02  EIBFIL01 PIC X(1).
  02  EIBATT   PIC X(1).
  02  EIBEOC   PIC X(1).
  02  EIBFMH   PIC X(1).
  02  EIBCOMPL PIC X(1).
  02  EIBSIG   PIC X(1).
  02  EIBCONF  PIC X(1).
  02  EIBERR   PIC X(1).
  02  EIBERRCD PIC X(4).
  02  EIBSYNRB PIC X(1).
  02  EIBNODAT PIC X(1).
  02  EIBRESP  COMP PIC S9(8).
  02  EIBRESP2 COMP PIC S9(8).
  02  EIBRLDBK PIC X(1).
01 DHFCOMMAREA PIC X(1).
PROCEDURE DIVISION USING DFHEIBLK DFHCOMMAREA. 
    
*EXEC CICS 
*   RETURN
*END-EXEC.

MOVE '00011'  TO DFHEIVO.
CALL 'DFHEI1' USING DFHEIVO.

 

The first thing you will notice is that the program has become significantly bigger with many additional fields included in working storage as well as linkage section.The fields DHFLDVER thru  DFHEIVO are inserted by the translator after your last working storage entry. These are inserted because atleast one of these fields is used by every CICS command . In our example , the modified code for RETURN uses DFHEIVO , larger programs uses many of these working storage fields in their corresponding MOVE and CALL equivalents. Here is another example .

*EXEC CICS
*   RECEIVE MAP('A') 
*END-EXEC
MOVE '     ' TO DFHEIV0.
MOVE 'A' TO DFHC0070.
CALL 'DFHEI1' USING DFHEIV0 DFHC0070 AI.

The translator also inserts the DFHEIBLK or the Execute Interface Block as the first entry in your Linkage section. CICS inserts information into these fields before control is passed back to the program . Example EIBAID contains the attention identifier (AID) that is associated with the last terminal control or EIBCPOSN which contains the cursor address (position) that is associated with the last terminal control. It also inserts a DFHCOMMAREA if the first item in the linkage section is not a DFHCOMMAREA.

Lastly the translator changes the PROCEDURE DIVISION statement to include addressability to DHFEIBLK and DFHCOMMAREA . It should be noted that if any other linkage section variable are used in the program they must be specifically coded in your Procedure Division Using statement.

 

Mainframe Wiki © 2015 Frontier Theme