Compaq COBOL
Reference Manual


Previous Contents Index


        DISPLAY "TEST 7". 
        COPY "LIBRARY-1". 
        move 1 to extra-item. 
        COPY "LIBRARY-2". 

Format 2 (OpenVMS)

  1. record-name can be a nonnumeric literal or COBOL word formed according to the rules for user-defined names. It represents a complete or partial Oracle CDD/Repository pathname specifying the Oracle CDD/Repository record description to be copied into the source program. If record-name is not a literal, the compiler translates hyphens in the COBOL word to underline characters.
    The resultant pathname must conform to all rules for forming Oracle CDD/Repository pathnames.
  2. Table 8-1 shows the representation of Oracle CDD/Repository data types in the Compaq COBOL compiler. It lists the data types that can be specified using CDO with the corresponding COBOL data item picture. Note that COBOL does not have an equivalent specification for some data types.

    Table 8-1 Oracle CDD/Repository Data Types and Compaq COBOL Equivalents (OpenVMS)
    Oracle CDD/Repository Data Type Compaq COBOL Equivalent
    BIT l No equivalent 1
    SIGNED BYTE l s No equivalent 1
    UNSIGNED BYTE l s No equivalent 1
    D_FLOATING s COMP-2 (with /FLOAT=D_FLOAT)
    D_FLOATING COMPLEX s No equivalent 1
    DATE No exact equivalent 2
    F_FLOATING s COMP-1 (with /FLOAT=D_FLOAT or /FLOAT=G_FLOAT)
    F_FLOATING COMPLEX s No equivalent 1
    G_FLOATING s COMP-2 (with /FLOAT=G_FLOAT)
    G_FLOATING COMPLEX s No equivalent 1
    H_FLOATING s No equivalent 1
    H_FLOATING COMPLEX s No equivalent 1
    IEEE S_FLOATING COMP-1 (with /FLOAT=IEEE_FLOAT)
    IEEE T_FLOATING COMP-2 (with /FLOAT=IEEE_FLOAT)
    SIGNED LONGWORD l s S9(9) COMP
    UNSIGNED LONGWORD l s No exact equivalent 3
    UNSIGNED NUMERIC l s 9(m)V9(n)
    SIGNED NUMERIC LEFT SEPARATE l s S9(m)V9(n) LEADING SEPARATE
    SIGNED NUMERIC LEFT OVERPUNCHED l s S9(m)V9(n) LEADING
    SIGNED NUMERIC RIGHT SEPARATE l s S9(m)V9(n) TRAILING SEPARATE
    SIGNED NUMERIC RIGHT OVERPUNCHED l s S9(m)V9(n) TRAILING
    SIGNED OCTAWORD l s S9(31) COMP
    UNSIGNED OCTAWORD l s No exact equivalent 3
    PACKED NUMERIC l s S9(m)V9(n) COMP-3
    SIGNED QUADWORD l s S9(18) COMP
    UNSIGNED QUADWORD l s No exact equivalent 3
    TEXT m CHARACTERS X(m)
    UNSPECIFIED m BYTES X(m)
    VARYING STRING m CHARACTERS No equivalent 1
    VIRTUAL FIELD Ignored 4
    SIGNED WORD l s S9(4) COMP
    UNSIGNED WORD l s No exact equivalent 3
    POINTER POINTER
    SEGMENTED STRING No equivalent 1
    ZONED No equivalent 1


    1COBOL has no equivalent for this data type. A warning diagnostic will be issued for such an item that is part of a record description entry. The compiler will treat that item as if it had been specified as an alphanumeric data item that occupies that same number of bytes.
    2COBOL has no exact equivalent for this data type. A warning diagnostic will be issued for such an item that is part of a record description entry. The compiler will treat that item as if it had been specified as PIC S9(11)V9(7) COMP. (This gives the item units of seconds.)
    3COBOL has no exact equivalent for this data type. A warning diagnostic will be issued for such an item that is part of a record description entry. The compiler will treat that item as if it had been specified as the corresponding unsigned COMP data type.
    4The Compaq COBOL compiler ignores this data item and all its phrases.

    l The total number of digits in the item.
    s The decimal offset to l.


    The method for describing the assumed decimal point is different in the two products. In a COBOL picture, the decimal position is directly indicated by the symbol V or implied by the symbol P. In CDO, scaled numbers are specified by two integers: (1) the first integer represents the total number of decimal digits that the item represents, and (2) the second integer represents the decimal offset to the first integer. These are indicated in Table 8-1 by l and s, respectively.
    For example, the COBOL data item described by PIC 9(4)V99 is equivalent to the CDO entry UNSIGNED NUMERIC 6 DIGITS SCALE -2. Similarly, the CDO entry SIGNED NUMERIC LEFT SEPARATE NUMERIC 6 DIGITS SCALE 2 is equivalent to the COBOL description PIC S9(6)PP SIGN IS LEADING SEPARATE. You can also represent digits to the right of the decimal point in CDO with the FRACTIONS phrase. For example, instead of UNSIGNED NUMERIC 6 DIGITS SCALE -2, you can also use UNSIGNED NUMERIC 6 DIGITS 2 FRACTIONS.
  3. One of the primary goals of Oracle CDD/Repository is to describe data in such a way that data definitions can be shared among many different processors. Many languages have different semantic interpretations for the same physical data. Record descriptions in Oracle CDD/Repository must be able to describe the physical characteristics of data unambiguously. In other words, the logical view of the data must be separated from the physical description if different processors are to access the same record description.
    Compaq COBOL expects numeric literals and PICTURE character-strings to be obtained from Oracle CDD/Repository in standard representation. Whether or not a particular COBOL source program uses the DECIMAL-POINT IS COMMA clause or the CURRENCY SIGN clause in the SPECIAL-NAMES paragraph, the record description that was stored in Oracle CDD/Repository must have used the period (.) to represent the decimal point in numeric literals and PICTURE character-strings, the comma (,) to represent the comma in PICTURE character-strings, and the currency symbol ($) to represent the currency symbol in PICTURE character-strings.
    When the COBOL source program contains the DECIMAL-POINT IS COMMA clause, the Compaq COBOL compiler substitutes commas for decimal points in numeric literals and PICTURE character-strings obtained from Oracle CDD/Repository. It substitutes decimal points for commas in PICTURE character-strings obtained from Oracle CDD/Repository.
    When the COBOL source program contains the CURRENCY SIGN clause, the Compaq COBOL compiler substitutes the currency symbol for the currency sign in PICTURE character-strings obtained from Oracle CDD/Repository. <>

