Let's understand Mainframe
Home Tutorials Interview Q&A Quiz Mainframe Memes Contact us About us

Module 11:- Library Facility and sub-programming


Sub-programming

  • Sometimes it is very difficult to code a large and complex business recruitment into one program. Thus, modular programming concept is used, where large program functionality is divided into smaller sub-programs known as modules. We will learn how to code such code and call sub-programs in this section
  • Sub-program is preferred when you are coding a functionality which is common to multiple programs. This way you do not have to write same functionality repeatedly in multiple programs

Coding a sub-program in COBOL

  • program-name coded in PROGRAM-ID entry of the sub-program will be used while calling it
  • PROCEDURE DIVISION header should be coded using a USING phrase
  • Basic syntax of PROCEDURE DIVISION for sub-program

    PROCEDURE DIVISION [USING data-name-1 [,data-name-2]…]

  • Where,
    • The data-name1, data-name-2 are those datanames for which values will be passed by main-program while calling this sub-program
    • All datanames coded in USING clause must be defined in the LINKAGE SECTION of DATA DIVISION.
    • The LINKAGE SECTION can appear only in sub-programs.
    • General format of LINKAGE SECTION:-

      DATA DIVISION. LINKAGE SECTION. [linkage-section-entries…]

    • LINKAGE SECTION is explained in brief in < LINK > LINKAGE SECTION OF DATA DIVISON MODULE-5 < /LINK >
  • The data values which are passed back and forth between main program and sub program referred to as parameter.
  • These parameters must be defined in WORKING-STORAGE SECTION of main program and LINKAGE SECTION of sub-program.
  • Parameter’s data type coded in main program and sub-program should be compatible
  • Sub-program must be terminated by either GO BACK or EXIT PROGRAM statement

Calling a sub-program in COBOL

  • Sub-program can be called from any main-program or from another sub-program
  • Sub-program can be called by its name (coded in the PROGRAM-ID)
  • CALL statement is used to call any sub-program
  • Basic syntax of CALL:-

    CALL {identifier/literal} USING     [{BY REFERENCE/BY CONTENT/BY VALUE} data-name-1     [,{BY REFERENCE/BY CONTENT/BY VALUE} data-name-2]…]

  • Identifier/literal indicates the name of sub-program to be called
  • Parameter passing can be done in three ways:-
    • BY REFERENCE (default)
    • BE CONTENT
    • BY VALUE
  • Call BY REFERENCE
    • The address of parameter is passed
    • The subprogram refers to and processes data items in the storage of calling program rather than working on a copy of the data
    • Changes done by sub-program on parameters is visible in the calling program
  • Call BY CONTENT
    • The parameters are passed immediately by value
    • Calling program passes only the contents of the literal or identifier.
    • The called program cannot change the value of the literal or identifier in the calling program, even if it modifies the data item in which it received the literal or identifier
  • Call BY VALUE
    • The parameters are passed directly, by value
    • Calling program passes the value of literal or identifier, not a reference to the sending data item.
    • Called program can change the parameters value but it will not be visible to main program
    • It is coded to mostly call non-COBOL program

Example program to call sub-program from main-program

  • For example, you are designing a simple program ‘SUBPROG’ that will displays the sum of two values passed to it. Now, when SUBPROG is called either from JCL or from another program, two values will be passed to it. In SUBPROG these values needs to be received in order to process it, and therefore, in LINKAGE SECTION we can specify the data item declaration of the values that it will receive.
  • COBOL Sub-routine program to compute sum of values passed to it:-

    000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. SUBPROG. 000300 ENVIRONMENT DIVISION. 000400 DATA DIVISION. 000500 WORKING-STORAGE SECTION. 000600 01 OUTPUT-DATA PIC 9(4). 000700 LINKAGE SECTION. 000800 01 PARM-BUFFER. 000900 05 PARM-LENGTH PIC S9(4) COMP. 001000 05 PARM-INPUT1 PIC 9(2). 001100 05 PARM-INPUT2 PIC 9(2). 001200 PROCEDURE DIVISION USING PARM-BUFFER. 001300 MAIN-PARA. 001400 COMPUTE OUTPUT-DATA = PARM-INPUT1 + PARM-INPUT2. 001500 DISPLAY 'PARM-INPUT1: ' PARM-INPUT1. 001600 DISPLAY 'PARM-INPUT2: ' PARM-INPUT2. 001700 DISPLAY 'SUM VALUE : ' OUTPUT-DATA. 001800 GOBACK.

    Above sub routine program can be called from another COBOL Program or JCL.
    SUBPROG called from another COBOL program ‘MAINPROG:-
    IMP Note:- When you compile the program that is calling another program, make sure to specify the load library of called program in SYSLIB DD of Link Edit step.

    000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. MAINPROG. 000300 ENVIRONMENT DIVISION. 000400 DATA DIVISION. 000500 WORKING-STORAGE SECTION. 000600 01 INPUTS. 000600 05 PRM-LENGTH PIC S9(4) COMP. 000600 05 INPUT1 PIC 9(2). 000700 05 INPUT2 PIC 9(2). 000800 PROCEDURE DIVISION. 000900 MAIN-PARA. 001000 MOVE 12 TO INPUT1. 001100 MOVE 13 TO INPUT2. 001200 CALL 'MFPROG1' USING PRM-LENGTH, INPUT1, INPUT2. 001300 STOP RUN.

    JCL used to execute MAINPROG:-

    //DEPTJOB JOB A123,’STEVE’ //STEP01 EXEC PGM=MAINPROG //SYSOUT DD SYSOUT=A //

    Output:-

    PARM-INPUT1: 12 PARM-INPUT2: 13 SUM VALUE : 0025

    SUBPROG called from JCL:-

    //DEPTJOB JOB A123,’STEVE’ //STEP01 EXEC PGM=SUBPROG,PARM='0410' //SYSOUT DD SYSOUT=A //

    Output:-

    PARM-INPUT1: 04 PARM-INPUT2: 10 SUM VALUE : 0014






© copyright mainframebug.com
Privacy Policy