MainframeMaster

COBOL Comparison Operations

Comparison operations in COBOL are fundamental to program logic and decision-making. They allow programs to compare values, make decisions, and control program flow based on data relationships. Understanding comparison operations is essential for implementing business logic, data validation, and conditional processing in COBOL programs.

Understanding Comparison Operations

Comparison operations in COBOL evaluate the relationship between two values and return a true or false result. These operations are used in IF statements, EVALUATE clauses, and other conditional logic to control program flow. COBOL supports various relational operators for different types of comparisons.

Relational Operators

1. Basic Relational Operators

COBOL provides six basic relational operators for comparing values. These operators work with both numeric and alphanumeric data, though the comparison behavior differs based on the data type being compared.

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
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
IDENTIFICATION DIVISION. PROGRAM-ID. RELATIONAL-OPERATORS-EXAMPLE. *> This program demonstrates basic relational operators in COBOL DATA DIVISION. WORKING-STORAGE SECTION. *> Test data for relational operator demonstrations 01 NUMERIC-COMPARISON-DATA. 05 FIRST-NUMBER PIC 9(3) VALUE 100. 05 SECOND-NUMBER PIC 9(3) VALUE 200. 05 THIRD-NUMBER PIC 9(3) VALUE 100. 05 FOURTH-NUMBER PIC 9(3) VALUE 50. 01 CHARACTER-COMPARISON-DATA. 05 FIRST-STRING PIC X(10) VALUE 'APPLE'. 05 SECOND-STRING PIC X(10) VALUE 'BANANA'. 05 THIRD-STRING PIC X(10) VALUE 'APPLE'. 05 FOURTH-STRING PIC X(10) VALUE 'CHERRY'. 01 COMPARISON-RESULTS. 05 RESULT-STATUS PIC X(1). 88 COMPARISON-TRUE VALUE 'T'. 88 COMPARISON-FALSE VALUE 'F'. PROCEDURE DIVISION. DEMONSTRATE-RELATIONAL-OPERATORS. DISPLAY 'Demonstrating COBOL Relational Operators' DISPLAY '========================================' *> Demonstrate numeric comparisons PERFORM DEMONSTRATE-NUMERIC-COMPARISONS *> Demonstrate character comparisons PERFORM DEMONSTRATE-CHARACTER-COMPARISONS STOP RUN. DEMONSTRATE-NUMERIC-COMPARISONS. DISPLAY 'Numeric Comparisons:' DISPLAY 'First Number: ' FIRST-NUMBER DISPLAY 'Second Number: ' SECOND-NUMBER DISPLAY 'Third Number: ' THIRD-NUMBER DISPLAY 'Fourth Number: ' FOURTH-NUMBER DISPLAY ' ' *> Equal comparison (=) IF FIRST-NUMBER = THIRD-NUMBER DISPLAY '100 = 100 (TRUE) - Equal comparison' ELSE DISPLAY '100 = 100 (FALSE) - Equal comparison' END-IF *> Not equal comparison (NOT =) IF FIRST-NUMBER NOT = SECOND-NUMBER DISPLAY '100 NOT = 200 (TRUE) - Not equal comparison' ELSE DISPLAY '100 NOT = 200 (FALSE) - Not equal comparison' END-IF *> Greater than comparison (>) IF SECOND-NUMBER > FIRST-NUMBER DISPLAY '200 > 100 (TRUE) - Greater than comparison' ELSE DISPLAY '200 > 100 (FALSE) - Greater than comparison' END-IF *> Less than comparison (<) IF FOURTH-NUMBER < FIRST-NUMBER DISPLAY '50 < 100 (TRUE) - Less than comparison' ELSE DISPLAY '50 < 100 (FALSE) - Less than comparison' END-IF *> Greater than or equal comparison (>=) IF FIRST-NUMBER >= THIRD-NUMBER DISPLAY '100 >= 100 (TRUE) - Greater than or equal comparison' ELSE DISPLAY '100 >= 100 (FALSE) - Greater than or equal comparison' END-IF *> Less than or equal comparison (<=) IF FOURTH-NUMBER <= FIRST-NUMBER DISPLAY '50 <= 100 (TRUE) - Less than or equal comparison' ELSE DISPLAY '50 <= 100 (FALSE) - Less than or equal comparison' END-IF. DEMONSTRATE-CHARACTER-COMPARISONS. DISPLAY 'Character String Comparisons:' DISPLAY 'First String: ' FIRST-STRING DISPLAY 'Second String: ' SECOND-STRING DISPLAY 'Third String: ' THIRD-STRING DISPLAY 'Fourth String: ' FOURTH-STRING DISPLAY ' ' *> Equal comparison for strings IF FIRST-STRING = THIRD-STRING DISPLAY 'APPLE = APPLE (TRUE) - String equal comparison' ELSE DISPLAY 'APPLE = APPLE (FALSE) - String equal comparison' END-IF *> Not equal comparison for strings IF FIRST-STRING NOT = SECOND-STRING DISPLAY 'APPLE NOT = BANANA (TRUE) - String not equal comparison' ELSE DISPLAY 'APPLE NOT = BANANA (FALSE) - String not equal comparison' END-IF *> Greater than comparison for strings (alphabetical order) IF SECOND-STRING > FIRST-STRING DISPLAY 'BANANA > APPLE (TRUE) - String greater than comparison' ELSE DISPLAY 'BANANA > APPLE (FALSE) - String greater than comparison' END-IF *> Less than comparison for strings (alphabetical order) IF FIRST-STRING < SECOND-STRING DISPLAY 'APPLE < BANANA (TRUE) - String less than comparison' ELSE DISPLAY 'APPLE < BANANA (FALSE) - String less than comparison' END-IF *> Greater than or equal comparison for strings IF FIRST-STRING >= THIRD-STRING DISPLAY 'APPLE >= APPLE (TRUE) - String greater than or equal comparison' ELSE DISPLAY 'APPLE >= APPLE (FALSE) - String greater than or equal comparison' END-IF *> Less than or equal comparison for strings IF FIRST-STRING <= FOURTH-STRING DISPLAY 'APPLE <= CHERRY (TRUE) - String less than or equal comparison' ELSE DISPLAY 'APPLE <= CHERRY (FALSE) - String less than or equal comparison' END-IF.

