Your Browser is not longer supported

Please use Google Chrome, Mozilla Firefox or Microsoft Edge to view the page correctly
Loading...

{{viewport.spaceProperty.prod}}

CALL statement

Function

The CALL statement passes control to a called program. Optionally, operands may be specified to enable the called program to access data of the calling program. The CALL statement (format 4) can also be used to execute BS2000 system commands from a COBOL program.

Format 1


CALL {identifier-1 | literal-1} [USING {[BY REFERENCE] {identifier-2|file-name-1}... 
                                       | BY VALUE {identifier-5}...
                                       | BY CONTENT {identifier-2|literal-2}...
                                       }...]
  [RETURNING identifier-3]
  [ON OVERFLOW imperative-statement-1]
  [END-CALL]


Format 2


CALL {identifier-1 | literal-1} [USING {[BY REFERENCE] {identifier-2|file-name-1}... 
                                       | BY VALUE {identifier-5}...
                                       | BY CONTENT {identifier-2|literal-2}...
                                       }... ]
  [RETURNING identifier-3] 
  [ON EXCEPTION imperative-statement-1] 
  [NOT ON EXCEPTION imperative-statement-2]

  [END-CALL]


Syntax rules for formats 1 and 2

  1. literal-1 must be a alphanumeric literal. However, it may not be a figurative constant.

    If literal-1 is the program-name of an individual program or of the outermost containing program of a nested program, it must begin with an alphabetic character and may contain only uppercase letters and digits. The length of the name is dependent on the module format (see the "COBOL2000 User Guide" [1]).
    If literal-1 is the program-name of a contained program of a nested program, it must begin with an alphabetic character, may contain uppercase letters, lowercase letters and digits, and must not be longer than 30 characters.

  2. identifier-1 must be defined as a program pointer or an alphanumeric data item. The contents of the alphanumeric data item must be a valid program name, as described under point 1. The contents of the program pointer are interpreted as the address of the entry point.

  3. The USING phrase in a CALL statement may be supplied only if a USING phrase has been written either after the associated Procedure Division header or in the ENTRY statement of the called program. Each USING phrase must have the same number of operands, otherwise the result will be unpredictable.

  4. Every identifier-1 specified in the USING phrase must have been defined in the FILE SECTION, WORKING-STORAGE SECTION, LOCAL-STORAGE SECTION, LINKAGE SECTION or SUB-SCHEMA SECTION. It may have level number 01 or level number 77. However, the compiler allows every level number except 88. In order to align elementary items with USAGE INDEX, BINARY, COMPUTATIONAL, COMPUTATIONAL-5, COMPUTATIONAL-1, COMPUTATIONAL-2 in the LINKAGE SECTION, all 01-level items included are aligned on doubleword boundaries. Consequently, the user must ensure that these operands are aligned accordingly in the USING phrase.

  5. file-name-1 is appropriate only if the called program is written in a language other than COBOL.

  6. identifier-2 must not be a function-identifier.

  7. identifier-3 must not be defined in the REPORT SECTION.

  8. identifier-3 is a receiving item.

  9. Object references, pointer and strongly typed data items may also be used as parameters. They may only be passed BY CONTENT as USING parameters.

  10. identifier-5 must have been defined as a 2- or 4-byte data item with USAGE COMP-5 or as a 1-byte data item. If this is not the case, the result of the parameter transfer is undefined. This type of parameter transfer is not a good idea unless the called program was written in a language other than COBOL (see CALL statement).

  11. literal-2 must be an alphanumeric or national literal or one of the figurative constants SPACE, LOW-VALUE or HIGH-VALUE.

  12. identifier-2, identifier-3 and identifier-5 must not be defined with the ANY LENGTH clause.

