Compaq COBOL
Reference Manual


Previous Contents Index

6.5.3 Condition-Name Condition

The condition-name condition determines if a data item contains a value assigned to one of that item's condition-names. The term conditional variable refers to the data item. condition-name refers to a level 88 entry associated with that item.

The general format for this condition is:


The condition is true if one of the values corresponding to condition-name equals the value of the associated conditional variable. The data description for a variable can associate condition-name with one or more ranges of values. In this case, the condition tests to determine if the value of the variable falls in the specified range (end values included).

The following example illustrates testing condition-names associated with both one value and a range of values.


    WORKING-STORAGE SECTION. 
    01  STUDENT-REC. 
        05  YEAR-ID           PIC 99. 
        88  FRESHMAN                    VALUE IS 1. 
        88  SOPHOMORE                   VALUE IS 2. 
        88  JUNIOR                      VALUE IS 3. 
        88  SENIOR                      VALUE IS 4. 
        88  GRADUATE                    VALUE IS 5 THRU 10. 
        . 
        . 
        . 
PROCEDURE DIVISION. 
        . 
        . 
        . 
    IF FRESHMAN ...
    IF SOPHOMORE ...
    IF JUNIOR ...
    IF SENIOR ...
    IF GRADUATE ...
Condition-Name Test Is True When the Value of the
Conditional Variable YEAR-ID Equals:
FRESHMAN 1
SOPHOMORE 2
JUNIOR 3
SENIOR 4
GRADUATE 5, 6, 7, 8, 9, or 10

When your program evaluates a conditional variable and its condition-name, the procedure is the same as the one used with the relation condition. (See Section 6.5.1.)

6.5.4 Switch-Status Condition

The switch-status condition tests the on or off setting of an external logical program switch. Its general format is as follows:


You use the SWITCH clause of the SPECIAL-NAMES paragraph to associate condition-name with a logical switch setting. (See the Section 4.1.3 paragraph in Chapter 4.) The condition is true if the switch setting in effect during program execution is the same one assigned to condition-name.

Note

The translated value of the OpenVMS Alpha logical name COB$SWITCHES or the Tru64 UNIX and Windows NT environment variable COBOL_SWITCHES specifies logical program switch settings. (See the description of program switches in the Compaq COBOL User Manual.)

6.5.5 Sign Condition

The sign condition determines if the algebraic value of an arithmetic expression is less than, greater than, or equal to zero.

Its general format is as follows:


An operand is defined as:

arithmetic-expression must contain at least one reference to a variable.

NOT and the key word following it are treated as a unit. For example, NOT ZERO tests for a nonzero condition.

6.5.6 Success/Failure Condition

The success/failure condition tests the return status codes of COBOL and non-COBOL procedures for success or failure conditions.


status-code-id

must be a COMP integer represented by PIC 9(1 to 9) COMP or PIC S9(1 to 9) COMP.

You can use the SET statement to initialize or alter the status of status-code-id.

The SUCCESS class condition is true if you specify status-code-id IS SUCCESS and status-code-id is in a SUCCESS state. Otherwise, the SUCCESS class condition is false.

The FAILURE class condition is true if you specify status-code-id IS FAILURE and status-code-id is in a FAILURE state. Otherwise, the FAILURE class condition is false.

status-code-id is in the SUCCESS state when the low-order bit of status-code-id is 1. It is in the FAILURE state when its low-order bit is 0.

Examples

  1. On OpenVMS, calling a non-COBOL procedure:


    WORKING-STORAGE SECTION. 
    01  RMS-EOF       PIC S9(9) COMP VALUE EXTERNAL RMS$_EOF. 
    01  RETURN-STATUS PIC S9(9) COMP. 
    PROCEDURE DIVISION. 
    A000-BEGIN. 
        . 
        . 
        . 
        CALL "LIB$GET_SCREEN" 
                  USING BY DESCRIPTOR INPUT-TEXT, PROMPT, 
                        BY REFERENCE  OUT-LEN, 
                  GIVING RETURN-STATUS. 
        IF RETURN-STATUS = RMS-EOF PERFORM CTRL-Z-TRAP-ROUTINE. 
        IF RETURN-STATUS IS FAILURE PERFORM FAILURE-ROUTINE. 
        . 
        . 
        .                                            <>
    

  2. Calling a COBOL procedure:


    IDENTIFICATION DIVISION. 
    PROGRAM-ID. MAIN-PROGRAM. 
    DATA DIVISION. 
    WORKING-STORAGE SECTION. 
    01  RETURN-STATUS      PIC S9(9) COMP. 
    PROCEDURE DIVISION. 
        . 
        . 
        . 
        CALL "SUB" GIVING RETURN-STATUS. 
        IF RETURN-STATUS IS FAILURE PERFORM FAILURE-ROUTINE. 
        . 
        . 
        . 
    IDENTIFICATION DIVISION. 
    PROGRAM-ID. SUB. 
        . 
        . 
        . 
    WORKING-STORAGE SECTION. 
    01  RETURN-STATUS      PIC S9(9) COMP. 
    PROCEDURE DIVISION GIVING RETURN-STATUS. 
        . 
        . 
        . 
        IF A = B 
               SET RETURN-STATUS TO SUCCESS 
           ELSE 
               SET RETURN-STATUS TO FAILURE. 
        . 
        . 
        . 
        EXIT PROGRAM. 
    END PROGRAM SUB. 
    END PROGRAM MAIN-PROGRAM. 
    

