LINKAGE SECTION


LINKAGE SECTION is used for -

  • Passing data between programs
  • Receiving data from run JCL
Note!
  • The maximum length of the data received through the LINKAGE SECTION is 64KB (from one program to another). However, it is advisable to pass only 32KB.
  • The maximum length of the data received through the LINKAGE SECTION is 100 bytes (from the JCL PARM parameter).

Syntax -

----+----1----+----2----+----3----+----4----+----5----+
	   DATA DIVISION.
	   LINKAGE SECTION.
	   variable-declaration-entries.

Rules to Remember -

  • All variables declared in the LINKAGE SECTION should be unique.
  • The variables should not have a VALUE clause.
  • When we declared LINKAGE SECTIO variables for receiving the data from JCL, all 01 level variable should present in PROCEDURE DIVISION USING clause to receive the data.

Data passing between programs -


LINKAGE SECTION is used to receive data from the called program to the calling program. It is an optional section mainly used in subprograms to receive the data from the main or calling program. The variables should match the PIC declaration in both main and subprograms.

Example -

Scenario - LINKAGE SECTION usage to pass the data between the programs.

Main Program (MAINPROG) -

----+----1----+----2----+----3----+----4----+----5----+
       ...
       WORKING-STORAGE SECTION.
       01 WS-VAR.
          05 WS-IP1          PIC 9(02) VALUE 47.    *> Input Variable1
          05 WS-IP2          PIC 9(02) VALUE 25.    *> Input Variable2
          05 WS-RESULT       PIC 9(04).             *> Result Variable
       01 WS-CALLING-PROG    PIC X(08) VALUE "SUBPROG".
       ... 
	   PROCEDURE DIVISION. 
	  * Calling subprogram with two inputs and getting result back   
           CALL WS-CALLING-PROG USING WS-IP1, WS-IP2, WS-RESULT. 
		   
           DISPLAY "RESULTS: " WS-RESULT. 
		   STOP RUN.

Sub Program (SUBPROG) -

----+----1----+----2----+----3----+----4----+----5----+
       ...                                                   
       LINKAGE SECTION.                                         
       01 LN-VAR.                                                       
          05 LN-IP1          PIC 9(02).  *> To receive input1 from MAINPROG
          05 LN-IP2          PIC 9(02).  *> To receive input2 from MAINPROG
          05 LN-RESULT       PIC 9(04).  *> To send result to MAINPROG
       ... 
	  *Receiving data from main program CALL statement 
       PROCEDURE DIVISION USING LN-IP1, LN-IP2, LN-RESULT. 

           COMPUTE LN-RESULT = LN-IP1 * LN-IP2.
		   GOBACK.

Explaining Example -

In the above example:

  • MAINPROG is the main program and SUBPROG is the subprogram.
  • WS-IP1, WS-IP2 are the inputs passed from MAINPROG to the SUBPROG. SUBPROG receives the data into LN-IP1, LN-IP2 from MAINPROG, multiply those values and place the result into LN-RESULT.
  • SUBPROG returns the output LN-RESULT to MAINPROG, MAINPROG displays the result received from SUBPROG.

We will discuss more detail about this topic in CALL Statement .

Receiving data from run JCL -


LINKAGE SECTION is also used to receive the data from run JCL through the PARM parameter. To receive the data from JCL, a variable of length 2 bytes (S9(4) COMP) should be declared in addition to the other variables. The maximum length of the data that can pass through the PARM parameter is 100 bytes.

Example -

Scenario - Receiving the data from JCL PARM.

Run JCL -

----+----1----+----2----+----3----+----4----+----5----+
//MATEGJR JOB MSGLEVEL=(1,1), NOTIFY=&SYSUID
//*
//STEP01  EXEC PGM=LINKPROG,PARM=(10,20)
//STEPLIB  DD  DSN=MATEGJ.COBOL.LOADLIB,DISP=SHR
//SYSOUT   DD  SYSOUT=*

Program (LINKPROG) -

----+----1----+----2----+----3----+----4----+----5----+
       ...
       WORKING-STORAGE SECTION.
       01 WS-RESULT       PIC 9(04).
       LINKAGE SECTION.                                         
       01 LN-VAR.
		  05 LN-LENGTH    PIC S9(04) COMP.
          05 LN-IP1       PIC 9(02).    *> Input Variable1
		  05 FILLER       PIC X(01).
          05 LN-IP2       PIC 9(02).    *> Input Variable2
       ...
	   PROCEDURE DIVISION USING LN-VAR. 
           COMPUTE WS-RESULT = LN-IP1 * LN-IP2.
           DISPLAY "RESULT: " WS-RESULT.
		   ...

Explaining Example -

In the above example:

  • LINKPROG is receiving the data from run JCL. LN-IP1, LN-IP2 receives the data from JCL, multiply those values and place the result into WS-RESULT.

We will discuss more detail about this topic in JCL PARAM parameter .