General rules for formats 1 and 2

  1. literal-1 or identifier-1 contains the name of the called program. The program which contains a CALL statement is the calling program. If the called program is a COBOL program, literal-1 or identifier-1 must contain the program-name specified in the PROGRAM-ID paragraph or in the ENTRY statement. If identifier-1 is defined as a program pointer, it contains the address of an entry point into a program.

  2. When the CALL statement is executed, control is passed to the called program. When control is returned to the calling program, imperative-statement-2 (if specified) is executed and the program then branches to the end of the CALL statement. If NOT ON EXCEPTION is omitted, the program branches immediately to the end of the CALL statement.

  3. If the called program is not available or already active during execution of the CALL statement, one of the following actions is executed:

    • If ON OVERFLOW or ON EXCEPTION is specified, control is passed to imperativestatement-1. After completion of imperative-statement-1, control is passed to the end of the CALL statement.

    • If ON OVERFLOW or ON EXCEPTION is not specified, an error message is issued and program execution is aborted.

  4. If two programs in a run unit have the same name, then at least one of them must be a contained program within a nested program. A program having a multiply used program name can only be successfully called under the following conditions:

    • The called program is directly contained in the calling program.

    • The called program has the COMMON attribute and is called by the directly superordinate program or by one of the latter’s sibling programs or their descendants.

    • The calling program is a contained program within a nested program and calls a separately compiled program of a run unit.

  5. The data to be passed as parameters from the calling program to the called program are specified in the USING phrase of the CALL statement with identifier-2... .
    The number and sequence of the parameters must match the specifications in the USING phrase of the Procedure Division header or the ENTRY statement. Excepted here are the indices assigned to tables (INDEXED BY phrase): The indices in a calling program and a called program always point to separate indices.

  6. If file-name-1 is specified in the list of the USING phrase, the starting address of the system file control block of that file is supplied to the called program.

  7. BY CONTENT and BY REFERENCE may be used together. The phrase BY CONTENT or BY REFERENCE applies to all subsequent parameters until another BY CONTENT or BY REFERENCE phrase is encountered. If neither BY CONTENT nor BY REFERENCE is specified, the default is BY REFERENCE.

  8. If a parameter is passed BY REFERENCE, it occupies the same memory location in the calling program and the called program. The description of the item in the called program must specify the same number of characters as the description of the corresponding item in the calling program.

  9. If a parameter is passed BY CONTENT, the calling program makes a copy of the parameter and passes this copy BY REFERENCE.
    The data description of the corresponding parameter in the called program must be chosen as follows:

    • if identifier-4 is specified: the same as that of identifier-4

    • if figurative constants are specified: PIC X

    • if an alphanumeric literal is specified: PIC X(n). Repetition factor n may not exceed the length of the literal. In contrast with the behavior for other transfers, the literal at the end may not be filled with blanks to the length of the corresponding parameter from the subprogram.

    • if an national literal is specified: PIC N(n). Repetition factor n may not exceed the length of the literal. In contrast with the behavior for other transfers, the literal at the end may not be filled with blanks to the length of the corresponding parameter from the subprogram.

  10. Specifying BY VALUE enables the direct, C-compliant transfer of values to C programs. If the parameter value “by value” is specified, this means that only the value of the parameter is passed to the called C program. The called program can access this value; it can also modify it, in which case the value remains unchanged in the COBOL program.

  11. A called program may contain CALL statements, but must not execute any CALL statement that directly or indirectly calls the calling program via the standard entry point or an entry point generated by means of the ENTRY statement.

  12. If the RETURNING phrase is defined, the result of the current program is placed in identifier-5.

Format 3


CALL { identifier-1 | literal-1 } ASNESTED | program-prototype-name-1 }
       [USING { [BY REFERENCE] { identifier-2 | OMITTED } 
              | [BY  CONTENT] { identifier-4 | arithmetic-expression-1 | literal-2 }
              | [BY  VALUE] { identifier-4 | arithmetic-expression-1 | literal-2 }
              }...]
[RETURNING identifier-3] 
[ON EXCEPTION imperative-statement-1] 
[NOT ON EXCEPTION imperative-statement-2]
[END-CALL]