Additional References

Examples Using Format 1

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

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 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)


In Figure 8-1, the repository is named SALES (USA and GERMANY are not used). ANCHOR is the starting directory for the full repository pathname. Repository directories are analogous to OpenVMS Alpha subdirectories. They catalog other repository directories or repository objects, and they are labeled by the paths through the hierarchy that lead to them.

The repository objects are named PAYROLL and INVENTORY. These objects are the named record descriptions stored in Oracle CDD/Repository, and they form the end-points of the repository hierarchy branches. The examples that follow copy these record descriptions.

The full repository pathname provides a unique designation for every directory and object in Oracle CDD/Repository hierarchy. It traces the paths from ANCHOR to the directory or object.

For information on how to create and maintain a hierarchical structure in Oracle CDD/Repository, see the Oracle CDD/Repository documentation set.

Note

Not all Oracle CDD/Repository data types are valid Compaq COBOL data types. See the Technical Notes.

Example 8-7 shows how to use a command file to create the repository directories and objects shown in Figure 8-1 using CDO.

Example 8-7 Command File That Creates Oracle CDD/Repository Directories and Objects in Figure 8-1 (OpenVMS)

define field name 
    datatype is text 
    size 30. 
define field address 
    datatype is text 
    size is 40. 
define field salesman_id 
    datatypes is text 
    size is 5. 
