MainframeMaster

COBOL Tutorial

COBOL B-AND - Binary AND Operations

The B-AND function in COBOL performs binary (bitwise) AND operations on numeric data items. It enables low-level bit manipulation and logical operations essential for system programming, data masking, and binary arithmetic operations.

Key Purpose

B-AND performs bitwise AND operations where each bit in the result is 1 only when corresponding bits in both operands are 1, enabling precise bit-level control and data manipulation.

Basic Syntax

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

Fundamental Concepts

1. Binary AND Truth Table

The binary AND operation follows this logic for each bit position:

Bit ABit BA AND B
000
010
100
111
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-AND-DEMO. COMPUTE WS-RESULT = FUNCTION B-AND(WS-VALUE-A, WS-VALUE-B) *> WS-RESULT = 3 (Binary: 00000011) DISPLAY "Value A: " WS-VALUE-A " (Binary: 00001111)" DISPLAY "Value B: " WS-VALUE-B " (Binary: 00110011)" DISPLAY "Result: " WS-RESULT " (Binary: 00000011)"

2. Basic AND Operations

Simple examples demonstrating B-AND functionality:

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-OPERANDS. 05 WS-OP1 PIC 9(4) COMP VALUE 255. *> 11111111 05 WS-OP2 PIC 9(4) COMP VALUE 170. *> 10101010 05 WS-OP3 PIC 9(4) COMP VALUE 85. *> 01010101 01 WS-RESULTS. 05 WS-RESULT1 PIC 9(4) COMP. 05 WS-RESULT2 PIC 9(4) COMP. 05 WS-RESULT3 PIC 9(4) COMP. PROCEDURE DIVISION. BASIC-AND-OPERATIONS. *> AND with all bits set (255 = 11111111) COMPUTE WS-RESULT1 = FUNCTION B-AND(WS-OP1, WS-OP2) *> Result: 170 (10101010) *> AND with alternating patterns COMPUTE WS-RESULT2 = FUNCTION B-AND(WS-OP2, WS-OP3) *> Result: 0 (00000000) *> AND with same values COMPUTE WS-RESULT3 = FUNCTION B-AND(WS-OP2, WS-OP2) *> Result: 170 (10101010) DISPLAY "255 AND 170 = " WS-RESULT1 DISPLAY "170 AND 85 = " WS-RESULT2 DISPLAY "170 AND 170 = " WS-RESULT3

3. Bit Masking Applications

B-AND is commonly used for bit masking to extract 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
WORKING-STORAGE SECTION. 01 WS-STATUS-BYTE PIC 9(4) COMP VALUE 157. *> 10011101 01 WS-MASKS. 05 WS-MASK-BIT0 PIC 9(4) COMP VALUE 1. *> 00000001 05 WS-MASK-BIT3 PIC 9(4) COMP VALUE 8. *> 00001000 05 WS-MASK-LOW4 PIC 9(4) COMP VALUE 15. *> 00001111 05 WS-MASK-HIGH4 PIC 9(4) COMP VALUE 240. *> 11110000 01 WS-EXTRACTED-BITS. 05 WS-BIT0 PIC 9(4) COMP. 05 WS-BIT3 PIC 9(4) COMP. 05 WS-LOW-NIBBLE PIC 9(4) COMP. 05 WS-HIGH-NIBBLE PIC 9(4) COMP. PROCEDURE DIVISION. BIT-MASKING-DEMO. *> Extract individual bits COMPUTE WS-BIT0 = FUNCTION B-AND(WS-STATUS-BYTE, WS-MASK-BIT0) COMPUTE WS-BIT3 = FUNCTION B-AND(WS-STATUS-BYTE, WS-MASK-BIT3) *> Extract nibbles (4-bit groups) COMPUTE WS-LOW-NIBBLE = FUNCTION B-AND(WS-STATUS-BYTE, WS-MASK-LOW4) COMPUTE WS-HIGH-NIBBLE = FUNCTION B-AND(WS-STATUS-BYTE, WS-MASK-HIGH4) DISPLAY "Original value: " WS-STATUS-BYTE " (Binary: 10011101)" DISPLAY "Bit 0 (LSB): " WS-BIT0 DISPLAY "Bit 3: " WS-BIT3 DISPLAY "Low nibble: " WS-LOW-NIBBLE " (Binary: 1101)" DISPLAY "High nibble: " WS-HIGH-NIBBLE " (Binary: 10010000)"

