MainframeMaster

COBOL Tutorial

COBOL ROLLBACK Statement - Quick Reference

Progress0 of 0 lessons

Overview

The ROLLBACK statement is used to undo database changes and restore the database to its previous state. It cancels all uncommitted changes made since the last COMMIT, ensuring data integrity when errors occur.

Purpose and Usage

  • Error recovery - Undo changes when errors occur
  • Data integrity - Maintain database consistency
  • Transaction management - Control database transactions
  • Error handling - Provide recovery mechanisms
  • Concurrent access - Handle multi-user scenarios

Transaction Concept

Transaction Start
├── Update Record 1 ✓
├── Update Record 2 ✓
├── Update Record 3 ✗ (ERROR)
└── ROLLBACK (undo all changes)
Database restored to original state

ROLLBACK undoes all changes when errors occur in a transaction.

Syntax

The ROLLBACK statement has a simple syntax but requires proper transaction setup.

Basic Syntax

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
* Basic ROLLBACK syntax ROLLBACK * With error handling IF ERROR-CONDITION ROLLBACK PERFORM ERROR-HANDLING END-IF * Complete example IDENTIFICATION DIVISION. PROGRAM-ID. ROLLBACK-EXAMPLE. DATA DIVISION. WORKING-STORAGE SECTION. 01 ERROR-FLAG PIC X(1) VALUE "N". 01 FILE-STATUS PIC XX. PROCEDURE DIVISION. MAIN-LOGIC. * Start transaction PERFORM PROCESS-TRANSACTION IF ERROR-FLAG = "Y" ROLLBACK DISPLAY "Transaction rolled back due to errors" ELSE COMMIT DISPLAY "Transaction committed successfully" END-IF STOP RUN. PROCESS-TRANSACTION. * Perform database operations PERFORM UPDATE-CUSTOMER PERFORM UPDATE-ACCOUNT PERFORM UPDATE-TRANSACTION. UPDATE-CUSTOMER. * Simulate customer update IF CUSTOMER-VALID * Update customer record CONTINUE ELSE MOVE "Y" TO ERROR-FLAG END-IF. UPDATE-ACCOUNT. * Simulate account update IF ACCOUNT-VALID * Update account record CONTINUE ELSE MOVE "Y" TO ERROR-FLAG END-IF. UPDATE-TRANSACTION. * Simulate transaction update IF TRANSACTION-VALID * Update transaction record CONTINUE ELSE MOVE "Y" TO ERROR-FLAG END-IF.

ROLLBACK requires transaction support and proper error handling.

ROLLBACK vs COMMIT Comparison

StatementActionUse Case
ROLLBACKUndo changesError recovery
COMMITSave changesSuccessful completion
BothTransaction controlData integrity

Practical Examples

These examples demonstrate how to use the ROLLBACK statement effectively in different error recovery scenarios.

Banking Transaction

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
IDENTIFICATION DIVISION. PROGRAM-ID. BANKING-TRANSACTION. DATA DIVISION. WORKING-STORAGE SECTION. 01 FROM-ACCOUNT PIC 9(10). 01 TO-ACCOUNT PIC 9(10). 01 TRANSFER-AMOUNT PIC 9(8)V99. 01 ERROR-FLAG PIC X(1) VALUE "N". 01 ERROR-MESSAGE PIC X(50). PROCEDURE DIVISION. PROCESS-TRANSFER. DISPLAY "Enter from account: " ACCEPT FROM-ACCOUNT DISPLAY "Enter to account: " ACCEPT TO-ACCOUNT DISPLAY "Enter amount: " ACCEPT TRANSFER-AMOUNT * Start transaction PERFORM VALIDATE-AND-TRANSFER IF ERROR-FLAG = "Y" ROLLBACK DISPLAY "Transfer failed: " ERROR-MESSAGE ELSE COMMIT DISPLAY "Transfer completed successfully" END-IF STOP RUN. VALIDATE-AND-TRANSFER. * Validate accounts IF FROM-ACCOUNT = TO-ACCOUNT MOVE "Y" TO ERROR-FLAG MOVE "Cannot transfer to same account" TO ERROR-MESSAGE EXIT PARAGRAPH END-IF * Check from account balance PERFORM CHECK-BALANCE IF ERROR-FLAG = "Y" EXIT PARAGRAPH END-IF * Perform transfer operations PERFORM DEBIT-FROM-ACCOUNT PERFORM CREDIT-TO-ACCOUNT. CHECK-BALANCE. * Simulate balance check IF TRANSFER-AMOUNT > 10000 MOVE "Y" TO ERROR-FLAG MOVE "Insufficient funds" TO ERROR-MESSAGE END-IF. DEBIT-FROM-ACCOUNT. * Simulate debit operation IF FROM-ACCOUNT-VALID * Debit from account CONTINUE ELSE MOVE "Y" TO ERROR-FLAG MOVE "Invalid from account" TO ERROR-MESSAGE END-IF. CREDIT-TO-ACCOUNT. * Simulate credit operation IF TO-ACCOUNT-VALID * Credit to account CONTINUE ELSE MOVE "Y" TO ERROR-FLAG MOVE "Invalid to account" TO ERROR-MESSAGE END-IF.

