



A condition-name condition tests a conditional variable to determine whether its value is equal to any value(s) associated with the condition-name.
    ___ Format _____________________________________________________________ 
   |                                                                        |
   | >>__condition-name__________________________________________________>< |
   |                                                                        |
   |________________________________________________________________________|
   A condition-name is used in conditions as an abbreviation for the relation
   condition.  The rules for comparing a conditional variable with a
   condition-name value are the same as those specified for relation
   conditions.
If the condition-name has been associated with a range of values (or with several ranges of values), the conditional variable is tested to determine whether or not its value falls within the range(s), including the end values. The result of the test is true if one of the values corresponding to the condition-name equals the value of its associated conditional variable.
The following example illustrates the use of conditional variables and condition-names:
     01  AGE-GROUP            PIC  99.
         88  INFANT           VALUE 0.
         88  BABY             VALUE 1, 2.
         88  CHILD            VALUE 3 THRU 12.
         88  TEEN-AGER        VALUE 13 THRU 19.
   AGE-GROUP is the conditional variable; INFANT, BABY, CHILD, and TEEN-AGER
   are condition-names.  For individual records in the file, only one of the
   values specified in the condition-name entries can be present.
The following IF statements can be added to the above example to determine the age group of a specific record:
     IF INFANT...             (Tests for value 0)
     IF BABY...               (Tests for values 1, 2)
     IF CHILD...              (Tests for values 3 through 12)
     IF TEEN-AGER...          (Tests for values 13 through 19)
   Depending on the evaluation of the condition-name condition, alternative
   paths of execution are taken by the object program.
Subtopics:
  © Copyright IBM Corp. 1991, 1998
Adobe, the Adobe logo, Acrobat, the Acrobat logo, and Acrobat Reader are registered trademarks of Adobe Systems incorporated.