MainframeMaster

COBOL Tutorial

COBOL B-OR - Binary OR Operations

The B-OR function in COBOL performs binary (bitwise) OR operations on numeric data items. It's essential for setting specific bits, combining flags, creating bit patterns, and implementing logical combinations in binary operations.

Key Purpose

B-OR performs inclusive OR operations where each result bit is 1 when at least one corresponding bit in the operands is 1, making it perfect for setting bits and combining flags.

Basic Syntax

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

Fundamental Concepts

1. Binary OR Truth Table

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

Bit ABit BA OR B
000
011
101
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-OR-DEMO. COMPUTE WS-RESULT = FUNCTION B-OR(WS-VALUE-A, WS-VALUE-B) *> WS-RESULT = 63 (Binary: 00111111) DISPLAY "Value A: " WS-VALUE-A " (Binary: 00001111)" DISPLAY "Value B: " WS-VALUE-B " (Binary: 00110011)" DISPLAY "Result: " WS-RESULT " (Binary: 00111111)"

2. Bit Setting Operations

B-OR is perfect for setting specific bits while preserving others:

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
WORKING-STORAGE SECTION. 01 WS-STATUS-FLAGS PIC 9(4) COMP VALUE 0. *> 00000000 01 WS-BIT-MASKS. 05 WS-SET-BIT-0 PIC 9(4) COMP VALUE 1. *> 00000001 05 WS-SET-BIT-3 PIC 9(4) COMP VALUE 8. *> 00001000 05 WS-SET-BITS-04 PIC 9(4) COMP VALUE 17. *> 00010001 05 WS-SET-UPPER-4 PIC 9(4) COMP VALUE 240. *> 11110000 01 WS-UPDATED-FLAGS PIC 9(4) COMP. PROCEDURE DIVISION. BIT-SETTING-DEMO. DISPLAY "Initial flags: " WS-STATUS-FLAGS " (Binary: 00000000)" *> Set bit 0 (rightmost bit) COMPUTE WS-UPDATED-FLAGS = FUNCTION B-OR(WS-STATUS-FLAGS, WS-SET-BIT-0) DISPLAY "Set bit 0: " WS-UPDATED-FLAGS " (Binary: 00000001)" MOVE WS-UPDATED-FLAGS TO WS-STATUS-FLAGS *> Set bit 3 COMPUTE WS-UPDATED-FLAGS = FUNCTION B-OR(WS-STATUS-FLAGS, WS-SET-BIT-3) DISPLAY "Set bit 3: " WS-UPDATED-FLAGS " (Binary: 00001001)" MOVE WS-UPDATED-FLAGS TO WS-STATUS-FLAGS *> Set multiple bits at once (bits 0 and 4) COMPUTE WS-UPDATED-FLAGS = FUNCTION B-OR(WS-STATUS-FLAGS, WS-SET-BITS-04) DISPLAY "Set bits 0&4: " WS-UPDATED-FLAGS " (Binary: 00011001)"

3. Flag Combination Operations

Combining multiple flag values using B-OR:

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-PERMISSION-FLAGS. 05 WS-READ-FLAG PIC 9(4) COMP VALUE 1. *> 00000001 05 WS-WRITE-FLAG PIC 9(4) COMP VALUE 2. *> 00000010 05 WS-EXECUTE-FLAG PIC 9(4) COMP VALUE 4. *> 00000100 05 WS-DELETE-FLAG PIC 9(4) COMP VALUE 8. *> 00001000 05 WS-ADMIN-FLAG PIC 9(4) COMP VALUE 16. *> 00010000 01 WS-USER-PERMISSIONS PIC 9(4) COMP VALUE 0. 01 WS-TEMP-PERMISSIONS PIC 9(4) COMP. PROCEDURE DIVISION. FLAG-COMBINATION-DEMO. *> Grant basic user permissions (read + write) COMPUTE WS-TEMP-PERMISSIONS = FUNCTION B-OR(WS-READ-FLAG, WS-WRITE-FLAG) MOVE WS-TEMP-PERMISSIONS TO WS-USER-PERMISSIONS DISPLAY "Basic user: " WS-USER-PERMISSIONS " (read+write)" *> Add execute permission COMPUTE WS-USER-PERMISSIONS = FUNCTION B-OR(WS-USER-PERMISSIONS, WS-EXECUTE-FLAG) DISPLAY "With execute: " WS-USER-PERMISSIONS " (read+write+execute)" *> Grant admin permissions (all flags) COMPUTE WS-TEMP-PERMISSIONS = FUNCTION B-OR( FUNCTION B-OR( FUNCTION B-OR(WS-READ-FLAG, WS-WRITE-FLAG), FUNCTION B-OR(WS-EXECUTE-FLAG, WS-DELETE-FLAG)), WS-ADMIN-FLAG) DISPLAY "Admin permissions: " WS-TEMP-PERMISSIONS " (all flags)"