ROLLBACK ensures banking transactions maintain data integrity.

Inventory Update

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
* Inventory update with ROLLBACK DATA DIVISION. WORKING-STORAGE SECTION. 01 PRODUCT-CODE PIC X(10). 01 QUANTITY PIC 9(6). 01 ERROR-FLAG PIC X(1) VALUE "N". 01 UPDATE-STATUS PIC X(20). PROCEDURE DIVISION. UPDATE-INVENTORY. DISPLAY "Enter product code: " ACCEPT PRODUCT-CODE DISPLAY "Enter quantity to add: " ACCEPT QUANTITY PERFORM PROCESS-INVENTORY-UPDATE IF ERROR-FLAG = "Y" ROLLBACK DISPLAY "Inventory update failed: " UPDATE-STATUS ELSE COMMIT DISPLAY "Inventory updated successfully" END-IF. PROCESS-INVENTORY-UPDATE. * Validate product PERFORM VALIDATE-PRODUCT IF ERROR-FLAG = "Y" EXIT PARAGRAPH END-IF * Update inventory records PERFORM UPDATE-STOCK-LEVEL PERFORM UPDATE-REORDER-POINT PERFORM UPDATE-LAST-UPDATE. VALIDATE-PRODUCT. * Simulate product validation IF PRODUCT-CODE = SPACES MOVE "Y" TO ERROR-FLAG MOVE "Invalid product code" TO UPDATE-STATUS END-IF. UPDATE-STOCK-LEVEL. * Simulate stock level update IF STOCK-UPDATE-VALID * Update stock level CONTINUE ELSE MOVE "Y" TO ERROR-FLAG MOVE "Stock update failed" TO UPDATE-STATUS END-IF. UPDATE-REORDER-POINT. * Simulate reorder point update IF REORDER-UPDATE-VALID * Update reorder point CONTINUE ELSE MOVE "Y" TO ERROR-FLAG MOVE "Reorder update failed" TO UPDATE-STATUS END-IF. UPDATE-LAST-UPDATE. * Simulate timestamp update IF TIMESTAMP-UPDATE-VALID * Update timestamp CONTINUE ELSE MOVE "Y" TO ERROR-FLAG MOVE "Timestamp update failed" TO UPDATE-STATUS END-IF.

ROLLBACK ensures inventory updates maintain consistency.

Customer Order Processing

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
* Customer order processing with ROLLBACK DATA DIVISION. WORKING-STORAGE SECTION. 01 ORDER-ID PIC 9(10). 01 CUSTOMER-ID PIC 9(8). 01 ORDER-AMOUNT PIC 9(8)V99. 01 ERROR-FLAG PIC X(1) VALUE "N". 01 PROCESS-STATUS PIC X(30). PROCEDURE DIVISION. PROCESS-ORDER. DISPLAY "Enter order ID: " ACCEPT ORDER-ID DISPLAY "Enter customer ID: " ACCEPT CUSTOMER-ID DISPLAY "Enter order amount: " ACCEPT ORDER-AMOUNT PERFORM PROCESS-ORDER-TRANSACTION IF ERROR-FLAG = "Y" ROLLBACK DISPLAY "Order processing failed: " PROCESS-STATUS ELSE COMMIT DISPLAY "Order processed successfully" END-IF. PROCESS-ORDER-TRANSACTION. * Validate customer PERFORM VALIDATE-CUSTOMER IF ERROR-FLAG = "Y" EXIT PARAGRAPH END-IF * Process order components PERFORM CREATE-ORDER-RECORD PERFORM UPDATE-CUSTOMER-BALANCE PERFORM UPDATE-INVENTORY PERFORM CREATE-INVOICE. VALIDATE-CUSTOMER. * Simulate customer validation IF CUSTOMER-ID = ZERO MOVE "Y" TO ERROR-FLAG MOVE "Invalid customer ID" TO PROCESS-STATUS END-IF. CREATE-ORDER-RECORD. * Simulate order creation IF ORDER-CREATION-VALID * Create order record CONTINUE ELSE MOVE "Y" TO ERROR-FLAG MOVE "Order creation failed" TO PROCESS-STATUS END-IF. UPDATE-CUSTOMER-BALANCE. * Simulate balance update IF BALANCE-UPDATE-VALID * Update customer balance CONTINUE ELSE MOVE "Y" TO ERROR-FLAG MOVE "Balance update failed" TO PROCESS-STATUS END-IF. UPDATE-INVENTORY. * Simulate inventory update IF INVENTORY-UPDATE-VALID * Update inventory CONTINUE ELSE MOVE "Y" TO ERROR-FLAG MOVE "Inventory update failed" TO PROCESS-STATUS END-IF. CREATE-INVOICE. * Simulate invoice creation IF INVOICE-CREATION-VALID * Create invoice CONTINUE ELSE MOVE "Y" TO ERROR-FLAG MOVE "Invoice creation failed" TO PROCESS-STATUS END-IF.

