CALL Statement
The CALL Statement calls a sub-program, and passes parameters that are referenced in the LINKAGE SECTION of the CALL'ed program.
General Format:
CALL program-identifier-1
[ USING { [ BY {REFERENCE} ] {data-1} ...} ...]
{CONTENT } {OMITTED }
{VALUE } {NULL }
[ {RETURNING} INTO identifier-2 ]
{GIVING }
[ ON {EXCEPTION} statement-1 ]
{OVERFLOW }
[ NOT ON {EXCEPTION} statement-2 ]
{OVERFLOW }
[ END-CALL ]
Syntax:
program-identifier-nis a program name, which may be expressed as a data element, literal, or data returned from a function call.data-nis a data item.identifier-nis a numeric or alphanumeric data item.statement-nis an imperative statement.
General Rules:
-
Program-identifier-nis the name of the subprogram to be called. The rules that COBOL-IT uses for resolving program names, and locating the named module are described in Getting Started with COBOL IT Compiler Suite. -
The
RETURNINGdata item may be numeric or alphanumeric. WhenCALL’ing a C program, which is designed to return a data item that is non numeric/non alphanumeric such as a pointer, the COBOL variable receiving the data item must be described with aPIC Xnotation, or as a group item. - The
GIVING/RETURNINGphrase may precede theUSINGphrase. - For details about how the
CALL'ing program will search for the target program beingCALL’ed, see Getting Started with COBOL-IT. Note that where target programs are entered in lower case, theCALLstatement will also search for the symbol in upper case, and vice versa.
The CALL’ed subprogram
- If the
CALL’ed subprogram contains theIS INITIAL PROGRAMclause, then the subprogram is placed into itsINITIALstate every time it isCALL’ed. - If the
CALL’ed subprogram does not contain theIS INITIAL PROGRAMclause, then the subprogram is placed into itsINITIALstate the first time it is called. However, for all subsequentCALL’s, the program retains its state in resident memory. Retained state includes the value of variables inLOCAL-STORAGE, andWORKING-STORAGESections, and theOPENstate of files, as well as file position. - If a subprogram that does not contain the
IS INITIAL PROGRAMclause is the target of aCANCELverb, then the next time it isCALL’ed, it is placed into itsINITIALstate.
The USING clause
- The
USINGclause names the parameters that are passed to the subprogram. - The manner in which the parameters are passed is determined by the
BYclause, which indicates whether the parameters are passedBY REFERENCE(the default),BY VALUE, orBY CONTENT. - The order in which the parameters appear in the
USINGclause of theCALL’ing program must match the order in which the parameters are listed in theUSINGclause of thePROCEDURE DIVISIONstatement in theCALL’ed program. - The
USINGclause allows figurative constants to be used as parameters. In the case below, the figurative constant zero is considered to be alphanumeric data that is one byte in length.
Example:CALL “MYPROG” USING ZERO.
The BY clause
- The
BY REFERENCEclause indicates that the address of the data item has been passed through the Linkage Section. Updates to the data item are made directly to the memory address of the data item, and changes to the value of the data item will be seen in theCALL’ing program. - The
BY VALUEclause indicates that theVALUE, rather than memory address of the item is passed through the Linkage Section. Updates to the data item will only be seen locally in the sub program, and will not be returned through the data item to theCALL’ing program. - The
BY CONTENTclause indicates that a copy of the address of the data item has been passed through the Linkage Section. Updates to the data item will only be seen locally in the sub program, and will not be returned through the data item to theCALL’ing program. BY REFERENCEis assumed as the default if noBYclause is present.- In the
RETURNING/GIVINGclause,RETURNINGandGIVINGare synonyms.
The ON EXCEPTION/ON OVERFLOW clause
ON EXCEPTIONandON OVERFLOWare synonyms- The
EXCEPTION/OVERFLOWcondition is triggered if the subprogram that is the target of theCALLstatement cannot be loaded and executed. - If an
EXCEPTION/OVERFLOWcondition is triggered, and there is noON EXCEPTION/ON OVERFLOWclause, the following occur:- Program execution is halted,
- The error message
“Cannot find module ‘[subprogram name]’is written tostderr. - If the module has been compiled with
-fsource-location,-debug, or-g, then the line number of theCALLwill also be included in the output message, for example:C:/COBOL/CobolIT/Samples/call1.cbl:10: libcob: Cannot find module 'subpgm'
Otherwise, the line number is represented as “0”, for example:C:/COBOL/CobolIT/Samples/call1.cbl:0: libcob: Cannot find module 'subpgm' - If the program has been compiled with
-gor-fmem-info, the exception condition will also include a memory dump, for example:C:\COBOL\CobolIT\Samples>cobc –g call1.cblC:\COBOL\CobolIT\Samples>cobcrun call1C:/COBOL/CobolIT/Samples/call1.cbl:10: libcob: Cannot find module 'subpgm'Cobol memory dump+++++++++++++++++PROGRAM ID : call1(C:/COBOL/CobolIT/Samples/call1.cbl)
Current line : C:/COBOL/CobolIT/Samples/call1.cbl:10----------------------------
WORKING-STORAGE
RETURN-CODE = +000000000
TALLY = +000000000
SORT-RETURN = +000000000
NUMBER-OF-CALL-PARAMETERS = +000000000
ws-dummy =
COB-CRT-STATUS = 0000----------------------------
- If an
EXCEPTION/OVERFLOWcondition is triggered, and there is anON EXCEPTION/ON OVERFLOWclause, the following occur:- Program execution is not halted.
- The imperative statement(s) contained within the
ON EXCEPTION/ON OVERFLOWclause are executed. - The
NOT ON EXCEPTION/NOT ON OVERFLOWclause can be used to cause a set of imperative statements to be executed in the case where aCALLstatement is performed, and returns without triggering anON EXCEPTIONcondition. - Statements associated with a
NOT ON EXCEPTION/NOT ON OVERFLOWclause are executed after the CALL’ed program has finished executing, and returned control to theCALL’ing program.
LINKAGE-related runtime errors
- In the case where the Linkage Section of a
CALL’ed program contains more parameters than are passed by theCALL’ing program, a memory allocation error will result if the parameter not passed by the CALL’ing program is referenced in theCALL’ed program. - If a parameter passed by the
CALL’ing program is smaller than the corresponding data item in the Linkage Section of theCALL’ed program, no error is generated. However, a memory allocation error can result if undefined memory is referenced in theCALL’ed program. - If a parameter passed by the
CALL’ing program is larger than the corresponding data item in the Linkage Section of theCALL’ed program, no error is generated. The smaller receiving data item truncates the larger data item to be passed.
Code Sample:
IDENTIFICATION DIVISION.
PROGRAM-ID. CALL-1.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
77 DUMMY PIC X.
77 SUBPGM-NAME PIC X(5) VALUE "SUB-2".
77 DATA-1 PIC X(5) VALUE "HELLO".
77 RTN-VALUE PIC 99 VALUE 0.
PROCEDURE DIVISION.
CALL "SUB-2" USING BY REFERENCE DATA-1
RETURNING RTN-VALUE
ON EXCEPTION
DISPLAY "SUB-2 NOT FOUND!" LINE 10 COL 10
ACCEPT DUMMY LINE 10 COL 30
STOP RUN
END-CALL.
CALL"SUB-2".
CALL SUBPGM-NAME.
CALL "SUB-2" USING BY REFERENCE DATA-1.
CALL "SUB-2" USING BY CONTENT DATA-1.
CALL "SUB-2" USING BY VALUE DATA-1.
DISPLAY "CALL-1 COMPLETE!" LINE 15 COL 10.
ACCEPT DUMMY LINE 15 COL 30.
STOP RUN.
The CALL Prototype
General Rules for the CALL prototype:
ENTRYdeclarations must use parameters declared either asTYPEDEF, or with the reserved wordANY.- The external program must be properly structured. That is, it must contain a declaration for each of the
IDENTIFICATION DIVISION,ENVIRONMENT DIVISION,DATA DIVISION, andPROCEDURE DIVISION. - The
DELIMITEDclause is supported in the prototype definition.
For example:entry C-FUNCTION-VALc-call using By reference schar delimited - When the
DELIMITEDclause is used, strings passed to the C function are automatically null terminated.
For an example, see the Code Samples below for prog.cbl, cproto.cpy, and cfunc.c.
Code Sample (prog.cbl)
COPY "cproto.cpy".
IDENTIFICATION DIVISION.
PROGRAM-ID. prog.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 grpstr.
03 AV-STR PIC XX VALUE 'AV'.
03 STR PIC X(10) VALUE "STR10".
03 AP-STR PIC XX VALUE 'AP'.
03 zz-STR PIC 0 VALUE X'00'.
01 A1 PIC 99 VALUE 1.
01 A2 PIC 99 VALUE 2.
01 A3 PIC 99 VALUE 3.
01 A4 PIC 99 VALUE 4.
PROCEDURE DIVISION.
CALL "cfunction_val" USING "vallit" 1 2 3 4.
CALL "cfunction_ref" USING "reflit" 1 2 3 4.
DISPLAY "'" grpstr "'"
CALL "cfunction_val" USING STR A1 A2 A3 A4.
CALL "cfunction_ref" USING STR A1 A2 A3 A4.
DISPLAY "'" grpstr "'"
CALL "cfunction_any" USING grpstr function BYTE-LENGTH(grpstr).
.
Code Sample (cproto.cpy)
program-id. "c_typedefs" is external.
DATA DIVISION.
WORKING-STORAGE SECTION.
77 schar pic x is typedef.
77 uns-schar pic 9(2) comp-5 is typedef.
77 short pic s9(4) comp-5 is typedef.
77 uns-short pic 9(4) comp-5 is typedef.
77 int pic s9(9) comp-5 is typedef.
77 uns-int pic 9(9) comp-5 is typedef.
77 long pic s9(9) comp-5 is typedef.
77 uns-long pic 9(9) comp-5 is typedef.
77 l-long pic s9(18) comp-5 is typedef.
77 uns-l-long pic 9(18) comp-5 is typedef.
end program "c_typedefs".
program-id. "c_typedefs" is external.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
special-names.
call-convention 3 is Pascal
call-convention 0 is c-call.
$set constant C-FUNCTION-VAL "cfunction_val"
$set constant C-FUNCTION-REF "cfunction_ref"
$set constant C-FUNCTION-ANY "cfunction_any"
PROCEDURE DIVISION.
entry
C-FUNCTION-VAL
c-call using
by reference schar delimited
by value uns-schar
by value uns-short
by value uns-int
by value uns-l-long
returning int
entry
C-FUNCTION-REF
c-call using
by reference schar delimited
by reference uns-schar
by reference uns-short
by reference uns-int
by reference uns-l-long
returning int
entry
C-FUNCTION-ANY
c-call using
by reference any
by value uns-int
returning int
.
end program "c_typedefs".
Code Sample (cfunc.c)
#include "stdio.h"
int cfunction_val(char *s, char c1, short c2, int c3, long long c4)
{
printf("'%s' %d %d %d %d %lld\n", s, strlen(s), (int)c1, (int)c2, c3, c4);
}
int cfunction_ref(char *s, char *c1, short *c2, int *c3, long long *c4)
{
printf("'%s' %d ", s, strlen(s));
if (c1) {
printf("%d ", (int)(*c1));
} else {
printf("<NULL>");
}
if (c2) {
printf("%d ", (int)(*c2));
} else {
printf("<NULL>");
}
if (c3) {
printf("%d ", (int)(*c3));
} else {
printf("<NULL>");
}
if (c4) {
printf("%lld\n", (*c4));
} else {
printf("<NULL>\n");
}
}
int cfunction_any(void *any , int c1)
{
printf("'%s' %d\n", (long long)any, (int)c1);
}