MainframeMaster

COBOL Tutorial

COBOL B-NOT - Binary NOT Operations

The B-NOT function in COBOL performs binary (bitwise) NOT operations on numeric data items, inverting each bit in the operand. It's essential for creating complement values, inverting bit patterns, and implementing logical negation in binary operations.

Key Purpose

B-NOT inverts every bit in the operand, changing 0s to 1s and 1s to 0s, creating the one's complement of the value. This is useful for bit manipulation, creating inverse masks, and logical operations.

Basic Syntax

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

Fundamental Concepts

1. Binary NOT Truth Table

The binary NOT operation follows this simple logic for each bit:

Input BitNOT Output
01
10
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
WORKING-STORAGE SECTION. 01 WS-ORIGINAL-VALUE PIC 9(8) COMP VALUE 15. *> Binary: 00001111 01 WS-INVERTED-VALUE PIC 9(8) COMP. PROCEDURE DIVISION. BINARY-NOT-DEMO. COMPUTE WS-INVERTED-VALUE = FUNCTION B-NOT(WS-ORIGINAL-VALUE) DISPLAY "Original: " WS-ORIGINAL-VALUE " (Binary: 00001111)" DISPLAY "Inverted: " WS-INVERTED-VALUE " (Binary: 11110000)" *> Note: Actual result depends on the numeric field size *> For 8-bit: 15 (00001111) becomes 240 (11110000)

2. One's Complement Operation

B-NOT creates the one's complement by inverting all bits:

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
WORKING-STORAGE SECTION. 01 WS-TEST-VALUES. 05 WS-VALUE-1 PIC 9(4) COMP VALUE 0. *> 00000000 05 WS-VALUE-2 PIC 9(4) COMP VALUE 255. *> 11111111 05 WS-VALUE-3 PIC 9(4) COMP VALUE 170. *> 10101010 05 WS-VALUE-4 PIC 9(4) COMP VALUE 85. *> 01010101 01 WS-COMPLEMENT-VALUES. 05 WS-COMP-1 PIC 9(4) COMP. 05 WS-COMP-2 PIC 9(4) COMP. 05 WS-COMP-3 PIC 9(4) COMP. 05 WS-COMP-4 PIC 9(4) COMP. PROCEDURE DIVISION. ONES-COMPLEMENT-DEMO. COMPUTE WS-COMP-1 = FUNCTION B-NOT(WS-VALUE-1) *> 255 (11111111) COMPUTE WS-COMP-2 = FUNCTION B-NOT(WS-VALUE-2) *> 0 (00000000) COMPUTE WS-COMP-3 = FUNCTION B-NOT(WS-VALUE-3) *> 85 (01010101) COMPUTE WS-COMP-4 = FUNCTION B-NOT(WS-VALUE-4) *> 170 (10101010) DISPLAY "NOT(0) = " WS-COMP-1 DISPLAY "NOT(255) = " WS-COMP-2 DISPLAY "NOT(170) = " WS-COMP-3 DISPLAY "NOT(85) = " WS-COMP-4 *> Verify double negation property: NOT(NOT(x)) = x COMPUTE WS-TEMP = FUNCTION B-NOT(WS-COMP-3) DISPLAY "NOT(NOT(170)) = " WS-TEMP " (Should be 170)"

3. Creating Inverse Masks

