Top
NetCOBOL V11.0 Syntax Samples
FUJITSU Software

1.43 ADDR and LENG Functions

The ADDR function is used to obtain memory addresses of data items.

The obtained address can be used for pointer qualification, non-COBOL linkage of an address interface, and so on.

The LENG function is used to obtain the actual length of data items in bytes.

The LENGTH function is similar to the LENG function. The LENGTH function, however, returns the number of character positions. That is, the LENGTH function returns the number of characters. For example, using a DBCS (Double Byte Character Set) the LENGTH function might return 2, where the LENG function will return 4 - the actual number of bytes.

000010 @OPTIONS MAIN
000020*----------------------------------------------------------------------
000030* The pointer obtained using the ADDR function and the two forms 
000040* defined in the based-storage section are used to store data in the 
000050* work area. In addition, the LENG function is used to obtain the data 
000055* item length.
000060*----------------------------------------------------------------------
000070 IDENTIFICATION   DIVISION.
000080 PROGRAM-ID.      SAMPLE.
000090 DATA             DIVISION.
000100 BASED-STORAGE    SECTION.
000110 01 LONG-FORM.
000120    02 FIRST-NAME-L   PIC X(8).
000130    02 LAST-NAME-L    PIC X(8).
000140    02 AGE-L          PIC 9(2).
000150    02 SEPARATER-L    PIC X(1).
000160    02 NEXT-TOP-L     PIC X(1).
000170 01 SHORT-FORM.
000180    02 FIRST-NAME-S   PIC X(8).
000190    02 AGE-S          PIC 9(2).
000200    02 SEPARATER-S    PIC X(1).
000210    02 NEXT-TOP-S     PIC X(1).
000220 WORKING-STORAGE  SECTION.
000230 01 PTR           USAGE POINTER.
000240 01 WORK          PIC X(255).
000250 01 FORMS         PIC 9(1).
000260 01 COUNT-L       PIC 9(2) VALUE 0.
000270 01 COUNT-S       PIC 9(2) VALUE 0.
000280 01 TOTAL-SIZE    PIC 9(3).
000290 PROCEDURE        DIVISION.
000300*----------------------------------------------------------------------
000310* The ADDR function obtains the starting address of the work area 
000315* (data storage area).
000320*----------------------------------------------------------------------
000330     MOVE FUNCTION ADDR (WORK) TO PTR.
000340*----------------------------------------------------------------------
000350     PERFORM TEST AFTER
000360             UNTIL FORMS = 0
000370       DISPLAY " "
000380       DISPLAY "Which forms do you want to select?"
000390       DISPLAY "1:  Long forms (First-name  Last-name  Age)"
000400       DISPLAY "2:  Short forms (First-Name  Age)"
000410       DISPLAY "0:  End processing                  >>" WITH NO 
000415               ADVANCING
000420       ACCEPT FORMS
000430       EVALUATE FORMS
000440       WHEN "1"
000450         DISPLAY "First-name >> " WITH NO ADVANCING
000460         ACCEPT PTR->FIRST-NAME-L FROM CONSOLE
000470         DISPLAY "Last-name  >> " WITH NO ADVANCING
000480         ACCEPT PTR->LAST-NAME-L FROM CONSOLE
000490         DISPLAY "Age        >> " WITH NO ADVANCING
000500         ACCEPT PTR->AGE-L FROM CONSOLE
000510         MOVE   "/" TO PTR->SEPARATER-L
000520         COMPUTE COUNT-L = COUNT-L + 1
000530         MOVE FUNCTION ADDR (PTR->NEXT-TOP-L) TO PTR
000540       WHEN "2"
000550         DISPLAY "First-Name >> " WITH NO ADVANCING
000560         ACCEPT PTR->FIRST-NAME-S FROM CONSOLE
000570         DISPLAY "Age        >> " WITH NO ADVANCING
000580         ACCEPT PTR->AGE-S FROM CONSOLE
000590         MOVE   "/" TO PTR->SEPARATER-S
000600         COMPUTE COUNT-S = COUNT-S + 1
000610         MOVE FUNCTION ADDR (PTR->NEXT-TOP-S) TO PTR
000620       END-EVALUATE
000630     END-PERFORM.
000640*----------------------------------------------------------------------
000650* The LENG function is used to obtain the data item length.
000660* Using the LENG function enables coding that will not be affected when 
000670* items are added (the group item length is changed).
000680*----------------------------------------------------------------------
000690     COMPUTE TOTAL-SIZE = 
000695         (FUNCTION LENG (PTR->LONG-FORM) - 1 ) * COUNT-L
000700         + ( FUNCTION LENG (PTR->SHORT-FORM) - 1 ) * COUNT-S.
000710*----------------------------------------------------------------------
000720     DISPLAY "DATA           :" WORK.
000730     DISPLAY "TOTAL DATA SIZE:" TOTAL-SIZE.
000740 END PROGRAM SAMPLE.