Advanced Applications

1. Flag Testing and Processing

Using B-AND to test multiple flags in a status byte:

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
WORKING-STORAGE SECTION. 01 WS-SYSTEM-FLAGS PIC 9(4) COMP. 01 WS-FLAG-DEFINITIONS. 05 WS-ACTIVE-FLAG PIC 9(4) COMP VALUE 1. *> Bit 0 05 WS-ERROR-FLAG PIC 9(4) COMP VALUE 2. *> Bit 1 05 WS-READY-FLAG PIC 9(4) COMP VALUE 4. *> Bit 2 05 WS-BUSY-FLAG PIC 9(4) COMP VALUE 8. *> Bit 3 05 WS-DEBUG-FLAG PIC 9(4) COMP VALUE 16. *> Bit 4 01 WS-FLAG-TESTS. 05 WS-IS-ACTIVE PIC 9(4) COMP. 05 WS-HAS-ERROR PIC 9(4) COMP. 05 WS-IS-READY PIC 9(4) COMP. 05 WS-IS-BUSY PIC 9(4) COMP. 05 WS-DEBUG-ON PIC 9(4) COMP. PROCEDURE DIVISION. FLAG-PROCESSING. MOVE 23 TO WS-SYSTEM-FLAGS *> Binary: 00010111 *> Test individual flags COMPUTE WS-IS-ACTIVE = FUNCTION B-AND(WS-SYSTEM-FLAGS, WS-ACTIVE-FLAG) COMPUTE WS-HAS-ERROR = FUNCTION B-AND(WS-SYSTEM-FLAGS, WS-ERROR-FLAG) COMPUTE WS-IS-READY = FUNCTION B-AND(WS-SYSTEM-FLAGS, WS-READY-FLAG) COMPUTE WS-IS-BUSY = FUNCTION B-AND(WS-SYSTEM-FLAGS, WS-BUSY-FLAG) COMPUTE WS-DEBUG-ON = FUNCTION B-AND(WS-SYSTEM-FLAGS, WS-DEBUG-FLAG) IF WS-IS-ACTIVE > 0 DISPLAY "System is ACTIVE" END-IF IF WS-HAS-ERROR > 0 DISPLAY "ERROR condition detected" PERFORM ERROR-HANDLING END-IF IF WS-IS-READY > 0 AND WS-IS-BUSY = 0 DISPLAY "System is READY for processing" PERFORM START-PROCESSING END-IF IF WS-DEBUG-ON > 0 DISPLAY "Debug mode enabled" PERFORM DEBUG-OUTPUT END-IF.

2. Data Validation and Filtering

Using B-AND 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
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
WORKING-STORAGE SECTION. 01 WS-PERMISSION-BYTE PIC 9(4) COMP. 01 WS-PERMISSIONS. 05 WS-READ-PERM PIC 9(4) COMP VALUE 1. *> 00000001 05 WS-WRITE-PERM PIC 9(4) COMP VALUE 2. *> 00000010 05 WS-EXECUTE-PERM PIC 9(4) COMP VALUE 4. *> 00000100 05 WS-DELETE-PERM PIC 9(4) COMP VALUE 8. *> 00001000 05 WS-ADMIN-PERM PIC 9(4) COMP VALUE 16. *> 00010000 01 WS-ACCESS-TESTS. 05 WS-CAN-READ PIC 9(4) COMP. 05 WS-CAN-WRITE PIC 9(4) COMP. 05 WS-CAN-EXECUTE PIC 9(4) COMP. 05 WS-CAN-DELETE PIC 9(4) COMP. 05 WS-IS-ADMIN PIC 9(4) COMP. 01 WS-OPERATION PIC X(10). PROCEDURE DIVISION. PERMISSION-CHECK. *> Set user permissions (Read + Write + Execute = 7) MOVE 7 TO WS-PERMISSION-BYTE ACCEPT WS-OPERATION EVALUATE WS-OPERATION WHEN 'READ' COMPUTE WS-CAN-READ = FUNCTION B-AND(WS-PERMISSION-BYTE, WS-READ-PERM) IF WS-CAN-READ > 0 PERFORM READ-OPERATION ELSE DISPLAY "Access denied: No read permission" END-IF WHEN 'write' COMPUTE WS-CAN-WRITE = FUNCTION B-AND(WS-PERMISSION-BYTE, WS-WRITE-PERM) IF WS-CAN-WRITE > 0 PERFORM WRITE-OPERATION ELSE DISPLAY "Access denied: No write permission" END-IF WHEN 'delete' COMPUTE WS-CAN-DELETE = FUNCTION B-AND(WS-PERMISSION-BYTE, WS-DELETE-PERM) IF WS-CAN-DELETE > 0 PERFORM DELETE-OPERATION ELSE DISPLAY "Access denied: No delete permission" END-IF END-EVALUATE.