This example demonstrates all six basic relational operators in COBOL: equal (=), not equal (NOT =), greater than (>), less than (<), greater than or equal (>=), and less than or equal (<=). The program shows how these operators work with both numeric and character data. For numeric data, comparisons are based on numeric values, while for character data, comparisons are based on the collating sequence (alphabetical order).

2. Advanced Comparison Techniques

Advanced comparison techniques include using condition names, complex logical expressions, and specialized comparison functions. These techniques provide more sophisticated ways to evaluate conditions and make decisions in COBOL programs.

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
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
IDENTIFICATION DIVISION. PROGRAM-ID. ADVANCED-COMPARISON-TECHNIQUES. *> This program demonstrates advanced comparison techniques DATA DIVISION. WORKING-STORAGE SECTION. *> Data for advanced comparison demonstrations 01 CUSTOMER-DATA. 05 CUSTOMER-ID PIC 9(8) VALUE 12345678. 05 CUSTOMER-AGE PIC 9(3) VALUE 25. 05 CUSTOMER-INCOME PIC 9(8)V99 VALUE 50000.00. 05 CUSTOMER-CREDIT-SCORE PIC 9(3) VALUE 750. 05 CUSTOMER-STATUS PIC X(1) VALUE 'A'. 88 ACTIVE-CUSTOMER VALUE 'A'. 88 INACTIVE-CUSTOMER VALUE 'I'. 88 SUSPENDED-CUSTOMER VALUE 'S'. 01 ACCOUNT-DATA. 05 ACCOUNT-BALANCE PIC 9(10)V99 VALUE 2500.00. 05 ACCOUNT-LIMIT PIC 9(10)V99 VALUE 10000.00. 05 ACCOUNT-TYPE PIC X(1) VALUE 'C'. 88 CHECKING-ACCOUNT VALUE 'C'. 88 SAVINGS-ACCOUNT VALUE 'S'. 88 BUSINESS-ACCOUNT VALUE 'B'. 01 TRANSACTION-DATA. 05 TRANSACTION-AMOUNT PIC 9(8)V99 VALUE 500.00. 05 TRANSACTION-TYPE PIC X(1) VALUE 'D'. 88 DEPOSIT-TRANSACTION VALUE 'D'. 88 WITHDRAWAL-TRANSACTION VALUE 'W'. 88 TRANSFER-TRANSACTION VALUE 'T'. 01 COMPARISON-RESULTS. 05 VALIDATION-STATUS PIC X(1). 88 VALIDATION-PASSED VALUE 'P'. 88 VALIDATION-FAILED VALUE 'F'. 05 ERROR-MESSAGE PIC X(100). PROCEDURE DIVISION. DEMONSTRATE-ADVANCED-COMPARISONS. DISPLAY 'Demonstrating Advanced Comparison Techniques' DISPLAY '===========================================' *> Demonstrate condition name comparisons PERFORM DEMONSTRATE-CONDITION-NAMES *> Demonstrate complex logical expressions PERFORM DEMONSTRATE-COMPLEX-LOGICAL-EXPRESSIONS *> Demonstrate range comparisons PERFORM DEMONSTRATE-RANGE-COMPARISONS STOP RUN. DEMONSTRATE-CONDITION-NAMES. DISPLAY 'Condition Name Comparisons:' DISPLAY 'Customer Status: ' CUSTOMER-STATUS DISPLAY 'Account Type: ' ACCOUNT-TYPE DISPLAY 'Transaction Type: ' TRANSACTION-TYPE DISPLAY ' ' *> Test customer status using condition names IF ACTIVE-CUSTOMER DISPLAY 'Customer is ACTIVE (using condition name)' ELSE IF INACTIVE-CUSTOMER DISPLAY 'Customer is INACTIVE (using condition name)' ELSE IF SUSPENDED-CUSTOMER DISPLAY 'Customer is SUSPENDED (using condition name)' END-IF END-IF END-IF *> Test account type using condition names IF CHECKING-ACCOUNT DISPLAY 'Account is CHECKING (using condition name)' ELSE IF SAVINGS-ACCOUNT DISPLAY 'Account is SAVINGS (using condition name)' ELSE IF BUSINESS-ACCOUNT DISPLAY 'Account is BUSINESS (using condition name)' END-IF END-IF END-IF *> Test transaction type using condition names IF DEPOSIT-TRANSACTION DISPLAY 'Transaction is DEPOSIT (using condition name)' ELSE IF WITHDRAWAL-TRANSACTION DISPLAY 'Transaction is WITHDRAWAL (using condition name)' ELSE IF TRANSFER-TRANSACTION DISPLAY 'Transaction is TRANSFER (using condition name)' END-IF END-IF END-IF. DEMONSTRATE-COMPLEX-LOGICAL-EXPRESSIONS. DISPLAY 'Complex Logical Expressions:' DISPLAY 'Customer Age: ' CUSTOMER-AGE DISPLAY 'Customer Income: ' CUSTOMER-INCOME DISPLAY 'Customer Credit Score: ' CUSTOMER-CREDIT-SCORE DISPLAY ' ' *> Complex condition: Age AND Income requirements IF CUSTOMER-AGE >= 18 AND CUSTOMER-AGE <= 65 IF CUSTOMER-INCOME >= 30000.00 DISPLAY 'Customer meets age AND income requirements' ELSE DISPLAY 'Customer meets age requirements but not income' END-IF ELSE DISPLAY 'Customer does not meet age requirements' END-IF *> Complex condition: Credit score OR Income requirements IF CUSTOMER-CREDIT-SCORE >= 700 OR CUSTOMER-INCOME >= 75000.00 DISPLAY 'Customer meets credit score OR income requirements' ELSE DISPLAY 'Customer does not meet credit score OR income requirements' END-IF *> Complex condition: Multiple conditions with NOT IF ACTIVE-CUSTOMER AND NOT SUSPENDED-CUSTOMER IF CUSTOMER-CREDIT-SCORE > 600 DISPLAY 'Customer is active, not suspended, and has good credit' ELSE DISPLAY 'Customer is active and not suspended but has poor credit' END-IF ELSE DISPLAY 'Customer is not active or is suspended' END-IF. DEMONSTRATE-RANGE-COMPARISONS. DISPLAY 'Range Comparisons:' DISPLAY 'Account Balance: ' ACCOUNT-BALANCE DISPLAY 'Account Limit: ' ACCOUNT-LIMIT DISPLAY 'Transaction Amount: ' TRANSACTION-AMOUNT DISPLAY ' ' *> Range comparison: Check if balance is within acceptable range IF ACCOUNT-BALANCE >= 0 AND ACCOUNT-BALANCE <= ACCOUNT-LIMIT DISPLAY 'Account balance is within acceptable range' ELSE DISPLAY 'Account balance is outside acceptable range' END-IF *> Range comparison: Check if transaction amount is reasonable IF TRANSACTION-AMOUNT > 0 AND TRANSACTION-AMOUNT <= 5000.00 DISPLAY 'Transaction amount is within reasonable range' ELSE DISPLAY 'Transaction amount is outside reasonable range' END-IF *> Range comparison: Check if customer qualifies for premium service IF CUSTOMER-INCOME >= 100000.00 AND CUSTOMER-CREDIT-SCORE >= 800 DISPLAY 'Customer qualifies for premium service' ELSE IF CUSTOMER-INCOME >= 50000.00 AND CUSTOMER-CREDIT-SCORE >= 700 DISPLAY 'Customer qualifies for standard service' ELSE DISPLAY 'Customer qualifies for basic service' END-IF END-IF.

