COBOL CORR and CORRESPONDING
Master group data movement and operations with CORR and CORRESPONDING. Learn how to efficiently move, add, and subtract data between structures with matching field names, simplifying complex data manipulation tasks in your COBOL applications.
Overview
The CORRESPONDING clause (abbreviated as CORR) in COBOL provides a powerful way to perform operations between group items where only fields with identical names are affected. This feature automatically matches fields by name and performs the specified operation only on those fields that exist in both groups, making it an efficient tool for bulk data manipulation and structure-to-structure operations.
CORRESPONDING is particularly valuable when working with similar data structures that may have evolved over time or when interfacing between different systems that use related but not identical record layouts. It eliminates the need to write individual MOVE, ADD, or SUBTRACT statements for each matching field, reducing code volume and maintenance overhead.
Understanding CORRESPONDING is essential for efficient COBOL programming, especially in environments where data structures are frequently modified or where you need to merge information from multiple sources with similar but not identical field layouts.
Basic MOVE CORRESPONDING
Simple Structure Mapping
The most common use of CORRESPONDING is with the MOVE statement to copy data between similar structures:
1234567891011121301 INPUT-RECORD. 05 CUSTOMER-ID PIC 9(6). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(50). 05 PHONE-NUMBER PIC X(15). 01 OUTPUT-RECORD. 05 CUSTOMER-ID PIC 9(6). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(50). 05 EMAIL-ADDRESS PIC X(40). MOVE CORRESPONDING INPUT-RECORD TO OUTPUT-RECORD.
In this example, MOVE CORRESPONDING will automatically move CUSTOMER-ID, CUSTOMER-NAME, and CUSTOMER-ADDRESS from INPUT-RECORD to OUTPUT-RECORD because these fields have matching names in both structures. PHONE-NUMBER and EMAIL-ADDRESS are ignored because they don't have corresponding matches.
Complex Nested Structures
CORRESPONDING works with nested group items, matching fields at any level within the hierarchy:
1234567891011121314151617181901 EMPLOYEE-INPUT. 05 PERSONAL-INFO. 10 FIRST-NAME PIC X(20). 10 LAST-NAME PIC X(25). 10 BIRTH-DATE PIC 9(8). 05 WORK-INFO. 10 DEPARTMENT PIC X(10). 10 SALARY PIC 9(6)V99. 01 EMPLOYEE-OUTPUT. 05 PERSONAL-DATA. 10 FIRST-NAME PIC X(20). 10 LAST-NAME PIC X(25). 10 SSN PIC 9(9). 05 JOB-DATA. 10 DEPARTMENT PIC X(10). 10 HIRE-DATE PIC 9(8). MOVE CORRESPONDING EMPLOYEE-INPUT TO EMPLOYEE-OUTPUT.
This operation will move FIRST-NAME, LAST-NAME, and DEPARTMENT to their corresponding fields in EMPLOYEE-OUTPUT, regardless of the different group names (PERSONAL-INFO vs PERSONAL-DATA, WORK-INFO vs JOB-DATA). The field names themselves determine the correspondence.
Data Type Conversion
MOVE CORRESPONDING automatically handles data type conversion between compatible fields:
123456789101101 SOURCE-DATA. 05 AMOUNT PIC 9(5)V99. 05 QUANTITY PIC 9(4). 05 DESCRIPTION PIC X(30). 01 TARGET-DATA. 05 AMOUNT PIC 9(7)V99. 05 QUANTITY PIC 9(6). 05 DESCRIPTION PIC X(50). MOVE CORRESPONDING SOURCE-DATA TO TARGET-DATA.
The MOVE CORRESPONDING operation will handle the size differences automatically, padding or truncating as necessary according to standard COBOL conversion rules. AMOUNT will be moved with proper decimal alignment, QUANTITY will be zero-filled on the left, and DESCRIPTION will be space-filled on the right.
Arithmetic CORRESPONDING Operations
ADD CORRESPONDING
ADD CORRESPONDING allows you to add corresponding numeric fields from one group to another:
123456789101112131401 MONTHLY-SALES. 05 PRODUCT-A-SALES PIC 9(6)V99. 05 PRODUCT-B-SALES PIC 9(6)V99. 05 PRODUCT-C-SALES PIC 9(6)V99. 05 COMMISSION PIC 9(4)V99. 01 QUARTERLY-TOTALS. 05 PRODUCT-A-SALES PIC 9(8)V99. 05 PRODUCT-B-SALES PIC 9(8)V99. 05 PRODUCT-C-SALES PIC 9(8)V99. 05 COMMISSION PIC 9(6)V99. 05 BONUS PIC 9(4)V99. ADD CORRESPONDING MONTHLY-SALES TO QUARTERLY-TOTALS.
This operation will add the monthly sales figures to the quarterly totals for all corresponding fields. PRODUCT-A-SALES, PRODUCT-B-SALES, PRODUCT-C-SALES, and COMMISSION will be added to their corresponding fields in QUARTERLY-TOTALS. The BONUS field is unaffected because it has no corresponding field in MONTHLY-SALES.
SUBTRACT CORRESPONDING
SUBTRACT CORRESPONDING works similarly to ADD, subtracting corresponding numeric fields:
1234567891011121301 BUDGET-AMOUNTS. 05 SALARY-BUDGET PIC 9(7)V99. 05 SUPPLY-BUDGET PIC 9(6)V99. 05 TRAVEL-BUDGET PIC 9(5)V99. 05 TRAINING-BUDGET PIC 9(5)V99. 01 ACTUAL-EXPENSES. 05 SALARY-BUDGET PIC 9(7)V99. 05 SUPPLY-BUDGET PIC 9(6)V99. 05 TRAVEL-BUDGET PIC 9(5)V99. 05 EQUIPMENT-COST PIC 9(6)V99. SUBTRACT CORRESPONDING ACTUAL-EXPENSES FROM BUDGET-AMOUNTS.
This operation subtracts the actual expenses from the budget amounts for all corresponding fields, effectively calculating the remaining budget. EQUIPMENT-COST is ignored because it has no corresponding field in BUDGET-AMOUNTS, and TRAINING-BUDGET remains unchanged because it has no corresponding field in ACTUAL-EXPENSES.
Mixed Data Types
When using arithmetic CORRESPONDING operations, non-numeric fields are automatically ignored:
1234567891011121301 SALES-RECORD. 05 SALESPERSON-NAME PIC X(25). 05 REGION-CODE PIC X(5). 05 CURRENT-SALES PIC 9(6)V99. 05 COMMISSION-RATE PIC 9V99. 01 TOTALS-RECORD. 05 SALESPERSON-NAME PIC X(25). 05 TERRITORY PIC X(10). 05 CURRENT-SALES PIC 9(8)V99. 05 COMMISSION-RATE PIC 9V99. ADD CORRESPONDING SALES-RECORD TO TOTALS-RECORD.
In this ADD CORRESPONDING operation, only CURRENT-SALES and COMMISSION-RATE will be added because they are numeric. SALESPERSON-NAME is ignored even though it has a corresponding field, because ADD operations only work with numeric data. REGION-CODE and TERRITORY don't correspond by name.
Tutorial: Building a Data Integration System
Let's create a comprehensive data integration system that demonstrates the power of CORRESPONDING operations for merging data from multiple sources with different but related structures. This tutorial will show you how to build a flexible system that can handle evolving data formats efficiently.
Step 1: Define Source Data Structures
First, we'll establish different source data structures that represent the same basic information in slightly different formats:
123456789101112131415161718192021WORKING-STORAGE SECTION. 01 LEGACY-CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(6). 05 CUSTOMER-NAME PIC X(30). 05 STREET-ADDRESS PIC X(40). 05 CITY PIC X(20). 05 STATE PIC X(2). 05 ZIP-CODE PIC 9(5). 05 PHONE-NUMBER PIC X(12). 05 CREDIT-LIMIT PIC 9(6)V99. 01 NEW-CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(8). 05 CUSTOMER-NAME PIC X(50). 05 STREET-ADDRESS PIC X(60). 05 CITY PIC X(25). 05 STATE PIC X(2). 05 ZIP-CODE PIC 9(9). 05 EMAIL-ADDRESS PIC X(40). 05 CREDIT-LIMIT PIC 9(8)V99. 05 LAST-UPDATE PIC 9(8).
These structures represent customer data from legacy and new systems. While they have many fields in common, there are differences in field sizes and some unique fields. CORRESPONDING operations will help us merge this data efficiently.
Step 2: Create a Master Integration Structure
Next, we'll define a master structure that can accommodate data from all sources:
1234567891011121314151601 MASTER-CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(8). 05 CUSTOMER-NAME PIC X(50). 05 STREET-ADDRESS PIC X(60). 05 CITY PIC X(25). 05 STATE PIC X(2). 05 ZIP-CODE PIC 9(9). 05 PHONE-NUMBER PIC X(15). 05 EMAIL-ADDRESS PIC X(40). 05 CREDIT-LIMIT PIC 9(8)V99. 05 LAST-UPDATE PIC 9(8). 05 DATA-SOURCE PIC X(10). 05 INTEGRATION-FLAGS. 10 PHONE-AVAILABLE PIC X(1). 10 EMAIL-AVAILABLE PIC X(1). 10 ADDRESS-VERIFIED PIC X(1).
The master structure includes all possible fields from both source systems, with sizes large enough to accommodate the largest values. Additional fields track data source and availability flags to manage the integration process.
Step 3: Implement Legacy Data Integration
Now we'll create the logic to integrate legacy customer data:
1234567891011121314151617INTEGRATE-LEGACY-CUSTOMER. INITIALIZE MASTER-CUSTOMER-RECORD MOVE CORRESPONDING LEGACY-CUSTOMER-RECORD TO MASTER-CUSTOMER-RECORD MOVE 'LEGACY' TO DATA-SOURCE MOVE 'Y' TO PHONE-AVAILABLE MOVE 'N' TO EMAIL-AVAILABLE MOVE 'N' TO ADDRESS-VERIFIED IF PHONE-NUMBER NOT = SPACES MOVE 'Y' TO PHONE-AVAILABLE END-IF PERFORM VALIDATE-CUSTOMER-DATA PERFORM WRITE-MASTER-RECORD.
This integration routine uses MOVE CORRESPONDING to automatically copy all matching fields from the legacy record to the master record. Additional logic sets integration flags and handles data source identification. The CORRESPONDING operation eliminates the need to code individual MOVE statements for each field.
Step 4: Implement New System Data Integration
Let's create similar logic for the new system data with different processing rules:
123456789101112131415161718192021INTEGRATE-NEW-CUSTOMER. INITIALIZE MASTER-CUSTOMER-RECORD MOVE CORRESPONDING NEW-CUSTOMER-RECORD TO MASTER-CUSTOMER-RECORD MOVE 'NEW_SYS' TO DATA-SOURCE MOVE 'N' TO PHONE-AVAILABLE MOVE 'Y' TO EMAIL-AVAILABLE MOVE 'Y' TO ADDRESS-VERIFIED IF EMAIL-ADDRESS NOT = SPACES MOVE 'Y' TO EMAIL-AVAILABLE END-IF IF LAST-UPDATE = ZERO MOVE FUNCTION CURRENT-DATE(1:8) TO LAST-UPDATE END-IF PERFORM VALIDATE-CUSTOMER-DATA PERFORM WRITE-MASTER-RECORD.
The new system integration follows a similar pattern but with different business rules. The MOVE CORRESPONDING operation works identically, automatically handling the field mapping regardless of the source system differences.
Step 5: Implement Data Consolidation
Finally, we'll create logic to consolidate data from multiple sources for the same customer:
12345678910111213141516171819202122232425262728CONSOLIDATE-CUSTOMER-DATA. READ MASTER-FILE INTO EXISTING-CUSTOMER-RECORD IF CUSTOMER-ID = EXISTING-CUSTOMER-ID PERFORM MERGE-CUSTOMER-INFORMATION ELSE PERFORM WRITE-NEW-CUSTOMER-RECORD END-IF. MERGE-CUSTOMER-INFORMATION. IF EMAIL-ADDRESS = SPACES AND EXISTING-EMAIL-ADDRESS NOT = SPACES MOVE EXISTING-EMAIL-ADDRESS TO EMAIL-ADDRESS MOVE 'Y' TO EMAIL-AVAILABLE END-IF IF PHONE-NUMBER = SPACES AND EXISTING-PHONE-NUMBER NOT = SPACES MOVE EXISTING-PHONE-NUMBER TO PHONE-NUMBER MOVE 'Y' TO PHONE-AVAILABLE END-IF IF CREDIT-LIMIT > EXISTING-CREDIT-LIMIT MOVE CREDIT-LIMIT TO EXISTING-CREDIT-LIMIT END-IF MOVE CORRESPONDING MASTER-CUSTOMER-RECORD TO CONSOLIDATED-CUSTOMER-RECORD.
The consolidation logic merges information from multiple sources, filling in missing data and applying business rules for conflict resolution. MOVE CORRESPONDING is used in the final step to create the consolidated record efficiently.
Advanced CORRESPONDING Techniques
Conditional CORRESPONDING Operations
You can combine CORRESPONDING with conditional logic for more sophisticated data processing:
12345678910111213141516171819PROCESS-CUSTOMER-UPDATE. IF UPDATE-TYPE = 'FULL' MOVE CORRESPONDING INPUT-CUSTOMER TO MASTER-CUSTOMER ELSE IF UPDATE-TYPE = 'PARTIAL' PERFORM SELECTIVE-UPDATE END-IF END-IF. SELECTIVE-UPDATE. IF INPUT-CUSTOMER-NAME NOT = SPACES MOVE INPUT-CUSTOMER-NAME TO MASTER-CUSTOMER-NAME END-IF IF INPUT-PHONE-NUMBER NOT = SPACES MOVE INPUT-PHONE-NUMBER TO MASTER-PHONE-NUMBER END-IF ADD CORRESPONDING INPUT-AMOUNTS TO MASTER-AMOUNTS.
This approach allows you to use CORRESPONDING for bulk operations while maintaining fine-grained control over specific fields. The combination provides both efficiency and flexibility in data processing.
Error Handling with CORRESPONDING
Implement proper error handling when using CORRESPONDING operations, especially with arithmetic operations:
1234567891011121314SAFE-ADD-CORRESPONDING. MOVE ZERO TO WS-ERROR-COUNT ADD CORRESPONDING SOURCE-AMOUNTS TO TARGET-AMOUNTS ON SIZE ERROR ADD 1 TO WS-ERROR-COUNT PERFORM LOG-SIZE-ERROR END-ADD IF WS-ERROR-COUNT = ZERO PERFORM COMMIT-TRANSACTION ELSE PERFORM ROLLBACK-TRANSACTION END-IF.
Error handling ensures that arithmetic CORRESPONDING operations are performed safely, with appropriate recovery actions when size errors or other exceptions occur.
Performance Optimization
For high-volume processing, consider the performance implications of CORRESPONDING operations:
123456789101112* For frequently used operations, consider explicit moves * when you know exactly which fields need to be processed OPTIMIZED-CUSTOMER-COPY. IF FULL-COPY-REQUIRED MOVE CORRESPONDING SOURCE-CUSTOMER TO TARGET-CUSTOMER ELSE * Explicit moves for known critical fields MOVE SOURCE-CUSTOMER-ID TO TARGET-CUSTOMER-ID MOVE SOURCE-CUSTOMER-NAME TO TARGET-CUSTOMER-NAME MOVE SOURCE-CREDIT-LIMIT TO TARGET-CREDIT-LIMIT END-IF.
While CORRESPONDING is convenient, explicit field moves may be more efficient for high-frequency operations where you know exactly which fields need processing. Balance convenience with performance requirements based on your specific application needs.
Practical Exercises
Exercise 1: Employee Data Migration
Create an employee data migration system using CORRESPONDING operations:
1234567* Design structures for: * - Old employee records (different field sizes) * - New employee records (additional fields) * - Temporary migration records * Use CORRESPONDING to migrate data efficiently * Handle field size differences and new fields * Implement validation and error handling
Solution Approach: Create structures with overlapping field names but different sizes. Use MOVE CORRESPONDING for bulk migration, then add specific logic for new fields and validation. Include error handling for size overflow and data conversion issues.
Exercise 2: Financial Report Consolidation
Build a financial report consolidation system with multiple data sources:
1234567* Implement consolidation for: * - Monthly departmental reports * - Quarterly divisional summaries * - Annual company totals * Use ADD CORRESPONDING for accumulation * Handle different reporting periods * Include variance calculations and analysis
Solution Approach: Create hierarchical structures with matching field names for different reporting levels. Use ADD CORRESPONDING to accumulate totals efficiently. Implement period validation and variance analysis using SUBTRACT CORRESPONDING operations.
Exercise 3: Inventory System Integration
Design an inventory integration system for multiple warehouse systems:
1234567* Create integration for: * - Different warehouse management systems * - Varying product code formats * - Multiple inventory tracking methods * Use CORRESPONDING for data normalization * Implement product matching algorithms * Handle quantity and value consolidation
Solution Approach: Design flexible structures that can accommodate different warehouse formats. Use CORRESPONDING for initial data mapping, then implement specific logic for product code normalization and inventory consolidation. Include comprehensive validation and reconciliation procedures.
Best Practices and Guidelines
Structure Design
- Use consistent field naming conventions across related structures
- Design field sizes to accommodate the largest expected values
- Group related fields logically within structures
- Document which fields are intended to correspond between structures
- Consider future expansion when designing field layouts
- Use meaningful names that clearly indicate field purpose
Operation Selection
- Use MOVE CORRESPONDING for structure-to-structure copying
- Use ADD CORRESPONDING for accumulating totals and summaries
- Use SUBTRACT CORRESPONDING for variance analysis and adjustments
- Consider explicit moves for performance-critical operations
- Validate data types before arithmetic CORRESPONDING operations
- Test with various data combinations to ensure correct behavior
Error Handling and Validation
- Always include SIZE ERROR handling for arithmetic operations
- Validate field compatibility before CORRESPONDING operations
- Log any data conversion issues or truncation warnings
- Test with boundary values and edge cases
- Implement rollback procedures for failed operations
- Document expected behavior for non-corresponding fields
Maintenance and Documentation
Maintain clear documentation of which fields are expected to correspond between structures. When modifying data structures, consider the impact on existing CORRESPONDING operations. Field name changes can break correspondence relationships, so plan changes carefully and update all affected code.
Regular review of CORRESPONDING operations ensures they continue to work as intended as data structures evolve. Include CORRESPONDING operations in your testing strategy, particularly when field layouts change or new fields are added to existing structures.
Interactive Quiz
Test Your CORR and CORRESPONDING Knowledge
Question 1:
How does COBOL determine which fields correspond in a CORRESPONDING operation?
Question 2:
What happens to fields that don't have corresponding matches in a MOVE CORRESPONDING operation?
Question 3:
Which statement about ADD CORRESPONDING is correct?