Syntax rules

  1. literal-1 must not be an alphanumeric literal. However, it may not be a figurative constant.

    If literal-1 is the program name of an individual program or the outermost program of a nested program, it must begin with an alphabetic character and can only contain uppercase letters and digits. The length of the name depends on the module format (see the "COBOL2000 User Guide" [1]).

    If literal-1 is the program name of a program inside a nested program, it must begin with an alphabetic character, can contain uppercase and lowercase letters and digits and can have a length of up to 30 characters.

  2. identifier-1 must be defined as a program pointer or an alphanumeric data item. As an alphanumeric data item, its value must be a valid program name, as described in 1. The content of the program pointer is interpreted as the address of the entry point.

  3. The NESTED phrase may only be specified in a program definition.

  4. The NESTED phrase may only be specified together with literal-1.
    literal-1 must be the same as the program-name specified in a PROGRAM-ID paragraph of a nested program.

  5. If program-prototype-name-1 is specified, there must be an entry for this name in the REPOSITORY paragraph.

  6. identifier-4 and any identifier specified in arithmetic-expression-1 is a sending operand.

  7. If BY CONTENT or BY REFERENCE is specified for an argument, the BY REFERENCE phrase must be specified for the corresponding formal parameter in the PROCEDURE DIVISION header.

  8. BY CONTENT must not be omitted when identifier-4 is an identifier that is permitted as a receiving operand.

  9. If BY VALUE is specified for an argument, the BY VALUE phrase must be specified for the corresponding formal parameter in the PROCEDURE DIVISION header.

  10. If identifier-4 or its corresponding formal parameter is specified with a BY VALUE phrase in the Procedure Division header, identifier-4 must be of class “numeric”, “object” or ”pointer”.

  11. If OMITTED is specified or an argument is omitted, the OPTIONAL phrase must be specified for the corresponding formal parameter in the PROCEDURE DIVISION header.

  12. identifier-2 and identifier-3 must not be defined using the ANY LENGTH clause.

  13. If identifier-2 or the corresponding formal parameter is specified with a BY VALUE phrase then it may only be of the class “numeric”, “object” or “pointer”.

  14. identifier-2 must reference an address identifier or elementary item defined in the File Section, Working-Storage Section, Local-Storage Section or Linkage Section.

  15. If the BY REFERENCE phrase is specified or implied for identifier-2, which is not an address identifier, then identifier-2 represents both the sending and the receiving item.
    Otherwise identifier-2 is a sending item.

    Note:
    BY REFERENCE ADDRESS OF data-name is processed in the same way as BY CONTENT ADDRESS OF data-name.

  16. identifier-3 must not be defined in the REPORT SECTION.

  17. identifier-3 is a receiving item.

  18. Conformity of parameters and return elements (see "Conformance for parameters and returning items") must be ensured.

General rules

In general, the rules for format 1 and 2 apply. The following rules apply in addition:

  1. The BY REFERENCE, BY CONTENT and BY VALUE phrases refer only to the argument that follows the phrase immediately.

  2. If an argument is specified without any of the keywords BY REFERENCE, BY CONTENT, or BY VALUE, that argument is handled as follows:

    1. BY REFERENCE is assumed if the BY REFERENCE phrase is specified or implied for the corresponding formal parameter in the PROCEDURE DIVISION header and if the argument is an identifier that is permitted as the receiving item.

    2. BY CONTENT is assumed if the BY REFERENCE phrase is specified or implied for the corresponding formal parameter and if the argument is a literal, an arithmetic expression or any other identifier that is not permitted as the receiving item.

    3. BY VALUE is assumed if the BY VALUE phrase is specified or implied for the corresponding formal parameter in the Procedure Division header.

  3. An argument at the end of the USING list may also be omitted totally (i.e. the OMITTED phrase need not be specified for it) if all the following arguments are omitted as well (Note syntax rule 11).

  4. If an OMITTED phrase is specified or a trailing argument is omitted, the omitted-argument condition for that argument must be true in the called program.

  5. If an argument for which the omitted-argument condition is true is referenced in a called program (except in the omitted-argument condition), the behavior is undefined.

  6. When the CALL statement is executed, control is passed to the called program. After control is returned by the called program, imperative-statement-2 is executed, if present, and a branch is made to the end of the CALL statement. If NOT ON EXCEPTION is missing, a branch is made to the end of the CALL statement.

  7. If the called program is not available during execution of the CALL statement, or if it is already active without being recursive, one of the following actions is executed:

    1. If ON EXCEPTION is specified, controlo is passed to imperative-statement-1. After termination of imperative-statement-1, control passes to the end of the CALL statement.

    2. If ON EXCEPTION is not specified, program execution is aborted after an error message is output.

Format 4