B-NOT is commonly used to create inverse bit masks for clearing specific bits:

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
WORKING-STORAGE SECTION. 01 WS-BIT-MASKS. 05 WS-MASK-BIT-0 PIC 9(4) COMP VALUE 1. *> 00000001 05 WS-MASK-BIT-3 PIC 9(4) COMP VALUE 8. *> 00001000 05 WS-MASK-LOWER-4 PIC 9(4) COMP VALUE 15. *> 00001111 05 WS-MASK-UPPER-4 PIC 9(4) COMP VALUE 240. *> 11110000 01 WS-INVERSE-MASKS. 05 WS-INV-BIT-0 PIC 9(4) COMP. 05 WS-INV-BIT-3 PIC 9(4) COMP. 05 WS-INV-LOWER-4 PIC 9(4) COMP. 05 WS-INV-UPPER-4 PIC 9(4) COMP. 01 WS-TARGET-VALUE PIC 9(4) COMP VALUE 255. *> 11111111 01 WS-CLEARED-VALUE PIC 9(4) COMP. PROCEDURE DIVISION. INVERSE-MASK-DEMO. *> Create inverse masks COMPUTE WS-INV-BIT-0 = FUNCTION B-NOT(WS-MASK-BIT-0) *> 11111110 COMPUTE WS-INV-BIT-3 = FUNCTION B-NOT(WS-MASK-BIT-3) *> 11110111 COMPUTE WS-INV-LOWER-4 = FUNCTION B-NOT(WS-MASK-LOWER-4) *> 11110000 COMPUTE WS-INV-UPPER-4 = FUNCTION B-NOT(WS-MASK-UPPER-4) *> 00001111 DISPLAY "Original value: " WS-TARGET-VALUE " (11111111)" *> Clear specific bits using inverse masks with AND COMPUTE WS-CLEARED-VALUE = FUNCTION B-AND(WS-TARGET-VALUE, WS-INV-BIT-0) DISPLAY "Clear bit 0: " WS-CLEARED-VALUE " (11111110)" COMPUTE WS-CLEARED-VALUE = FUNCTION B-AND(WS-TARGET-VALUE, WS-INV-LOWER-4) DISPLAY "Clear lower 4 bits: " WS-CLEARED-VALUE " (11110000)"

Advanced Applications

1. Bit Field Manipulation

Using B-NOT for sophisticated bit field 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
26
27
28
29
30
31
32
33
34
35
36
37
38
WORKING-STORAGE SECTION. 01 WS-STATUS-REGISTER PIC 9(4) COMP VALUE 187. *> 10111011 01 WS-BIT-OPERATIONS. 05 WS-SET-MASK PIC 9(4) COMP VALUE 4. *> 00000100 05 WS-CLEAR-MASK PIC 9(4) COMP VALUE 8. *> 00001000 05 WS-TOGGLE-MASK PIC 9(4) COMP VALUE 16. *> 00010000 01 WS-RESULT-VALUES. 05 WS-AFTER-SET PIC 9(4) COMP. 05 WS-AFTER-CLEAR PIC 9(4) COMP. 05 WS-AFTER-TOGGLE PIC 9(4) COMP. PROCEDURE DIVISION. BIT-FIELD-MANIPULATION. DISPLAY "Original status: " WS-STATUS-REGISTER " (10111011)" *> Set a bit (bit 2) COMPUTE WS-AFTER-SET = FUNCTION B-OR(WS-STATUS-REGISTER, WS-SET-MASK) DISPLAY "After set bit 2: " WS-AFTER-SET " (10111111)" *> Clear a bit (bit 3) using NOT to create inverse mask COMPUTE WS-AFTER-CLEAR = FUNCTION B-AND(WS-STATUS-REGISTER, FUNCTION B-NOT(WS-CLEAR-MASK)) DISPLAY "After clear bit 3: " WS-AFTER-CLEAR " (10110011)" *> Toggle a bit (bit 4) COMPUTE WS-AFTER-TOGGLE = FUNCTION B-XOR(WS-STATUS-REGISTER, WS-TOGGLE-MASK) DISPLAY "After toggle bit 4: " WS-AFTER-TOGGLE " (10101011)" *> Complex operation: Clear multiple bits COMPUTE WS-RESULT = FUNCTION B-AND(WS-STATUS-REGISTER, FUNCTION B-NOT( FUNCTION B-OR(WS-CLEAR-MASK, WS-SET-MASK))) DISPLAY "After clear bits 2&3: " WS-RESULT.

2. Data Validation and Filtering

Using B-NOT for data validation and filtering 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
26
27
28
29
30
31
WORKING-STORAGE SECTION. 01 WS-DATA-FILTER. 05 WS-INCLUDE-MASK PIC 9(8) COMP VALUE 65535. *> 00001111 11111111 05 WS-EXCLUDE-MASK PIC 9(8) COMP VALUE 240. *> 11110000 05 WS-FILTER-MASK PIC 9(8) COMP. 01 WS-INPUT-DATA PIC 9(8) COMP. 01 WS-FILTERED-DATA PIC 9(8) COMP. 01 WS-COUNTER PIC 9(3) COMP. 01 WS-TEST-DATA. 05 WS-DATA-ITEM PIC 9(8) COMP OCCURS 5 TIMES VALUE 123, 456, 789, 1011, 1213. PROCEDURE DIVISION. DATA-FILTERING. *> Create filter mask: include certain bits, exclude others COMPUTE WS-FILTER-MASK = FUNCTION B-AND(WS-INCLUDE-MASK, FUNCTION B-NOT(WS-EXCLUDE-MASK)) DISPLAY "Filter mask: " WS-FILTER-MASK *> Apply filter to each data item PERFORM VARYING WS-COUNTER FROM 1 BY 1 UNTIL WS-COUNTER > 5 COMPUTE WS-FILTERED-DATA = FUNCTION B-AND(WS-DATA-ITEM(WS-COUNTER), WS-FILTER-MASK) DISPLAY "Original: " WS-DATA-ITEM(WS-COUNTER) " Filtered: " WS-FILTERED-DATA END-PERFORM.

