Compaq COBOL
Reference Manual


Previous Contents Index

6.8.11 DIVIDE

Function

The DIVIDE statement divides one or more numeric data items by another and sets the value of the data items equal to the quotient, optionally storing the remainder.


num

is a numeric literal or the identifier of an elementary numeric item.

rsult

is the identifier of an elementary numeric item or an elementary numeric edited item. However, in Format 1, rsult must be an elementary numeric item. It is the resultant identifier.

stment

is an imperative statement executed when a size error condition has occurred.

stment2

is an imperative statement executed when no size error condition has occurred.

remaind

is the identifier of an elementary numeric item or an elementary numeric edited item.

General Rules

Format 1

  1. The value of num is divided into the value of the first rsult. This quotient replaces the current value of the first rsult. The process repeats for each of the other occurrences of rsult.

Format 2

  1. The value of the first num is divided into the value of the second. This quotient replaces the current value of each rsult.

Format 3

  1. The value of the first num is divided by the value of the second. This quotient replaces the current value of each rsult.

Formats 4 and 5

  1. These formats produce a remainder (remaind) from the division operation. The remainder is the result of subtracting the product of the quotient (rsult) and the divisor from the dividend.
    If rsult refers to a numeric edited item, the quotient is an equivalent unedited intermediate field. For example, if you describe rsult with the PICTURE -ZZ.99, the compiler uses an intermediate field with the implicit PICTURE S99V99.
    When the ROUNDED phrase is present, the remainder computation uses an intermediate quotient field that is truncated rather than rounded.
  2. The computation described in rule 4 determines the accuracy of remaind. It includes decimal point alignment and truncation (not rounding) required by the description of remaind.
  3. When the ON SIZE ERROR phrase is present:

Additional References

Examples

The following example shows a run-time message issued for an illegal attempt to divide by zero:


%COB-E-DIVBY-ZER, divide by zero; execution continues 

Each of the examples assume the following data descriptions and initial values. The initial values are listed in the righthand column:

INITIAL VALUES


     03  ITEMA  PIC 99V99 VALUE 9.                        9.00 
     03  ITEMB  PIC 99V99 VALUE 24.                       24.00 
     03  ITEMC  PIC 99V99 VALUE 8.                        8.00 
     03  ITEMD  PIC 99    VALUE 12.                       12 
     03  ITEME  PIC 99V99 VALUE 3.                        3.00 
     03  ITEMF  PIC 99    VALUE 47.                       47 
     03  ITEMG  PIC 9     VALUE 9.                        9 
     03  ITEMH  PIC 9     VALUE 2.                        2 
     03  ITEMI  PIC 99    VALUE 4.                        4 

In each of the following examples, the righthand column shows the results of the DIVIDE operation.

  1. Without GIVING phrase or rounding: RESULTS


    DIVIDE ITEMA INTO ITEMB.                          ITEMB = 2.66 
    

  2. With rounding:


    DIVIDE ITEMA INTO ITEMB ROUNDED.                  ITEMB = 2.67 
    

  3. GIVING phrase:


    DIVIDE ITEMA INTO ITEMB                           ITEMD = 2 
      GIVING ITEMD. 
    

  4. GIVING phrase with rounding:


    DIVIDE ITEMA INTO ITEMB                           ITEMD = 3 
      GIVING ITEMD ROUNDED. 
    

  5. BY phrase:


    DIVIDE ITEMA BY ITEMB                             ITEMD = 0 
      GIVING ITEMD. 
    

  6. REMAINDER phrase:


    DIVIDE ITEMA INTO ITEMB                           ITEMD = 2 
      GIVING ITEMD REMAINDER ITEMC.                   ITEMC = 6.00 
    

  7. REMAINDER phrase with rounding:


    DIVIDE ITEMA INTO ITEMB                           ITEMD = 3 
      GIVING ITEMD ROUNDED REMAINDER ITEMC.           ITEMC = 6.00 
    

  8. Effects of decimal alignment on quotient and remainder:


    DIVIDE ITEMA INTO ITEMB                           ITEME = 2.66 
      GIVING ITEME REMAINDER ITEMC.                   ITEMC =  .06 
    

  9. Effects of decimal alignment on remainder and quotient with rounding:


    DIVIDE ITEMA INTO ITEMB                           ITEME = 2.67 
      GIVING ITEME ROUNDED REMAINDER ITEMC.           ITEMC =  .06 
    

  10. The ON SIZE ERROR phrase: (IF ON SIZE ERROR occurs on an occurrence of rsult, the contents of that occurrence of rsult are unchanged.)


    DIVIDE ITEME INTO ITEMF                           
       GIVING ITEMG ITEMD                             ITEMD = 15 
       ON SIZE ERROR                                  ITEMG = 9 
         MOVE 0 TO ITEMH.                             ITEMH = 0 
    

  11. The ON SIZE ERROR phrase:
    (IF ON SIZE ERROR occurs on remaind, the contents of remaind are unchanged.)


    DIVIDE ITEMD INTO ITEMF                           
       GIVING ITEMI REMAINDER ITEMG                   ITEMI = 3 
       ON SIZE ERROR                                  ITEMG = 9 
         MOVE 0 TO ITEMH.                             ITEMH = 0 
    

  12. The NOT ON SIZE ERROR phrase:


    DIVIDE ITEMD INTO ITEMF                           ITEMI = 3 
       GIVING ITEMI REMAINDER ITEMC                   ITEMC = 11.00 
       ON SIZE ERROR                                  
          MOVE 0 TO ITEMH                             
       NOT ON SIZE ERROR                              
          MOVE 1 TO ITEMH.                            ITEMH = 1 
    

