MainframeMaster

COBOL Tutorial

COBOL CONTAINS Clause

Master table and array size specification with the CONTAINS clause. Learn how to define data structure capacities, manage variable-length records, and optimize memory usage in your COBOL applications.

Overview

The CONTAINS clause in COBOL is used to specify the size or capacity of data structures, particularly when working with tables, arrays, and variable-length records. It provides important information to the COBOL compiler and runtime system about the maximum number of occurrences or the size limits of repetitive data structures.

When combined with the OCCURS clause, CONTAINS helps define the boundaries and capacity of tables and arrays. This is especially valuable for variable-length data structures where the actual number of occurrences may vary at runtime, but you need to establish maximum limits for memory allocation and bounds checking.

Understanding the CONTAINS clause is essential for efficient memory management, proper data structure design, and creating robust COBOL programs that handle varying amounts of data safely and efficiently.

Basic Syntax and Usage

Simple CONTAINS Declaration

The basic syntax for using CONTAINS involves specifying the maximum number of occurrences or size for a data structure. Here's the fundamental structure:

cobol
1
2
3
4
5
6
7
01 WS-EMPLOYEE-TABLE. 05 WS-EMP-COUNT PIC 9(3) COMP. 05 WS-EMP-ENTRIES OCCURS 0 TO 100 TIMES DEPENDING ON WS-EMP-COUNT CONTAINS 100 OCCURRENCES. 10 WS-EMP-ID PIC 9(6). 10 WS-EMP-NAME PIC X(30).

In this example, we define a variable-length table that can contain up to 100 employee entries. The CONTAINS clause specifies the maximum capacity, while the DEPENDING ON clause allows the actual number to vary based on the WS-EMP-COUNT field.

Fixed-Size Table with CONTAINS

CONTAINS can also be used with fixed-size tables to document the table capacity and assist with memory management:

cobol
1
2
3
4
5
6
01 WS-SALES-DATA. 05 WS-MONTHLY-SALES OCCURS 12 TIMES CONTAINS 12 OCCURRENCES. 10 WS-MONTH PIC 9(2). 10 WS-AMOUNT PIC 9(7)V99 COMP-3. 10 WS-UNITS PIC 9(5) COMP.

This fixed-size table contains exactly 12 monthly sales records. The CONTAINS clause documents the table size and may be used by the compiler for optimization or by development tools for analysis.

Multi-Dimensional Arrays

CONTAINS becomes particularly useful when working with multi-dimensional arrays or nested data structures:

cobol
1
2
3
4
5
6
01 WS-MATRIX-DATA. 05 WS-ROWS OCCURS 10 TIMES CONTAINS 10 OCCURRENCES. 10 WS-COLUMNS OCCURS 10 TIMES CONTAINS 10 OCCURRENCES. 15 WS-VALUE PIC S9(5)V99 COMP-3.

This creates a 10x10 matrix where each dimension is documented with CONTAINS. This structure can hold 100 values total, with clear documentation of the capacity at each level of the hierarchy.

Variable-Length Record Handling

Dynamic Table Management

CONTAINS is essential for managing dynamic tables where the number of entries changes during program execution:

cobol
1
2
3
4
5
6
7
8
9
01 WS-CUSTOMER-LIST. 05 WS-CUSTOMER-COUNT PIC 9(4) COMP VALUE ZERO. 05 WS-MAX-CUSTOMERS PIC 9(4) COMP VALUE 500. 05 WS-CUSTOMERS OCCURS 0 TO 500 TIMES DEPENDING ON WS-CUSTOMER-COUNT CONTAINS 500 OCCURRENCES. 10 WS-CUST-ID PIC 9(8). 10 WS-CUST-NAME PIC X(40). 10 WS-CUST-STATUS PIC X(1).

This structure allows the customer list to grow and shrink dynamically up to the maximum of 500 customers. The CONTAINS clause ensures proper memory allocation while the DEPENDING ON clause controls the active portion of the table.

Record Size Specification

CONTAINS can specify the maximum record size for variable-length record processing:

cobol
1
2
3
4
5
6
7
01 WS-VARIABLE-RECORD. 05 WS-RECORD-LENGTH PIC 9(4) COMP. 05 WS-RECORD-DATA PIC X(1000) CONTAINS 1000 CHARACTERS. 05 WS-ACTUAL-DATA REDEFINES WS-RECORD-DATA. 10 WS-DATA-FIELD PIC X OCCURS 1 TO 1000 TIMES DEPENDING ON WS-RECORD-LENGTH.

