Record management in COBOL involves handling individual records within files, including record layout definition, data validation, record processing, and record operations. Understanding record management concepts is essential for COBOL programming as most business applications require efficient record handling. Proper record management ensures data integrity, efficient processing, and reliable data operations.
Record management in COBOL encompasses all aspects of handling individual records including layout definition, data validation, processing operations, and error handling. Records are the fundamental units of data in COBOL files, and proper record management ensures data integrity and efficient processing. Different record management techniques are appropriate for different file organizations and business requirements.
Record layout definition specifies the structure and format of records within files. Proper record definition ensures data integrity and efficient processing operations.
1234567891011121314151617181920212223242526272829303132333435363738394041DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(20). 05 CUSTOMER-ADDRESS PIC X(50). 05 CUSTOMER-BALANCE PIC 9(8)V99. 05 CUSTOMER-PHONE PIC X(12). 05 CUSTOMER-STATUS PIC X(1). 88 ACTIVE-CUSTOMER VALUE 'A'. 88 INACTIVE-CUSTOMER VALUE 'I'. WORKING-STORAGE SECTION. 01 RECORD-CONTROLS. 05 RECORD-COUNT PIC 9(6) VALUE 0. 05 VALID-RECORDS PIC 9(6) VALUE 0. 05 INVALID-RECORDS PIC 9(6) VALUE 0. PROCEDURE DIVISION. RECORD-MANAGEMENT-EXAMPLE. DISPLAY 'Record Management Example' OPEN INPUT CUSTOMER-FILE PERFORM UNTIL FILE-EOF READ CUSTOMER-FILE IF FILE-OK ADD 1 TO RECORD-COUNT PERFORM VALIDATE-CUSTOMER-RECORD IF RECORD-VALID ADD 1 TO VALID-RECORDS PERFORM PROCESS-VALID-RECORD ELSE ADD 1 TO INVALID-RECORDS PERFORM PROCESS-INVALID-RECORD END-IF END-IF END-PERFORM CLOSE CUSTOMER-FILE
Record layout definition provides a clear structure for data within files. Hierarchical record structures help organize related data fields logically and enable efficient processing.
Complex record structures use hierarchical organization with multiple levels and groups to represent complex data relationships and business entities.
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748DATA DIVISION. FILE SECTION. FD EMPLOYEE-FILE. 01 EMPLOYEE-RECORD. 05 EMPLOYEE-ID PIC 9(6). 05 EMPLOYEE-NAME. 10 FIRST-NAME PIC X(15). 10 LAST-NAME PIC X(20). 05 EMPLOYEE-ADDRESS. 10 STREET PIC X(30). 10 CITY PIC X(20). 10 STATE PIC X(2). 10 ZIP-CODE PIC X(10). 05 EMPLOYEE-DATA. 10 DEPARTMENT PIC X(10). 10 SALARY PIC 9(8)V99. 10 HIRE-DATE PIC 9(8). 10 BENEFITS. 15 HEALTH-INS PIC X(1). 15 DENTAL-INS PIC X(1). 15 LIFE-INS PIC X(1). WORKING-STORAGE SECTION. 01 RECORD-PROCESSING. 05 PROCESSING-STATUS PIC X(1). 88 RECORD-VALID VALUE 'V'. 88 RECORD-INVALID VALUE 'I'. PROCEDURE DIVISION. COMPLEX-RECORD-EXAMPLE. DISPLAY 'Complex Record Structure Example' OPEN INPUT EMPLOYEE-FILE PERFORM UNTIL FILE-EOF READ EMPLOYEE-FILE IF FILE-OK PERFORM PROCESS-EMPLOYEE-RECORD END-IF END-PERFORM CLOSE EMPLOYEE-FILE. PROCESS-EMPLOYEE-RECORD. DISPLAY 'Processing employee: ' EMPLOYEE-ID DISPLAY 'Name: ' FIRST-NAME ' ' LAST-NAME DISPLAY 'Department: ' DEPARTMENT DISPLAY 'Salary: ' SALARY
Complex record structures use hierarchical organization to represent complex business entities. This approach provides clear data organization and enables efficient access to related data fields.
Data validation ensures record integrity by checking data content for correctness, completeness, and business rule compliance before processing.
1234567891011121314151617181920212223242526272829303132333435363738PROCEDURE DIVISION. VALIDATE-CUSTOMER-RECORD. MOVE 'V' TO PROCESSING-STATUS *> Check required fields IF CUSTOMER-ID = 0 DISPLAY 'ERROR: Customer ID is required' MOVE 'I' TO PROCESSING-STATUS END-IF IF CUSTOMER-NAME = SPACES DISPLAY 'ERROR: Customer name is required' MOVE 'I' TO PROCESSING-STATUS END-IF *> Check data ranges IF CUSTOMER-BALANCE < 0 OR CUSTOMER-BALANCE > 999999.99 DISPLAY 'ERROR: Balance out of range: ' CUSTOMER-BALANCE MOVE 'I' TO PROCESSING-STATUS END-IF *> Check status values IF CUSTOMER-STATUS NOT = 'A' AND CUSTOMER-STATUS NOT = 'I' DISPLAY 'ERROR: Invalid status: ' CUSTOMER-STATUS MOVE 'I' TO PROCESSING-STATUS END-IF *> Check phone format IF CUSTOMER-PHONE = SPACES DISPLAY 'ERROR: Phone number is required' MOVE 'I' TO PROCESSING-STATUS END-IF. PROCESS-VALID-RECORD. DISPLAY 'Processing valid record: ' CUSTOMER-ID ' ' CUSTOMER-NAME. PROCESS-INVALID-RECORD. DISPLAY 'Skipping invalid record: ' CUSTOMER-ID
Data validation ensures record integrity by checking required fields, data ranges, format compliance, and business rules. Invalid records are identified and handled appropriately.
Business rule validation enforces specific business logic and constraints that must be satisfied for records to be considered valid for processing.
1234567891011121314151617181920212223242526272829303132333435363738PROCEDURE DIVISION. VALIDATE-BUSINESS-RULES. DISPLAY 'Validating business rules' *> Check credit limit rules IF CUSTOMER-BALANCE > CREDIT-LIMIT DISPLAY 'ERROR: Customer exceeds credit limit' DISPLAY 'Balance: ' CUSTOMER-BALANCE DISPLAY 'Credit Limit: ' CREDIT-LIMIT MOVE 'I' TO PROCESSING-STATUS END-IF *> Check account status rules IF CUSTOMER-STATUS = 'I' DISPLAY 'WARNING: Processing inactive customer' PERFORM HANDLE-INACTIVE-CUSTOMER END-IF *> Check transaction limits IF DAILY-TRANSACTION-COUNT >= MAX-DAILY-TRANSACTIONS DISPLAY 'ERROR: Daily transaction limit exceeded' MOVE 'I' TO PROCESSING-STATUS END-IF *> Check business hours IF CURRENT-TIME < BUSINESS-START-TIME OR CURRENT-TIME > BUSINESS-END-TIME DISPLAY 'WARNING: Processing outside business hours' PERFORM HANDLE-AFTER-HOURS-PROCESSING END-IF. HANDLE-INACTIVE-CUSTOMER. DISPLAY 'Handling inactive customer: ' CUSTOMER-ID ADD 1 TO INACTIVE-CUSTOMER-COUNT. HANDLE-AFTER-HOURS-PROCESSING. DISPLAY 'After hours processing for: ' CUSTOMER-ID ADD 1 TO AFTER-HOURS-COUNT
Business rule validation enforces specific business constraints and logic. These rules ensure records comply with business policies and regulatory requirements.
Record reading operations retrieve records from files using various access methods and handle different file organizations efficiently.
123456789101112131415161718192021222324252627282930313233343536373839404142PROCEDURE DIVISION. RECORD-READING-OPERATIONS. DISPLAY 'Record Reading Operations' OPEN INPUT CUSTOMER-FILE *> Sequential reading PERFORM UNTIL FILE-EOF READ CUSTOMER-FILE IF FILE-OK PERFORM PROCESS-CURRENT-RECORD ELSE IF FILE-EOF DISPLAY 'End of file reached' ELSE DISPLAY 'Read error: ' FILE-STATUS END-IF END-IF END-PERFORM CLOSE CUSTOMER-FILE. PROCESS-CURRENT-RECORD. DISPLAY 'Processing record: ' CUSTOMER-ID ADD 1 TO RECORD-COUNT *> Process record data PERFORM CALCULATE-TOTALS PERFORM UPDATE-STATISTICS. CALCULATE-TOTALS. ADD CUSTOMER-BALANCE TO TOTAL-BALANCE ADD 1 TO CUSTOMER-COUNT. UPDATE-STATISTICS. IF CUSTOMER-BALANCE > HIGH-BALANCE MOVE CUSTOMER-BALANCE TO HIGH-BALANCE END-IF IF CUSTOMER-BALANCE < LOW-BALANCE MOVE CUSTOMER-BALANCE TO LOW-BALANCE END-IF
Record reading operations retrieve records from files using appropriate access methods. Proper error handling ensures reliable record processing and error recovery.
Record writing operations create new records in files, handling various file organizations and ensuring proper data formatting and validation.
12345678910111213141516171819202122232425262728293031323334353637383940414243PROCEDURE DIVISION. RECORD-WRITING-OPERATIONS. DISPLAY 'Record Writing Operations' OPEN OUTPUT OUTPUT-FILE *> Write header record PERFORM WRITE-HEADER-RECORD *> Write data records PERFORM VARYING WRITE-INDEX FROM 1 BY 1 UNTIL WRITE-INDEX > 10 PERFORM WRITE-DATA-RECORD END-PERFORM *> Write trailer record PERFORM WRITE-TRAILER-RECORD CLOSE OUTPUT-FILE. WRITE-HEADER-RECORD. MOVE 'HEADER' TO RECORD-TYPE MOVE FUNCTION CURRENT-DATE TO RECORD-DATE MOVE 'CUSTOMER REPORT' TO RECORD-DESCRIPTION WRITE OUTPUT-RECORD DISPLAY 'Header record written'. WRITE-DATA-RECORD. MOVE 'DATA' TO RECORD-TYPE MOVE WRITE-INDEX TO RECORD-NUMBER STRING 'Customer ' DELIMITED BY SIZE WRITE-INDEX DELIMITED BY SIZE INTO RECORD-DESCRIPTION END-STRING WRITE OUTPUT-RECORD DISPLAY 'Data record written: ' WRITE-INDEX. WRITE-TRAILER-RECORD. MOVE 'TRAILER' TO RECORD-TYPE MOVE RECORD-COUNT TO RECORD-NUMBER MOVE 'END OF REPORT' TO RECORD-DESCRIPTION WRITE OUTPUT-RECORD DISPLAY 'Trailer record written'
Record writing operations create new records in files with proper formatting and validation. Header, data, and trailer records provide structured file organization.
Data transformation involves converting record data from one format to another, applying business rules, and preparing data for different processing requirements.
12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455PROCEDURE DIVISION. DATA-TRANSFORMATION-EXAMPLE. DISPLAY 'Data Transformation Example' OPEN INPUT INPUT-FILE OPEN OUTPUT OUTPUT-FILE PERFORM UNTIL FILE-EOF READ INPUT-FILE IF FILE-OK PERFORM TRANSFORM-RECORD WRITE OUTPUT-RECORD END-IF END-PERFORM CLOSE INPUT-FILE CLOSE OUTPUT-FILE. TRANSFORM-RECORD. *> Transform customer data MOVE CUSTOMER-ID TO OUTPUT-CUSTOMER-ID *> Convert name to uppercase MOVE FUNCTION UPPER-CASE(CUSTOMER-NAME) TO OUTPUT-CUSTOMER-NAME *> Format balance with currency MOVE CUSTOMER-BALANCE TO OUTPUT-BALANCE *> Format phone number PERFORM FORMAT-PHONE-NUMBER *> Calculate derived fields PERFORM CALCULATE-DERIVED-FIELDS. FORMAT-PHONE-NUMBER. *> Format phone as (XXX) XXX-XXXX MOVE CUSTOMER-PHONE(1:3) TO OUTPUT-PHONE(2:3) MOVE CUSTOMER-PHONE(4:3) TO OUTPUT-PHONE(7:3) MOVE CUSTOMER-PHONE(7:4) TO OUTPUT-PHONE(11:4) MOVE '(' TO OUTPUT-PHONE(1:1) MOVE ')' TO OUTPUT-PHONE(5:1) MOVE ' ' TO OUTPUT-PHONE(6:1) MOVE '-' TO OUTPUT-PHONE(10:1). CALCULATE-DERIVED-FIELDS. *> Calculate customer tier based on balance IF CUSTOMER-BALANCE > 10000.00 MOVE 'GOLD' TO OUTPUT-CUSTOMER-TIER ELSE IF CUSTOMER-BALANCE > 5000.00 MOVE 'SILVER' TO OUTPUT-CUSTOMER-TIER ELSE MOVE 'BRONZE' TO OUTPUT-CUSTOMER-TIER END-IF END-IF
Data transformation converts record data between formats, applies business rules, and prepares data for different processing requirements. This ensures data consistency and proper formatting.
Record aggregation combines multiple records to create summary information, totals, and aggregated data for reporting and analysis purposes.
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354PROCEDURE DIVISION. RECORD-AGGREGATION-EXAMPLE. DISPLAY 'Record Aggregation Example' OPEN INPUT CUSTOMER-FILE *> Initialize aggregation variables MOVE 0 TO TOTAL-CUSTOMERS MOVE 0 TO TOTAL-BALANCE MOVE 0 TO ACTIVE-CUSTOMERS MOVE 0 TO INACTIVE-CUSTOMERS PERFORM UNTIL FILE-EOF READ CUSTOMER-FILE IF FILE-OK PERFORM AGGREGATE-RECORD-DATA END-IF END-PERFORM *> Display aggregation results PERFORM DISPLAY-AGGREGATION-RESULTS CLOSE CUSTOMER-FILE. AGGREGATE-RECORD-DATA. ADD 1 TO TOTAL-CUSTOMERS ADD CUSTOMER-BALANCE TO TOTAL-BALANCE IF ACTIVE-CUSTOMER ADD 1 TO ACTIVE-CUSTOMERS ELSE ADD 1 TO INACTIVE-CUSTOMERS END-IF *> Track balance ranges IF CUSTOMER-BALANCE > 10000.00 ADD 1 TO HIGH-BALANCE-CUSTOMERS ELSE IF CUSTOMER-BALANCE > 1000.00 ADD 1 TO MEDIUM-BALANCE-CUSTOMERS ELSE ADD 1 TO LOW-BALANCE-CUSTOMERS END-IF END-IF. DISPLAY-AGGREGATION-RESULTS. DISPLAY 'Aggregation Results:' DISPLAY 'Total Customers: ' TOTAL-CUSTOMERS DISPLAY 'Total Balance: ' TOTAL-BALANCE DISPLAY 'Active Customers: ' ACTIVE-CUSTOMERS DISPLAY 'Inactive Customers: ' INACTIVE-CUSTOMERS DISPLAY 'High Balance (>10K): ' HIGH-BALANCE-CUSTOMERS DISPLAY 'Medium Balance (1K-10K): ' MEDIUM-BALANCE-CUSTOMERS DISPLAY 'Low Balance (<1K): ' LOW-BALANCE-CUSTOMERS
Record aggregation combines multiple records to create summary information and totals. This provides valuable insights for reporting and business analysis.