HP 3000 Manuals

LENGTH Function [ HP COBOL II/XL Reference Manual ] MPE/iX 5.0 Documentation


HP COBOL II/XL Reference Manual

LENGTH Function 

The LENGTH function returns an integer equal to the length of the
argument in character positions (bytes).  To conform to ANSI
standard COBOL, you can use the LENGTH function instead of the .LEN.
pseudo-intrinsic (see Chapter 11 , "Interprogram Communication," for
details on .LEN.).  The function type is integer.

Syntax 

     FUNCTION LENGTH (parameter-1)

Parameters 

parameter-1           A nonnumeric literal or a data item of any class or
                      category.

                      If parameter-1 or any data item subordinate to
                      parameter-1 is described with the DEPENDING phrase
                      of the OCCURS clause, the contents of the data item
                      referenced by the data-name specified in the
                      DEPENDING phrase are used at the time the LENGTH
                      function is evaluated.

Return Values 

If parameter-1 is a nonnumeric literal or an elementary data item or
parameter-1 is a group data item that does not contain a variable
occurrence data item, the value returned is an integer equal to the
length of parameter-1 in character positions.

If parameter-1 is a group data item containing a variable occurrence data
item, the returned value is an integer determined by evaluation of the
data item specified in the DEPENDING phrase of the OCCURS clause for that
variable occurrence data item.  This evaluation is accomplished according
to the rules in the OCCURS clause dealing with the data item as a sending
data item.  See the OCCURS clause for additional information.

The returned value includes implicit filler items, if any.

Example 1 

     77  CITY        PIC X(9) VALUE "CHICAGO".
     77  ID-LENGTH   PIC 99 VALUE ZERO.
          :
     COMPUTE ID-LENGTH = FUNCTION LENGTH (CITY).
     DISPLAY CITY.
     DISPLAY ID-LENGTH.

The above example displays the following:

     CHICAGO__
     09

Example 2 

     77  SIZER     PIC 99.
     77  NUM       PIC 999.
     01  TAB-REC.
         05  TAB-ELEMENT OCCURS 1 TO 10 TIMES
                         DEPENDING ON SIZER.
             10  TAB-ITEM-1  PIC X(3).
             10  TAB-ITEM-2  PIC S9(9) COMP SYNC.
     PROCEDURE DIVISION.
     010-PARA.
        MOVE 5 TO SIZER.
        COMPUTE NUM = FUNCTION LENGTH (TAB-ELEMENT (1)).
        DISPLAY "TAB-ELEMENT LENGTH = " NUM.
        COMPUTE NUM = FUNCTION LENGTH (TAB-REC).
        DISPLAY "TAB-REC LENGTH = " NUM.
        STOP RUN.

The above example displays the following:

     TAB-ELEMENT LENGTH = 008
     TAB-REC LENGTH = 040

The length of TAB-ELEMENT is 8 because of the implicit 1-byte filler
between TAB-ITEM-1 and TAB-ITEM-2.  If SYNC is removed from TAB-ITEM-2,
the length of TAB-ELEMENT is 7.



MPE/iX 5.0 Documentation