MainframeMaster

COBOL Tutorial

COBOL B-EXOR (B-XOR) - Binary Exclusive OR

The B-EXOR (also known as B-XOR) function in COBOL performs binary exclusive OR operations on numeric data items. It's essential for data encryption, bit toggling, checksum calculations, and creating unique identifiers through binary manipulation.

Key Purpose

B-EXOR performs exclusive OR operations where each result bit is 1 only when corresponding bits in the operands are different, making it ideal for encryption, data comparison, and bit manipulation tasks.

Basic Syntax

cobol
1
2
3
4
5
6
FUNCTION B-EXOR(argument-1, argument-2) FUNCTION B-XOR(argument-1, argument-2) COMPUTE result-field = FUNCTION B-EXOR(operand-1, operand-2) MOVE FUNCTION B-XOR(data-item-1, data-item-2) TO target-field

Note

B-EXOR and B-XOR are equivalent functions. Both perform the same exclusive OR operation. Use whichever naming convention matches your coding standards.

Fundamental Concepts

1. Exclusive OR Truth Table

The exclusive OR operation follows this logic for each bit position:

Bit ABit BA XOR B
000
011
101
110
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
WORKING-STORAGE SECTION. 01 WS-VALUE-A PIC 9(8) COMP VALUE 15. *> Binary: 00001111 01 WS-VALUE-B PIC 9(8) COMP VALUE 51. *> Binary: 00110011 01 WS-RESULT PIC 9(8) COMP. *> Result PROCEDURE DIVISION. BINARY-XOR-DEMO. COMPUTE WS-RESULT = FUNCTION B-EXOR(WS-VALUE-A, WS-VALUE-B) *> WS-RESULT = 60 (Binary: 00111100) DISPLAY "Value A: " WS-VALUE-A " (Binary: 00001111)" DISPLAY "Value B: " WS-VALUE-B " (Binary: 00110011)" DISPLAY "Result: " WS-RESULT " (Binary: 00111100)"

2. Basic XOR Properties

XOR has unique mathematical properties that make it useful for various applications:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
WORKING-STORAGE SECTION. 01 WS-ORIGINAL-VALUE PIC 9(4) COMP VALUE 123. 01 WS-KEY PIC 9(4) COMP VALUE 85. *> 01010101 01 WS-ENCRYPTED PIC 9(4) COMP. 01 WS-DECRYPTED PIC 9(4) COMP. PROCEDURE DIVISION. XOR-PROPERTIES-DEMO. *> Property 1: A XOR 0 = A COMPUTE WS-RESULT = FUNCTION B-EXOR(WS-ORIGINAL-VALUE, 0) DISPLAY "123 XOR 0 = " WS-RESULT *> Result: 123 *> Property 2: A XOR A = 0 COMPUTE WS-RESULT = FUNCTION B-EXOR(WS-ORIGINAL-VALUE, WS-ORIGINAL-VALUE) DISPLAY "123 XOR 123 = " WS-RESULT *> Result: 0 *> Property 3: Encryption/Decryption (A XOR B) XOR B = A COMPUTE WS-ENCRYPTED = FUNCTION B-EXOR(WS-ORIGINAL-VALUE, WS-KEY) COMPUTE WS-DECRYPTED = FUNCTION B-EXOR(WS-ENCRYPTED, WS-KEY) DISPLAY "Original: " WS-ORIGINAL-VALUE DISPLAY "Encrypted: " WS-ENCRYPTED DISPLAY "Decrypted: " WS-DECRYPTED *> Should equal original

3. Bit Toggling Applications

XOR is perfect for toggling specific bits while leaving others unchanged:

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
WORKING-STORAGE SECTION. 01 WS-STATUS-FLAGS PIC 9(4) COMP VALUE 170. *> 10101010 01 WS-TOGGLE-MASKS. 05 WS-TOGGLE-BIT0 PIC 9(4) COMP VALUE 1. *> 00000001 05 WS-TOGGLE-BIT3 PIC 9(4) COMP VALUE 8. *> 00001000 05 WS-TOGGLE-ALL PIC 9(4) COMP VALUE 255. *> 11111111 01 WS-TOGGLED-FLAGS PIC 9(4) COMP. PROCEDURE DIVISION. BIT-TOGGLE-DEMO. DISPLAY "Original flags: " WS-STATUS-FLAGS " (Binary: 10101010)" *> Toggle bit 0 (rightmost bit) COMPUTE WS-TOGGLED-FLAGS = FUNCTION B-EXOR(WS-STATUS-FLAGS, WS-TOGGLE-BIT0) DISPLAY "Toggle bit 0: " WS-TOGGLED-FLAGS " (Binary: 10101011)" *> Toggle bit 3 COMPUTE WS-TOGGLED-FLAGS = FUNCTION B-EXOR(WS-STATUS-FLAGS, WS-TOGGLE-BIT3) DISPLAY "Toggle bit 3: " WS-TOGGLED-FLAGS " (Binary: 10100010)" *> Toggle all bits (invert) COMPUTE WS-TOGGLED-FLAGS = FUNCTION B-EXOR(WS-STATUS-FLAGS, WS-TOGGLE-ALL) DISPLAY "Toggle all: " WS-TOGGLED-FLAGS " (Binary: 01010101)"