Advanced Applications

1. System Status Management

Using B-OR for comprehensive system status tracking:

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-STATUS. 05 WS-CURRENT-STATUS PIC 9(8) COMP VALUE 0. 05 WS-STATUS-CODES. 10 WS-INITIALIZED PIC 9(8) COMP VALUE 1. *> System ready 10 WS-CONNECTED PIC 9(8) COMP VALUE 2. *> Network connected 10 WS-LOGGED-IN PIC 9(8) COMP VALUE 4. *> User authenticated 10 WS-PROCESSING PIC 9(8) COMP VALUE 8. *> Task in progress 10 WS-ERROR PIC 9(8) COMP VALUE 16. *> Error condition 10 WS-WARNING PIC 9(8) COMP VALUE 32. *> Warning condition 10 WS-MAINTENANCE PIC 9(8) COMP VALUE 64. *> Maintenance mode 10 WS-BACKUP PIC 9(8) COMP VALUE 128. *> Backup running PROCEDURE DIVISION. SYSTEM-STATUS-MANAGEMENT. *> Initialize system COMPUTE WS-CURRENT-STATUS = FUNCTION B-OR(WS-CURRENT-STATUS, WS-INITIALIZED) DISPLAY "System initialized: " WS-CURRENT-STATUS *> Connect to network COMPUTE WS-CURRENT-STATUS = FUNCTION B-OR(WS-CURRENT-STATUS, WS-CONNECTED) DISPLAY "Network connected: " WS-CURRENT-STATUS *> User login COMPUTE WS-CURRENT-STATUS = FUNCTION B-OR(WS-CURRENT-STATUS, WS-LOGGED-IN) DISPLAY "User logged in: " WS-CURRENT-STATUS *> Start processing with warning COMPUTE WS-CURRENT-STATUS = FUNCTION B-OR( FUNCTION B-OR(WS-CURRENT-STATUS, WS-PROCESSING), WS-WARNING) DISPLAY "Processing with warning: " WS-CURRENT-STATUS *> Check specific status IF FUNCTION B-AND(WS-CURRENT-STATUS, WS-WARNING) > 0 DISPLAY "Warning condition active" END-IF IF FUNCTION B-AND(WS-CURRENT-STATUS, WS-PROCESSING) > 0 DISPLAY "System is processing" END-IF.

2. Configuration Management

Managing configuration options with B-OR 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
WORKING-STORAGE SECTION. 01 WS-CONFIG-OPTIONS. 05 WS-CURRENT-CONFIG PIC 9(8) COMP VALUE 0. 05 WS-OPTION-FLAGS. 10 WS-LOGGING PIC 9(8) COMP VALUE 1. *> Enable logging 10 WS-DEBUGGING PIC 9(8) COMP VALUE 2. *> Debug mode 10 WS-ENCRYPTION PIC 9(8) COMP VALUE 4. *> Data encryption 10 WS-COMPRESSION PIC 9(8) COMP VALUE 8. *> Data compression 10 WS-CACHING PIC 9(8) COMP VALUE 16. *> Enable caching 10 WS-MONITORING PIC 9(8) COMP VALUE 32. *> Performance monitoring 10 WS-BACKUP-AUTO PIC 9(8) COMP VALUE 64. *> Automatic backup 10 WS-VALIDATION PIC 9(8) COMP VALUE 128. *> Data validation 01 WS-PROFILE-CONFIGS. 05 WS-DEVELOPMENT PIC 9(8) COMP. *> Dev profile 05 WS-PRODUCTION PIC 9(8) COMP. *> Prod profile 05 WS-TESTING PIC 9(8) COMP. *> Test profile PROCEDURE DIVISION. CONFIGURATION-MANAGEMENT. *> Development profile: logging + debugging + monitoring COMPUTE WS-DEVELOPMENT = FUNCTION B-OR( FUNCTION B-OR(WS-LOGGING, WS-DEBUGGING), WS-MONITORING) DISPLAY "Development config: " WS-DEVELOPMENT *> Production profile: encryption + compression + caching + auto-backup COMPUTE WS-PRODUCTION = FUNCTION B-OR( FUNCTION B-OR(WS-ENCRYPTION, WS-COMPRESSION), FUNCTION B-OR(WS-CACHING, WS-BACKUP-AUTO)) DISPLAY "Production config: " WS-PRODUCTION *> Testing profile: logging + validation + monitoring COMPUTE WS-TESTING = FUNCTION B-OR( FUNCTION B-OR(WS-LOGGING, WS-VALIDATION), WS-MONITORING) DISPLAY "Testing config: " WS-TESTING *> Apply production configuration MOVE WS-PRODUCTION TO WS-CURRENT-CONFIG *> Add debugging for troubleshooting COMPUTE WS-CURRENT-CONFIG = FUNCTION B-OR(WS-CURRENT-CONFIG, WS-DEBUGGING) DISPLAY "Production + debug: " WS-CURRENT-CONFIG.

