Compaq COBOL
User Manual


Previous Contents Index

12.4.2 The Linkage Section

You must define each data name from the Procedure Division header's USING data name list in the called subprogram's Linkage Section. For example:


LINKAGE SECTION. 
 
01 PART     PICTURE... 
01 AMOUNT   PICTURE... 
01 INVOICE  PICTURE... 
01 COLOR    PICTURE... 
01 COST     PICTURE... 
 
PROCEDURE DIVISION USING PART, AMOUNT, COLOR, COST. 

Of those data items you define in the Linkage Section, only those named in the calling program's Procedure Division header's USING phrase are accessible to the called program. In the previous example, INVOICE is not accessible from the called program.

When a subprogram references a data name from the Procedure Division header's USING data name list, the subprogram processes it according to the definition in its Linkage Section.

A called program's Procedure Division can reference data names in its Linkage Section only if it references one of the following:

In Figure 12-4, SUB is called by MAINPROG. Because MAINPROG names FILE-RECORD and WORK-RECORD in its CALL "SUB" USING statement, SUB can reference these data names just as if they were in its own Data Division. However, SUB accesses these two data items with its own data names, F-RECORD and W-RECORD.

Figure 12-4 Defining Data Names in the Linkage Section


12.5 Communicating with Contained COBOL Programs

A contained COBOL program is a subprogram nested in another COBOL program (the containing program). The complete source of the contained program is found within the containing program. A contained program can also be a containing program.

A COBOL containing/contained program provides you with program and data attributes that noncontained COBOL programs do not have. These attributes, described in the next several sections, often allow you to more easily share and more conveniently access COBOL data items and other program resources.

This COBOL programming and data structuring capability encourages modular programming. In modular programming, you divide the solution of a large data processing problem into individual parts (the contained programs) that can be developed relatively independently.

Consequently, the use of the COBOL containing/contained block structure as a modular programming design can increase program efficiency and assist in program modification and maintainability.

The contained program uses all calling procedures described in Sections 12.3 and 12.4. However, when a contained program includes the COMMON clause (a program attribute) and the GLOBAL clause (a data and file trait), the additional rules described in the following sections apply.

12.5.1 The COMMON Clause

The COMMON clause is a program attribute that can be applied to a directly contained program. The COMMON clause is a means of overriding normal scoping rules for program names, namely that a program that does not possess the common attribute and that is directly contained within another program can be referenced only by statements included in that containing program. For more information on Scope of Names rules, refer to the Compaq COBOL Reference Manual.

The common attribute is attained by specifying the COMMON clause in a program's Identification Division. A program that possesses the common attribute can be referenced by statements included in that containing program and by any programs directly or indirectly contained in that containing program, except the program possessing the common attribute and any programs contained within it.