Advanced Applications

1. Simple Data Encryption

XOR encryption is reversible and commonly used for simple data protection:

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
WORKING-STORAGE SECTION. 01 WS-ENCRYPTION-SYSTEM. 05 WS-ENCRYPTION-KEY PIC 9(8) COMP VALUE 123456789. 05 WS-DATA-COUNTER PIC 9(3) COMP. 01 WS-SENSITIVE-DATA. 05 WS-PASSWORD PIC X(20) VALUE "MySecretPassword123". 05 WS-ACCOUNT-NUMBER PIC 9(16) VALUE 1234567890123456. 05 WS-SSN PIC 9(9) VALUE 123456789. 01 WS-ENCRYPTED-DATA. 05 WS-ENC-PASSWORD PIC X(20). 05 WS-ENC-ACCOUNT PIC 9(16). 05 WS-ENC-SSN PIC 9(9). 01 WS-DECRYPTED-DATA. 05 WS-DEC-PASSWORD PIC X(20). 05 WS-DEC-ACCOUNT PIC 9(16). 05 WS-DEC-SSN PIC 9(9). PROCEDURE DIVISION. ENCRYPTION-SYSTEM. *> Encrypt account number COMPUTE WS-ENC-ACCOUNT = FUNCTION B-EXOR(WS-ACCOUNT-NUMBER, WS-ENCRYPTION-KEY) *> Encrypt SSN COMPUTE WS-ENC-SSN = FUNCTION B-EXOR(WS-SSN, WS-ENCRYPTION-KEY) DISPLAY "=== ENCRYPTION DEMO ===" DISPLAY "Original Account: " WS-ACCOUNT-NUMBER DISPLAY "Encrypted Account: " WS-ENC-ACCOUNT DISPLAY "Original SSN: " WS-SSN DISPLAY "Encrypted SSN: " WS-ENC-SSN *> Decrypt to verify COMPUTE WS-DEC-ACCOUNT = FUNCTION B-EXOR(WS-ENC-ACCOUNT, WS-ENCRYPTION-KEY) COMPUTE WS-DEC-SSN = FUNCTION B-EXOR(WS-ENC-SSN, WS-ENCRYPTION-KEY) DISPLAY "=== DECRYPTION VERIFICATION ===" DISPLAY "Decrypted Account: " WS-DEC-ACCOUNT DISPLAY "Decrypted SSN: " WS-DEC-SSN IF WS-DEC-ACCOUNT = WS-ACCOUNT-NUMBER AND WS-DEC-SSN = WS-SSN DISPLAY "Encryption/Decryption successful!" ELSE DISPLAY "Encryption/Decryption failed!" END-IF.

2. Checksum and Data Integrity