CALL UPON SYSTEM USING { identifier-1 | literal-1 } [identifier-2]

   [STATUS identifier-3]

   [ON EXCEPTION imperative-statement-1]
   [NOT ON EXCEPTION imperative-statement-2]

       [END-CALL]


Syntax rules

  1. identifier-1 and identifier-2 must be alphanumeric data items.

  2. literal-1 must be an alphanumeric literal.

  3. identifier-3 must be a numeric data item described with PIC S9(8) SYNC and USAGE COMP, USAGE COMP-5 or USAGE BINARY.

  4. identifier-2 may not be a function identifier.

General rules

  1. literal-1 or identifier-1 contains the BS2000 command to be executed.
    A slash (/) can be specified in front of the command. Lower-case letters are not converted into upper-case.

  2. identifier-2 specifies an area for recording system output.
    This response area should be large enough to record the complete output of the specified BS2000 command.
    If identifier-2 is variable in length and contains the DEPENDING ON item, the maximum length of identifier-2 is used.

  3. If identifier-2 is not specified or its current length is 0, the output is written to SYSOUT.

  4. If an error occurs during execution of the command, the response area contains the system’s error message text, provided it is large enough.

  5. identifier-3 can be used to specify a status item in which specific values show the result of the execution of the command. The following values can occur.

    00Command executed successfully
    04The command was executed, but one or more records could not be entered because the response area is too small.
    30Error during command execution; no more information available
    34This command may not be specified in a program .
    40The current length of identifier-1 is invalid (<= 0 or > 32767 bytes).
    41The current length of identifier-2 is invalid (< 0).
    90There is not enough main memory available to execute the command; workaround: specify smaller areas (identifier-1 or identifier-2)
  6. If an error occurs while the CALL statement is being executed, one of the following actions is performed:

    1. If ON EXCEPTION is specified, imperative-statement-1 is executed. When imperative-statement-1 has been completed, the program continues at the end of the CALL statement.

    2. If ON EXCEPTION is not executed, the program sequence is resumed without an error message.

  7. If the CALL statement is executed successfully, one of the following actions is performed:

    1. If NOT ON EXCEPTION is specified, imperative-statement-2 is executed.

    2. If NOT ON EXCEPTION is not specified, a branch is made to the end of the CALL statement.

The system output consists of variable records with length items and special characters for feed control, etc.; a record is usually represented by several lines on the screen. Only complete records are entered in the response area; the rest of the response area which is not used is deleted. For information on the structures and further processing of the response area, see User Guide "Executive Macros - CMD macro" [12].

Example 8-24

of the use of the CALL statement in the format CALL identifier-1

Main program:

IDENTIFICATION DIVISION.
PROGRAM-ID. MAIN.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SPECIAL-NAMES.
    TERMINAL IS T.
DATA DIVISION.
WORKING-STORAGE SECTION.
01   CALL-OPERAND PIC X(8) VALUE SPACE.
01   TABLE-FUNCTION.
     02  FUNCTION-1 PIC X(8) VALUE "ADDREC".
     02  FILLER     PIC X(72) VALUE SPACE.
     02  FUNCTION-2 PIC X(8) VALUE "DELREC".
     02  FILLER     PIC X(72) VALUE SPACE.
     02  FUNCTION-3 PIC X(8) VALUE "CHGREC".
     02  FILLER     PIC X(72) VALUE SPACE.
01   RECORD-NUMBER PIC 9(8).
PROCEDURE DIVISION.
P1 SECTION.
PMAIN.
    PERFORM UNTIL CALL-OPERAND = FUNCTION-1 OR FUNCTION-2
                                            OR FUNCTION-3
       DISPLAY "Please enter desired function"
              UPON T
       DISPLAY TABLE-FUNCTION UPON T
       ACCEPT CALL-OPERAND FROM T
    END-PERFORM
    PERFORM UNTIL RECORD-NUMBER NUMERIC
       DISPLAY "Please enter record number"
               "(numeric, 8 digits)" UPON T
       ACCEPT RECORD-NUMBER FROM T
    END-PERFORM
    CALL CALL-OPERAND USING RECORD-NUMBER
    END-CALL
    STOP RUN.


Subprogram "ADDREC":