6.8.12 EVALUATE

Function

The EVALUATE statement selects a program action based on the evaluation of one or more conditions.


subj-item

is an identifier, an arithmetic or conditional expression, or a literal other than the figurative constant ZERO.

cond

is a conditional expression.

obj-item

is a literal, an identifier, or an arithmetic expression.

stment1

is an imperative statement.

stment2

is an imperative statement.

Syntax Rules

  1. Before the first WHEN phrase: (a) subj-item and the words TRUE and FALSE are called subjects, and (b) all subjects comprise the subject set.
  2. In a WHEN phrase: (a) ANY, TRUE, FALSE, and the operands are called objects, and (b) all objects in a single WHEN phrase comprise an object set.
  3. The number of objects in the object set must equal the number of subjects in the subject set.
  4. The words THROUGH and THRU are equivalent.
  5. Two obj-items connected by a THROUGH phrase:
  6. Each object in an object set must correspond to the subject by appearing in the same ordinal position as in the subject set. For each pair:
  7. Conditional expressions can be simple or complex conditions.

General Rules

Evaluation Procedure

  1. The EVALUATE statement operates as if each subject and object were evaluated and assigned one of the following:
    The statement assigns values according to the following rules:
      Condition Value Assigned
    a. An identifier for a subject, or for an object without the NOT or THROUGH phrases Value and class of the identifier's data item.
    b. A literal for a subject, or for an object without the NOT or THROUGH phrases Value and class of the literal.
    c. The figurative constant ZERO for an object without the NOT or THROUGH phrases Value and class of the corresponding subject.
    d. An arithmetic expression for a subject, or for an object without the NOT or THROUGH phrases Numeric value, according to the rules for evaluating arithmetic expressions.
    e. A conditional expression for a subject or a conditional expression for an object Truth value, according to the rules for evaluating conditional expressions.
    f. TRUE or FALSE as a subject or object Truth value: true for the word TRUE and false for the word FALSE.
    g. ANY for an object No further evaluation.
    h. THROUGH phrase for an object without the NOT phrase The range of values is all values that, when compared to the subject, are greater than or equal to the first obj-item and less than or equal to the second obj-item. If the first obj-item is greater than the second obj-item, there are no values in the range.
    i. Object with the NOT phrase All values not equal to the value (or range of values) that would be assigned without the NOT phrase.

Comparison Procedure

  1. After values have been assigned to each subject and object, comparison begins. It proceeds as if the values were compared to determine if any WHEN phrase satisfies the subject set.
  2. EVALUATE compares each object in the object set of the first WHEN phrase to the subject in the same ordinal position in the subject set. The comparison is satisfied if one of the following conditions is true:
  3. If the comparison is satisfied for every object in an object set, the WHEN phrase containing that object set is selected.
  4. If the comparison is not satisfied for every object in an object set, the object set does not satisfy the subject set.
  5. The comparison procedure is repeated for each object set, in order of appearance, until one of these conditions occur:

Execution Procedure

  1. If a WHEN phrase is selected, execution continues with stment1.
  2. If no WHEN phrase is selected, and a WHEN OTHER phrase is present, execution continues with stment2.
  3. EVALUATE statement execution ends when one of the following conditions occurs:

Additional References

Examples

