One of COBOL's most distinctive and powerful features is the 88-level condition name. Condition names provide a way to create symbolic constants and assign meaningful names to specific values that a data item can have. This enhances code readability and maintainability by allowing programmers to use meaningful names instead of literal values in conditional expressions.
123456WORKING-STORAGE SECTION. 01 WS-STATUS-CODE PIC X. 88 STATUS-ACTIVE VALUE 'A'. 88 STATUS-SUSPENDED VALUE 'S'. 88 STATUS-TERMINATED VALUE 'T'. 88 STATUS-PENDING VALUE 'P'.
In this example, four condition names are associated with the WS-STATUS-CODE field, each representing a different status value.
The 88-level condition names are not separate data items but rather boolean conditions associated with the parent data item. When the parent item contains a value specified in the condition name's VALUE clause, the condition is considered true; otherwise, it's false.
Note: 88-level items don't occupy any additional storage. They simply provide a symbolic way to test whether their parent data item contains a specific value or one of a set of values.
The primary benefit of 88-level condition names is that they can be used directly in conditional statements, making the code more readable and self-documenting. Instead of comparing a field to literal values, you can use descriptive condition names that clearly express the intent of the code.
1234567IF WS-STATUS-CODE = 'A' PERFORM PROCESS-ACTIVE-ACCOUNT ELSE IF WS-STATUS-CODE = 'S' PERFORM PROCESS-SUSPENDED-ACCOUNT ELSE IF WS-STATUS-CODE = 'T' PERFORM PROCESS-TERMINATED-ACCOUNT END-IF.
1234567IF STATUS-ACTIVE PERFORM PROCESS-ACTIVE-ACCOUNT ELSE IF STATUS-SUSPENDED PERFORM PROCESS-SUSPENDED-ACCOUNT ELSE IF STATUS-TERMINATED PERFORM PROCESS-TERMINATED-ACCOUNT END-IF.
As you can see, using condition names makes the code much more readable and self-documenting. The intent is clear without needing to know the specific codes used for different statuses.
1234567891011* Using condition names in PERFORM UNTIL PERFORM PROCESS-RECORD UNTIL END-OF-FILE * Using the SET statement with condition names SET STATUS-ACTIVE TO TRUE * Using condition names with AND/OR IF VALID-CUSTOMER AND NOT ACCOUNT-CLOSED PERFORM PROCESS-TRANSACTION END-IF.
Condition names can be used in any context where a condition is expected, and they can be combined with AND, OR, and NOT operators.
An 88-level condition name can be associated with multiple values, either as individual literals or as ranges. This allows you to create conditions that represent a set of valid values, making your code even more expressive.
123401 WS-DEPARTMENT-CODE PIC X(3). 88 SALES-DEPARTMENT VALUE 'S01' 'S02' 'S03' 'S04'. 88 MARKETING-DEPARTMENT VALUE 'M01' 'M02' 'M03'. 88 IT-DEPARTMENT VALUE 'I01' 'I02' 'I03' 'I04' 'I05'.
In this example, SALES-DEPARTMENT is true if WS-DEPARTMENT-CODE contains any of the values 'S01', 'S02', 'S03', or 'S04'.
12345601 WS-GRADE PIC 9(3). 88 PASSING-GRADE VALUE 60 THRU 100. 88 FAILING-GRADE VALUE 0 THRU 59. 88 EXCELLENT-GRADE VALUE 90 THRU 100. 88 AVERAGE-GRADE VALUE 70 THRU 89. 88 POOR-GRADE VALUE 60 THRU 69.
The THRU keyword (or THROUGH, they are synonymous) defines a range of values. In this example, PASSING-GRADE is true if WS-GRADE contains any value from 60 through 100, inclusive.
123401 WS-TRANSACTION-CODE PIC X. 88 VALID-TRANSACTION VALUE 'A' 'B' 'C' 'D' THRU 'H' 'X' 'Y' 'Z'. 88 PRIORITY-TRANSACTION VALUE 'A' 'X' 'Y' 'Z'. 88 STANDARD-TRANSACTION VALUE 'B' 'C' 'D' THRU 'H'.
You can mix individual values and ranges in the same VALUE clause. Here, VALID-TRANSACTION is true for 'A', 'B', 'C', any letter from 'D' through 'H', and 'X', 'Y', 'Z'.
To make the most effective use of 88-level condition names in your COBOL programs, follow these best practices:
Choose condition names that clearly describe what the condition represents, making your code self-documenting. Avoid abbreviations unless they are widely understood in your domain.
1234567* Good - descriptive names 88 CUSTOMER-IS-PREFERRED VALUE 'P'. 88 TRANSACTION-COMPLETED VALUE 'C'. * Not as good - abbreviations, less clear 88 CUST-PRF VALUE 'P'. 88 TRANS-CMP VALUE 'C'.
Define all related condition names together right after their parent data item. This makes it easier to see all possible states that the data item can represent.
12345601 WS-ACCOUNT-STATUS PIC X. 88 ACCOUNT-ACTIVE VALUE 'A'. 88 ACCOUNT-DORMANT VALUE 'D'. 88 ACCOUNT-CLOSED VALUE 'C'. 88 ACCOUNT-FROZEN VALUE 'F'. 88 ACCOUNT-VALID VALUE 'A' 'D'. * Both active and dormant are valid
When appropriate, define conditions that are logical complements of each other. This increases readability by avoiding negations in the code.
123456789101112131415161701 WS-VALIDATION-FLAG PIC X. 88 RECORD-IS-VALID VALUE 'Y'. 88 RECORD-IS-INVALID VALUE 'N'. * Better to write: IF RECORD-IS-VALID PERFORM PROCESS-VALID-RECORD ELSE PERFORM PROCESS-INVALID-RECORD END-IF. * Instead of: IF NOT RECORD-IS-VALID PERFORM PROCESS-INVALID-RECORD ELSE PERFORM PROCESS-VALID-RECORD END-IF.
When setting a field to a value represented by a condition name, use the SET statement rather than moving literal values. This maintains consistency with your use of condition names.
12345* Preferred approach SET ACCOUNT-ACTIVE TO TRUE * Rather than MOVE 'A' TO WS-ACCOUNT-STATUS
Even with descriptive condition names, it's good practice to include comments explaining what each value represents, especially for complex business rules or regulatory codes.
1234567801 WS-TAX-CODE PIC X(2). * Standard tax rates by region 88 DOMESTIC-TAX VALUE '01'. * Standard domestic rate 20% 88 EU-TAX VALUE '02'. * European Union rate 15% 88 INTERNATIONAL-TAX VALUE '03'. * International rate 25% * Special tax statuses 88 TAX-EXEMPT VALUE '00'. * No tax charged 88 REDUCED-RATE VALUE '04'. * Reduced rate for qualifying goods 5%
While 88-level condition names are a powerful COBOL feature, there are alternative approaches to representing conditions in your programs:
12345678901 STATUS-VALUES. 05 STATUS-ACTIVE-VALUE PIC X VALUE 'A'. 05 STATUS-INACTIVE-VALUE PIC X VALUE 'I'. 05 STATUS-PENDING-VALUE PIC X VALUE 'P'. * Usage: IF WS-STATUS = STATUS-ACTIVE-VALUE PERFORM PROCESS-ACTIVE END-IF.
12345678910EVALUATE WS-STATUS WHEN 'A' PERFORM PROCESS-ACTIVE WHEN 'I' PERFORM PROCESS-INACTIVE WHEN 'P' PERFORM PROCESS-PENDING WHEN OTHER PERFORM PROCESS-UNKNOWN-STATUS END-EVALUATE.
Important: While these alternatives work, 88-level condition names generally provide the most readable and maintainable solution for representing symbolic conditions in COBOL programs. They're a core language feature specifically designed for this purpose.
Define and Use Status Conditions
Create a WORKING-STORAGE data item for order status with condition names for "Pending", "Processing", "Shipped", "Delivered", and "Cancelled". Then write an IF/ELSE structure that performs different paragraphs based on the order status.
Create Age Group Conditions
Define a numeric field for a person's age, then create condition names for different age groups: "Child" (0-12), "Teen" (13-19), "Young-Adult" (20-39), "Middle-Age" (40-64), and "Senior" (65+). Write code that sets a discount percentage based on the age group.
Convert IF/ELSE to Condition Names
Refactor the following code to use 88-level condition names:
IF WS-ACCOUNT-TYPE = 'S'
PERFORM PROCESS-SAVINGS
ELSE IF WS-ACCOUNT-TYPE = 'C'
PERFORM PROCESS-CHECKING
ELSE IF WS-ACCOUNT-TYPE = 'M'
PERFORM PROCESS-MONEY-MARKET
END-IF.
Combine Conditions with AND/OR
Define a customer record with fields for status (Active/Inactive) and type (Regular/Premium/VIP). Create condition names for each value, then write IF statements that combine these conditions to handle different scenarios (e.g., active premium customers).
Use SET Statement with Conditions
Write code that uses the SET statement to mark an order as "Shipped" and a customer account as "Active". Use appropriate condition names and document the expected effect on the underlying data items.
1. What level number is used for condition names in COBOL?
2. What is the primary purpose of 88-level condition names?
3. How many 88-level condition names can be associated with a single data item?
4. How are 88-level condition names used in a COBOL program?
5. Which of the following is a valid use of an 88-level item?
Understanding how data is organized and structured in COBOL programs
Different ways to implement decision-making in COBOL
How to control the flow of execution in COBOL programs
Techniques for validating data in COBOL programs
Best practices for writing clear, maintainable COBOL code