3. Error Detection and Correction

Using B-NOT in error detection and simple correction algorithms:

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
WORKING-STORAGE SECTION. 01 WS-ERROR-DETECTION. 05 WS-DATA-WORD PIC 9(8) COMP VALUE 123456. 05 WS-PARITY-MASK PIC 9(8) COMP VALUE 1. *> 00000001 05 WS-ERROR-MASK PIC 9(8) COMP VALUE 2. *> 00000010 01 WS-ERROR-PROCESSING. 05 WS-TRANSMITTED PIC 9(8) COMP. 05 WS-RECEIVED PIC 9(8) COMP. 05 WS-ERROR-BITS PIC 9(8) COMP. 05 WS-CORRECTED PIC 9(8) COMP. PROCEDURE DIVISION. ERROR-DETECTION-DEMO. *> Simulate transmission with parity MOVE WS-DATA-WORD TO WS-TRANSMITTED *> Add parity bit (even parity) IF FUNCTION MOD(FUNCTION B-AND(WS-TRANSMITTED, 255), 2) = 1 COMPUTE WS-TRANSMITTED = FUNCTION B-OR(WS-TRANSMITTED, WS-PARITY-MASK) END-IF DISPLAY "Transmitted: " WS-TRANSMITTED *> Simulate error during transmission COMPUTE WS-RECEIVED = FUNCTION B-XOR(WS-TRANSMITTED, WS-ERROR-MASK) DISPLAY "Received (with error): " WS-RECEIVED *> Detect error by checking parity COMPUTE WS-ERROR-BITS = FUNCTION B-XOR(WS-TRANSMITTED, WS-RECEIVED) IF WS-ERROR-BITS > 0 DISPLAY "Error detected in bits: " WS-ERROR-BITS *> Simple correction: flip back the error bit COMPUTE WS-CORRECTED = FUNCTION B-XOR(WS-RECEIVED, WS-ERROR-BITS) DISPLAY "Corrected data: " WS-CORRECTED ELSE DISPLAY "No errors detected" END-IF.

Performance and Optimization

1. Efficient NOT Operations

Optimizing B-NOT 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
WORKING-STORAGE SECTION. 01 WS-OPTIMIZATION. 05 WS-COMMON-MASKS. 10 WS-ALL-ONES PIC 9(8) COMP VALUE 4294967295. *> 32-bit all 1s 10 WS-BYTE-MASK PIC 9(8) COMP VALUE 255. *> 8-bit all 1s 05 WS-BATCH-DATA PIC 9(8) COMP OCCURS 100 TIMES. 05 WS-BATCH-INDEX PIC 9(3) COMP. PROCEDURE DIVISION. OPTIMIZED-NOT-OPERATIONS. *> Initialize test data PERFORM VARYING WS-BATCH-INDEX FROM 1 BY 1 UNTIL WS-BATCH-INDEX > 100 COMPUTE WS-BATCH-DATA(WS-BATCH-INDEX) = WS-BATCH-INDEX * 12345 END-PERFORM *> Efficient batch inversion PERFORM VARYING WS-BATCH-INDEX FROM 1 BY 1 UNTIL WS-BATCH-INDEX > 100 COMPUTE WS-BATCH-DATA(WS-BATCH-INDEX) = FUNCTION B-NOT(WS-BATCH-DATA(WS-BATCH-INDEX)) END-PERFORM DISPLAY "Processed " WS-BATCH-INDEX " NOT operations".

2. Combining NOT with Other Operations

