Library View Topics Framed Contents Revised Topics Previous Topic Next Topic Search Search ResultsPrevious Topic MatchNext Topic Match Notes List Notes Print Download No PDF Handheld DisconnectedHandheld ConnectedHelp

6.1.2 The Procedure Division Header



The Procedure Division, if specified, is identified by one of the following headers, depending on whether you are defining a program, method, or class.


    ___ Format--Procedure Division Header for Programs and  Methods  _______ 
   |                                                                        |
   | >>__PROCEDURE DIVISION_______________________________________________> |
   |                                                                        |
   | >__ _______________________________________________________ _________> |
   |    |        <____________________________________________  |           |
   |    |                                      <___________   | |           |
   |    |_USING_____ _______________________ ___data-name-1|__|_|           |
   |                |_ ______ __ REFERENCE _|                               |
   |                | |_ BY _|              |                               |
   |                |_ ______ __ VALUE _____|                               |
   |                  |_ BY _|                                              |
   |                                                                        |
   | >__ ______________________________ __.______________________________>< |
   |    |__ RETURNING __ data-name-2 __|                                    |
   |                                                                        |
   |________________________________________________________________________|

 X  ___ Format--Procedure Division Header for Classes ______________________ 
 X |                                                                        |
 X | >>__PROCEDURE DIVISION__.___________________________________________>< |
   |                                                                        |
   |________________________________________________________________________|
USING
The USING phrase makes data items defined in a calling program
X available to a called subprogram or an invoked method.

Only specify the USING phrase if the program is invoked by a CALL
X statement or a method is invoked by the INVOKE statement and the CALL
X or INVOKE statement includes a USING phrase.

The USING phrase is valid in the Procedure Division header of a called subprogram entered at the beginning of the nondeclaratives portion; each USING identifier must be defined as a level-01 or level-77 item
X in the Linkage Section of the called subprogram or invoked method; it must not contain a REDEFINES clause.


X A data item in the USING phrase of the Procedure Division header can
X have a REDEFINES clause in its data description entry.


X In a called subprogram entered at the first executable statement
X following an ENTRY statement, the USING option is valid in the ENTRY
X statement; each USING identifier must be defined as a level-01 or
X level-77 item in the Linkage Section of the called subprogram or
X invoked method. In a calling program, the USING phrase is valid for
X the CALL or INVOKE statement; each USING identifier must be defined as a level-01, level-77, or an elementary item in the Data Division.


X Each USING identifier in a calling program can be a data item of any
X level in the Data Division.

It is possible to call from non-COBOL programs or pass user parameters from a system command to a COBOL main program.

>_Workstation_> For AIX, OS/2, and Windows, command-line arguments are
X always passed in as native data types. If you specify the host data
X type compiler options (CHAR(EBCDIC), FLOAT(HEX), or BINARY(S390)), you
X must specify the NATIVE phrase on any arguments with data types
X affected by these compiler options. (Note, the BINARY compiler option
X is only applicable to OS/2 and Windows programs.) <_Workstation_<

The order of appearance of USING identifiers in both calling and
X called subprograms or invoking and invoked methods, determines the correspondence of single sets of data available to both programs. The correspondence is positional and not by name. For calling and called subprograms, corresponding identifiers must contain the same number of characters, although their data descriptions need not be the same.
X For invoking and invoked methods, see "Conformance Requirements for
X USING Phrase" in topic 6.2.22.5.

For index-names, no correspondence is established; index-names in
X calling and called programs or invoking and invoked methods always refer to separate indexes.


X The identifiers specified in a CALL USING or INVOKE USING statement
X name data items available to the calling program or invoking method
X that can be referred to in the called program or invoked method; a given identifier can appear more than once. These items are defined in any Data Division section.


X As an IBM extension, an identifier can appear more than once in a
X Procedure Division USING phrase. The last value passed to it by a
X CALL USING or INVOKE USING statement is used. The BY REFERENCE or BY
X VALUE phrase applies to all parameters that follow until overridden by
X another BY REFERENCE or BY VALUE phrase.


X BY REFERENCE

