Top
NetCOBOL V11.0 Syntax Samples
FUJITSU Software

1.25.1 OCCURS Clause (format 1) Specific Occurrence Count

000010 @OPTIONS MAIN
000020*----------------------------------------------------------------------
000030* OCCURS clause (format 1)
000040* Array data is defined.
000050*----------------------------------------------------------------------
000060 IDENTIFICATION   DIVISION.
000070 PROGRAM-ID.      SAMPLE.
000080 DATA             DIVISION.
000090 WORKING-STORAGE  SECTION.
000100 01 RESIDENTS.
000110    02              PIC X(25) VALUE "Room 101:  Suzuki".
000120    02              PIC X(25) VALUE "Room 102:  Nakamura".
000130    02              PIC X(25) VALUE "Room 103:  Saito".
000140    02              PIC X(25) VALUE "Room 201:  Yamamoto".
000150    02              PIC X(25) VALUE "Room 202:  Kimura".
000160    02              PIC X(25) VALUE "Room 203:  Tanaka".
000170*----------------------------------------------------------------------
000180* The resident data is redefined as a table.
000190* Apartment Fujitsu is a two-story building with three rooms on each 
000195* floor (two-dimensional array).
000200*----------------------------------------------------------------------
000210 01              REDEFINES RESIDENTS.
000220    02 FLOOR        OCCURS 2 TIMES.
000230      03 OCCUPANT     OCCURS 3 TIMES PIC X(25).
000240*----------------------------------------------------------------------
000250 77 FLOOR-NUMBER   PIC 9(1).
000260 77 ROOM-NUMBER    PIC 9(1).
000270 PROCEDURE          DIVISION.
000280     DISPLAY "This is the Apartment Fujitsu residents guide."
000290     DISPLAY "The room is on which floor? (1 or 2) >>"
000295             WITH NO ADVANCING.
000300     ACCEPT FLOOR-NUMBER.
000310     DISPLAY "Which room number? (1 to 3) >>"
000315             WITH NO ADVANCING.
000320     ACCEPT ROOM-NUMBER.
000330     DISPLAY " ".
000340*----------------------------------------------------------------------
000350* The arrayed data can be referenced by subscripting.
000360* Because the data is a two-dimensional array, two subscripts are used 
000365* to specify the data.
000370*----------------------------------------------------------------------
000380     DISPLAY OCCUPANT (FLOOR-NUMBER, ROOM-NUMBER) " is the resident."
000390*----------------------------------------------------------------------
000400 END PROGRAM SAMPLE.