The OCCURS clause is used in COBOL to define tables (arrays), allowing you to create a collection of data items with the same description and contiguous storage. This is essential for handling repetitive data structures efficiently.
1234501 STUDENT-TABLE. 05 STUDENT OCCURS 100 TIMES. 10 STUDENT-ID PIC 9(7). 10 STUDENT-NAME PIC X(30). 10 STUDENT-GRADE PIC 9(3).
This creates a table with 100 student records, each containing an ID, name, and grade.
1234501 PRODUCT-TABLE. 05 PRODUCT OCCURS 50 TIMES INDEXED BY PROD-IDX. 10 PRODUCT-ID PIC X(8). 10 PRODUCT-NAME PIC X(20). 10 PRODUCT-PRICE PIC 9(5)V99.
The INDEXED BY clause defines an index (PROD-IDX) that can be used with the SET statement for efficient table access.
Tables in COBOL are crucial for handling collections of similar data, such as employee records, inventory items, or transaction logs. The OCCURS clause offers flexibility in defining both simple and complex data structures.
Fixed-length tables have a predetermined number of elements that doesn't change during program execution. These are the most common and straightforward type of tables in COBOL.
12345WORKING-STORAGE SECTION. 01 MONTH-TABLE. 05 MONTH-NAME PIC X(10) OCCURS 12 TIMES. 01 SUBSCRIPTS. 05 MONTH-IDX PIC 9(2) VALUE 1.
This example defines a table of 12 month names and a subscript to access them.
123456789101112* Using a literal subscript MOVE "January" TO MONTH-NAME (1). DISPLAY MONTH-NAME (1). * Using a variable subscript MOVE 3 TO MONTH-IDX. MOVE "March" TO MONTH-NAME (MONTH-IDX). DISPLAY MONTH-NAME (MONTH-IDX). * Using an expression as a subscript ADD 1 TO MONTH-IDX. DISPLAY MONTH-NAME (MONTH-IDX - 1).
Table elements are accessed using subscripts enclosed in parentheses. Subscripts can be literals, variables, or expressions.
1234567891011121314151617* Initializing with individual values MOVE "January" TO MONTH-NAME (1). MOVE "February" TO MONTH-NAME (2). MOVE "March" TO MONTH-NAME (3). * ... and so on * Using a loop to initialize PERFORM VARYING MONTH-IDX FROM 1 BY 1 UNTIL MONTH-IDX > 12 MOVE SPACES TO MONTH-NAME (MONTH-IDX) END-PERFORM. * In modern COBOL, you can use VALUE directly (in WORKING-STORAGE) 01 MONTH-TABLE-MODERN. 05 MONTH-NAME-MODERN PIC X(10) OCCURS 12 TIMES VALUE "January" "February" "March" "April" "May" "June" "July" "August" "September" "October" "November" "December".
Tables can be initialized individually, with loops, or (in modern COBOL) directly with the VALUE clause.
12345678910111213141516* Looping through all elements PERFORM VARYING MONTH-IDX FROM 1 BY 1 UNTIL MONTH-IDX > 12 DISPLAY "Month " MONTH-IDX ": " MONTH-NAME (MONTH-IDX) END-PERFORM. * Searching for a specific value MOVE "April" TO WS-SEARCH-MONTH. MOVE 0 TO WS-FOUND-FLAG. PERFORM VARYING MONTH-IDX FROM 1 BY 1 UNTIL MONTH-IDX > 12 OR WS-FOUND-FLAG = 1 IF MONTH-NAME (MONTH-IDX) = WS-SEARCH-MONTH MOVE 1 TO WS-FOUND-FLAG DISPLAY "Found " WS-SEARCH-MONTH " at position " MONTH-IDX END-IF END-PERFORM.
The PERFORM statement with VARYING is commonly used to process all elements in a table.
Fixed-length tables are ideal when the number of elements is known in advance and doesn't change during execution. They are simpler to implement and more efficient in terms of memory usage and access speed compared to variable-length tables.
Multi-dimensional tables are created by nesting OCCURS clauses, allowing you to represent data in a grid-like structure with rows and columns, or even more complex arrangements.
123456701 SALES-DATA. 05 REGION-DATA OCCURS 4 TIMES INDEXED BY REGION-IDX. 10 QUARTER-DATA OCCURS 4 TIMES INDEXED BY QUARTER-IDX. 15 SALES-AMOUNT PIC 9(7)V99. * This creates a 4x4 table representing sales data for * 4 regions across 4 quarters
A two-dimensional table is created by nesting one OCCURS clause inside another.
12345678901 INVENTORY-DATA. 05 WAREHOUSE-DATA OCCURS 5 TIMES INDEXED BY WAREHOUSE-IDX. 10 PRODUCT-CATEGORY OCCURS 10 TIMES INDEXED BY CATEGORY-IDX. 15 PRODUCT-ITEM OCCURS 20 TIMES INDEXED BY PRODUCT-IDX. 20 ITEM-QUANTITY PIC 9(5). 20 ITEM-VALUE PIC 9(7)V99. * This creates a 5x10x20 table for tracking inventory across * 5 warehouses, 10 product categories, and 20 products per category
Additional dimensions can be added by further nesting of OCCURS clauses.
123456789101112* Accessing a specific element in a two-dimensional table MOVE 1000.00 TO SALES-AMOUNT (2, 3). * This sets the sales amount for region 2, quarter 3 * Using variables as subscripts MOVE 2 TO REGION-IDX. MOVE 3 TO QUARTER-IDX. DISPLAY SALES-AMOUNT (REGION-IDX, QUARTER-IDX). * Accessing a three-dimensional table element MOVE 500 TO ITEM-QUANTITY (3, 4, 12). * This sets the quantity for warehouse 3, category 4, product 12
Multiple subscripts are separated by commas, with the leftmost subscript representing the outermost level.
12345678910111213141516* Nested loops to process a two-dimensional table PERFORM VARYING REGION-IDX FROM 1 BY 1 UNTIL REGION-IDX > 4 PERFORM VARYING QUARTER-IDX FROM 1 BY 1 UNTIL QUARTER-IDX > 4 DISPLAY "Region " REGION-IDX ", Quarter " QUARTER-IDX ": " SALES-AMOUNT (REGION-IDX, QUARTER-IDX) END-PERFORM END-PERFORM. * Calculate totals by region PERFORM VARYING REGION-IDX FROM 1 BY 1 UNTIL REGION-IDX > 4 MOVE 0 TO REGION-TOTAL PERFORM VARYING QUARTER-IDX FROM 1 BY 1 UNTIL QUARTER-IDX > 4 ADD SALES-AMOUNT (REGION-IDX, QUARTER-IDX) TO REGION-TOTAL END-PERFORM DISPLAY "Total for Region " REGION-IDX ": " REGION-TOTAL END-PERFORM.
Nested PERFORM statements are used to process multi-dimensional tables, with one loop for each dimension.
Multi-dimensional tables are powerful for organizing complex data relationships, but they come with increased complexity and potential performance considerations. Use them when your data naturally fits a multi-dimensional structure.
The OCCURS DEPENDING ON clause creates variable-length tables that can dynamically adjust their size during program execution, optimizing memory usage for scenarios where the exact number of elements is not known in advance.
1234567891011WORKING-STORAGE SECTION. 01 TABLE-CONTROL. 05 ACTUAL-TABLE-SIZE PIC 9(3) VALUE 0. 01 EMPLOYEE-TABLE. 05 MAX-EMPLOYEES PIC 9(3) VALUE 100. 05 EMPLOYEE-RECORD OCCURS 1 TO 100 TIMES DEPENDING ON ACTUAL-TABLE-SIZE INDEXED BY EMP-IDX. 10 EMPLOYEE-ID PIC 9(5). 10 EMPLOYEE-NAME PIC X(30). 10 EMPLOYEE-DEPT PIC X(3).
The OCCURS DEPENDING ON clause specifies a minimum and maximum number of occurrences, with the actual size determined by a data item (ACTUAL-TABLE-SIZE in this example).
1234567891011121314151617* Start with an empty table MOVE 0 TO ACTUAL-TABLE-SIZE. * Add records to the table PERFORM UNTIL NO-MORE-RECORDS OR ACTUAL-TABLE-SIZE = MAX-EMPLOYEES READ EMPLOYEE-FILE AT END SET NO-MORE-RECORDS TO TRUE NOT AT END ADD 1 TO ACTUAL-TABLE-SIZE MOVE EMP-ID-IN TO EMPLOYEE-ID (ACTUAL-TABLE-SIZE) MOVE EMP-NAME-IN TO EMPLOYEE-NAME (ACTUAL-TABLE-SIZE) MOVE EMP-DEPT-IN TO EMPLOYEE-DEPT (ACTUAL-TABLE-SIZE) END-READ END-PERFORM. DISPLAY "Loaded " ACTUAL-TABLE-SIZE " employees into table."
As records are added, the table grows by incrementing the DEPENDING ON field.
123456789FD VARIABLE-RECORD-FILE RECORD CONTAINS 10 TO 1000 CHARACTERS. 01 VARIABLE-RECORD. 05 RECORD-TYPE PIC X. 05 ITEM-COUNT PIC 9(3). 05 ITEMS OCCURS 0 TO 99 TIMES DEPENDING ON ITEM-COUNT. 10 ITEM-DATA PIC X(10).
Variable-length tables are common in file record definitions where each record may contain a different number of items.
Variable-length tables offer flexibility but require careful handling to ensure you're not accessing elements beyond the current size as determined by the DEPENDING ON item. They're especially useful for file I/O and cases where the amount of data varies considerably.
COBOL provides several mechanisms for accessing and manipulating table elements efficiently.
123456789101112131415161718WORKING-STORAGE SECTION. 01 TABLE-DATA. 05 DATA-ITEM OCCURS 100 TIMES INDEXED BY DATA-IDX. 10 ITEM-CODE PIC X(5). 10 ITEM-VALUE PIC 9(5). 01 SUBSCRIPTS. 05 SUB1 PIC 9(3) COMP VALUE 1. * Using a subscript (regular data item) MOVE "CODE1" TO ITEM-CODE (SUB1). ADD 1 TO SUB1. MOVE "CODE2" TO ITEM-CODE (SUB1). * Using an index (more efficient) SET DATA-IDX TO 1. MOVE "CODE1" TO ITEM-CODE (DATA-IDX). SET DATA-IDX UP BY 1. MOVE "CODE2" TO ITEM-CODE (DATA-IDX).
123456789101112131415161718192021222324* Serial search with SEARCH SET PROD-IDX TO 1. SEARCH PRODUCT AT END DISPLAY "Product not found" WHEN PRODUCT-ID (PROD-IDX) = SEARCH-ID DISPLAY "Found product: " PRODUCT-NAME (PROD-IDX) DISPLAY "Price: " PRODUCT-PRICE (PROD-IDX) END-SEARCH. * Binary search with SEARCH ALL (for sorted tables) 01 PRODUCT-CODES. 05 PRODUCT-CODE OCCURS 50 TIMES ASCENDING KEY IS PROD-CODE INDEXED BY CODE-IDX. 10 PROD-CODE PIC X(8). 10 PROD-DESC PIC X(30). SEARCH ALL PRODUCT-CODE AT END DISPLAY "Code not found" WHEN PROD-CODE (CODE-IDX) = SEARCH-CODE DISPLAY "Description: " PROD-DESC (CODE-IDX) END-SEARCH.
SEARCH performs sequential searches, while SEARCH ALL performs binary searches on sorted tables for better performance with large datasets.
12345678910111213141501 EMPLOYEE-DATA. 05 EMPLOYEE-RECORD OCCURS 100 TIMES. 10 EMP-ID PIC 9(5). 10 EMP-NAME. 15 EMP-FIRST PIC X(15). 15 EMP-LAST PIC X(20). 10 EMP-SALARY PIC 9(6)V99. * Accessing a sub-field DISPLAY EMP-FIRST (10). DISPLAY EMP-LAST (10). * Using reference modification DISPLAY EMP-NAME (10) (1:10). * Displays first 10 characters of employee 10's name
You can access subfields of table elements directly, and even use reference modification for more precision.
1234567891011121301 TABLE-ONE. 05 DATA-ITEM OCCURS 10 TIMES PIC X(5). 01 TABLE-TWO. 05 DATA-ITEM OCCURS 10 TIMES PIC X(5). * Using qualification to distinguish between tables MOVE "AAAAA" TO DATA-ITEM (5) OF TABLE-ONE. MOVE "BBBBB" TO DATA-ITEM (5) OF TABLE-TWO. * Comparing elements across tables IF DATA-ITEM (3) OF TABLE-ONE = DATA-ITEM (7) OF TABLE-TWO DISPLAY "Elements match" END-IF.
Qualified names help distinguish between table elements with the same name in different tables.
Efficient table access is critical for performance in COBOL programs that process large amounts of data. Using indexes instead of subscripts, properly structured tables, and the right search methods can significantly improve program performance.
Complete the following COBOL program to create and manipulate tables:
1234567891011121314151617181920212223242526272829IDENTIFICATION DIVISION. PROGRAM-ID. TABLEXRC. DATA DIVISION. WORKING-STORAGE SECTION. 01 STUDENT-SCORES. 05 CLASS-SIZE PIC 9(2) VALUE 10. 05 STUDENT-DATA OCCURS 10 TIMES INDEXED BY STUDENT-IDX. 10 STUDENT-ID PIC 9(4). 10 STUDENT-NAME PIC X(20). 10 EXAM-SCORES OCCURS 3 TIMES INDEXED BY EXAM-IDX. 15 SCORE-VALUE PIC 9(3). 01 CALCULATION-FIELDS. 05 TOTAL-SCORE PIC 9(4) VALUE 0. 05 AVERAGE-SCORE PIC 9(3)V99. 05 HIGHEST-AVG PIC 9(3)V99 VALUE 0. 05 HIGHEST-STUDENT PIC X(20). 05 CURRENT-AVG PIC 9(3)V99. PROCEDURE DIVISION. * Initialize the table with some data * Calculate the average score for each student * Find the student with the highest average score * Display all student data with their average scores * Display the student with the highest average STOP RUN.
Complete the procedure division code to initialize the table, calculate averages, and find the highest-scoring student.
1. What is the primary purpose of the OCCURS clause in COBOL?
2. How do you access an element in a one-dimensional table?
3. Which of the following correctly defines a two-dimensional table in COBOL?
4. What is the purpose of the OCCURS DEPENDING ON clause?
5. When using OCCURS with the INDEXED BY clause, what type of variable is created?