define record salesman. 
    name. 
    address. 
    salesman_id. 
end record. 
define field ytd_sales 
    datatype is right overpunched numeric 
    size is 11 digits 
    scale -2. 
define field ytd_commission 
    datatype is right overpunched numeric 
    size is 11 digits 
    scale -2. 
define field curr_month_sales 
    datatype is right overpunched numeric 
    size is 11 digits 
    scale -2. 
define field curr_month_commission 
    datatype is right overpunched numeric 
    size is 11 digits 
    scale -2. 
define field curr_week_sales 
    datatype is right overpunched numeric 
    size is 11 digits 
    scale -2. 
define field curr_week_commission 
    datatype is right overpunched numeric 
    size is 11 digits 
    scale -2. 
define record payroll_record. 
    salesman. 
    ytd_sales. 
    ytd_commission. 
    curr_month_sales. 
    curr_month_commission. 
    curr_week_sales. 
    curr_week_commission. 
end record. 
define field part_number 
    datatype is right overpunched numeric 
    size is 6 digits. 
define field quantity_on_hand 
    datatype is right overpunched numeric 
    size is 9 digits. 
define field quantity_on_order 
    datatype is right overpunched numeric 
    size is 9 digits. 
define field retail_price 
    datatype is right overpunched numeric 
    size is 8 digits 
    scale -2. 
define field wholesale_price 
    datatype is right overpunched numeric 
    size is 8 digits 
    scale -2. 
define field supplier 
    datatype is text 
    size is 5 characters. 
define record inventory_record. 
    part_number. 
    quantity_on_hand. 
    quantity_on_order. 
    retail_price. 
    wholesale_price. 
    supplier. 
end record. 

Example 8-8 shows the results of copying the repository object PAYROLL in Figure 8-1. The program defines the logical name payroll to be equivalent to the full Oracle CDD/Repository pathname DEVICE:[DIRECTORY.ANCHOR]. Line 27 of the program shows the DCL command used to define the logical name and line 30 contains the COPY FROM DICTIONARY statement.

On OpenVMS Alpha systems, the COPY statement produces lines 31 to 44 in your program listing if you include the /COPY_LIST compiler option. Line 32 is the resulting full Oracle CDD/Repository pathname used by the compiler. Lines 31 and 33 are separator comment lines. Lines 34 to 44 are the COBOL compiler-translated record description entries taken from the PAYROLL repository object in Oracle CDD/Repository.

Example 8-8 Using a Logical Name in a COPY Statement (OpenVMS)

              1 IDENTIFICATION DIVISION. 
              2 PROGRAM-ID.  TEST-CDD. 
              3 * 
              4 *   Copy from CDD/Repository 
              5 *   FILE SECTION 
              6 *           Records:    PERSONNEL 
              7 *                       INVENTORY 
              8 *                       PAYROLL 
              9 * 
             10 *   WORKING-STORAGE SECTION 
             11 *           Records:    SYDNEY 
             12 *                       MAPLE 
             13 *                       FRENCH 
             14 * 
             15 ENVIRONMENT DIVISION. 
             16 INPUT-OUTPUT SECTION. 
             17 FILE-CONTROL. 
             18     SELECT SALES-CDD-FILE 
             19     ASSIGN TO "CDD.TMP". 
             20 DATA DIVISION. 
             21 FILE SECTION. 
             22 FD SALES-CDD-FILE. 
             23 * 
             24 *   To create a logical name entry for the repository object 
             25 *   PAYROLL, use this command: 
             26 * 
             27 *   $ DEFINE PAYROLL_RECORD "DEVICE:[DIRECTORY.ANCHOR]SALES.PAYROLL" 
             28 * 
             29 * 
             30     COPY PAYROLL FROM DICTIONARY. 