This example demonstrates advanced comparison techniques including condition names (88-level items), complex logical expressions with AND and OR operators, and range comparisons. Condition names provide a more readable way to test for specific values, while complex logical expressions allow for sophisticated decision-making based on multiple conditions. Range comparisons are useful for validating data within acceptable limits.

Comparison with Different Data Types

1. Numeric Data Comparisons

Numeric data comparisons in COBOL work with various numeric formats including binary, packed decimal, and display numeric. COBOL automatically handles the conversion between different numeric formats during comparison 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
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
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
IDENTIFICATION DIVISION. PROGRAM-ID. NUMERIC-DATA-COMPARISONS. *> This program demonstrates numeric data comparisons DATA DIVISION. WORKING-STORAGE SECTION. *> Different numeric data types for comparison 01 BINARY-NUMERIC-DATA. 05 BINARY-NUMBER-1 PIC 9(5) COMP VALUE 1000. 05 BINARY-NUMBER-2 PIC 9(5) COMP VALUE 2000. 01 PACKED-DECIMAL-DATA. 05 PACKED-NUMBER-1 PIC 9(5)V99 COMP-3 VALUE 1000.50. 05 PACKED-NUMBER-2 PIC 9(5)V99 COMP-3 VALUE 2000.75. 01 DISPLAY-NUMERIC-DATA. 05 DISPLAY-NUMBER-1 PIC 9(5)V99 VALUE 1000.50. 05 DISPLAY-NUMBER-2 PIC 9(5)V99 VALUE 2000.75. 01 MIXED-NUMERIC-DATA. 05 INTEGER-VALUE PIC 9(3) VALUE 100. 05 DECIMAL-VALUE PIC 9(3)V99 VALUE 100.00. 05 FRACTIONAL-VALUE PIC 9(3)V99 VALUE 100.50. PROCEDURE DIVISION. DEMONSTRATE-NUMERIC-COMPARISONS. DISPLAY 'Demonstrating Numeric Data Comparisons' DISPLAY '======================================' *> Compare binary numeric values PERFORM COMPARE-BINARY-NUMERIC *> Compare packed decimal values PERFORM COMPARE-PACKED-DECIMAL *> Compare display numeric values PERFORM COMPARE-DISPLAY-NUMERIC *> Compare mixed numeric types PERFORM COMPARE-MIXED-NUMERIC-TYPES STOP RUN. COMPARE-BINARY-NUMERIC. DISPLAY 'Binary Numeric Comparisons:' DISPLAY 'Binary Number 1: ' BINARY-NUMBER-1 DISPLAY 'Binary Number 2: ' BINARY-NUMBER-2 DISPLAY ' ' IF BINARY-NUMBER-1 < BINARY-NUMBER-2 DISPLAY 'Binary: 1000 < 2000 (TRUE)' END-IF IF BINARY-NUMBER-1 = 1000 DISPLAY 'Binary: 1000 = 1000 (TRUE)' END-IF IF BINARY-NUMBER-2 > BINARY-NUMBER-1 DISPLAY 'Binary: 2000 > 1000 (TRUE)' END-IF. COMPARE-PACKED-DECIMAL. DISPLAY 'Packed Decimal Comparisons:' DISPLAY 'Packed Number 1: ' PACKED-NUMBER-1 DISPLAY 'Packed Number 2: ' PACKED-NUMBER-2 DISPLAY ' ' IF PACKED-NUMBER-1 < PACKED-NUMBER-2 DISPLAY 'Packed: 1000.50 < 2000.75 (TRUE)' END-IF IF PACKED-NUMBER-1 = 1000.50 DISPLAY 'Packed: 1000.50 = 1000.50 (TRUE)' END-IF IF PACKED-NUMBER-2 > PACKED-NUMBER-1 DISPLAY 'Packed: 2000.75 > 1000.50 (TRUE)' END-IF. COMPARE-DISPLAY-NUMERIC. DISPLAY 'Display Numeric Comparisons:' DISPLAY 'Display Number 1: ' DISPLAY-NUMBER-1 DISPLAY 'Display Number 2: ' DISPLAY-NUMBER-2 DISPLAY ' ' IF DISPLAY-NUMBER-1 < DISPLAY-NUMBER-2 DISPLAY 'Display: 1000.50 < 2000.75 (TRUE)' END-IF IF DISPLAY-NUMBER-1 = 1000.50 DISPLAY 'Display: 1000.50 = 1000.50 (TRUE)' END-IF IF DISPLAY-NUMBER-2 > DISPLAY-NUMBER-1 DISPLAY 'Display: 2000.75 > 1000.50 (TRUE)' END-IF. COMPARE-MIXED-NUMERIC-TYPES. DISPLAY 'Mixed Numeric Type Comparisons:' DISPLAY 'Integer Value: ' INTEGER-VALUE DISPLAY 'Decimal Value: ' DECIMAL-VALUE DISPLAY 'Fractional Value: ' FRACTIONAL-VALUE DISPLAY ' ' *> Compare integer with decimal (both represent 100) IF INTEGER-VALUE = DECIMAL-VALUE DISPLAY 'Integer 100 = Decimal 100.00 (TRUE)' ELSE DISPLAY 'Integer 100 ≠ Decimal 100.00 (FALSE)' END-IF *> Compare integer with fractional IF INTEGER-VALUE < FRACTIONAL-VALUE DISPLAY 'Integer 100 < Fractional 100.50 (TRUE)' ELSE DISPLAY 'Integer 100 ≥ Fractional 100.50 (FALSE)' END-IF *> Compare decimal with fractional IF DECIMAL-VALUE < FRACTIONAL-VALUE DISPLAY 'Decimal 100.00 < Fractional 100.50 (TRUE)' ELSE DISPLAY 'Decimal 100.00 ≥ Fractional 100.50 (FALSE)' END-IF.

