[an error occurred while processing this directive]

HP OpenVMS Systems Documentation

Content starts here

HP COBOL
Reference Manual


Previous Contents Index

Additional References

  • Oracle CDD/Repository documentation set

Examples Using Format 1

The examples that follow copy library text from two library files:

  • Contents of CUSTFILE.LIB:


    01[Tab]CUSTOMER-REC.
    [Tab]03  CUST-REC-KEY[Tab]PIC X(03) VALUE "KEY".
    [Tab]03  CUST-NAME[Tab]PIC X(25).
    [Tab]03  CUST-ADDRESS.
    [Tab]    05  CUST-CUST-STREET[Tab]PIC X(20).
    [Tab]    05  CUST-CITY[Tab]PIC X(20).
    [Tab]    05  CUST-STATE[Tab]PIC XX.
    [Tab]    05  CUST-ZIP[Tab]PIC 9(5).
    * THE COMPILER IGNORES COMMENT LINES AND BLANK LINES
    
    * FOR MATCHING PURPOSES
    [Tab]03  CUST-ORDERS OCCURS XYZ TIMES.
    [Tab]    05  CUST-ORDER[Tab]PIC 9(6).
    [Tab]    05  CUST-ORDER-DATE[Tab]PIC 9(6).
    [Tab]    05  CUST-ORDER-AMT[Tab]PIC 9(R)V99.
    
  • Contents of CPROC01.LIB:


    [Tab]ADD CUST-ORDER-AMT (X) TO TOTAL-ORDERS.
    [Tab]COMPUTE AVERAGE-ORDER = (TOTAL-ORDERS - CANCELED-ORDERS)
    [Tab]  / NUMBER-ORDERS.
    [Tab]MOVE CUST-REC-KEY
    [Tab]  OF CUSTOMER-REC TO CUST-ID (X).
    [Tab]MOVE CUST-REC-KEY
    [Tab]  OF KEY-HOLD TO NEW-KEY.
    

In the following examples, the original source program text is shown in lowercase text. The text that is copied is shown in uppercase. (The messages in these examples are in OpenVMS Alpha and I64 format.)

Example 8-1 shows the results of a COPY statement with no REPLACING phrase. The compiler copies the library text without change. In this example, syntax errors result from invalid library text.

Example 8-1 COPY with No REPLACING Phrase

            1 identification division.
            2 program-id. cust01.
            3 data division.
            4 working-storage section.
            5 copy custfile.
L           6 01  CUSTOMER-REC.
L           7     03  CUST-REC-KEY        PIC X(03) VALUE "KEY".
L           8     03  CUST-NAME   PIC X(25).
L           9     03  CUST-ADDRESS.
L          10         05  CUST-CUST-STREET        PIC X(20).
L          11         05  CUST-CITY       PIC X(20).
L          12         05  CUST-STATE      PIC XX.
L          13         05  CUST-ZIP        PIC 9(5).
L          14 * THE COMPILER IGNORES COMMENT LINES AND BLANK LINES
L          15
L          16 * FOR MATCHING PURPOSES
L          17     03  CUST-ORDERS OCCURS XYZ TIMES.
                                         1        2
%COBOL-F-SYN5  121, (1) Invalid OCCURS clause
%COBOL-W-RESTART  297, (2) Processing of source program resumes at this point
L          18         05  CUST-ORDER      PIC 9(6).
L          19         05  CUST-ORDER-DATE PIC 9(6).
L          20         05  CUST-ORDER-AMT  PIC 9(R)V99.
                                              1
%COBOL-F-ERROR  178, (1) Invalid repetition factor

Example 8-2 shows the results of replacing a word ("xyz") by a literal (6).

Example 8-2 Replacing a Word with a Literal

           22 copy custfile replacing xyz by 6.
L          23 01  CUSTOMER-REC.
L          24     03  CUST-REC-KEY        PIC X(03) VALUE "KEY".
L          25     03  CUST-NAME   PIC X(25).
L          26     03  CUST-ADDRESS.
L          27         05  CUST-CUST-STREET        PIC X(20).
L          28         05  CUST-CITY       PIC X(20).
L          29         05  CUST-STATE      PIC XX.
L          30         05  CUST-ZIP        PIC 9(5).
L          31 * THE COMPILER IGNORES COMMENT LINES AND BLANK LINES
L          32
L          33 * FOR MATCHING PURPOSES
LR         34     03  CUST-ORDERS OCCURS 6   TIMES.
L          35         05  CUST-ORDER      PIC 9(6).
L          36         05  CUST-ORDER-DATE PIC 9(6).
L          37         05  CUST-ORDER-AMT  PIC 9(R)V99.
                                              1
%COBOL-F-PICREPEAT  178, (1) Invalid repetition factor

Example 8-3 shows the results of replacing a word ("xyz") by a literal (6), and pseudo-text by pseudo-text. The compiler recognizes R as a text-word because parentheses enclose it. The other R characters are not text-words; they are part of other text-words.

Example 8-3 Replacing a Word by a Literal and Pseudo-Text by Pseudo-Text

           39 copy custfile replacing xyz by 6, ==r== by ==4==.