L            31 * 
L            32 * _DEVICE:[DIRECTORY.ANCHOR]PAYROLL_RECORD 
L            33 * 
L            34 01  PAYROLL_RECORD. 
L            35     02  SALESMAN. 
L            36         03  NAME            PIC X(30). 
L            37         03  ADDRESS         PIC X(40). 
L            38         03  SALESMAN_ID     PIC X(5). 
L            39     02  YTD_SALES           PIC S9(9)V9(2) SIGN TRAILING. 
L            40     02  YTD_COMMISSION      PIC S9(9)V9(2) SIGN TRAILING. 
L            41     02  CURR_MONTH_SALES    PIC S9(9)V9(2) SIGN TRAILING. 
L            42     02  CURR_MONTH_COMMISSION PIC S9(9)V9(2) SIGN TRAILING. 
L            43     02  CURR_WEEK_SALES     PIC S9(9)V9(2) SIGN TRAILING. 
L            44     02  CURR_WEEK_COMMISSION PIC S9(9)V9(2) SIGN TRAILING. 
             45 
             46     COPY "DEVICE:[DIRECTORY.ANCHOR]INVENTORY_RECORD" FROM DICTIONARY. 
L            47 * 
L            48 * _DEVICE:[DIRECTORY.ANCHOR]INVENTORY_RECORD 
L            49 * 
L            50 01  INVENTORY_RECORD. 
L            51     02  PART_NUMBER         PIC S9(6) SIGN TRAILING. 
L            52     02  QUANTITY_ON_HAND    PIC S9(9) SIGN TRAILING. 
L            53     02  QUANTITY_ON_ORDER   PIC S9(9) SIGN TRAILING. 
L            54     02  RETAIL_PRICE        PIC S9(6)V9(2) SIGN TRAILING. 
L            55     02  WHOLESALE_PRICE     PIC S9(6)V9(2) SIGN TRAILING. 
L            56     02  SUPPLIER            PIC X(5). 
             57 
             58 
        ...      

Example 8-9 shows the results of copying a repository object INVENTORY by specifying its full Oracle CDD/Repository pathname.

In Example 8-9, line 44 contains the COPY FROM DICTIONARY statement. On OpenVMS Alpha systems, this COPY statement produces lines 45 to 54 in your program listing if you include the /COPY_LIST compiler option. Line 46 is the resulting full Oracle CDD/Repository pathname used by the compiler. Lines 45 and 47 are separator comment lines. Lines 48 to 54 are the compiler-translated record description entries taken from the inventory repository object in Oracle CDD/Repository.

Example 8-9 Using a Full Pathname in a COPY Statement (OpenVMS)

       44      COPY "DEVICE:[DIRECTORY.ANCHOR]SALES.INVENTORY" FROM DICTIONARY. 
L      45 * 
L      46 * DEVICE:[DIRECTORY.ANCHOR]SALES.INVENTORY 
L      47 * 
L      48 01  INVENTORY_RECORD. 
L      49      02  PART_NUMBER               PIC 9(6). 
L      50      02  QUANTITY_ON_HAND          PIC S9(9) SIGN TRAILING. 
L      51      02  QUANTITY_ON_ORDER         PIC S9(9) SIGN TRAILING. 
L      52      02  RETAIL_PRICE              PIC S9(6)V9(2) SIGN TRAILING. 
L      53      02  WHOLESALE_PRICE           PIC S9(6)V9(2) SIGN TRAILING. 
L      54      02  SUPPLIER                  PIC X(5). 

Figure 8-2 shows a nonhierarchical repository structure. In this example, fields NAME and ADDRESS are used by both the EMPLOYEE-RECORD and the CUSTOMER-RECORD. As such, they are defined in a separate directory (COMMON_FIELD_DEFINITIONS). The fields PART and PART_NUMBER are used exclusively by the INVENTORY_RECORD. As such, they are defined in the INVENTORY directory. This functionality is only available in CDO formatted repositories.

Figure 8-2 Nonhierarchical Repository Structure (OpenVMS)



Previous Next Contents Index