Using XOR for creating checksums and verifying data integrity:

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
WORKING-STORAGE SECTION. 01 WS-DATA-ARRAY. 05 WS-DATA-ITEM PIC 9(8) COMP OCCURS 10 TIMES. 01 WS-CHECKSUM-CALC. 05 WS-RUNNING-CHKSUM PIC 9(8) COMP VALUE 0. 05 WS-COUNTER PIC 9(3) COMP. 05 WS-FINAL-CHKSUM PIC 9(8) COMP. 01 WS-VERIFICATION. 05 WS-STORED-CHKSUM PIC 9(8) COMP. 05 WS-COMPUTED-CHKSUM PIC 9(8) COMP. 05 WS-DATA-VALID PIC X VALUE 'N'. PROCEDURE DIVISION. CHECKSUM-PROCESSING. *> Initialize test data PERFORM VARYING WS-COUNTER FROM 1 BY 1 UNTIL WS-COUNTER > 10 COMPUTE WS-DATA-ITEM(WS-COUNTER) = WS-COUNTER * 1234567 END-PERFORM *> Calculate XOR checksum PERFORM VARYING WS-COUNTER FROM 1 BY 1 UNTIL WS-COUNTER > 10 COMPUTE WS-RUNNING-CHKSUM = FUNCTION B-EXOR(WS-RUNNING-CHKSUM, WS-DATA-ITEM(WS-COUNTER)) END-PERFORM MOVE WS-RUNNING-CHKSUM TO WS-STORED-CHKSUM DISPLAY "Data checksum: " WS-STORED-CHKSUM *> Simulate data corruption COMPUTE WS-DATA-ITEM(5) = WS-DATA-ITEM(5) + 1 *> Verify checksum after potential corruption MOVE 0 TO WS-COMPUTED-CHKSUM PERFORM VARYING WS-COUNTER FROM 1 BY 1 UNTIL WS-COUNTER > 10 COMPUTE WS-COMPUTED-CHKSUM = FUNCTION B-EXOR(WS-COMPUTED-CHKSUM, WS-DATA-ITEM(WS-COUNTER)) END-PERFORM IF WS-COMPUTED-CHKSUM = WS-STORED-CHKSUM MOVE 'Y' TO WS-DATA-VALID DISPLAY "Data integrity verified" ELSE MOVE 'N' TO WS-DATA-VALID DISPLAY "Data corruption detected!" END-IF.

3. Unique ID Generation

Combining multiple values with XOR to create unique identifiers:

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
WORKING-STORAGE SECTION. 01 WS-ID-COMPONENTS. 05 WS-TIMESTAMP PIC 9(14) COMP. *> YYYYMMDDHHMMSS 05 WS-PROCESS-ID PIC 9(8) COMP. 05 WS-SEQUENCE PIC 9(6) COMP. 05 WS-RANDOM-SEED PIC 9(8) COMP VALUE 987654321. 01 WS-UNIQUE-ID PIC 9(18) COMP. 01 WS-TEMP-ID PIC 9(18) COMP. PROCEDURE DIVISION. UNIQUE-ID-GENERATOR. *> Get current timestamp (simplified for demo) ACCEPT WS-TIMESTAMP FROM DATE YYYYMMDD *> Simulate process ID and sequence MOVE 12345 TO WS-PROCESS-ID MOVE 678 TO WS-SEQUENCE *> Generate unique ID using XOR operations COMPUTE WS-TEMP-ID = FUNCTION B-EXOR(WS-TIMESTAMP, WS-PROCESS-ID) COMPUTE WS-TEMP-ID = FUNCTION B-EXOR(WS-TEMP-ID, WS-SEQUENCE) COMPUTE WS-UNIQUE-ID = FUNCTION B-EXOR(WS-TEMP-ID, WS-RANDOM-SEED) DISPLAY "=== UNIQUE ID GENERATION ===" DISPLAY "Timestamp: " WS-TIMESTAMP DISPLAY "Process ID: " WS-PROCESS-ID DISPLAY "Sequence: " WS-SEQUENCE DISPLAY "Random Seed: " WS-RANDOM-SEED DISPLAY "Generated Unique ID: " WS-UNIQUE-ID *> Increment sequence for next ID ADD 1 TO WS-SEQUENCE.

Performance and Optimization

1. Efficient XOR Operations

Optimizing XOR operations for high-performance applications:

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
WORKING-STORAGE SECTION. 01 WS-PERFORMANCE-TEST. 05 WS-LOOP-COUNTER PIC 9(6) COMP. 05 WS-TEST-VALUE PIC 9(8) COMP VALUE 12345678. 05 WS-XOR-MASK PIC 9(8) COMP VALUE 87654321. 05 WS-RESULT PIC 9(8) COMP. 01 WS-BATCH-PROCESSING. 05 WS-DATA-BATCH PIC 9(8) COMP OCCURS 1000 TIMES. 05 WS-BATCH-INDEX PIC 9(4) COMP. PROCEDURE DIVISION. PERFORMANCE-OPTIMIZATION. *> Initialize batch data PERFORM VARYING WS-BATCH-INDEX FROM 1 BY 1 UNTIL WS-BATCH-INDEX > 1000 COMPUTE WS-DATA-BATCH(WS-BATCH-INDEX) = WS-BATCH-INDEX * 123 END-PERFORM *> Efficient batch XOR processing PERFORM VARYING WS-BATCH-INDEX FROM 1 BY 1 UNTIL WS-BATCH-INDEX > 1000 COMPUTE WS-DATA-BATCH(WS-BATCH-INDEX) = FUNCTION B-EXOR(WS-DATA-BATCH(WS-BATCH-INDEX), WS-XOR-MASK) END-PERFORM DISPLAY "Processed " WS-BATCH-INDEX " items efficiently".

