Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

Procedure Division header

Function

In a called program (subroutine) or method, the Procedure Division header determines the standard entry point. Optionally, data-names may be specified if data is transferred from the calling program as a parameter.

Format 1


PROCEDURE DIVISION [USING-phrase] [RETURNING data-name-2].


where the USING phrase is defined as follows:


USING {[BY REFERENCE] {[OPTIONAL] data-name-1}... | BY VALUE {data-name-1}... }...


Format 2

For object, factory or interface definitions.


PROCEDURE DIVISION.


Syntax rules

  1. The USING phrase may be written only if the program is called by a CALL statement or a method by an INVOKE statement and the CALL /INVOKE statement in the calling source unit includes a USING phrase. For calls as subprograms from “programs written in other languages“, see the "CRTE" manual [2].

  2. The RETURNING phrase may only be written if the program is called by a CALL statement or a method by an INVOKE statement and the CALL /INVOKE statement in the calling source unit includes a RETURNING phrase.

  3. Each data-name supplied in the USING or RETURNING phrase of the Procedure Division header must be defined in the LINKAGE SECTION of the source unit containing this header and must have the level number 01 or 77.
    The data description of data-name-1 or data-name-2 must not contain a REDEFINES clause or BASED clause.

  4. Each data-name-1 defined in the BY VALUE phrase may identify only one data item of the class “numeric”, “alphanumeric” or “object”.

  5. The RETURNING phrase may be specified in a method, program or program prototype definition.

  6. data-name-2 must not be identical with data-name-1.

General rules

  1. The standard entry point within a called program or method is determined by the Procedure Division header. In order to transfer control from a calling source unit to that entry point, the calling source unit must contain a CALL or INVOKE statement. The name supplied in this CALL or INVOKE statement must be the same as the name specified in the PROGRAM-ID or METHOD-ID paragraph of the Identification Division of the called program or method.

  2. The USING phrase, when specified, has the effect that data-name-1 of the Procedure Division header in the called program/method and identifier-2 or identifier-5 in theUSING phrase of the CALL or INVOKE statement in the calling source unit refer to the same set of data, which is equally available both to the called and the calling source unit. It is not necessary for the names to be identical.

    A data-name may appear only once in the Procedure Division header of the called program or method, whereas the same identifier may occur several times in the USING phrase of the CALL or INVOKE statement.

  3. In the called program/method, the operands of the USING phrase are treated according to the data description supplied in the LINKAGE SECTION.

  4. A source unit may run both as a called source unit and as a calling source unit at execution time. An exception to this is the first source unit (called for execution by the system); it must not contain a USING phrase in the Procedure Division header.

Example 8-1

Calling program:

IDENTIFICATION DIVISION
PROGRAM-ID. A-PROG.
...
WORKING-STORAGE SECTION.
01  ALPHA ...
01  BETA ...
77  GAMMA ...
...
PROCEDURE DIVISION.
...
    CALL "B-PROG" USING ALPHA BETA GAMMA.        (1)
...

Called program:

IDENTIFICATION DIVISION.
PROGRAM-ID. B-PROG.
...
LINKAGE SECTION.
01  DELTA ...
01  EPSILON ...
77  THETA ...
...
PROCEDURE DIVISION USING DELTA EPSILON THETA.    (1)
...

(1)

The parameters of the USING phrases relate to one another in pairs, i.e. ALPHA and DELTA, BETA and EPSILON, GAMMA and THETA respectively each relate to the same data item.

For details on passing parameters between ICLS refer to the "CRTE" User Guide [2].