This example demonstrates how COBOL handles comparisons between different numeric data types. The program shows comparisons between binary numeric, packed decimal, and display numeric values. COBOL automatically converts between these formats during comparison operations, allowing seamless comparison of different numeric representations. The example also shows how integer and decimal values are compared, including cases where they represent the same numeric value.

2. Character Data Comparisons

Character data comparisons in COBOL are based on the collating sequence, which determines the order of characters. String comparisons are performed character by character from left to right, and the comparison stops when a difference is found or when one string is exhausted.

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
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
IDENTIFICATION DIVISION. PROGRAM-ID. CHARACTER-DATA-COMPARISONS. *> This program demonstrates character data comparisons DATA DIVISION. WORKING-STORAGE SECTION. *> Character data for comparison demonstrations 01 STRING-COMPARISON-DATA. 05 STRING-1 PIC X(10) VALUE 'APPLE'. 05 STRING-2 PIC X(10) VALUE 'BANANA'. 05 STRING-3 PIC X(10) VALUE 'APPLE'. 05 STRING-4 PIC X(10) VALUE 'APPLES'. 05 STRING-5 PIC X(10) VALUE 'APRICOT'. 01 CASE-SENSITIVE-DATA. 05 UPPERCASE-STRING PIC X(10) VALUE 'HELLO'. 05 LOWERCASE-STRING PIC X(10) VALUE 'hello'. 05 MIXED-CASE-STRING PIC X(10) VALUE 'Hello'. 01 ALPHANUMERIC-DATA. 05 ALPHA-STRING-1 PIC X(10) VALUE 'ABC123'. 05 ALPHA-STRING-2 PIC X(10) VALUE 'ABC124'. 05 ALPHA-STRING-3 PIC X(10) VALUE 'ABD123'. PROCEDURE DIVISION. DEMONSTRATE-CHARACTER-COMPARISONS. DISPLAY 'Demonstrating Character Data Comparisons' DISPLAY '======================================' *> Demonstrate basic string comparisons PERFORM DEMONSTRATE-BASIC-STRING-COMPARISONS *> Demonstrate case sensitivity PERFORM DEMONSTRATE-CASE-SENSITIVITY *> Demonstrate alphanumeric comparisons PERFORM DEMONSTRATE-ALPHANUMERIC-COMPARISONS STOP RUN. DEMONSTRATE-BASIC-STRING-COMPARISONS. DISPLAY 'Basic String Comparisons:' DISPLAY 'String 1: ' STRING-1 DISPLAY 'String 2: ' STRING-2 DISPLAY 'String 3: ' STRING-3 DISPLAY 'String 4: ' STRING-4 DISPLAY 'String 5: ' STRING-5 DISPLAY ' ' *> Equal comparison IF STRING-1 = STRING-3 DISPLAY 'APPLE = APPLE (TRUE) - Exact match' ELSE DISPLAY 'APPLE ≠ APPLE (FALSE) - No match' END-IF *> Not equal comparison IF STRING-1 NOT = STRING-2 DISPLAY 'APPLE ≠ BANANA (TRUE) - Different strings' ELSE DISPLAY 'APPLE = BANANA (FALSE) - Same strings' END-IF *> Less than comparison (alphabetical order) IF STRING-1 < STRING-2 DISPLAY 'APPLE < BANANA (TRUE) - A comes before B' ELSE DISPLAY 'APPLE ≥ BANANA (FALSE) - A does not come before B' END-IF *> Greater than comparison IF STRING-2 > STRING-1 DISPLAY 'BANANA > APPLE (TRUE) - B comes after A' ELSE DISPLAY 'BANANA ≤ APPLE (FALSE) - B does not come after A' END-IF *> Comparison with different lengths IF STRING-1 < STRING-4 DISPLAY 'APPLE < APPLES (TRUE) - Shorter string comes first' ELSE DISPLAY 'APPLE ≥ APPLES (FALSE) - Shorter string does not come first' END-IF. DEMONSTRATE-CASE-SENSITIVITY. DISPLAY 'Case Sensitivity Comparisons:' DISPLAY 'Uppercase: ' UPPERCASE-STRING DISPLAY 'Lowercase: ' LOWERCASE-STRING DISPLAY 'Mixed Case: ' MIXED-CASE-STRING DISPLAY ' ' *> Case-sensitive comparisons IF UPPERCASE-STRING = LOWERCASE-STRING DISPLAY 'HELLO = hello (TRUE) - Case insensitive' ELSE DISPLAY 'HELLO ≠ hello (FALSE) - Case sensitive' END-IF IF UPPERCASE-STRING = MIXED-CASE-STRING DISPLAY 'HELLO = Hello (TRUE) - Case insensitive' ELSE DISPLAY 'HELLO ≠ Hello (FALSE) - Case sensitive' END-IF IF LOWERCASE-STRING = MIXED-CASE-STRING DISPLAY 'hello = Hello (TRUE) - Case insensitive' ELSE DISPLAY 'hello ≠ Hello (FALSE) - Case sensitive' END-IF. DEMONSTRATE-ALPHANUMERIC-COMPARISONS. DISPLAY 'Alphanumeric Comparisons:' DISPLAY 'Alpha String 1: ' ALPHA-STRING-1 DISPLAY 'Alpha String 2: ' ALPHA-STRING-2 DISPLAY 'Alpha String 3: ' ALPHA-STRING-3 DISPLAY ' ' *> Compare alphanumeric strings IF ALPHA-STRING-1 < ALPHA-STRING-2 DISPLAY 'ABC123 < ABC124 (TRUE) - Numbers compared' ELSE DISPLAY 'ABC123 ≥ ABC124 (FALSE) - Numbers not compared correctly' END-IF IF ALPHA-STRING-1 < ALPHA-STRING-3 DISPLAY 'ABC123 < ABD123 (TRUE) - Letters compared' ELSE DISPLAY 'ABC123 ≥ ABD123 (FALSE) - Letters not compared correctly' END-IF IF ALPHA-STRING-2 < ALPHA-STRING-3 DISPLAY 'ABC124 < ABD123 (TRUE) - Mixed comparison' ELSE DISPLAY 'ABC124 ≥ ABD123 (FALSE) - Mixed comparison' END-IF.

This example demonstrates character data comparisons in COBOL, showing how strings are compared character by character based on the collating sequence. The program illustrates basic string comparisons, case sensitivity (which depends on the system's collating sequence), and alphanumeric comparisons. String comparisons stop at the first difference found, and shorter strings are considered "less than" longer strings when they are otherwise identical.

Best Practices for Comparison Operations

Common Comparison Patterns