 
 
 
 
 
 
 


 
 
 
 
 
 


 
X 6.2.4.5   RETURNING Phrase
- 
 X identifier-5
-  
 X     The RETURNING data item, which must be defined in the DATA DIVISION.
 X     The return value of the CALLed program is implicitly stored into
 X     identifier-5.
 
 
 X You can specify the RETURNING phrase for calls to functions written in
 X COBOL, C, or in other programming languages that use C linkage
 X conventions.  If you specify the RETURNING phrase on a CALL to a COBOL
 X subprogram:
-   X     The CALLed subprogram must specify the RETURNING phrase on its
 X     Procedure Division header.
 
-   X     Identifier-5 and the corresponding Procedure Division RETURNING
 X     identifier in the target program must have the same PICTURE, USAGE,
 X     SIGN, SYNCHRONIZE, JUSTIFIED, and BLANK WHEN ZERO clauses (except that
 X     PICTURE clause currency symbols can differ, and periods and commas can
 X     be interchanged due to the DECIMAL POINT IS COMMA clause).
 
 X     When the target returns, its return value is assigned to identifier-5,
 X     using either the rules for SET statement, if identifier-6 is USAGE IS
 X     INDEX, USAGE IS POINTER, USAGE IS PROCEDURE-POINTER, or USAGE IS
 X     OBJECT REFERENCE; otherwise, the rules for the MOVE statement are
 X     used.
 
 
 X Note:  The CALL... RETURNING data item is an output-only parameter.  On
 X entry to the called program, the initial state of the PROCEDURE DIVISION
 X RETURNING data item has an undefined and unpredictable value.  You must
 X initialize the PROCEDURE DIVISION RETURNING data item in the called
 X program before you reference its value.  The value that is passed back to
 X the calling program is the final value of the PROCEDURE DIVISION RETURNING
 X data item when the called program returns.
 X If an EXCEPTION or OVERFLOW occurs, identifier-5 is not changed.
 X Identifier-5 must not be reference-modified.
 X The RETURN-CODE special register is not set by execution of CALL
 X statements that include the RETURNING phrase.
 
 © Copyright IBM Corp. 1991, 1998
  © 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.