Efficient combinations of B-NOT with other binary functions:

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
WORKING-STORAGE SECTION. 01 WS-COMPLEX-OPS. 05 WS-VALUE-A PIC 9(8) COMP VALUE 170. *> 10101010 05 WS-VALUE-B PIC 9(8) COMP VALUE 204. *> 11001100 05 WS-MASK PIC 9(8) COMP VALUE 15. *> 00001111 01 WS-RESULTS. 05 WS-NAND-RESULT PIC 9(8) COMP. 05 WS-NOR-RESULT PIC 9(8) COMP. 05 WS-COMPLEX-1 PIC 9(8) COMP. 05 WS-COMPLEX-2 PIC 9(8) COMP. PROCEDURE DIVISION. COMPLEX-NOT-OPERATIONS. *> NAND operation: NOT(A AND B) COMPUTE WS-NAND-RESULT = FUNCTION B-NOT(FUNCTION B-AND(WS-VALUE-A, WS-VALUE-B)) *> NOR operation: NOT(A OR B) COMPUTE WS-NOR-RESULT = FUNCTION B-NOT(FUNCTION B-OR(WS-VALUE-A, WS-VALUE-B)) *> Complex operation: (NOT A) AND (B OR mask) COMPUTE WS-COMPLEX-1 = FUNCTION B-AND( FUNCTION B-NOT(WS-VALUE-A), FUNCTION B-OR(WS-VALUE-B, WS-MASK)) *> Another complex operation: NOT((A XOR B) AND mask) COMPUTE WS-COMPLEX-2 = FUNCTION B-NOT( FUNCTION B-AND( FUNCTION B-XOR(WS-VALUE-A, WS-VALUE-B), WS-MASK)) DISPLAY "NAND result: " WS-NAND-RESULT DISPLAY "NOR result: " WS-NOR-RESULT DISPLAY "Complex 1: " WS-COMPLEX-1 DISPLAY "Complex 2: " WS-COMPLEX-2.

Best Practices

Recommended Practices

  • Use B-NOT to create inverse masks for bit clearing operations
  • Combine with B-AND to clear specific bits efficiently
  • Document the purpose and expected bit patterns clearly
  • Test with various input values including edge cases
  • Use descriptive names for inverted masks and values
  • Consider the data size when working with NOT operations

Common Pitfalls

  • Remember that NOT results depend on the field size
  • Be careful with signed vs unsigned interpretations
  • Test double negation properties: NOT(NOT(x)) should equal x
  • Consider overflow issues with large numeric fields
  • Don't confuse bitwise NOT with logical NOT operations

Related COBOL Features

B-AND

Binary AND operations for bit masking

B-OR

Binary OR operations for bit setting

B-XOR

Binary XOR operations for bit toggling

COMP Fields

Binary data storage for efficient operations

Frequently Asked Questions

Q: How does field size affect B-NOT results?

B-NOT inverts all bits within the field size. A PIC 9(4) COMP field will invert 16 bits, while PIC 9(8) COMP inverts 32 bits.

Q: Can B-NOT work with negative numbers?

Yes, B-NOT works with the binary representation of numbers, including negative numbers in two's complement format.

Q: What's the difference between B-NOT and logical NOT?

B-NOT inverts individual bits, while logical NOT operates on true/false conditions. Use B-NOT for bit manipulation, logical NOT for program logic.

Q: Is NOT(NOT(x)) always equal to x?

Yes, double negation with B-NOT always returns the original value, as inverting bits twice restores the original pattern.

Practical Exercises

Exercise 1: Bit Clearing System

Create a system that uses B-NOT to clear specific bits in a status register.

cobol
1
2
3
4
5
6
7
* Your task: Implement bit clearing using B-NOT WORKING-STORAGE SECTION. 01 WS-STATUS-REGISTER PIC 9(4) COMP VALUE 255. *> All bits set 01 WS-CLEAR-BIT-2 PIC 9(4) COMP VALUE 4. *> 00000100 01 WS-CLEARED-STATUS PIC 9(4) COMP. * Use B-NOT to create inverse mask and clear the bit

Exercise 2: Data Complement Calculator

Build a program that calculates one's complement of various numeric values and verifies the double negation property.

Summary

The COBOL B-NOT function is an essential tool for binary manipulation, providing the ability to invert bit patterns and create complement values. It's particularly valuable for creating inverse masks used in bit clearing operations, implementing logical negation at the bit level, and supporting error detection algorithms. Understanding B-NOT operations enables sophisticated bit manipulation techniques when combined with other binary functions like B-AND, B-OR, and B-XOR. The function's simplicity belies its power in system programming tasks, data validation, and low-level operations where precise bit control is required. Mastering B-NOT is essential for any COBOL programmer working with binary data, system interfaces, or applications requiring detailed bit-level manipulation.