88 Level Number


In some scenarios, the variable might need to be compared with multiple values to control the program flow. The conditions become more complex when we use multiple relational operators with operands. These complex conditions might not produce accurate results if we do not use relational operators according to their priority.

COBOL introduced an 88 level number to avoid the above issue and make the code more understandable by declaring a name for each condition.

The name associated with 88-level numbers is Condition Name, and the variables with 88-level numbers are Conditional Variable.

How condition names are declared?


Condition names declartion syntax below -

 01 conditional-variable PIC variable-declaration.
    88 condition-name    VALUE condition-value.

For Example -

 01 WS-GENDER      PIC X(01).
    88 WS-MALE           VALUE "M".
    88 WS-FEMALE         VALUE "F".

In the above example, WS-GENDER is the conditional variable, and WS-MALE and WS-FEMALE are the condition names.

Points to Note -

  • An 88-level number can't declare a variable. However, it provides a descriptive name for a condition.
  • Condition name is always associated with a variable.
  • If the conditional variable is subscripted or indexed, the condition name should be subscripted or indexed.
  • The condition name doesn't occupy any storage.
  • Condition names can be coded in either Area-A or Area-B.

Rules to Remember -

  • No PICTURE clause is associated with 88-level numbers.
  • 88 level number is always associated with level number 01-49.
  • The VALUE clause is mandatory for the condition name.
  • The keywords THROUGH and THRU are equivalent.
  • Condition names can be coded both at the group and elementary levels.

How condition variables be initialized?


Condition variables are initialized in two ways -

  • During the declaration.
  • Using SET statement.

During the declaration -

Condition variables are initialized by coding the VALUE clause during the declaration. For example -

 01 WS-GENDER       PIC X(01) VALUE 'M'.
   88 MALE         VALUE 'M'.
   88 FEMALE       VALUE 'F'.

The declaration below initializes the WS-GENDER with 'M', which sets the MALE condition name to true.

Using SET statement -

The condition variables are initialized using the SET statement during the program execution. For example - the declaration below sets the WS-GENDER value to 'M'.

SET MALE    TO TRUE.
Note! SET statement assigns the condition name value to the conditional variable. So, it is always good to double-check before using the SET statement.

How do we validate the condition name?


The IF and EVALUATE statements use condition names to validate conditions that produce TRUE or FALSE. Based on the result, the program flow is decided. For example -

01 WS-GENDER       PIC X(01).
   88 MALE         VALUE 'M'.
   88 FEMALE       VALUE 'F'.
...
IF MALE
	statement-set1
ELSE
	statement-set2
END-IF.

If the WS-GENDER value is 'M', it executes statement-set1; otherwise, it executes statement-set2.

Different Formats -


Condition name has the advantage of being used in three different formats, which are very useful in validating the data.

Format1 - Single Value


The condition name is declared with only one value to validate. Syntax -

 88 Condition-Name VALUE single-value.

For example - MALE & FEMALE condition names having a single value.

 01 WS-GENDER       PIC X(01).
   88 WS-MALE         VALUE 'M'.
   88 WS-FEMALE       VALUE 'F'.

With the above definition, we can write -

 IF WS-MALE ...

Instead of -

 IF WS-GENDER EQUAL "M" ...

Format2 - Multiple values


The condition name is declared with more than one value to validate. i.e., In a single condition, it can validate with more than one value. Syntax -

 88 Condition-Name VALUE value1 value2...valueN.

For example - VALID-GENDER condition name has multiple values.

 01 WS-GENDER       PIC X(01).
   88 WS-VALID-GENDER    VALUE "M" "F".
   88 WS-MALE            VALUE "M".
   88 WS-FEMALE          VALUE "F".

With the above definition, we can write -

 IF WS-VALID-GENDER ...

Instead of -

 IF WS-GENDER EQUAL 'M' 
 OR WS-GENDER EQUAL 'Y' ...

Format3 - Range of values


The condition name is declared with a range of values to validate. i.e., in a single condition, it validates the value between starting and ending of a range. Syntax -

88 Condition-Name VALUE value1 THRU literalN.

For example - FIRST-CLASS, SECOND-CALSS, THIRD-CLASS & FAIL condition name has a range of values.

 01 WS-MARKS       PIC 9(03).
   88 WS-FIRST-CLASS     VALUE 60 THROUGH 100.
   88 WS-SECOND-CLASS    VALUE 50 THROUGH 59.
   88 WS-THIRD-CLASS     VALUE 35 THROUGH 49.
   88 WS-FAIL            VALUE 00 THROUGH 34.

With the above definition, we can write -

 IF WS-FIRST-CLASS ...

Instead of -

 IF  WS-MARKS >= 60 
 AND WS-MARKS <= 100...

Practical Example -


Scenario - Condition names declaration (all formats) using 88 level number and their usage for validation in PROCEDURE DIVISION.

Code -

----+----1----+----2----+----3----+----4----+----5----+
       ...
       DATA DIVISION.  
       WORKING-STORAGE SECTION.

       01 WS-ALPHABET       PIC X(01).
	  * Condition names with single values
          88 ALPHABET-A     VALUE "A". 
          88 ALPHABET-S     VALUE "S".
      * Condition names with multiple values
          88 VALID-ALPHABET VALUE "A" THROUGH "Z". 
          88 VOWELS         VALUE "A" "E" "I" "O" "U".
      * Condition names with range of values		  
          88 CONSONANTS     VALUE "B" THRU "D" 
                                  "F" THRU "H"
                                  "J" THRU "N"
                                  "P" THRU "T"
                                  "V" THRU "Z". 
       ...
       PROCEDURE DIVISION. 

           SET ALPHABET-A    TO TRUE.
           IF  VOWELS
               DISPLAY "ALPHABET IS VOWEL: " WS-ALPHABET
           END-IF.

           SET ALPHABET-S    TO TRUE. 
           IF  CONSONANTS
               DISPLAY  "ALPHABET IS CONSONENT: " WS-ALPHABET
           END-IF. 
		   ...

Output -

ALPHABET IS VOWEL: A
ALPHABET IS CONSONENT: S