GOBACK
GOBACK Example
Scenario - Usage of the GOBACK in SUBPROG.
MAINPROG -
----+----1----+----2----+----3----+----4----+----5----+
IDENTIFICATION DIVISION.
PROGRAM-ID. MAINPROG.
AUTHOR. MTH.
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
05 WS-SUBPROG PIC X908) VALUE 'SUBPROG'.
PROCEDURE DIVISION.
* Calling subprogram staically with two inputs
* and receiving the result from SUBPROG
CALL WS-SUBPROG USING WS-INP1, WS-INP2, WS-RESULT.
DISPLAY "INPUTS: " WS-INP1 ", " WS-INP2.
DISPLAY "RESULTS: " WS-RESULT.
STOP RUN.
SUBPROG -
----+----1----+----2----+----3----+----4----+----5----+
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 //*********************************************** //* RUN A COBOL PROGRAM //*********************************************** //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.
- MAINPROG is coded with STOP RUN which returns the control to the system where the control is received.
- SUBPROG is coded with GOBACK that needs to return the control to the main program from where the control received.
- 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.