3. Data Encryption and Scrambling

B-AND in simple encryption and data scrambling 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
WORKING-STORAGE SECTION. 01 WS-ENCRYPTION-KEY PIC 9(8) COMP VALUE 85. *> 01010101 01 WS-DATA-BYTE PIC 9(4) COMP. 01 WS-ENCRYPTED-BYTE PIC 9(4) COMP. 01 WS-DECRYPTED-BYTE PIC 9(4) COMP. 01 WS-COUNTER PIC 9(4) COMP. 01 WS-DATA-TABLE. 05 WS-DATA-ITEM PIC 9(4) COMP OCCURS 10 TIMES. 01 WS-ENCRYPTED-TABLE. 05 WS-ENC-ITEM PIC 9(4) COMP OCCURS 10 TIMES. PROCEDURE DIVISION. ENCRYPTION-DEMO. *> Initialize sample data PERFORM VARYING WS-COUNTER FROM 1 BY 1 UNTIL WS-COUNTER > 10 COMPUTE WS-DATA-ITEM(WS-COUNTER) = WS-COUNTER * 17 END-PERFORM *> Simple encryption using AND operation PERFORM VARYING WS-COUNTER FROM 1 BY 1 UNTIL WS-COUNTER > 10 COMPUTE WS-ENC-ITEM(WS-COUNTER) = FUNCTION B-AND(WS-DATA-ITEM(WS-COUNTER), WS-ENCRYPTION-KEY) DISPLAY "Original: " WS-DATA-ITEM(WS-COUNTER) " Encrypted: " WS-ENC-ITEM(WS-COUNTER) END-PERFORM.

Performance and Optimization

1. Efficient Bit Operations

Optimizing B-AND operations for performance:

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
WORKING-STORAGE SECTION. 01 WS-OPTIMIZED-MASKS. 05 WS-SINGLE-BITS. 10 WS-BIT-0 PIC 9(4) COMP VALUE 1. 10 WS-BIT-1 PIC 9(4) COMP VALUE 2. 10 WS-BIT-2 PIC 9(4) COMP VALUE 4. 10 WS-BIT-3 PIC 9(4) COMP VALUE 8. 05 WS-MULTI-BITS. 10 WS-LOWER-4 PIC 9(4) COMP VALUE 15. *> 00001111 10 WS-UPPER-4 PIC 9(4) COMP VALUE 240. *> 11110000 10 WS-EVEN-BITS PIC 9(4) COMP VALUE 170. *> 10101010 10 WS-ODD-BITS PIC 9(4) COMP VALUE 85. *> 01010101 01 WS-INPUT-VALUE PIC 9(4) COMP. 01 WS-PROCESSED-VALUE PIC 9(4) COMP. PROCEDURE DIVISION. OPTIMIZED-PROCESSING. *> Use precomputed masks for common operations COMPUTE WS-PROCESSED-VALUE = FUNCTION B-AND(WS-INPUT-VALUE, WS-LOWER-4) *> Process multiple values efficiently PERFORM VARYING WS-INPUT-VALUE FROM 0 BY 1 UNTIL WS-INPUT-VALUE > 255 IF FUNCTION B-AND(WS-INPUT-VALUE, WS-EVEN-BITS) > 0 PERFORM PROCESS-EVEN-BITS END-IF IF FUNCTION B-AND(WS-INPUT-VALUE, WS-ODD-BITS) > 0 PERFORM PROCESS-ODD-BITS END-IF END-PERFORM.

