Program Communication Statement


Program communication statements manage interactions between program components, different programs, or external entities. They enable structured programming by sharing code and data among different parts of a program or between separate programs.

The program communication statements are –

  • CALL Statement
  • Cancel Statement
  • STOP RUN Statement
  • EXIT PROGRAM Statement
  • GOBACK Statement
  • GO TO Statement

CALL Statement


A CALL statement is used to invoke a subprogram to complete a task. The CALL statement is always coded in the calling or main program and the program name in the CALL statement is called or subprogram.

Syntax -

CALL literal-1 [USING variable1, ..., variable-n]
  • literal-1 - Specifies name of the subprogram (or the data item holding it) to be invoked.
  • variable1, ..., variable-n - Specifies the data items or literals that are passed from the main program to the subprogram.

CALL Types -

CALLs are two types based on how the subprogram is called from main program -

  • Static call - CALL statement with SUBPROG name in quotes makes the call as STATIC CALL. When we compile the MAINPROG, the SUBPROG load module is attached to the MAINPROG load module and stored together.
    CALL "subprogram-name" [USING variable1, ..., variable-n]
    MAINPROG should be compiled with NODYNAM compiler option. Example - Static call
    CALL "SUBPROG" USING WS-INPUT1, WS-INPUT2.

  • Dynamic call - A CALL statement with a variable that contains the SUBPROG name makes the call as DYNAMIC CALL. When we compile MAINPROG and SUBPROG, their load modules are stored separately, and the load modules are not linked to each other.
    CALL ws-variable [USING variable1, ..., variable-n]
    MAINPROG should be compiled with DYNAM compiler option. Example - Dynamic call
    MOVE "SUBPROG"  TO WS-SUBPROG.
    CALL WS-SUBPROG USING WS-INPUT1, WS-INPUT2.

CALL with Passing Parameters

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

  • BY REFERENCE - Default option. It is used to pass the memory location of the actual data, not a copy of the data. If the SUBPROG modifies the value of the passing input variable, the new value is reflected in the MAINPROG.
    CALL subprog-name USING BY REFERENCE PARM1, PARM2, ...
    Example - Dynamic call with BY REFERENCE
    CALL WS-SUBPROG USING BY REFERENCE WS-INP1, WS-PARM2, ...

  • BY VALUE - It is used to pass the copy of the data to the subprogram. If the SUBPROG modifies the value of the passing input variable, the new value is not reflected in the MAINPROG.
    CALL subprog-name USING BY VALUE PARM1, PARM2, ...
    Example - Dynamic call with BY VALUE
    CALL WS-SUBPROG USING BY VALUE WS-INP1, WS-PARM2, ...

Example -

Scenario - Static Call from MAINPROG to SUBPROG and receiving the result back from SUBPROG.

MAINPROG -

----+----1----+----2----+----3----+----4----+----5----+
       ...
       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
       ...
	   PROCEDURE DIVISION. 
	  * Calling subprogram staically with two inputs 
      * and receiving the result from SUBPROG
           CALL "SUBPROG" USING WS-INP1, WS-INP2, WS-RESULT.

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

SUBPROG -

----+----1----+----2----+----3----+----4----+----5----+
       ...
       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

CANCEL


CANCEL is used to release the resources associated with a previously called subprogram. If the subprogram is no longer needed, it is used to free up the resources used by the subprogram.

CANCEL subprogram-name

Example - Let us assume SUBPROG is the subprogram name and WS-SUBPROG is working-storage variable that holds the subprogram name.

MOVE "SUBPROG" TO WS-SUBPROG.
CANCEL WS-SUBPROG

STOP RUN


STOP RUN is used to terminate the execution of a program. Once it is executed, control returns to the operating system. It always uses the main or calling program.

STOP RUN.

Example - MAINPROG with STOP RUN.

----+----1----+----2----+----3----+----4----+----5----+
       IDENTIFICATION DIVISION.
       PROGRAM-ID. MAINROG.
	   AUTHOR. MTH.
	   ...
       PROCEDURE DIVISION.
           ...
           STOP RUN.

EXIT PROGRAM


EXIT PROGRAM marks the end of a subprogram (called program) processing and returns control to the main program (calling program). It's mainly used in subprograms, or called programs within COBOL.

EXIT PROGRAM.

Example - MAINPROG calls the SUBPROG and it is coded with EXIT PROGRAM.

----+----1----+----2----+----3----+----4----+----5----+
       IDENTIFICATION DIVISION.
       PROGRAM-ID. SUBPROG.
	   AUTHOR. MTH.
	   ...
       PROCEDURE DIVISION.
           ...
           EXIT PROGRAM.

Control returns to the MAINPROG when the EXIT PROGRAM is executed.

GOBACK


GOBACK defines the logical end of a program and gives the control back from where it was received. It can code in both the main program and subprogram.

GOBACK.

Example - MAINPROG coded with GOBACK.

----+----1----+----2----+----3----+----4----+----5----+
       IDENTIFICATION DIVISION.
       PROGRAM-ID. MAINPROG.
	   AUTHOR. MTH.
	   ...
       PROCEDURE DIVISION.
           ...
           GOBACK.

Control returns to the operating system when the GOBACK is executed.

GO TO


GO TO transfers control to another part of the program, allowing the program to "jump" to a different paragraph or section.

Other ways of using the GO TO statement are -

  • Unconditional GO TO - It is used to transfer control unconditionally to another part of the program. It is not advised to use individually.
    GO TO paragraph-1.
    Example - Passing control to a END-PARA.
    PROCEDURE DIVISION.
    BEGIN-PARA.
        DISPLAY 'Start'.
        GO TO END-PARA.
        DISPLAY 'This will be skipped'.
    	STOP RUN.
    END-PARA.
        DISPLAY 'End'.
    Output -
    Start
    End

  • Conditional GO TO - It is advised to use with conditional statements like IF and EVALUATE.
    GO TO paragraph-1.
    Example - GO TO with IF.
    PROCEDURE DIVISION.
    PARA0.
        DISPLAY 'Para0'.
    	MOVE 3      TO WS-P
        PERFORM PARA1
    	   THRU PARA1-EXIT.
        DISPLAY 'Return to para0'.
    	STOP RUN.
    PARA1.
        DISPLAY 'Para1'.
    	IF WS-P > 1
    	   GO TO PARA1-EXIT
    	ELSE
    	   COMPUTE WS-P = WS-P + 1
    	END-IF.
    	DISPLAY 'WS-P: ' WS-P.
    PARA1-EXIT.
        EXIT.
    Output -
    Para0
    Return to para0