IDENTIFICATION DIVISION.
PROGRAM-ID. ADDREC.
ENVIRONMENT DIVISION.
DATA DIVISION.
...
LINKAGE SECTION.
01 RECORD-NUMBER PIC 9(8).
PROCEDURE DIVISION USING RECORD-NUMBER.
    ...
    EXIT PROGRAM.

Subprogram "DELREC":

IDENTIFICATION DIVISION.
PROGRAM-ID. DELREC.
ENVIRONMENT DIVISION.
DATA DIVISION.
...
LINKAGE SECTION.
01  RECORD-NUMBER PIC 9(8).
PROCEDURE DIVISION USING RECORD-NUMBER.
    ...
    EXIT PROGRAM.

Subprogram "CHGREC":

IDENTIFICATION DIVISION.
PROGRAM-ID. CHGREC.
ENVIRONMENT DIVISION.
DATA DIVISION.
...
LINKAGE SECTION.
01  RECORD-NUMBER PIC 9(8).
PROCEDURE DIVISION USING RECORD-NUMBER.
    ...
    EXIT PROGRAM.

Example 8-25

for the use of CALL ... USING BY VALUE

Main program:

IDENTIFICATION DIVISION.
PROGRAM-ID. MAIN.
ENVIRONMENT DIVISION.
    CONFIGURATION SECTION.
    SPECIAL-NAMES.
        TERMINAL IS T.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  C  PIC  9(4) USAGE COMP-5 VALUE 1.
01  D  PIC  9(9) USAGE COMP-5 VALUE 1.
01  E  PIC  S9(4) USAGE COMP-5 VALUE -1.
01  F  PIC  S9(9) USAGE COMP-5 VALUE -1.
01  RTC  PIC S9(10) SIGN IS LEADING SEPARATE.
PROCEDURE DIVISION.
1ST SECTION.
1.
CALL "C1" USING BY VALUE C, D.
    MOVE RETURN-CODE TO RTC.
    DISPLAY "RETURN-CODE = " RTC UPON T.
    CALL "D1" USING BY VALUE E, F.
    MOVE RETURN-CODE TO RTC.
    DISPLAY "RETURN-CODE = " RTC UPON T.
    MOVE 0 TO RETURN-CODE.
    STOP RUN.

Subprogram C1:

Subprogram D1:

long C1(unsigned short c, unsigned long d)
{
long ret_val;
if (c && d)
   ret_val = 1;
else
   ret_val = -1;
return ret_val;
}
long D1(signed short c, signed long d)
{
long ret_val;
if (c && d)
   ret_val = 1;
else
   ret_val = -1;
return ret_val;
}

Example 8-26

File name assignment with the SET-FILE-LINK command in dialogs and status queries:

IDENTIFICATION DIVISION.
PROGRAM-ID.  CMD.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SPECIAL-NAMES.
    TERMINAL IS T.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  LINKFILE.                                                       (1) 
  02  FILLER   PIC X(30) VALUE "ADD-FILE-LINK LINK=XXX,F-NAME=".
  02  FILNAM   PIC X(54).  
01  RTC        PIC S9(8) SYNC BINARY.                                (2) 
01  RTC-ED     PIC Z(6)99.
01  TFT-CMD    PIC X(40) VALUE "SHOW-FILE-LINK".
01  RESP       PIC X(2000) VALUE ALL SPACE.                          (3) 
PROCEDURE DIVISION.
MAIN SECTION.
PARA.
    DISPLAY "PLEASE ENTER FILE NAME X(54)" UPON T.
    ACCEPT FILNAM FROM T.
    CALL UPON SYSTEM USING LINKFILE
                           STATUS RTC
      ON EXCEPTION 
         MOVE RTC TO RTC-ED
         DISPLAY "ERROR DURING COMMAND CAL, STATUS= "
                    RTC-ED UPON T
    END-CALL
    CALL UPON SYSTEM USING TFT-CMD
                           RESP
    END-CALL.
    DISPLAY "RESPONSE AREA RESP" RESP UPON T.
FIN.
    STOP RUN.

(1)

Description of identifier-1 with substructures for BS2000 system command and file name.

(2)

Description of identifier-3 (status item RTC)

(3)

Description of identifier-2 (response area RESP)