Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

Using data pointers

Pointers can be used as follows:

  1. as formal parameters in the PROCEDURE DIVISION USING phrase

  2. as current parameters in the CALL or INVOKE statement

  3. in the SET statement: assignment and updating of addresses (UP/DOWN)

  4. in relational conditions: comparisons of equality or inequality with the predefined NULL address, with a data address identifier and other pointers

  5. in the LENGTH function: this function returns the value 4 for FUNCTION LENGTH (LENGTH OF ...) and FUNCTION LENGTH (pointer).
    FUNCTION LENGTH (ADDRESS OF ...) is not currently supported.

Example 12-28

Let us assume that the subprogram GNR returns a pointer to a record in accordance with the following program prototype:

Program-id. Get-Next-Record is prototype. *> returns the address of a
                                             record
Data Division.
Linkage Section.
01 ptrl usage pointer.
Procedure Division returning ptrl.
End-program Get-Next-Record.

and that a user program contains the following declarations

program get-next-record  *> in the Repository Paragraph

01 p usage pointer.  *> in the Working-Storage Section

01 my-wreck based.   *> in the Linkage Section
   02 name pic x(30).
   02 addr pic x(30).

The following statement in the Procedure Division calls the program described by the prototype:

Call "GNR" as Get-Next-Record returning p

The data can be accessed with my-wreck since the pointer p contains the address of a record:

Set address of my-wreck to p
Move "SAM JONES" to name in my-wreck

Example 12-29

01 p2 usage pointer.
01 data-record.     *> the full record layout is described
   02 ...

If the Program Process Record “PR” is to be passed to a pointer then coding can be as follows:

Set p2 to address of data-record.
Call "PR" using p2.

Alternatively, the address of data-record could be passed as follows *:

Call "PR" using address of data-record

* in this case, however, any change to the passed pointer by the called program remains ineffective for the calling program.