L          40 01  CUSTOMER-REC.
L          41     03  CUST-REC-KEY        PIC X(03) VALUE "KEY".
L          42     03  CUST-NAME   PIC X(25).
L          43     03  CUST-ADDRESS.
L          44         05  CUST-CUST-STREET        PIC X(20).
L          45         05  CUST-CITY       PIC X(20).
L          46         05  CUST-STATE      PIC XX.
L          47         05  CUST-ZIP        PIC 9(5).
L          48 * THE COMPILER IGNORES COMMENT LINES AND BLANK LINES
L          49
L          50 * FOR MATCHING PURPOSES
LR         51     03  CUST-ORDERS OCCURS 6   TIMES.
L          52         05  CUST-ORDER      PIC 9(6).
L          53         05  CUST-ORDER-DATE PIC 9(6).
LR         54         05  CUST-ORDER-AMT  PIC 9(4)V99.

Example 8-4 shows the results of matching a nonnumeric literal. The opening and closing quotation marks are part of the text-word.

Example 8-4 Matching a Nonnumeric Literal

           129 copy custfile replacing xyz by 6, ==r== by ==4==
           130    "KEY" by "abc".
L          131 01  CUSTOMER-REC.
LR         132     03  CUST-REC-KEY        PIC X(03) VALUE "abc" .
L          133     03  CUST-NAME   PIC X(25).
L          134     03  CUST-ADDRESS.
L          135         05  CUST-CUST-STREET        PIC X(20).
L          136         05  CUST-CITY       PIC X(20).
L          137         05  CUST-STATE      PIC XX.
L          138         05  CUST-ZIP        PIC 9(5).
L          139 * THE COMPILER IGNORES COMMENT LINES AND BLANK LINES
L          140
L          141 * FOR MATCHING PURPOSES
LR         142     03  CUST-ORDERS OCCURS 6   TIMES.
L          143         05  CUST-ORDER      PIC 9(6).
L          144         05  CUST-ORDER-DATE PIC 9(6).
LR         145         05  CUST-ORDER-AMT  PIC 9(4)V99.

Example 8-5 shows the results of a multiple-line pseudo-text replacement item. The replacement item starts after the pseudo-text delimiter on line 167 and ends before the delimiter on line 169. The continuation area on the new line (172) contains the same characters as line 168 in the pseudo-text replacement item. This example is not a recommended use of the COPY statement. It only shows the mechanics of the statement.

Example 8-5 Multiple-Line Pseudo-Text Replacement Item

         166  copy custfile replacing xyz by 6, ==r== by ==4==
         167      "KEY" by =="abc".
         168 * cust-number is a new field
         169      03  cust-number pic 9(8)==.
L        170  01  CUSTOMER-REC.
LR       171      03  CUST-REC-KEY        PIC X(03) VALUE "abc".
LR       172 * cust-number is a new field
LR       173      03  cust-number pic 9(8).
L        174      03  CUST-NAME   PIC X(25).
L        175      03  CUST-ADDRESS.
L        176          05  CUST-CUST-STREET        PIC X(20).
L        177          05  CUST-CITY       PIC X(20).
L        178          05  CUST-STATE      PIC XX.
L        179          05  CUST-ZIP        PIC 9(5).
L        180 * THE COMPILER IGNORES COMMENT LINES AND BLANK LINES
L        181
L        182 * FOR MATCHING PURPOSES
LR       183      03  CUST-ORDERS OCCURS 6   TIMES.
L        184          05  CUST-ORDER      PIC 9(6).
L        185          05  CUST-ORDER-DATE PIC 9(6).
LR       186          05  CUST-ORDER-AMT  PIC 9(4)V99.

Example 8-6 shows the results of matching pseudo-text that includes separators.

The replacement phrase in line 210 fails to match the library text in line 212. The text-matching argument contains one text-word: the 13 characters beginning with c and ending with a period (.). The period is not a separator period, because it is not followed by a space. This argument fails to match the two text-words on line 212. The two text-words are: (1) CUSTOMER-REC and (2) the separator period.

The replacement phrase in line 211 replaces library text on line 215. The text-matching argument contains the same two text-words that are in the library text: (1) CUST-ADDRESS and (2) the separator period.

Example 8-6 Matching Pseudo-Text That Includes Separators

           209 copy custfile replacing xyz by 6, ==r== by ==4==
           210    ==customer-rec.== by ==record-a.==
           211    ==cust-address. == by ==customer-address.==.
L          212 01  CUSTOMER-REC.
L          213     03  CUST-REC-KEY        PIC X(03) VALUE "KEY".
L          214     03  CUST-NAME   PIC X(25).
LR         215     03  customer-address.
L          216         05  CUST-CUST-STREET        PIC X(20).
L          217         05  CUST-CITY       PIC X(20).
L          218         05  CUST-STATE      PIC XX.
L          219         05  CUST-ZIP        PIC 9(5).
L          220 * THE COMPILER IGNORES COMMENT LINES AND BLANK LINES
L          221
L          222 * FOR MATCHING PURPOSES
LR         223     03  CUST-ORDERS OCCURS 6   TIMES.
L          224         05  CUST-ORDER      PIC 9(6).
L          225         05  CUST-ORDER-DATE PIC 9(6).
LR         226         05  CUST-ORDER-AMT  PIC 9(4)V99.
           227

Examples Using Format 2 (OpenVMS)

Figure 8-1 represents a hierarchical repository structure for Examples 8-7, 8-8, and 8-9. It contains one repository directory and two repository objects.

Figure 8-1 Hierarchical Repository Structure (OpenVMS)



Previous Next Contents Index