CALL With Returning Example


Scenario - Dynamic Call from MAINPROG to SUBPROG and returning value from SUBPROG to MAINPROG.

MAINPROG -

----+----1----+----2----+----3----+----4----+----5----+
       IDENTIFICATION DIVISION. 
       PROGRAM-ID. MAINPRWR.
       AUTHOR. MTH.
 
       DATA DIVISION.
       WORKING-STORAGE SECTION. 
       01 WS-VAR.
          05 WS-INP1        PIC 9(02) VALUE 10.
          05 WS-INP2        PIC 9(02) VALUE 20.
          05 WS-RESULT      PIC 9(03) VALUE ZEROES.
          05 WS-PROG        PIC X(08) VALUE "SUBPROG".

       PROCEDURE DIVISION.
           DISPLAY "INPUTS (MAINPROG): " WS-INP1 ", " WS-INP2.
           CALL WS-PROG USING WS-INP1, WS-INP2 RETURNING WS-RESULT.

           DISPLAY "INPUTS AFTER CALL: " WS-INP1 ", " WS-INP2.
           DISPLAY "RESULT (MAINPROG) :  " WS-RESULT.

           STOP RUN.

SUBPROG -

----+----1----+----2----+----3----+----4----+----5----+
       IDENTIFICATION DIVISION.
       PROGRAM-ID. SUBPRWR.
       AUTHOR. MTH.

       DATA DIVISION.
       LINKAGE SECTION.
       01 LS-INP1      PIC 9(02).
       01 LS-INP2      PIC 9(02).
       01 LS-RESULT    PIC 9(03) VALUE ZEROES.

       PROCEDURE DIVISION USING LS-INP1, LS-INP2 
	                      RETURNING LS-RESULT.

           COMPUTE LS-RESULT = LS-INP1 + LS-INP2.
           GOBACK.

JCL -

//MATEPKRJ JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID     
//***********************************************
//*  RUN A COBOL PROGRAM 
//***********************************************
//STEP01  EXEC PGM=MAINPRWR                      
//STEPLIB  DD  DSN=MATEPK.COBOL.LOADLIB,DISP=SHR
//SYSOUT   DD  SYSOUT=*

Output -

INPUTS (MAINPROG): 10, 20
INPUTS AFTER CALL: 30, 20
RESULT (MAINPROG) :  030 

Explaining Example -

In the above example:

  • MAINPRWR is the main program, and SUBPRWR is the subprogram.
  • CALL WS-PROG makes the call as dynamic call.
  • WS-INP1 and WS-INP2 are the inputs passed from MAINPRWR to the SUBPRWR.
  • SUBPRWR receives the data into LS-INP1 and LS-INP2 from MAINPRWR, adds them, places the result into into LS-RESULT.
  • SUBPRWR returns the LS-RESULT, and MAINPRWR receives it into WS-RESULT and displays it.
Note! Returning data from SUBPROG to MAINPROG works in a similarly for Static calls as well.