Top
NetCOBOL V11.0 Syntax Samples
FUJITSU Software

1.4 Reference Modification

Reference modification is used to refer to a portion of a character data item.

When using reference modification, be careful about setting and referencing outside the scope, or length of the data field being referenced. Reference modification that exceeds the actual area length can destroy data or cause execution to terminate abnormally by referencing an incorrect area of memory.

000010 @OPTIONS MAIN
000020*-------------------------------------------------------------------------
000030* Reference modification enables part of character string data to be 
000035* specified.
000040*-------------------------------------------------------------------------
000050 IDENTIFICATION  DIVISION.
000060 PROGRAM-ID.     SAMPLE.
000070 DATA            DIVISION.
000080 WORKING-STORAGE SECTION.
000090 01 ALP          PIC X(26) VALUE "ABCDEFGHIJKLMNOPQRSTUVWXYZ".
000100 01 IN-DATA      PIC X.
000110 01 COUNTER      PIC 9(2).
000120 PROCEDURE       DIVISION.
000130     DISPLAY "Please input one upper-case letter. >>" WITH NO ADVANCING.
000140     ACCEPT IN-DATA.
000150     PERFORM TEST BEFORE
000160             VARYING COUNTER FROM 1 BY 1 UNTIL COUNTER > 26
000170*-------------------------------------------------------------------------
000180* Reference modification can specify character data of 
000185* (starting location:  Length).
000190*-------------------------------------------------------------------------
000200       IF IN-DATA = ALP(COUNTER:1) THEN
000210*-------------------------------------------------------------------------
000220         EXIT PERFORM
000230       END-IF
000240     END-PERFORM.
000250     IF COUNTER <= 26 THEN
000260       DISPLAY IN-DATA " is character " COUNTER " in alphabetical order."
000270     ELSE
000280       DISPLAY "The input character is incorrect."
000290     END-IF.
000300 END PROGRAM SAMPLE.

Uniqueness of qualification and reference modification may also be combined.

000010 @OPTIONS MAIN
000020*-------------------------------------------------------------------------
000030* A data name that must be uniquely qualified can also be reference 
000035* modified.
000040*-------------------------------------------------------------------------
000050 IDENTIFICATION    DIVISION.
000060 PROGRAM-ID.       SAMPLE.
000070 DATA              DIVISION.
000080 WORKING-STORAGE   SECTION.
000090 01 UPPER-CASE.
000100    02 ALP         PIC X(26) VALUE "ABCDEFGHIJKLMNOPQRSTUVWXYZ".
000110 01 LOWER-CASE.
000120    02 ALP         PIC X(26) VALUE "abcdefghijklmnopqrstuvwxyz".
000130 01 IN-DATA        PIC X.
000140 01 COUNTER        PIC 9(2).
000150 PROCEDURE         DIVISION.
000160     DISPLAY "Please input one upper-case letter. >>" WITH NO ADVANCING.
000170     ACCEPT IN-DATA.
000180     PERFORM TEST BEFORE
000190             VARYING COUNTER FROM 1 BY 1 UNTIL COUNTER > 26
000200*-------------------------------------------------------------------------
000210* COUNTER is used as a subscript and the input character is compared.
000220* The reference modifier is specified after the qualification to 
000230* reference-modify the uniquely qualified data.
000240*-------------------------------------------------------------------------
000250       IF IN-DATA = ALP OF UPPER-CASE (COUNTER:1) THEN
000260*-------------------------------------------------------------------------
000270        EXIT PERFORM
000280      END-IF
000290     END-PERFORM.
000300     IF COUNTER <= 26 THEN
000310      DISPLAY "The lower-case letter corresponding to " IN-DATA " is "  
000320              ALP OF LOWER-CASE (COUNTER:1)"."
000330     ELSE
000340      DISPLAY "The input character is incorrect."
000350     END-IF.
000360 END PROGRAM SAMPLE.