CALL Using Parameters


There are three ways of passing parameters from MAINPROG to SUBPROG and those are -

  • BY REFERENCE
  • BY CONTENT
  • BY VALUE

BY REFERENCE phrase -


BY REFERENCE phrase is used to pass the reference of the actual data, not a copy of the data to the subprogram. When we pass a variable BY REFERENCE, the SUBPROG receives the memory location of the variable. If the SUBPROG modifies the value of the passing input variable, the new value is reflected in the MAINPROG.

It is the default option if the BY phrase is not coded with a CALL statement.

Syntax -

CALL subprog-name USING BY REFERENCE PARM1, PARM2, ...

Example -

CALL WS-SUBPROG USING BY REFERENCE WS-INP1, WS-PARM2, ...

BY CONTENT phrase -


BY CONTENT phrase is used to pass the copy of the data to the subprogram. When we pass a variable using the BY CONTENT phrase, the SUBPROG receives a copy of the variable's content at the time of the call. If the SUBPROG modifies the value of the passing input variable, the new value will not reflected in the MAINPROG.

Syntax -

CALL subprog-name USING BY CONTENT PARM1, PARM2, ...

Example -

CALL WS-SUBPROG USING BY CONTENT WS-PARM1, WS-PARM2, ...

BY VALUE phrase -


The BY VALUE phrase is similar to the BY CONTENT phase and is used to pass the copy of the data to the subprogram. When we pass a variable using the BY VALUE phase, the SUBPROG receives a copy of the variable's value at the time of the call. BY VALUE clause is primarily introduced for communication with non-COBOL programs. It can also be used for COBOL-to-COBOL communication.

Syntax -

CALL subprog-name USING BY VALUE PARM1, PARM2, ...

Example -

CALL WS-SUBPROG USING BY VALUE WS-INP1, WS-INP2, WS-RESULT.
Note! Passing parameters should only code with CALL..USAGE, but not with PROCEDURE DIVISION USAGE.

Practical Example -


Scenario - CALL BY REFERENCE from MAINPROG to SUBPROG and receiving the result back from SUBPROG.

Main Program -

       IDENTIFICATION DIVISION.
       PROGRAM-ID. MAINPROG.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 WS-VAR.
          05 WS-INP1      PIC 9(02) VALUE 47. *> Input1
          05 WS-INP2      PIC 9(02) VALUE 25. *> Input2
          05 WS-RESULT    PIC 9(04).          *> Result Variable
       01 WS-CALLING-PROG PIC X(08) VALUE "SUBPROG".

	   PROCEDURE DIVISION. 

	  * Calling subprogram dynamically with two inputs 
      * and receiving the result from SUBPROG
           CALL WS-CALLING-PROG 
		        USING BY REFERENCE 
				WS-INP1, WS-INP2, WS-RESULT.

           DISPLAY "INPUTS:  " WS-INP1 ", " WS-INP2.
           DISPLAY "RESULTS: " WS-RESULT.

           STOP RUN. 

Sub Program -

       IDENTIFICATION DIVISION. 
       PROGRAM-ID. SUBPROG.
       AUTHOR. MTH.

       DATA DIVISION.
       LINKAGE SECTION.
       01 LK-INP1      PIC 9(02).  *> To receive input1 from MAINPROG
       01 LK-INP2      PIC 9(02).  *> To receive input2 from MAINPROG
       01 LK-RESULT    PIC 9(04).  *> To send result to MAINPROG

	  * Receiving data from main program CALL statement
       PROCEDURE DIVISION USING LK-INP1, LK-INP2, LK-RESULT. 

           COMPUTE LK-RESULT = LK-INP1 * LK-INP2.
           GOBACK.

JCL -

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

Output -

INPUTS:  47, 25
RESULTS:  1175

Explaining Example -

In the above example:

  • MAINPROG is the main program, and SUBPROG is the subprogram.
  • WS-INP1 and WS-INP2 are the inputs passed from MAINPROG to the SUBPROG. SUBPROG receives the data into LK-INP1, LK-INP2 from MAINPROG, multiplies those values, and places the result into LK-RESULT.
  • SUBPROG returns the output in LK-RESULT, and MAINPROG displays the result received from SUBPROG.