2. Combining with Other Binary Functions

Using B-AND with other binary functions for complex 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-VALUE1 PIC 9(8) COMP VALUE 204. *> 11001100 01 WS-VALUE2 PIC 9(8) COMP VALUE 170. *> 10101010 01 WS-MASK PIC 9(8) COMP VALUE 15. *> 00001111 01 WS-COMPLEX-RESULT PIC 9(8) COMP. 01 WS-TEMP-RESULT PIC 9(8) COMP. PROCEDURE DIVISION. COMPLEX-BINARY-OPS. *> Combine AND with OR operations COMPUTE WS-TEMP-RESULT = FUNCTION B-AND(WS-VALUE1, WS-MASK) COMPUTE WS-COMPLEX-RESULT = FUNCTION B-OR(WS-TEMP-RESULT, WS-VALUE2) *> Combine AND with XOR operations COMPUTE WS-TEMP-RESULT = FUNCTION B-AND(WS-VALUE1, WS-VALUE2) COMPUTE WS-COMPLEX-RESULT = FUNCTION B-XOR(WS-TEMP-RESULT, WS-MASK) *> Use AND for conditional bit clearing COMPUTE WS-COMPLEX-RESULT = FUNCTION B-AND(WS-VALUE1, FUNCTION B-NOT(WS-MASK)) DISPLAY "Complex operation result: " WS-COMPLEX-RESULT.

Best Practices

Recommended Practices

  • Use descriptive names for bit masks and flag constants
  • Document the bit patterns and their meanings
  • Precompute common masks for better performance
  • Use B-AND for extracting specific bit patterns
  • Combine with other binary functions for complex operations
  • Test thoroughly with various bit patterns

Common Pitfalls

  • Avoid confusion between logical AND and bitwise AND operations
  • Don't assume specific bit ordering across different systems
  • Be careful with signed vs unsigned interpretations
  • Test edge cases like all zeros and all ones
  • Consider numeric item size limitations

Related COBOL Features

B-OR

Binary OR operations for bit setting

B-XOR

Binary XOR operations for bit toggling

B-NOT

Binary NOT operations for bit inversion

COMP Fields

Binary data storage for efficient operations

Frequently Asked Questions

Q: When should I use B-AND instead of logical AND?

Use B-AND for bit-level operations, flag testing, and data masking. Use logical AND for conditional logic and program flow control.

Q: Can B-AND work with negative numbers?

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

Q: What's the maximum size for B-AND operands?

B-AND operands are limited by the numeric item size supported by your COBOL implementation, typically up to 18 digits.

Q: How does B-AND handle different sized operands?

COBOL typically promotes smaller operands to match the larger operand size, padding with zeros on the left.

Practical Exercises

Exercise 1: Flag Management System

Create a system that uses B-AND to manage user permission flags for a file system.

cobol
1
2
3
4
5
6
7
* Your task: Implement permission checking WORKING-STORAGE SECTION. 01 WS-USER-PERMISSIONS PIC 9(4) COMP VALUE 13. *> Binary: 1101 01 WS-REQUIRED-PERM PIC 9(4) COMP. 01 WS-ACCESS-GRANTED PIC X VALUE 'N'. * Define permission constants and implement checking logic

Exercise 2: Data Filtering

Use B-AND to extract specific bits from a status byte and determine system state.

Summary

The COBOL B-AND function is an essential tool for binary and bitwise operations, enabling precise bit-level manipulation and control. It's particularly valuable for flag testing, data masking, permission checking, and low-level data processing tasks. Understanding B-AND operations opens up possibilities for efficient system programming, data validation, and binary arithmetic operations. When combined with other binary functions like B-OR, B-XOR, and B-NOT, B-AND provides a complete toolkit for sophisticated bit manipulation in COBOL applications, making it an indispensable function for systems-level programming and data processing tasks.