3. Data Merging and Consolidation

Using B-OR for merging data from multiple sources:

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-DATA-SOURCES. 05 WS-SOURCE-A PIC 9(8) COMP VALUE 85. *> 01010101 05 WS-SOURCE-B PIC 9(8) COMP VALUE 170. *> 10101010 05 WS-SOURCE-C PIC 9(8) COMP VALUE 204. *> 11001100 05 WS-SOURCE-D PIC 9(8) COMP VALUE 51. *> 00110011 01 WS-MERGE-RESULTS. 05 WS-MERGED-AB PIC 9(8) COMP. 05 WS-MERGED-CD PIC 9(8) COMP. 05 WS-FINAL-MERGE PIC 9(8) COMP. 01 WS-ARRAY-DATA. 05 WS-DATA-ITEM PIC 9(8) COMP OCCURS 5 TIMES VALUE 15, 51, 85, 119, 153. 01 WS-ACCUMULATED PIC 9(8) COMP VALUE 0. 01 WS-COUNTER PIC 9(3) COMP. PROCEDURE DIVISION. DATA-MERGING-DEMO. *> Merge pairs of sources COMPUTE WS-MERGED-AB = FUNCTION B-OR(WS-SOURCE-A, WS-SOURCE-B) COMPUTE WS-MERGED-CD = FUNCTION B-OR(WS-SOURCE-C, WS-SOURCE-D) DISPLAY "Source A: " WS-SOURCE-A " (01010101)" DISPLAY "Source B: " WS-SOURCE-B " (10101010)" DISPLAY "Merged A+B: " WS-MERGED-AB " (11111111)" DISPLAY "Source C: " WS-SOURCE-C " (11001100)" DISPLAY "Source D: " WS-SOURCE-D " (00110011)" DISPLAY "Merged C+D: " WS-MERGED-CD " (11111111)" *> Final merge of all sources COMPUTE WS-FINAL-MERGE = FUNCTION B-OR(WS-MERGED-AB, WS-MERGED-CD) DISPLAY "Final merge: " WS-FINAL-MERGE *> Accumulate array data using OR PERFORM VARYING WS-COUNTER FROM 1 BY 1 UNTIL WS-COUNTER > 5 COMPUTE WS-ACCUMULATED = FUNCTION B-OR(WS-ACCUMULATED, WS-DATA-ITEM(WS-COUNTER)) DISPLAY "Step " WS-COUNTER ": " WS-ACCUMULATED END-PERFORM DISPLAY "Final accumulated value: " WS-ACCUMULATED.

Performance and Optimization

1. Efficient OR Operations

Optimizing B-OR 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
26
27
WORKING-STORAGE SECTION. 01 WS-PERFORMANCE-TEST. 05 WS-BATCH-SIZE PIC 9(4) COMP VALUE 1000. 05 WS-BATCH-DATA PIC 9(8) COMP OCCURS 1000 TIMES. 05 WS-OR-MASK PIC 9(8) COMP VALUE 15. *> 00001111 05 WS-BATCH-INDEX PIC 9(4) COMP. 01 WS-OPTIMIZATION. 05 WS-TEMP-RESULT PIC 9(8) COMP. 05 WS-COMBINED-MASK PIC 9(8) COMP. PROCEDURE DIVISION. PERFORMANCE-OPTIMIZATION. *> Initialize test data PERFORM VARYING WS-BATCH-INDEX FROM 1 BY 1 UNTIL WS-BATCH-INDEX > WS-BATCH-SIZE COMPUTE WS-BATCH-DATA(WS-BATCH-INDEX) = WS-BATCH-INDEX * 17 END-PERFORM *> Efficient batch OR processing PERFORM VARYING WS-BATCH-INDEX FROM 1 BY 1 UNTIL WS-BATCH-INDEX > WS-BATCH-SIZE COMPUTE WS-BATCH-DATA(WS-BATCH-INDEX) = FUNCTION B-OR(WS-BATCH-DATA(WS-BATCH-INDEX), WS-OR-MASK) END-PERFORM DISPLAY "Processed " WS-BATCH-SIZE " OR operations efficiently".

2. Complex Bit Patterns