ROLLBACK ensures order processing maintains data consistency.

Error Recovery Pattern

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
* Generic error recovery pattern with ROLLBACK PROCEDURE DIVISION. GENERIC-TRANSACTION. * Initialize error handling MOVE "N" TO ERROR-FLAG * Perform transaction operations PERFORM TRANSACTION-OPERATIONS * Check for errors and handle IF ERROR-FLAG = "Y" PERFORM ERROR-RECOVERY ELSE PERFORM SUCCESS-HANDLING END-IF. TRANSACTION-OPERATIONS. * Step 1: Validate input PERFORM VALIDATE-INPUT IF ERROR-FLAG = "Y" EXIT PARAGRAPH END-IF * Step 2: Process data PERFORM PROCESS-DATA IF ERROR-FLAG = "Y" EXIT PARAGRAPH END-IF * Step 3: Update database PERFORM UPDATE-DATABASE IF ERROR-FLAG = "Y" EXIT PARAGRAPH END-IF * Step 4: Generate output PERFORM GENERATE-OUTPUT. ERROR-RECOVERY. * Rollback transaction ROLLBACK * Log error PERFORM LOG-ERROR * Display error message DISPLAY "Transaction failed - changes rolled back" * Perform cleanup PERFORM CLEANUP-OPERATIONS. SUCCESS-HANDLING. * Commit transaction COMMIT * Log success PERFORM LOG-SUCCESS * Display success message DISPLAY "Transaction completed successfully". VALIDATE-INPUT. * Simulate input validation IF INPUT-VALID CONTINUE ELSE MOVE "Y" TO ERROR-FLAG END-IF. PROCESS-DATA. * Simulate data processing IF PROCESSING-SUCCESSFUL CONTINUE ELSE MOVE "Y" TO ERROR-FLAG END-IF. UPDATE-DATABASE. * Simulate database update IF UPDATE-SUCCESSFUL CONTINUE ELSE MOVE "Y" TO ERROR-FLAG END-IF. GENERATE-OUTPUT. * Simulate output generation IF OUTPUT-SUCCESSFUL CONTINUE ELSE MOVE "Y" TO ERROR-FLAG END-IF.

ROLLBACK provides consistent error recovery patterns.

Best Practices and Considerations

Understanding best practices ensures effective use of the ROLLBACK statement.

Best Practices

  • Check for errors - Always check return codes and file status
  • Rollback immediately - Call ROLLBACK as soon as errors are detected
  • Log errors - Record error details before rolling back
  • Handle cleanup - Perform necessary cleanup operations
  • Notify users - Provide clear error messages to users
  • Test thoroughly - Verify ROLLBACK behavior with various scenarios

Transaction Management

OperationPurposeWhen to Use
BEGIN TRANSACTIONStart transactionBefore operations
COMMITSave changesSuccess completion
ROLLBACKUndo changesError occurrence
SAVEPOINTCreate checkpointComplex transactions

Performance Considerations

  • Transaction size - Keep transactions as small as possible
  • Rollback cost - Large transactions are expensive to rollback
  • Resource usage - ROLLBACK may lock resources during recovery
  • Concurrent access - Consider impact on other users
  • Database system - Performance varies by database system

ROLLBACK Statement Quick Reference

UsageSyntaxExample
Basic ROLLBACKROLLBACKROLLBACK
With error handlingIF error ROLLBACKIF ERROR-FLAG = "Y" ROLLBACK
Error recoveryROLLBACK PERFORM ERROR-HANDLINGROLLBACK PERFORM LOG-ERROR
Transaction patternIF success COMMIT ELSE ROLLBACKIF OK COMMIT ELSE ROLLBACK
Conditional rollbackIF condition ROLLBACKIF INVALID-DATA ROLLBACK

Test Your Knowledge

1. What is the primary purpose of the ROLLBACK statement in COBOL?

  • To create a new database
  • To undo database changes and restore previous state
  • To commit database changes
  • To delete database records

2. When should you use ROLLBACK in a COBOL program?

  • After every successful operation
  • When an error occurs during database operations
  • At the beginning of a program
  • Only when creating new records

3. What happens to database changes after a ROLLBACK?

  • Changes are saved permanently
  • Changes are undone and lost
  • Changes are moved to a backup file
  • Changes are delayed until later

4. What is the relationship between ROLLBACK and COMMIT?

  • They are the same thing
  • ROLLBACK undoes changes, COMMIT saves changes
  • ROLLBACK is faster than COMMIT
  • They cannot be used together

5. Can ROLLBACK be used with all types of databases?

  • Yes, with all databases
  • Only with relational databases
  • Only with databases that support transactions
  • Only with mainframe databases

Frequently Asked Questions