In these examples, the results are shown as either data item values or procedure branches. However, stment can be any imperative statement, including multiple statements.

  1. One condition.


    EVALUATE ITEMA 
      WHEN "A01"            MOVE 1 TO ITEMB 
      WHEN "A02" THRU "C16" MOVE 2 TO ITEMB 
      WHEN "C20" THRU "L86" MOVE 3 TO ITEMB 
      WHEN "R20"            ADD 1 TO R-TOT 
                            GO TO  PROC-A 
      WHEN OTHER            MOVE 0 TO ITEMB 
      END-EVALUATE. 
    

    Samples:
    ITEMA Result
    "A15" ITEMB = 2
    "P80" ITEMB = 0
    "F01" ITEMB = 3
    "M19" ITEMB = 0
    "A01" ITEMB = 1
    "R20" PROC-A

  2. Multiple conditions. This example shows how EVALUATE can represent a decision table.


    EVALUATE LOW-STOK  WEEK-USE  LOC-VNDR ON-ORDER 
      WHEN   "Y",    16 THRU 999,  ANY,   "N" GO TO RUSH-ORDER 
      WHEN   "Y",    16 THRU 999,  ANY,   "Y" GO TO NORMAL-ORDER 
      WHEN   "Y",     8 THRU 15,   "N",   "N" GO TO RUSH-ORDER 
      WHEN   "Y",     8 THRU 15,   "N",   "Y" GO TO NORMAL-ORDER 
      WHEN   "Y",     8 THRU 15,   "Y",   "N" GO TO NORMAL-ORDER 
      WHEN   "Y",     0 THRU 7,    ANY,   "N" GO TO NORMAL-ORDER 
      WHEN   "N",       ANY,       ANY,   "Y" GO TO CANCEL-ORDER 
      END-EVALUATE. 
    

    Samples:
    LOW-STOK WEEK-USE LOC-VNDR ON-ORDER Result
    "Y" 38 "N" "Y" NORMAL-ORDER
    "N" 20 "Y" "Y" CANCEL-ORDER
    "N" 12 "Y" "N" next statement
    "Y" 12 "Y" "N" NORMAL-ORDER
    "Y" 12 "Y" "Y" next statement
    "Y" 40 "N" "N" RUSH-ORDER

  3. Relation conditions and arithmetic expressions.


    EVALUATE-ITEM-ROUTINE. 
    * 
    * After the imperative statement in the selected WHEN phrase 
    * executes (for example PERFORM PROC-A), control then 
    * transfers to the first statement following the end of the 
    * EVALUATE statement (MOVE A TO B). 
    * 
     
       EVALUATE ITEMA > 6 AND < 30, 8 * ITEMB - 1 
          WHEN   TRUE,              5 * ITEMC     PERFORM PROC-A 
          WHEN   FALSE,             ITEMC         PERFORM PROC-B 
          WHEN   ITEMC > 12,        -1            PERFORM PROC-C 
          WHEN   TRUE,              NOT 7 THRU 40 PERFORM PROC-D 
          WHEN   OTHER                            PERFORM PROC-E 
       END-EVALUATE. 
       MOVE A TO B. 
    

    Samples:
    ITEMA ITEMB ITEMC Result
    12 2 3 PROC-A
    25 0 14 PROC-C
    30 0 14 PROC-E
    6 3 23 PROC-B
    14 0 5 PROC-D
    5 0 11 PROC-C

Consider how the EVALUATE statement works using the values in the previous sample:

  1. The value of the first subject is a truth value (General Rule 1e). ITEMA is not greater than 6 and less than 30; therefore, the value of the first subject is false.
  2. The value of the second subject is a numeric value (General Rule 1d):
    8 * 0-1 = -1.
  3. When the first WHEN phrase is evaluated:
  4. When the second WHEN phrase is evaluated:
  5. When the third WHEN phrase is evaluated:
  6. The statement following the third WHEN phrase is PERFORM PROC-C. Control transfers to that procedure, and the EVALUATE statement ends.

6.8.13 EXIT

Function

The EXIT statement provides a common logical end point for a series of procedures.


Syntax Rule

The EXIT statement must appear in a sentence by itself and be the only sentence in the paragraph.

General Rule

The EXIT statement associates a procedure-name with a point in the program. It has no other effect on program compilation or execution.

Example


REPORT-INVALID-ADD. 
    DISPLAY " ". 
    DISPLAY "INVALID ADDITION". 
    DISPLAY "RECORD ALREADY EXISTS". 
    DISPLAY "UPDATE ATTEMPT: " UPDATE-REC. 
    DISPLAY "EXISTING RECORD: " OLD-REC. 
REPORT-INVALID-ADD-EXIT. 
    EXIT. 

6.8.14 EXIT PROGRAM

Function

The EXIT PROGRAM statement marks the logical end of a called program.


Syntax Rules

  1. If the EXIT PROGRAM statement is in a consecutive sequence of imperative statements, it must be the last statement in that sequence.
  2. The EXIT PROGRAM statement cannot appear in a GLOBAL USE procedure.

General Rules

  1. If EXIT PROGRAM executes in a program that is not a called program, it causes execution to continue with the next executable statement. See the Compaq COBOL User Manual for information on how the v3 setting of the standard compiler option affects the EXIT PROGRAM statement.
  2. If the EXIT PROGRAM statement executes in a called program without the INITIAL clause in its PROGRAM-ID paragraph, execution continues with the next executable statement after the CALL statement in the calling program.
    The state of the calling program does not change; it is the same as when the program executed the CALL statement. However, the contents of data items and the positioning of data files shared by the calling and called programs can change.
    The state of the called program does not change. However, the called program is considered to have reached the ends of the ranges of all PERFORM statements it executed. Therefore, an error does not occur if the called program is entered again during image execution.
  3. When EXIT PROGRAM executes in a called program with the INITIAL attribute, the actions described in General Rule 2 also apply. In addition, executing the EXIT PROGRAM statement is equivalent to executing a CANCEL statement that names the called program.
  4. Special handling of the EXIT PROGRAM statement is performed when you specify the standard compiler option with the v3 setting on the compiler command line. See the Compaq COBOL User Manual for more information.

Example


TEST-RETURN. 
    IF ITEMA NOT = ITEMB 
         MOVE ITEMA TO ITEMB 
         EXIT PROGRAM. 


Previous Next Contents Index