2. Complex Bit Patterns

Working with complex bit patterns and multiple XOR operations:

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
WORKING-STORAGE SECTION. 01 WS-COMPLEX-PATTERNS. 05 WS-PATTERN-A PIC 9(8) COMP VALUE 305419896. *> 12345678 hex 05 WS-PATTERN-B PIC 9(8) COMP VALUE 2309737967. *> 89ABCDEF hex 05 WS-PATTERN-C PIC 9(8) COMP VALUE 1732584193. *> 67452301 hex 01 WS-COMBINED-RESULT PIC 9(8) COMP. 01 WS-INTERMEDIATE PIC 9(8) COMP. PROCEDURE DIVISION. COMPLEX-BIT-OPERATIONS. *> Multi-step XOR operations COMPUTE WS-INTERMEDIATE = FUNCTION B-EXOR(WS-PATTERN-A, WS-PATTERN-B) COMPUTE WS-COMBINED-RESULT = FUNCTION B-EXOR(WS-INTERMEDIATE, WS-PATTERN-C) *> Equivalent single-step (XOR is associative) COMPUTE WS-INTERMEDIATE = FUNCTION B-EXOR( FUNCTION B-EXOR(WS-PATTERN-A, WS-PATTERN-B), WS-PATTERN-C) DISPLAY "Pattern A: " WS-PATTERN-A DISPLAY "Pattern B: " WS-PATTERN-B DISPLAY "Pattern C: " WS-PATTERN-C DISPLAY "Combined Result: " WS-COMBINED-RESULT.

Best Practices

Recommended Practices

  • Use XOR for encryption, checksums, and unique ID generation
  • Leverage XOR's reversible property for encryption/decryption
  • Document bit patterns and XOR operations clearly
  • Test encryption/decryption thoroughly with various data
  • Use descriptive names for XOR masks and patterns
  • Consider using XOR for simple obfuscation of sensitive data

Common Pitfalls

  • Don't rely on XOR alone for secure encryption in production
  • Remember that XOR encryption is easily breakable with pattern analysis
  • Be careful with key management in XOR encryption systems
  • Test edge cases like zero values and maximum values
  • Consider numeric overflow in large XOR operations

Related COBOL Features

B-AND

Binary AND operations for bit masking

B-OR

Binary OR operations for bit setting

B-NOT

Binary NOT operations for bit inversion

COMPUTE Statement

Arithmetic and logical calculations

Frequently Asked Questions

Q: What's the difference between B-EXOR and B-XOR?

They are identical functions. Both perform exclusive OR operations. The naming difference is purely stylistic.

Q: Is XOR encryption secure for production use?

Simple XOR encryption is not secure for production. It's easily broken and should only be used for basic obfuscation or educational purposes.

Q: Can XOR be used for error detection?

Yes, XOR is commonly used in checksums and parity checking for basic error detection, though it cannot correct errors.

Q: How does XOR help in creating unique IDs?

XOR combines multiple values (timestamp, process ID, sequence) to create unique identifiers with good distribution properties.

Practical Exercises

Exercise 1: Simple Encryption System

Create a simple XOR-based encryption system that can encrypt and decrypt numeric data.

cobol
1
2
3
4
5
6
7
8
* Your task: Complete the encryption/decryption system WORKING-STORAGE SECTION. 01 WS-SECRET-DATA PIC 9(10) VALUE 1234567890. 01 WS-ENCRYPTION-KEY PIC 9(10) VALUE 9876543210. 01 WS-ENCRYPTED-DATA PIC 9(10). 01 WS-DECRYPTED-DATA PIC 9(10). * Implement encryption and decryption logic here

Exercise 2: Data Integrity Checker

Build a system that uses XOR to create checksums for data integrity verification.

Summary

The COBOL B-EXOR (B-XOR) function is a versatile tool for binary manipulation, offering unique properties that make it ideal for encryption, data integrity checking, bit toggling, and unique identifier generation. Its reversible nature makes it particularly valuable for encryption/decryption operations, while its mathematical properties enable efficient checksum calculations and data verification. Understanding XOR operations opens up possibilities for sophisticated bit manipulation and data processing tasks. While simple XOR encryption isn't suitable for high-security applications, it remains an excellent tool for basic data obfuscation, integrity checking, and binary arithmetic operations in COBOL programs.