Working with complex bit patterns and multiple OR 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
WORKING-STORAGE SECTION. 01 WS-COMPLEX-PATTERNS. 05 WS-BASE-PATTERN PIC 9(8) COMP VALUE 0. 05 WS-PATTERN-1 PIC 9(8) COMP VALUE 15. *> 00001111 05 WS-PATTERN-2 PIC 9(8) COMP VALUE 240. *> 11110000 05 WS-PATTERN-3 PIC 9(8) COMP VALUE 85. *> 01010101 05 WS-PATTERN-4 PIC 9(8) COMP VALUE 170. *> 10101010 01 WS-LAYERED-RESULT PIC 9(8) COMP. 01 WS-STEP-COUNTER PIC 9(2) COMP. PROCEDURE DIVISION. COMPLEX-BIT-OPERATIONS. MOVE WS-BASE-PATTERN TO WS-LAYERED-RESULT *> Build complex pattern layer by layer MOVE 1 TO WS-STEP-COUNTER COMPUTE WS-LAYERED-RESULT = FUNCTION B-OR(WS-LAYERED-RESULT, WS-PATTERN-1) DISPLAY "Step " WS-STEP-COUNTER ": " WS-LAYERED-RESULT ADD 1 TO WS-STEP-COUNTER COMPUTE WS-LAYERED-RESULT = FUNCTION B-OR(WS-LAYERED-RESULT, WS-PATTERN-2) DISPLAY "Step " WS-STEP-COUNTER ": " WS-LAYERED-RESULT ADD 1 TO WS-STEP-COUNTER COMPUTE WS-LAYERED-RESULT = FUNCTION B-OR(WS-LAYERED-RESULT, WS-PATTERN-3) DISPLAY "Step " WS-STEP-COUNTER ": " WS-LAYERED-RESULT ADD 1 TO WS-STEP-COUNTER COMPUTE WS-LAYERED-RESULT = FUNCTION B-OR(WS-LAYERED-RESULT, WS-PATTERN-4) DISPLAY "Step " WS-STEP-COUNTER ": " WS-LAYERED-RESULT DISPLAY "Final complex pattern: " WS-LAYERED-RESULT.

Best Practices

Recommended Practices

  • Use B-OR for setting bits and combining flags
  • Create meaningful constant names for bit masks
  • Document bit patterns and their purposes clearly
  • Use B-OR to build complex configurations from simple options
  • Combine with B-AND to test individual flags after setting
  • Consider using B-OR for data merging operations

Common Pitfalls

  • Remember that OR with 1 always results in 1 (can't clear bits)
  • Be careful with large numbers that might cause overflow
  • Don't confuse bitwise OR with logical OR operations
  • Test with various bit patterns to ensure correct behavior
  • Consider the field size when working with large bit patterns

Related COBOL Features

B-AND

Binary AND operations for bit testing and masking

B-XOR

Binary XOR operations for bit toggling

B-NOT

Binary NOT operations for bit inversion

COMPUTE Statement

Arithmetic and logical calculations

Frequently Asked Questions

Q: Can B-OR be used to clear bits?

No, B-OR can only set bits (make them 1). To clear bits, use B-AND with an inverse mask created by B-NOT.

Q: What happens when I OR a value with itself?

ORing a value with itself returns the same value unchanged (A OR A = A).

Q: Can I use B-OR with more than two operands?

B-OR accepts two operands. For multiple values, chain B-OR operations or use nested function calls.

Q: Is B-OR commutative and associative?

Yes, B-OR is both commutative (A OR B = B OR A) and associative ((A OR B) OR C = A OR (B OR C)).

Practical Exercises

Exercise 1: Permission System

Create a permission management system that uses B-OR to combine various access rights.

cobol
1
2
3
4
5
6
7
8
9
10
11
* Your task: Build a permission combiner WORKING-STORAGE SECTION. 01 WS-PERMISSIONS. 05 WS-READ PIC 9(4) COMP VALUE 1. 05 WS-WRITE PIC 9(4) COMP VALUE 2. 05 WS-EXECUTE PIC 9(4) COMP VALUE 4. 05 WS-DELETE PIC 9(4) COMP VALUE 8. 01 WS-USER-ACCESS PIC 9(4) COMP VALUE 0. * Combine permissions based on user role

Exercise 2: Status Flag Manager

Design a system status manager that uses B-OR to build complex status combinations.

Summary

The COBOL B-OR function is a fundamental tool for binary manipulation, excelling at bit setting, flag combination, and data merging operations. Its ability to set specific bits while preserving others makes it essential for configuration management, permission systems, and status tracking. Understanding B-OR operations enables sophisticated bit manipulation techniques when combined with other binary functions like B-AND for testing and B-NOT for creating inverse masks. The function's mathematical properties (commutative and associative) make it reliable and predictable for complex operations. Mastering B-OR is crucial for any COBOL programmer working with flags, configuration systems, or applications requiring precise bit-level control and data consolidation.