6.5.7 Complex Conditions

You form complex conditions by combining or negating other conditions. The conditions being combined or negated can be either simple or complex.

The logical operators AND and OR combine conditions. The logical operator NOT negates conditions. A space must precede and follow each logical operator in your program.

The truth value of a complex condition depends upon the following:

Table 6-4 shows the effect of each logical operator in complex conditions.

Table 6-4 How Logical Operators Affect Evaluation of Conditions
Logical
Operator
Meaning and Effect
AND Logical conjunction. The truth value is true if both connected conditions are true. It is false if one or both connected conditions are false.
OR Logical inclusive OR. The truth value is true if one or both connected conditions are true. It is false if both conditions are false.
NOT Logical negation or reversal of truth value. The truth value is true if the original condition is false. It is false if the original condition is true.

Negated Simple Conditions

The logical operator NOT negates a simple condition. The truth value of a negated simple condition is the opposite of the simple condition's truth value. Thus, the truth value of a negated simple condition is true only if the simple condition's truth value is false. It is false only if the simple condition's truth value is true.

The format for a negated simple condition is as follows:


Combined and Negated Combined Conditions

A combined condition results from connecting conditions with one of the logical operators AND or OR.

The general format is as follows:


In the general format, condition can be one of the following:

You can use matched pairs of parentheses in a combined condition. You do not need to write parentheses if the condition combines two or more conditions with the same logical operator (either AND or OR). In this case, the parentheses have no effect on the condition's evaluation. However, you might have to use parentheses if you use a mixture of AND, OR, and NOT logical operators. In this case, the parentheses can affect the condition's evaluation.

When the relevant parentheses are missing from a complex condition, the evaluation order of the logical operators determines the conditions to which the specified logical operators apply and implies the equivalent parentheses. The evaluation order is NOT, AND, OR. Thus, specifying:


  a OR NOT b AND c 

implies and is equivalent to specifying:


  a OR ((NOT b) AND c) 

(See also Section 6.5.9.)

Table 6-5 shows the permissible combinations of conditions, logical operators, and parentheses.

Table 6-5 Combinations of Conditions, Logical Operators, and Parentheses
  In a Conditional Expression In a Left-to-Right Element Sequence
