Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

ANY LENGTH clause

Function

The ANY LENGTH clause ensures that the length of a method’s formal parameter is determined by the length of the argument.

Format


ANY LENGTH


Syntax rules

  1. In data entries, the ANY LENGTH clause can only be specified with level number 01 or 77 in a method’s LINKAGE SECTION.

  2. The data entry must contain a PICTURE clause with a picture string consisting of a single “X” oder "N".

General rules

  1. The ANY LENGTH clause defines the elementary item as being of variable length. The current length of the item corresponds to the length of the call argument or of the return value.

  2. If the call argument or return value corresponding to the elementary item is a zero length item, the elementary item is also a zero-length item.

Example 7-3

METHOD-ID. SEARCH-CHAR.
DATA DIVISION.
LINKAGE SECTION.
01    PAR1    PIC X ANY LENGTH.
01    PAR2    PIC X.
01    IDX     PIC 9(9) USAGE COMP-5.
PROCEDURE DIVISION USING PAR1 PAR2 RETURNING IDX.
  PERFORM VARYING IDX FROM 1 BY 1 UNTIL IDX > FUNCTION LENGTH(PAR1)
    IF PAR1(IDX:1) = PAR2
        EXIT METHOD           *> character found ---->>>>
     END-IF
  END-PERFORM
  MOVE 0 TO IDX.            *> character not found
  EXIT METHOD.
END METHOD SEARCH-CHAR.

Extract from a program in which the SEARCH-CHAR method is called:

...
01 OBJ      USAGE IS OBJECT REFERENCE.
01 I        PIC 9(9) USAGE IS COMP-5.
01 F1       PIC x(50).
01 F2
   02 ELEM  OCCURS 100 DEPENDING ON I.
...
INVOKE OBJ "SEARCH-CHAR" USING F1,"X" RETURNING I. ———————————— (1)
INVOKE OBJ "SEARCH-CHAR" USING F2,"Y" RETURNING I. ———————————— (2)
...

(1)

The current length of parameter PAR1 is 50. The length does not have to be passed by the user

(2)

The current length of parameter PAR1 is dynamic and known only at runtime.


Changes to the RETURNING parameter IDX in the SEARCH-VAR method do not affect the length of the current F2 parameter until after a return from the SEARCH-CHAR method.

The different lengths of the current F1 and F2 parameters do not violate the conformance rules because of the presence of the ANY LENGTH clause.