This example shows how CONTAINS can be used to specify the maximum size for variable-length records. The actual length is controlled by WS-RECORD-LENGTH, but CONTAINS establishes the upper boundary.

Buffer Management

CONTAINS is valuable for defining buffer sizes and managing memory allocation for I/O operations:

cobol
1
2
3
4
5
6
01 WS-INPUT-BUFFER. 05 WS-BUFFER-SIZE PIC 9(5) COMP VALUE 2048. 05 WS-BUFFER-DATA OCCURS 1 TO 2048 TIMES DEPENDING ON WS-BUFFER-SIZE CONTAINS 2048 OCCURRENCES. 10 WS-BYTE-DATA PIC X.

This buffer structure can handle variable amounts of data up to 2048 bytes. The CONTAINS clause ensures adequate memory allocation while allowing flexible usage based on actual data requirements.

Tutorial: Building a Dynamic Inventory System

Let's create a comprehensive inventory management system that demonstrates the effective use of CONTAINS for managing variable-length data structures. This tutorial will show you how to build a flexible system that can handle varying numbers of products, categories, and transactions.

Step 1: Define the Main Inventory Structure

First, we'll establish the main inventory data structure with appropriate CONTAINS specifications:

cobol
1
2
3
4
5
6
7
8
9
10
11
WORKING-STORAGE SECTION. 01 WS-INVENTORY-SYSTEM. 05 WS-PRODUCT-COUNT PIC 9(5) COMP VALUE ZERO. 05 WS-MAX-PRODUCTS PIC 9(5) COMP VALUE 10000. 05 WS-PRODUCTS OCCURS 0 TO 10000 TIMES DEPENDING ON WS-PRODUCT-COUNT CONTAINS 10000 OCCURRENCES. 10 WS-PROD-ID PIC 9(8). 10 WS-PROD-NAME PIC X(50). 10 WS-PROD-PRICE PIC 9(6)V99 COMP-3. 10 WS-QUANTITY PIC 9(6) COMP.

This structure can handle up to 10,000 products with the actual count controlled by WS-PRODUCT-COUNT. The CONTAINS clause ensures proper memory allocation for the maximum capacity while allowing dynamic growth and shrinkage of the active product list.

Step 2: Define Category Management

Next, we'll create a category system with variable-length subcategory lists:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
01 WS-CATEGORY-SYSTEM. 05 WS-CATEGORY-COUNT PIC 9(3) COMP VALUE ZERO. 05 WS-CATEGORIES OCCURS 0 TO 100 TIMES DEPENDING ON WS-CATEGORY-COUNT CONTAINS 100 OCCURRENCES. 10 WS-CAT-ID PIC 9(4). 10 WS-CAT-NAME PIC X(30). 10 WS-SUBCAT-COUNT PIC 9(2) COMP. 10 WS-SUBCATEGORIES OCCURS 0 TO 50 TIMES DEPENDING ON WS-SUBCAT-COUNT CONTAINS 50 OCCURRENCES. 15 WS-SUBCAT-ID PIC 9(6). 15 WS-SUBCAT-NAME PIC X(25).

This nested structure allows each category to have a variable number of subcategories. The CONTAINS clauses at both levels ensure proper memory management for the hierarchical data organization.

Step 3: Implement Transaction History

Now we'll create a transaction history system with variable-length records:

cobol
1
2
3
4
5
6
7
8
9
10
11
01 WS-TRANSACTION-LOG. 05 WS-TRANS-COUNT PIC 9(6) COMP VALUE ZERO. 05 WS-TRANSACTIONS OCCURS 0 TO 50000 TIMES DEPENDING ON WS-TRANS-COUNT CONTAINS 50000 OCCURRENCES. 10 WS-TRANS-ID PIC 9(10). 10 WS-TRANS-TYPE PIC X(1). 10 WS-TRANS-DATE PIC 9(8). 10 WS-PRODUCT-ID PIC 9(8). 10 WS-TRANS-QTY PIC S9(6) COMP. 10 WS-TRANS-VALUE PIC S9(8)V99 COMP-3.

