[an error occurred while processing this directive]

HP OpenVMS Systems Documentation

Content starts here

HP COBOL
Reference Manual


Previous Contents Index


WORKING-STORAGE SECTION.
01  TEXT-STRING           PIC X(30).
01  INPUT-MESSAGE         PIC X(60).
01  NAME-ADDRESS-RECORD.
    03  CIVIL-TITLE       PIC X(5).
    03  LAST-NAME         PIC X(10).
    03  FIRST-NAME        PIC X(10).
    03  STREET            PIC X(15).
    03  CITY              PIC X(15).
* Assume CITY ends with "/"
    03  STATE             PIC XX.
    03  ZIP               PIC 9(5).
01 PTR                    PIC 99.
01 HOLD-PTR               PIC 99.
01 LINE-COUNT             PIC 99.

  • Using both delimiters and SIZE:


    DISPLAY " ".
    DISPLAY NAME-ADDRESS-RECORD.
    MOVE SPACES TO TEXT-STRING.
    STRING CIVIL-TITLE DELIMITED BY " "
       " " DELIMITED BY SIZE
       FIRST-NAME DELIMITED BY " "
       " " DELIMITED BY SIZE
       LAST-NAME DELIMITED BY SIZE
         INTO TEXT-STRING.
    DISPLAY TEXT-STRING.
    DISPLAY STREET.
    MOVE SPACES TO TEXT-STRING.
    STRING CITY DELIMITED BY "/"
      ", " DELIMITED BY SIZE
      STATE DELIMITED BY SIZE
      " " DELIMITED BY SIZE
      ZIP DELIMITED BY SIZE
         INTO TEXT-STRING.
    DISPLAY TEXT-STRING.
    

    Results


    Mr.  Smith     Irwin     603 Main St.   Merrimack/     NH03054
    Mr. Irwin Smith
    603 Main St.
    Merrimack, NH 03054
    
    Miss Lambert   Alice     1229 Exeter St.Boston/        MA03102
    Miss Alice Lambert
    1229 Exeter St.
    Boston, MA 03102
    
    Mrs. Gilbert   Rose      8 State Street New York/      NY10002
    Mrs. Rose Gilbert
    8 State Street
    New York, NY 10002
    
    Mr.  Cowherd   Owen      1064 A St.     Washington/    DC20002
    Mr. Owen Cowherd
    1064 A St.
    Washington, DC 20002
    

  • Using the POINTER phrase:


        MOVE 0 TO LINE-COUNT.
        MOVE 1 TO PTR.
    GET-WORD.
        IF LINE-COUNT NOT < 4
          DISPLAY "   " TEXT-STRING
          GO TO GOT-WORDS.
        ACCEPT INPUT-MESSAGE.
        DISPLAY INPUT-MESSAGE.
    SAME-WORD.
        MOVE PTR TO HOLD-PTR.
        STRING INPUT-MESSAGE DELIMITED BY SPACE
          ", " DELIMITED BY SIZE
          INTO TEXT-STRING
          WITH POINTER PTR
          ON OVERFLOW
        STRING "                 " DELIMITED BY SIZE
              INTO TEXT-STRING
              WITH POINTER HOLD-PTR
            DISPLAY "   " TEXT-STRING
        MOVE SPACES TO TEXT-STRING
            ADD 1 TO LINE-COUNT
            MOVE 1 TO PTR
            GO TO SAME-WORD.
        GO TO GET-WORD.
    GOT-WORDS.
        EXIT.
    

    Results


    This
    example
    demonstrates
    how
       This, example, demonstrates,
    the
    STRING
    statement
    can
       how, the, STRING, statement,
    construct
    text
    strings
       can, construct, text,
    using
    the
    POINTER
    phrase
       strings, using, the, POINTER,
       phrase,
    

6.8.37 SUBTRACT

Function

The SUBTRACT statement subtracts one, or the sum of two or more, numeric items from one or more items. It stores the difference in one or more items.


num

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

rsult

is the identifier of an elementary numeric item. However, in Format 2, rsult can be an elementary numeric edited 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.

grp-1

is the identifier of a group item.

grp-2

is the identifier of a group item.

Syntax Rule

CORR is an abbreviation for CORRESPONDING.