Example 12-6 shows a run unit that has a COBOL program (PROG-MAIN) ((1)) with three contained programs ((2), (3), and (4)); one of which (((2)) has the COMMON clause. The example indicates which programs can call the common program.

Example 12-6 Using the COMMON Clause

                IDENTIFICATION DIVISION. 
                PROGRAM-ID. PROG-MAIN.   (1)
                . 
                . 
                . 
         
                CALL PROG-NAME-B 
                . 
                . 
                . 
                IDENTIFICATION DIVISION. 
                PROGRAM-ID. PROG-NAME-B IS COMMON PROGRAM.  (2)
                . 
                . 
                . 
                IDENTIFICATION DIVISION. 
                PROGRAM-ID. PROG-NAME-D.  (3)
                . 
                . 
                . 
                . 
                . 
                END PROGRAM PROG-NAME-D. 
                END PROGRAM PROG-NAME-B. 
         
                IDENTIFICATION DIVISION. 
                PROGRAM-ID. PROG-NAME-C.  (4)
                . 
                CALL PROG-NAME-B 
                . 
                .            
                END PROGRAM PROG-NAME-C. 
                END PROGRAM PROG-MAIN. 

PROG-NAME-B ((2)) and PROG-NAME-C ((4)) are directly contained in PROG-MAIN ((1)); PROG-NAME-D ((3)) is indirectly contained in PROG-MAIN.

PROG-MAIN ((1)) can call PROG-NAME-B ((2)) because PROG-MAIN directly contains PROG-NAME-B. PROG-NAME-B ((2)) can call PROG-NAME-D ((3)) because PROG-NAME-B directly contains PROG-NAME-D.

PROG-NAME-C ((4)) can call PROG-NAME-B ((2)) because:

However, PROG-NAME-D ((3)) cannot call PROG-NAME-B ((2)) because PROG-NAME-D ((3)) is contained within PROG-NAME-B ((2)). Similarly, PROG-NAME-D ((3)) cannot call PROG-NAME-C ((4)) because PROG-NAME-C ((4)) is not visible to PROG-NAME-D ((3)). If PROG-NAME-C ((4)) was made COMMON it could call PROG-NAME-D ((3)). Additionally, PROG-NAME-C ((4)) cannot call PROG-NAME-D ((3)) because PROG-NAME-C ((4)) is outside the scope of PROG-NAME-B ((2)).

12.5.2 The GLOBAL Clause

Data and files can be described as either global or local. A local name can be referenced only by the program that declares it. A global name is declared in only one program but can be referenced by both that program and any program contained in the program that declares the global name.

Some names are always global, other names are always local, and some names are either local or global depending on specifications in the program that declares the names. For more information on Scope of Names rules, see the Compaq COBOL Reference Manual.

12.5.2.1 Sharing GLOBAL Data

A data name is global if the GLOBAL clause is specified in the Data Description entry by which the data name is declared or in another entry to which that Data Description entry is subordinate. If a program is contained within another program, both programs may reference data possessing the global attribute. The following example shows the Working-Storage Section of a containing program MAINPROG. Any contained program in MAINPROG, as well as program MAINPROG, can reference that data (unless the contained program declares other data with the same name).


WORKING-STORAGE SECTION. 
01    CUSTOMER-FILE-STATUS   PIC XX      GLOBAL. 
01    REPLY                  PIC X(10)   GLOBAL. 
01    ACC-NUM                PIC 9(18)   GLOBAL. 

12.5.2.2 Sharing GLOBAL Files

A file connector is global if the GLOBAL clause is specified in the File Description entry for that file connector. If a program is contained within another program, both programs may reference a file possessing the global attribute. The following example shows a file (CUSTOMER-FILE) with the GLOBAL clause in a containing program MAINPROG. Any contained program in MAINPROG, as well as program MAINPROG, can reference that file.


IDENTIFICATION DIVISION. 
PROGRAM-ID.   MAINPROG. 
. 
. 
. 
DATA DIVISION. 
FILE SECTION. 
FD    CUSTOMER-FILE 
      GLOBAL 
. 
. 
. 

Any special registers associated with a GLOBAL file are also global.

12.5.2.3 Sharing USE Procedures

The USE statement specifies declarative procedures to handle input/output errors. It also can specify procedures to be executed before the program processes a specific report group.

More than one USE AFTER EXCEPTION procedure in any given program can apply to an input/output operation when there is one procedure for file name and another for the applicable open mode. In this case, only the procedure for file name executes. Figure 12-5 shows that FILE-NAME-PROBLEM SECTION executes.

Figure 12-5 Sharing USE Procedures


At run time, two special precedence rules apply for the selection of a declarative when programs are contained in other programs. In applying these two rules, only the first qualifying declarative is selected for execution. The order of precedence for the selection of a declarative follows:

Rule 1 ---The declarative that executes first is the declarative within the program containing the statement that caused the qualifying condition. In Figure 12-6, FILE-NAME-PROBLEM procedure executes.

Figure 12-6 Executing Declaratives with Contained Programs (Rule 1)



Rule 2 ---If a declarative is not found using Rule 1, the Run-Time System searches all programs directly or indirectly containing that program for a global use procedure. This search continues until the Run-Time System either: (1) finds an applicable USE GLOBAL declarative, or (2) finds the outermost containing program. Either condition terminates the search; the second condition terminates both the search and the run unit.

Figure 12-7 shows applicable USE GLOBAL declaratives found in a containing program before the outermost containing program. Note that the first OPEN goes to the mode-specific procedure in the USE-PROGRAM rather than the file-specific procedure in the MAINPROG-PROGRAM.

Figure 12-7 Executing Declaratives Within Contained Programs (Rule 2)


For information on the negative effect of USE procedures that reference LINKAGE SECTION items on compiler optimization, see Section 15.5.5, Minimizing USE Procedures with LINKAGE SECTION References .

12.5.2.4 Sharing Other Resources

Condition names, record names, and report names can also have the global attribute. Any program directly or indirectly contained within the program declaring the global name can reference the global name.

A condition name declared in a Data Description entry is global if the condition-variable it is associated with is a global name.

A record name is global if the GLOBAL clause is specified in the Record Description entry by which the record name is declared, or in the case of Record Description entries in the File Section, if the GLOBAL clause is specified in the File Description entry for the file name associated with the Record Description entry.

A report name is global if the GLOBAL clause is specified in the Report Description entry by which the report name is declared. In addition, if the Report Description entry contains the GLOBAL clause, the special registers LINE-COUNTER and PAGE-COUNTER are global names.

Because you cannot specify a Configuration Section for a program contained within another program, the following types of user-defined words are always global; that is, they are always accessible from within a contained program:

These user-defined words can be referenced by statements and entries either in the program that contains the Configuration Section or any program contained in that program.

12.6 Calling Compaq COBOL Programs from Other Languages

The CALL and CANCEL verbs allow you to call and cancel Compaq COBOL programs (including routines and separately compiled program units) from within a Compaq COBOL program. The cobcall , cobcancel , and cobfunc RTL calls allow you to call and cancel those programs from programs written in other languages.

When you use cobcall , cobcancel , and cobfunc , the same considerations and results will be in effect as if you had used the CALL and CANCEL statements (see Section 12.1.2 and Section 12.3).

If you need both a CANCEL (to reinitialize data) and a CALL, you can code it with a single cobfunc call. cobfunc is essentially a jacket that calls cobcancel and cobcall .

Table 12-1 shows these calls and their basic differences.

Table 12-1 Calls to COBOL Programs
RTL Call Function
cobcall Calls a COBOL program. Program variables remain in their last state.
cobcancel Cancels a COBOL program. Program variables are reset.
cobfunc Calls a COBOL program then cancels it. Program variables are reset on exit.

12.6.1 Calling COBOL Programs from C

Using cobfunc.h as shown in Example 12-8, the C code in Example 12-7 demonstrates a program that calls a COBOL program with three arguments. In this example the COBOL program, CALLEDFROMC, expects two strings and an integer.

Example 12-7 Calling a COBOL Program from C

#include <stdio.h> 
#include "cobfunc.h" 
extern int calledfromc(); 
 
main(int argc, char **argv) 
{ 
  char *arg1="arg1_string"; 
  char *arg2="1234"; 
  int arg3 = 16587; 
  int func_result; 
  char *arglist[10]; 
#ifdef __osf__ 
 
  cob_init(argc, argv, NULL); 
#endif 
  arglist[0] = arg1; 
  arglist[1] = arg2; 
  arglist[2] = (char *) &arg3; 
 
  func_result = cobfunc ("calledfromc", 3, arglist); 
} 

Example 12-8 could be used as an #include file for the cobfunc , cobcall , and cobcancel functions.

Example 12-8 C Include File cobfunc.h

void cobcancel ( /* CANCEL the named COBOL routine */ 
    char *name 
    ); 
 
int cobcall (   /* Call a COBOL program from a C routine */ 
    char *name, /* READ: name of the program */ 
    int argc,   /* READ: how many arguments */ 
    char **argv /* READ: array of pointers to the arguments */ 
    ); 
 
int cobfunc (   /* Call a COBOL program from a C routine, then CANCEL it */ 
    char *name, /* name of the program */ 
    int argc,   /* how many arguments */ 
    char **argv /* array of pointers to the arguments */ 
    ); 
 
#ifdef __osf__ 
 
void cob_init (                 /* init the RTL */ 
    int argc,                   /* argument count */ 
    char **argv,                /* arguments */ 
    char **envp                 /* environment variable pointers */ 
    ); 
#endif 

Note that argv[0] is the first argument to pass and argv[n-1] is the nth. The maximum number of arguments supported is 254.

For Tru64 UNIX programs, if the main routine is written in C, it must call cob_init. (See Section 12.1.2, Calling Procedures.) The Compaq COBOL program must expect its arguments by reference.

Example 12-9 COBOL Called Program "CALLEDFROMC"

IDENTIFICATION DIVISION. 
PROGRAM-ID. CALLEDFROMC. 
DATA DIVISION. 
WORKING-STORAGE SECTION. 
01 TEST-RESET PIC X(10) VALUE "OFF". 
01 RETVAL PIC 9(5) COMP VALUE 357. 
LINKAGE SECTION. 
01 ARG1 PIC X(10). 
01 ARG2 PIC 9(4). 
01 ARG3 PIC 9(5) COMP. 
PROCEDURE DIVISION USING ARG1 ARG2 ARG3 GIVING RETVAL. 
P0. 
        DISPLAY "In CALLEDFROMC". 
        DISPLAY "test-reset is: " TEST-RESET 
        MOVE "on" TO TEST-RESET. 
        DISPLAY "arg1=" ARG1. 
        DISPLAY "arg1=" ARG1 ", arg2=" ARG2 ", arg3=" ARG3 WITH CONVERSION. 
END PROGRAM CALLEDFROMC. 

Values Returned by cobcall and cobfunc

The RTL calls cobcall and cobfunc can return a signed integer value from the GIVING clause of the COBOL program whose value is a longword integer (for example, PIC S9(9) COMP). The results of returning other values from the program called by cobcall or cobfunc are undefined.

Consider this example of the use of cobcall / cobfunc / cobcancel in a C program that uses cobcall , cobfunc , and cobcancel to call or cancel another COBOL program. Following is progc.c, the C program that calls the COBOL program:

Example 12-10 C Program Using cobcall, cobfunc, and cobcancel

        /* File: progc.c */ 
        #include "stdlib.h" 
        #include "stdio.h"                      /* printf */ 
        #include "string.h"                     /* strlen */ 
 
        #define NUMARGS  4                      /* up to 254 allowed */ 
 
        void    cobcancel(char *name); 
        int     cobcall  (char *name, int argc, char **argv); 
        int     cobfunc  (char *name, int argc, char **argv); 
 
        void display(char *s, int r, int a); 
 
        extern int progcob();                   /* COBOL returns int */ 
 
            void mainx(){ 
            int  retval = 0;                    /* progcob returns int */ 
            char *a_list[NUMARGS];              /* progcob needs 4 args */ 
            int arg1 = 1, arg2 = 2, arg3 = 3, arg4 = 4; 
 
            a_list[0] = (char *) &arg1;         /* address of 1st arg */ 
            a_list[1] = (char *) &arg2;         /* address of 2nd arg */ 
            a_list[2] = (char *) &arg3;         /* address of 3rd arg */ 
            a_list[3] = (char *) &arg4;         /* address of 4th arg */ 
 
            display("[0] All the initialized values", retval, arg1); 
 
            retval = cobcall("progcob", NUMARGS, a_list); 
            display("[1] After calling cobcall:", retval, arg1); 
 
            retval = cobfunc("progcob", NUMARGS, a_list); 
            display("[2] After calling cobfunc:", retval, arg1); 
 
            retval = cobcall("progcob", NUMARGS, a_list); 
            display("[3] After calling cobcall again:", retval, arg1); 
 
            cobcancel("progcob"); 
            display("[4] After calling cobcancel:", retval, arg1); 
 
            retval = cobcall("progcob", NUMARGS, a_list); 
            display("[5] After calling cobcall again:", retval, arg1); 
        } 
                                                  
            void display(char *s, int r, int a){ 
            unsigned int i = 0; 
            printf("\n%s\n", s); 
            for (i = 0; i < strlen(s); i++) printf("="); 
            printf("\n   retval = %d", r); 
            printf("\n   arg1   = %d", a); 
            printf("\n"); 
        } 

Following is progcob.cob, the COBOL program that is called by the C program:

Example 12-11 COBOL Called Program "PROGCOB"

        identification division. 
        * File progcob.cob 
        ************************************************************** 
        * The C program calls this COBOL program with four arguments: 
        *    arg1, arg2, arg3, arg4. 
        * 
        * This program performs: 
        *    arg1, myVal get the value of arg1 + arg2 + arg3 + arg4 
        * 
        * When cobfunc or cobcancel is called the values in 
        * working-storage are reset to their initial values. 
        * 
        * retVal: to demonstrate the value returned by this program. 
        * myVal : to demonstrate cobcancel in the C program 
        * arg1  : to demonstrate cobcall and cobfunc in the C program. 
        ************************************************************** 
        program-id. progcob. 
        data division. 
        working-storage section. 
        01 retVal pic 9(9) comp value 987654321. 
        01 myVal  pic 9(9) comp value 0. 
        linkage section. 
        01 arg1   pic 9(9) comp value 0. 
        01 arg2   pic 9(9) comp value 0. 
        01 arg3   pic 9(9) comp value 0. 
        01 arg4   pic 9(9) comp value 0. 
procedure division using 
               arg1 arg2 arg3 arg4 giving retVal. 
        p0.    display "   +------------------- From COBOL --------------------". 
               display "   | myVal  = " myVal  with conversion. 
               display "   | arg1   = " arg1   with conversion. 
               display "   | arg2   = " arg2   with conversion. 
               display "   | arg3   = " arg3   with conversion. 
               display "   | arg4   = " arg4   with conversion. 
               display "   | retVal = " retVal with conversion. 
               add   arg1  arg2  arg3  arg4 giving arg1 myVal. 
               display "   + After 'add arg1 arg2 arg3 arg4 giving arg1 myVal':". 
               display "   | myVal  = " myVal  with conversion. 
               display "   | arg1   = " arg1   with conversion. 
               display "   | arg2   = " arg2   with conversion. 
               display "   | arg3   = " arg3   with conversion. 
               display "   | arg4   = " arg4   with conversion. 
               display "   | retVal = " retVal with conversion. 
               display "   +---------------------------------------------------". 

Note that the C program progc.c does not have a function called main . The function name "main" has to be renamed, because the COBOL RTL already contains a symbol called main on Windows NT Alpha. To resolve this, progc.c is called from a dummy COBOL program called progmain.cob. On Tru64 UNIX, if a COBOL routine is not the main program, you need to call cob_init.

Here is progmain.cob:


        identification division. 
        * file progmain.cob 
        program-id. progmain. 
        procedure division. 
        s1. 
            call "mainx". 
            stop run. 
        end program progmain. 

The return value from the COBOL program is an int . Therefore, it is customary to use the int data type for the variables in C and COBOL programs that are passed back and forth. For example, retval , arg1 , arg2, arg3, and arg4 are declared as int and pic(9) in the C and COBOL programs, respectively.

Here are the commands to compile, link, and run on different platforms:


            [OpenVMS] $ cobol PROGMAIN.COB, PROGCOB.COB 
                      $ cc PROGC.C 
                      $ link PROGMAIN.OBJ +PROGCOB.OBJ +PROGC.OBJ   (*) 
                      $ run PROGMAIN.EXE 
 
              [UNIX]  % cobol progmain.cob progcob.cob progc.c      (*) 
                      % a.out 
 
        [Windows NT]  c:\> cobol -c progmain.cob progcob.cob 
                      c:\> cl -c progc.c 
                      c:\> cobol progmain.obj progcob.obj progc.obj (*) 
                      c:\> progmain 

The order of listing at (*) is fundamental. Here is a sample run:


        [0] All the initialized values 
        ============================== 
           retval = 0 
           arg1   = 1 
           +------------------- From COBOL -------------------- 
           | myVal  =         0 
           | arg1   =         1 
           | arg2   =         2 
           | arg3   =         3 
           | arg4   =         4 
           | retVal = 987654321 
           + After 'add arg1 arg2 arg3 arg4 giving arg1 myVal': 
           | myVal  =        10 
           | arg1   =        10 
           | arg2   =         2 
           | arg3   =         3 
           | arg4   =         4 
           | retVal = 987654321 
           +--------------------------------------------------- 
 
        [1] After calling cobcall: 
        ========================== 
           retval = 987654321 
           arg1   = 10 
           +------------------- From COBOL -------------------- 
           | myVal  =        10 
           | arg1   =        10 
           | arg2   =         2 
           | arg3   =         3 
           | arg4   =         4 
           | retVal = 987654321 
           + After 'add arg1 arg2 arg3 arg4 giving arg1 myVal': 
           | myVal  =        19 
           | arg1   =        19 
           | arg2   =         2 
           | arg3   =         3 
           | arg4   =         4 
           | retVal = 987654321 
           +--------------------------------------------------- 
 
        [2] After calling cobfunc: 
        ========================== 
           retval = 987654321 
           arg1   = 19 
           +------------------- From COBOL -------------------- 
           | myVal  =         0 
           | arg1   =        19 
           | arg2   =         2 
           | arg3   =         3 
           | arg4   =         4 
           | retVal = 987654321 
           + After 'add arg1 arg2 arg3 arg4 giving arg1 myVal': 
           | myVal  =        28 
           | arg1   =        28 
           | arg2   =         2 
           | arg3   =         3 
           | arg4   =         4 
           | retVal = 987654321 
           +--------------------------------------------------- 
 
        [3] After calling cobcall again: 
        ================================ 
           retval = 987654321 
           arg1   = 28 
 
        [4] After calling cobcancel: 
        ============================ 
           retval = 987654321 
           arg1   = 28 
           +------------------- From COBOL -------------------- 
           | myVal  =         0 
           | arg1   =        28 
           | arg2   =         2 
           | arg3   =         3 
           | arg4   =         4 
           | retVal = 987654321 
           + After 'add arg1 arg2 arg3 arg4 giving arg1 myVal': 
           | myVal  =        37 
           | arg1   =        37 
           | arg2   =         2 
           | arg3   =         3 
           | arg4   =         4 
           | retVal = 987654321 
           +--------------------------------------------------- 
 
        [5] After calling cobcall again: 
        ================================ 
           retval = 987654321 
           arg1   = 37 


Previous Next Contents Index