The transaction log can grow to accommodate up to 50,000 transactions. The CONTAINS clause ensures adequate memory allocation while the DEPENDING ON clause allows efficient memory usage by only allocating space for actual transactions.

Step 4: Implement Dynamic Product Addition

Let's create logic to safely add products while respecting the CONTAINS limits:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
PROCEDURE DIVISION. ADD-NEW-PRODUCT. IF WS-PRODUCT-COUNT >= WS-MAX-PRODUCTS DISPLAY "ERROR: Maximum product limit reached" MOVE 1 TO WS-RETURN-CODE EXIT PARAGRAPH END-IF ADD 1 TO WS-PRODUCT-COUNT MOVE WS-NEW-PROD-ID TO WS-PROD-ID(WS-PRODUCT-COUNT) MOVE WS-NEW-PROD-NAME TO WS-PROD-NAME(WS-PRODUCT-COUNT) MOVE WS-NEW-PROD-PRICE TO WS-PROD-PRICE(WS-PRODUCT-COUNT) MOVE WS-NEW-QUANTITY TO WS-QUANTITY(WS-PRODUCT-COUNT).

This logic checks against the maximum capacity defined by CONTAINS before adding new products. This prevents runtime errors and ensures data integrity by respecting the established boundaries.

Step 5: Implement Search and Retrieval

Finally, we'll create efficient search routines that work within the CONTAINS boundaries:

cobol
1
2
3
4
5
6
7
8
9
SEARCH-PRODUCT-BY-ID. SET WS-SEARCH-INDEX TO 1 SEARCH WS-PRODUCTS AT END MOVE "PRODUCT NOT FOUND" TO WS-MESSAGE WHEN WS-PROD-ID(WS-SEARCH-INDEX) = WS-SEARCH-PROD-ID MOVE WS-SEARCH-INDEX TO WS-FOUND-INDEX MOVE "PRODUCT FOUND" TO WS-MESSAGE END-SEARCH.

The search operation automatically respects the current table size as controlled by WS-PRODUCT-COUNT and the maximum size specified by CONTAINS. This ensures efficient searching within the active portion of the table.

Advanced CONTAINS Techniques

Memory Optimization Strategies

CONTAINS can be used strategically to optimize memory usage in large applications:

cobol
1
2
3
4
5
6
7
8
9
10
11
01 WS-LARGE-DATASET. 05 WS-ACTIVE-COUNT PIC 9(6) COMP. 05 WS-ARCHIVED-COUNT PIC 9(6) COMP. 05 WS-ACTIVE-RECORDS OCCURS 0 TO 100000 TIMES DEPENDING ON WS-ACTIVE-COUNT CONTAINS 100000 OCCURRENCES. 10 WS-RECORD-DATA PIC X(200). 05 WS-ARCHIVED-RECORDS OCCURS 0 TO 1000000 TIMES DEPENDING ON WS-ARCHIVED-COUNT CONTAINS 1000000 OCCURRENCES. 10 WS-ARCH-DATA PIC X(50).

This structure separates active and archived data with different CONTAINS limits and record sizes. Active records are larger but fewer, while archived records are compressed but more numerous, optimizing memory usage for different data access patterns.

Hierarchical Data Management

CONTAINS excels at managing complex hierarchical data structures:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
01 WS-ORGANIZATION-CHART. 05 WS-DEPT-COUNT PIC 9(3) COMP. 05 WS-DEPARTMENTS OCCURS 0 TO 50 TIMES DEPENDING ON WS-DEPT-COUNT CONTAINS 50 OCCURRENCES. 10 WS-DEPT-INFO. 15 WS-DEPT-ID PIC 9(4). 15 WS-DEPT-NAME PIC X(30). 10 WS-EMP-COUNT PIC 9(4) COMP. 10 WS-EMPLOYEES OCCURS 0 TO 500 TIMES DEPENDING ON WS-EMP-COUNT CONTAINS 500 OCCURRENCES. 15 WS-EMP-ID PIC 9(6). 15 WS-EMP-NAME PIC X(40). 15 WS-EMP-ROLE PIC X(20).

This organizational structure allows each department to have a variable number of employees up to the specified limits. The CONTAINS clauses ensure proper memory allocation at each level of the hierarchy.

Performance Monitoring