General Rules

  1. In Format 1, the values of the operands before the word FROM are summed. This total is then subtracted from each rsult.
  2. In Format 2, the values of the operands before the word FROM are summed. This total is subtracted from the num following the word FROM. The result replaces the current value of each rsult.
  3. In Format 3, data items in grp-1 are subtracted from and stored in the corresponding data items in grp-2.

Additional References

Examples

Each of the examples assume these data descriptions and initial values.

INITIAL VALUES


     03  ITEMA  PIC S99 VALUE -85.             -85
     03  ITEMB  PIC 99 VALUE 2.                  2
     03  ITEMC  VALUE "123".
         05  ITEMD  OCCURS 3 TIMES             1 2 3
                 PIC 9.
     03  ITEME  PIC S99 VALUE -95.             -95
  1. Without GIVING phrase: RESULTS


    SUBTRACT 2 ITEMB FROM ITEMA.                   ITEMA = -89
    
  2. SIZE ERROR clause:
    (When the size error condition occurs and the SIZE ERROR clause is specified, the values of the affected resultant identifiers do not change.)


    SUBTRACT 14 FROM ITEMA, ITEME                  ITEMA = -99
      ON SIZE ERROR                                ITEME = -95
        MOVE 0 TO ITEMB.                           ITEMB = 0
    
  3. NOT ON SIZE ERROR clause:


    SUBTRACT 14 FROM ITEMA                         ITEMA = -99
      ON SIZE ERROR
        MOVE 9 TO ITEMB.
      NOT ON SIZE ERROR
        MOVE 1 TO ITEMB.                           ITEMB =  1
    

  4. Multiple receiving fields:
    (The operations proceed from left to right. Therefore, the subscript for ITEMB is evaluated after the subtraction changes its value.)


    SUBTRACT 1 FROM ITEMB ITEMD (ITEMB).           ITEMB = 1
                                                   ITEMD (1) = 0
    
  5. GIVING phrase:


    SUBTRACT ITEME ITEMD (ITEMB) FROM ITEMA        ITEMB = 8
         GIVING ITEMB.
    
  6. END-SUBTRACT:
    (The first SUBTRACT terminates with END-SUBTRACT. If the SIZE ERROR condition had not occurred, the second SUBTRACT statement would have executed anyway: the value of ITEMA would have been -86.)


    SUBTRACT 10 ITEMB FROM ITEMD (ITEMB)         ITEMD (2) = 2
      ON SIZE ERROR                              ITEMA = 0
          MOVE 0 TO ITEMA
      END-SUBTRACT.
    SUBTRACT 1 FROM ITEMA.                     ITEMA = -1
    

    (The following example shows the usefulness of END-SUBTRACT inside an IF statement. Without it, there would be no way to code the DISPLAY statements.)


    IF ITEMB < 3 AND > 1
       SUBTRACT 1 FROM ITEMD(ITEMB)
          ON SIZE ERROR
             MOVE 0 TO ITEMA
       END-SUBTRACT
       DISPLAY 'yes'
    ELSE
       DISPLAY 'no'.
    

6.8.38 SUPPRESS

Function

The SUPPRESS statement causes the Report Writer Control System (RWCS) to inhibit the presentation of a report group.


Syntax Rule

The SUPPRESS statement can appear only in a USE BEFORE REPORTING Declarative procedure.

General Rules

  1. The SUPPRESS statement inhibits only the presentation of a report-group-name (a 01-level Report Group Description entry).
  2. Each time the presentation of a report group is to be inhibited, the program must execute a SUPPRESS statement.
  3. The SUPPRESS statement directs the Report Writer Control System (RWCS) to inhibit the processing of these report group functions:
    • The presentation of the print lines
    • The processing of all LINE clauses
    • The processing of the NEXT GROUP clause
    • The adjustment of LINE-COUNTER
  4. The SUPPRESS statement does not inhibit the processing of sum counters or control breaks.

Additional References

Example


PROCEDURE DIVISION.
DECLARATIVES.
DET SECTION.
    USE BEFORE REPORTING DETAIL-LINE.
DETA-1.
    IF SORTED-NAME = NAME
        ADD A TO B
        SUPPRESS PRINTING.
    IF NAME = SPACES SUPPRESS PRINTING.
END DECLARATIVES.
MAIN SECTION.
    .
    .
    .


Previous Next Contents Index