X When a CALL or INVOKE argument is passed BY CONTENT or BY
X REFERENCE, BY REFERENCE must be specified or implied for the
X corresponding formal parameter on the PROCEDURE/ENTRY USING
X phrase.


X BY REFERENCE is the default if neither BY REFERENCE or BY VALUE is
X specified.


X If the reference to the corresponding data item in the CALL or
X INVOKE statement declares the parameter to be passed BY REFERENCE
X (explicit or implicit), the object program executes as if each
X reference to a USING identifier in the called subprogram or
X invoked method Procedure Division is replaced by a reference to
X the corresponding USING identifier in the calling program or
X invoked method.


X If the reference to the corresponding data item in the CALL or
X INVOKE statement declares the parameter to be passed BY CONTENT,
X the value of the item is moved when the CALL or INVOKE statement
X is executed and placed into a system-defined storage item
X possessing the attributes declared in the Linkage Section for
X data-name-1. The data description of each parameter in the BY
X CONTENT phrase of the CALL or INVOKE statement must be the same,
X meaning no conversion or extension or truncation, as the data
X description of the corresponding parameter in the USING phrase of
X the Procedure Division header.


X BY VALUE

X If the reference to the corresponding data item in the CALL or
X INVOKE statement declares the parameter to be passed BY VALUE,
X then the value of the argument is passed, not a reference to the
X sending data item. Since CALLed subprograms and INVOKEd methods
X have access only to a temporary copy of the sending data item, any
X modifications made to the formal parameters corresponding to the
X BY VALUE argument do not affect the argument.


X Examples illustrating these concepts can be found in IBM COBOL
X Programming Guide for your platform.


X RETURNING data-name-2

X Is the RETURNING phrase identifier. It specifies a data item to be
X returned as a program or method result. You must define data-name-2
X as either a level 01 or 77 entry in the Linkage Section.


X Data-name-2 is an output-only parameter. The initial state of
X data-name-2 has an undefined and unpredictable value when the program
X or method is entered. You must initialize data-name-2 in the program
X or method before you reference its value. When a program or method
X returns to its invoker, the final value in data-name-2 is implicitly
X stored into the identifier specified in the CALL RETURNING phrase or
X the INVOKE RETURNING phrase, as described in "CALL Statement" in
X topic 6.2.4 or "INVOKE Statement" in topic 6.2.22.


X When you specify Procedure Division RETURNING data-name-2, the
X RETURN-CODE special register can be used within the PROCEDURE DIVISION
X only as a means of accessing return codes from CALLed subprograms.
X The RETURN-CODE value is not returned to the caller of the current
X program (the value in data-name-2 is).


X When the RETURNING phrase is specified on the PROCEDURE DIVISION
X header of a program or method, the CALL or INVOKE statement used to
X pass control to the program or method must also specify a RETURNING
X phrase. The data-name-2 and the identifier specified on the CALL or
X INVOKE RETURNING must have the same PICTURE, USAGE, SIGN, SYNCHRONIZE,
X JUSTIFIED, and BLANK WHEN ZERO clauses (except that PICTURE clause
X currency symbols can differ, and periods and commas can be
X interchanged due to the DECIMAL POINT IS COMMA clause).


X Do not use the Procedure Division RETURNING phrase in:


X Data items defined in the Linkage Section of the called program or invoked
X method, can be referenced within the Procedure Division of that program if, and only if, they satisfy one of the following conditions:



Previous Topic Next Topic © Copyright IBM Corp. 1991, 1998

IBM Library Server Copyright 1989, 2005 IBM Corporation. All rights reserved.





Return to library:   z/OS | z/OS.e | TPF | z/VSE | z/VM | IBM Hardware | IBM System z Redbooks
Glossary:   IBM terminology
Publications:   How to order publications
Readers:   Download IBM Library Reader | Download IBM Softcopy Reader | Download Adobe® Acrobat® Reader®
Library management:   Download IBM Softcopy Librarian
Contacts:   Contact z/OS


Adobe, the Adobe logo, Acrobat, the Acrobat logo, and Acrobat Reader are registered trademarks of Adobe Systems incorporated.