You can implement monitoring to track usage against CONTAINS limits:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
MONITOR-TABLE-USAGE. COMPUTE WS-USAGE-PERCENT = (WS-PRODUCT-COUNT / WS-MAX-PRODUCTS) * 100 IF WS-USAGE-PERCENT > 90 DISPLAY "WARNING: Product table " WS-USAGE-PERCENT "% full" PERFORM LOG-CAPACITY-WARNING END-IF IF WS-USAGE-PERCENT > 95 DISPLAY "CRITICAL: Product table near capacity" PERFORM ARCHIVE-OLD-PRODUCTS END-IF.

This monitoring logic tracks table usage against the CONTAINS limits and takes appropriate action when thresholds are reached. This proactive approach prevents runtime errors and maintains system performance.

Practical Exercises

Exercise 1: Student Management System

Create a student management system with variable-length course enrollments:

cobol
1
2
3
4
5
6
* Design structures for: * - Students (up to 5000) * - Courses per student (up to 10) * - Grade history (up to 100 entries per student) * Include proper CONTAINS specifications * Implement enrollment and grade recording logic

Solution Approach: Create nested structures with CONTAINS clauses at each level. Implement bounds checking for enrollments and grade entries. Include logic to handle capacity limits gracefully and provide appropriate error messages.

Exercise 2: Multi-Location Inventory

Build an inventory system that tracks products across multiple locations:

cobol
1
2
3
4
5
6
* Create structures for: * - Locations (up to 100) * - Products per location (up to 1000) * - Stock movements (up to 10000 per location) * Use CONTAINS for capacity management * Implement transfer and adjustment logic

Solution Approach: Design a three-level hierarchy with appropriate CONTAINS specifications. Implement transfer logic that respects capacity limits. Include reporting functions that summarize usage across all locations.

Exercise 3: Document Management System

Create a document management system with variable-length content:

cobol
1
2
3
4
5
6
* Design for: * - Document categories (up to 50) * - Documents per category (up to 500) * - Variable-length content (up to 10000 characters) * - Version history (up to 20 versions per document) * Use CONTAINS for all variable structures

Solution Approach: Implement variable-length record handling with CONTAINS specifications. Create version control logic that manages capacity limits. Include search and retrieval functions that work efficiently within the defined boundaries.

Best Practices and Guidelines

Capacity Planning

  • Analyze actual data requirements before setting CONTAINS limits
  • Include growth projections in capacity planning
  • Consider memory constraints and system limitations
  • Document the rationale for chosen capacity limits
  • Review and adjust limits based on actual usage patterns
  • Plan for peak usage scenarios, not just average loads

Error Handling and Validation

  • Always check against CONTAINS limits before adding data
  • Implement graceful handling of capacity exceeded conditions
  • Provide clear error messages when limits are reached
  • Log capacity warnings for monitoring and planning
  • Consider implementing automatic archiving or cleanup
  • Test boundary conditions thoroughly during development

Performance Optimization

  • Use appropriate CONTAINS values to optimize memory allocation
  • Consider the trade-off between memory usage and processing speed
  • Implement efficient search algorithms within table boundaries
  • Monitor table usage to identify optimization opportunities
  • Use indexed access when working with large tables
  • Consider partitioning large data sets into smaller, manageable chunks

Maintenance and Documentation

Proper documentation of CONTAINS specifications is crucial for maintenance. Include comments that explain the business rationale for capacity limits, document any dependencies between related structures, and maintain a record of capacity changes over time.

Regular review of CONTAINS specifications ensures they remain appropriate as your system grows and evolves. Monitor actual usage patterns and adjust limits as needed to maintain optimal performance and reliability.

Interactive Quiz

Test Your CONTAINS Knowledge

Question 1:

What is the primary purpose of the CONTAINS clause in COBOL?

Answer: To specify the maximum size or capacity of a data structure. CONTAINS is used to define the maximum number of occurrences or the size limits for tables, arrays, and variable-length records.

Question 2:

How does CONTAINS work with variable-length tables?

Answer: It specifies the maximum capacity for memory allocation. CONTAINS establishes the upper boundary for variable-length tables, while DEPENDING ON controls the actual number of active entries.

Question 3:

What should you do before adding entries to a table with CONTAINS specifications?

Answer: Check that you won't exceed the CONTAINS limit. Always validate that adding new entries won't exceed the maximum capacity specified by CONTAINS to prevent runtime errors and data corruption.

Frequently Asked Questions

Related Pages