Element Can
Element
Be First?
Can
Element
Be Last?
Element, When Not First, Can Immediately Follow Element, When Not Last, Can Immediately Precede
simple-
condition
Yes Yes OR, NOT, AND, ( OR, AND, )
OR or AND No No simple-condition, ) simple-condition, NOT, (
NOT Yes No OR, AND, ( simple-condition, (
( Yes No OR, NOT, AND, ( simple-condition, NOT, (
) No Yes simple-condition, ) OR, AND, )

For example, Table 6-5 shows whether or not the following element pairs can occur in your program:
Element
Pair
Permitted?
OR NOT Yes
NOT OR No
NOT ( Yes
NOT NOT No

6.5.8 Abbreviated Combined Relation Conditions

When you combine simple or negated simple conditions in a consecutive sequence, you can abbreviate any of the relation conditions except the first. You do this by either:

The general format for abbreviated combined relation conditions is as follows:


The evaluation of a sequence of combined relation conditions proceeds as if the last preceding subject appears in place of the omitted subject and the last preceding relational operator appears in place of the omitted relational operator. The result of these substitutions must form a valid condition. (See Table 6-5.)

When the word NOT appears in a sequence of abbreviated conditions, its treatment depends upon the word that follows it. NOT is considered part of the relational operator when immediately followed by: GREATER, >, LESS, <, EQUAL, or =. Otherwise, NOT is considered a logical operator that negates the relation condition.

Table 6-6 shows abbreviated combined (and negated combined) relation conditions and their expanded equivalents:

Table 6-6 Expanded Equivalents for Abbreviated Combined Relation Conditions
Abbreviated Combined
Relation Condition
Expanded Equivalent
a > b AND NOT < c OR d ((a > b) AND (a NOT < c)) OR (a NOT < d)
a NOT = b OR c (a NOT = b) OR (a NOT = c)
NOT a = b OR c (NOT (a = b)) OR (a = c)
NOT (a GREATER b OR < c) NOT ((a GREATER b) OR (a < c))
a / b NOT = c AND NOT d ((a / b) NOT = c) AND (NOT ((a / b) NOT = d))
NOT (a NOT > b AND c AND NOT d) NOT ((((a NOT > b) AND (a NOT > c)) AND (NOT (a NOT > d))))

6.5.9 Condition Evaluation Rules

Parentheses can specify the evaluation order in complex conditions. Conditions in parentheses are evaluated first. In nested parentheses, evaluation starts with the innermost set of parentheses. It proceeds to the outermost set.

Conditions are evaluated in a hierarchical order when there are no parentheses in a complex condition. This same order applies when all sets of parentheses are at the same level (none are nested). The hierarchy is shown in the following list:

  1. Values for arithmetic expressions
  2. Truth values for simple conditions, in this order:
    1. Relation
    2. Class
    3. Condition-name
    4. Switch-status
    5. Sign
    6. Success/failure
  3. Truth values for negated simple conditions
  4. Truth values for combined conditions, in this order:
    1. AND logical operators
    2. OR logical operators
  5. Truth values for negated combined conditions

In the absence of parentheses, the order of evaluation of consecutive operations at the same hierarchical level is from left to right.

6.6 Common Rules and Options for Data Handling

This section describes the rules and options that apply when statements handle data. Data handling includes the following:

6.6.1 Arithmetic Operations

The arithmetic statements begin with the verbs ADD, COMPUTE, DIVIDE, MULTIPLY, and SUBTRACT. When an operand in these statements is a data item, its PICTURE must be numeric and specify no more than 31 digit positions. However, operands do not have to be the same size, nor must they have the same USAGE. Conversion and decimal point alignment occur throughout the calculation.

When you write an arithmetic statement, you specify one or more data items to receive the results of the operation. These data items are called resultant identifiers. However, the evaluation of each arithmetic statement can also use an intermediate data item. An intermediate data item is a compiler-supplied signed numeric data item that the program cannot access. It stores the results of intermediate steps in the arithmetic operation before moving the final value to the resultant identifiers.

When the final value of an arithmetic operation is moved to the resultant identifiers, it is transferred according to MOVE statement rules. Rounding and size error condition checking occur just before this final move. (See the Section 6.8.22 statement, Section 6.6.4, ON SIZE ERROR Phrase, and Section 6.6.3, ROUNDED Phrase.)

6.6.2 Multiple Receiving Fields in Arithmetic Statements

An arithmetic statement can move its final result to more than one data item. In this case, the statement is said to have multiple receiving fields (or multiple results). The statement operates as if it had been written as a series of statements. The following example illustrates these steps. The first statement in the example is equivalent to the four that follow it. (Temp is an intermediate data item.)


ADD a, b, c TO c, d (c), e 
 
ADD a, b, c GIVING temp 
ADD temp TO c 
ADD temp TO d (c) 
ADD temp TO e 

6.6.3 ROUNDED Phrase

The ROUNDED phrase allows you to specify rounding at the end of an arithmetic operation. The rounding operation adds 1 to the absolute value of the low-order digit of the resultant identifier if the absolute value of the next least significant (lower-valued) digit of the intermediate data item is greater than or equal to 5.

When the PICTURE string of the resultant identifier represents the low-order digit positions with the P character, rounding or truncation is relative to the rightmost integer position for which the compiler allocates storage. Therefore, when PIC 999PPP describes the item, the value 346711 is rounded to 347000.

If you do not use the ROUNDED phrase, any excess low-order digits in the arithmetic result are truncated when the result is moved to the resultant identifiers.

6.6.4 ON SIZE ERROR Phrase

The ON SIZE ERROR phrase allows you to specify an action for your program to take when a size error condition exists.

The NOT ON SIZE ERROR phrase allows you to specify an action for your program to take when a size error condition does not exist.

The format is as follows:


stment is an imperative statement.

Size error checking occurs after decimal point alignment. Rounding occurs before size error checking. Also, truncation of rightmost digits occurs before size error checking.

A size error condition is caused by the following:

In the second case above, the size error condition affects the contents of only those resultant identifiers for which the size error exists.

When a size error condition occurs and the statement contains an ON SIZE ERROR phrase:

  1. When standard arithmetic is in effect, the values of those resultant identifiers for which the size error exists are the same as before the operation began; when native arithmetic is in effect, those values are undefined.
  2. The values of those resultant identifiers for which no size error exists are the same as they would have been if the size error condition had not occurred for any of the resultant identifiers.
  3. The imperative statement in the ON SIZE ERROR phrase executes.
  4. The NOT ON SIZE ERROR phrase, if specified, is ignored.
  5. Control is transferred to the end of the arithmetic statement unless control has been transferred by executing the imperative statement of the ON SIZE ERROR phrase.
  6. When a size error occurs in any arithmetic statement with multiple results, your program must analyze the results to determine where the size error occurred.

When a size error condition occurs and the statement does not contain an ON SIZE ERROR phrase:

  1. The values of those resultant identifiers for which the size error exists are undefined.
  2. The NOT ON SIZE ERROR phrase, if specified, is ignored.
  3. Control is transferred to the end of the arithmetic statement.

When a size error condition does not occur:

  1. The ON SIZE ERROR phrase, if specified, is ignored.
  2. The imperative-statement in the NOT ON SIZE ERROR phrase, if specified, is executed.
  3. Control is transferred to the end of the arithmetic statement unless control has been transferred by executing the imperative statement of the NOT ON SIZE ERROR phrase.

If you use the ADD or SUBTRACT statements with the CORRESPONDING phrase, any individual operation can cause a size error condition. In this instance, the imperative statement in the ON SIZE ERROR phrase executes after all the individual additions or subtractions are complete.


Previous Next Contents Index