Compaq COBOL
Reference Manual


Previous Contents Index

Example 8-10 shows how to use a CDO command file to create the directories and objects shown in Figure 8-2 using CDO. The CDO file is executed from within CDO using the following command:


$ REPOSITORY 
CDO>@FILENAME.CDO 

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

DEFINE DICTIONARY DEVICE:[DIRECTORY.ANCHOR]. 
SET DEFAULT DEVICE:[DIRECTORY.ANCHOR] 
DEFINE DIRECTORY EMPLOYEE. 
DEFINE DIRECTORY CUSTOMER. 
DEFINE DIRECTORY INVENTORY. 
DEFINE DIRECTORY COMMON_FIELD_DEFINITIONS. 
SET DEFAULT DEVICE:[DIRECTORY.ANCHOR]COMMON_FIELD_DEFINITIONS 
DEFINE FIELD NAME DATATYPE IS TEXT SIZE IS 25 CHARACTERS. 
DEFINE FIELD ADDRESS DATATYPE IS TEXT SIZE IS 47 CHARACTERS. 
SET DEFAULT DEVICE:[DIRECTORY.ANCHOR]EMPLOYEE 
DEFINE FIELD DATE_OF_HIRE DATATYPE IS UNSIGNED NUMERIC SIZE IS 8 DIGITS. 
DEFINE FIELD SEX DATATYPE IS TEXT SIZE IS 1 CHARACTER. 
DEFINE FIELD DEPENDENTS DATATYPE IS UNSIGNED NUMERIC SIZE IS 2 DIGITS. 
DEFINE RECORD EMPLOYEE_RECORD. 
[DIRECTORY.ANCHOR]COMMON_FIELD_DEFINITIONS.NAME. 
[DIRECTORY.ANCHOR]COMMON_FIELD_DEFINITIONS.ADDRESS. 
DATE_OF_HIRE. 
SEX. 
DEPENDENTS. 
END RECORD. 
SET DEFAULT DEVICE:[DIRECTORY.ANCHOR]CUSTOMER 
DEFINE FIELD BUSINESS_TYPE DATATYPE IS TEXT SIZE IS 25 CHARACTERS. 
DEFINE FIELD CONTACT_PERSON DATATYPE IS TEXT SIZE IS 25 CHARACTERS. 
DEFINE RECORD CUSTOMER_RECORD. 
[DIRECTORY.ANCHOR]COMMON_FIELD_DEFINITIONS.NAME. 
[DIRECTORY.ANCHOR]COMMON_FIELD_DEFINITIONS.ADDRESS. 
BUSINESS_TYPE. 
CONTACT_PERSON. 
END RECORD. 
SET DEFAULT DEVICE:[DIRECTORY.ANCHOR]INVENTORY 
DEFINE FIELD PART DATATYPE IS TEXT SIZE IS 25 CHARACTERS. 
DEFINE FIELD PART_NUMBER DATATYPE IS TEXT SIZE IS 10 CHARACTERS. 
DEFINE RECORD INVENTORY_RECORD. 
PART. 
PART_NUMBER. 
END RECORD.                                              <>
 

8.1.2 REPLACE

Function

The REPLACE statement is used to replace source program text.


pseudo-text-1

is a text-matching argument that the compiler compares against text-words in the source text.

pseudo-text-2

is a replacement item that the compiler inserts into the source program.

Syntax Rules

  1. A REPLACE statement can be inserted anywhere that a character-string can be used. This statement must be preceded by a separator period unless it is the first statement in a separately compiled program.
  2. A REPLACE statement must be terminated by the separator period.
  3. pseudo-text-1 must contain at least one text-word.
  4. pseudo-text-2 can contain zero, one, or more text-words.
  5. Character-strings within pseudo-text-1 and pseudo-text-2 can be continued.
  6. pseudo-text-1 must not consist entirely of a separator comma or a separator semicolon.
  7. The word REPLACE is considered part of a comment-entry if it appears in the comment-entry or in the place where a comment-entry can appear.

General Rules

Format 1

  1. Each matched occurrence of pseudo-text-1 in the source program is replaced by the corresponding pseudo-text-2.

Format 2

  1. Any text replacement currently in effect is discontinued.

Both Formats

  1. A REPLACE statement remains in effect until the next occurrence of a REPLACE statement or until the end of a separately compiled program has been reached.
  2. Any occurrence of a REPLACE statement in a source program is processed after all COPY statements in the source program have been processed.
  3. pseudo-text-2 must not contain a REPLACE statement.
  4. The comparison operation starts with the leftmost source text word and the first text-matching argument. The compiler compares the entire text-matching argument to an equivalent number of consecutive source text-words.
  5. A text-matching argument matches the source text only if the ordered sequence of text-words that forms the text-matching argument is equal, character for character, to the ordered sequence of source text-words.
    In the matching operation, the compiler treats each occurrence or combination of the following items in source text as a single space:
  6. If no match occurs, the compiler repeats the comparison operation with each successive text-matching argument until a match is found or there are no more text-matching arguments.
  7. If no match occurs after the compiler has compared all of the text-matching arguments, the next successive source text-word becomes the leftmost text-word, and the comparison resumes with the first occurrence of pseudo-text-1.
  8. If a match occurs between a text-matching argument and the source program text, the compiler inserts the replacement text into the source program. The source text-word immediately following the rightmost replaced text-word becomes the leftmost text-word for the next cycle. The comparison cycle resumes with the first occurrence of pseudo-text-1.
  9. The comparison cycles continue until the rightmost text-word in the source text that is within the scope of the REPLACE statement has been either:
  10. The rules for Reference Format determine the sequence of text-words in the source text and the text-matching arguments.
  11. The compiler ignores comment lines and blank lines in the source program and in pseudo-text-1 for matching.
  12. When the compiler inserts pseudo-text-2 in the source program, it inserts comment lines and blank lines in pseudo-text-2 without modification.
  13. Debugging lines are permitted in pseudo-text-1 and pseudo-text-2. The compiler treats the comparison of debugging lines as if the conditional compilation character does not appear in the indicator area.
  14. The compiler cannot determine the syntactic correctness of source text or the source program until all COPY and REPLACE statements have been processed.
  15. Text words that are inserted as a result of a processed REPLACE statement are placed in the source program according to the rules for Reference Format.
  16. When the compiler inserts text words of pseudo-text-2 into the source program, additional spaces may be introduced between text words where spaces already exist (including the assumed space between source lines).
  17. If additional lines are added to the source program as a result of a REPLACE operation, the indicator area of the added lines contains the same character as the line on which the text being replaced begins (unless that line contains a hyphen, in which case the introduced line contains a space).
    If a literal within pseudo-text-2 cannot be contained on a single line without a continuation to another line in the resultant program and the literal is not being placed on a debugging line, additional continuation lines are introduced that contain the remainder of the literal. If replacement requires the continued literal to be continued on a debugging line, the program is in error.

Additional Reference

See Section 1.3, Source Reference Format.

Examples

In the following examples, uppercase words represent text-words that have been replaced.

  1. REPLACE statement with multiple replacement items:


             8 working-storage section.         
             9 replace ==alpha== by ==NUM-1==  
            10         ==num== by ==ALPHA-1==. 
     R      11 01  NUM-1  pic 9(10).           
     R      12 01  ALPHA-1                     
            13            pic x(10).           
            14 procedure division.             
    

  2. Multiple REPLACE statements:
    A given occurrence of the REPLACE statement is in effect from the point at which it is specified until the next occurrence of the REPLACE statement. The new REPLACE statement supersedes the text-matching established by the previous REPLACE statement.


             7 working-storage section. 
             8 01  total           pic 9(4)v99. 
             9 replace ==class== by ==CLASS1== 
            10         ==total== by ==ORDER-AMT==. 
            11 01  customer-rec. 
     R      12     03  CLASS1      pic x(02). 
            13     03  name        pic x(25). 
            14     03  address. 
            15         05  street  pic x(20). 
            16         05  city    pic x(20). 
            17         05  state   pic xx. 
            18         05  zip     pic 9(5). 
            19     03  orders occurs 6 times. 
            20         05  order-numb  pic 9(6). 
            21         05  order-date  pic 9(6). 
     R      22         05  ORDER-AMT   pic 9(4)v99. 
            23 procedure division. 
            24 replace ==class== by ==CLASS1==. 
            25 p0.  add order-amt of orders(3) to total. 
    

    In the previous example, the word total on line 25 is not replaced because the REPLACE statement on line 24 reestablished the text-matching arguments.

  3. REPLACE OFF:
    Any text-matching currently in effect is turned off.


           11 working-storage section. 
           12 replace ==add== by ==PIC 9(18)==. 
     R     13 01  a1              PIC 9(18). 
     R     14 01  a2              PIC 9(18). 
           15 procedure division. 
           16     replace off. 
           17 p0. add a1 to a2. 
    

    In the previous example, the word add on line 17 is not replaced because the REPLACE statement on line 16 turned off all text-matching arguments.

  4. COPY interaction:
    In the following example, library text is copied from the library file DATAFILE.LIB:


    Contents of "DATAFILE.LIB": 
    01      customer-rec. 
            03  class       pic x(02). 
            03  name        pic x(25). 
            03  address. 
                05  street  pic x(20). 
                05  city    pic x(20). 
                05  state   pic xx. 
                05  zip     pic 9(5). 
            03  orders occurs 6 times. 
                05  order-number    pic 9(6). 
                05  order-date      pic 9(6). 
                05  order-amt       pic 9(4)v99. 
    

    The text-matching specified by an active REPLACE statement occurs after COPY (and COPY REPLACING) processing is complete.


             7 working-storage section. 
             8 replace ==class== by ==CLASS1==. 
             9 copy datafile. 
    L       10 01  customer-rec. 
    L       11     03  CLASS1      pic x(02). 
    L       12     03  name        pic x(25). 
    L       13     03  address. 
    L       14         05  street  pic x(20). 
    L       15         05  city    pic x(20). 
    L       16         05  state   pic xx. 
    L       17         05  zip     pic 9(5). 
    L       18     03  orders occurs 6 times. 
    L       19         05  order-number    pic 9(6). 
    L       20         05  order-date      pic 9(6). 
    L       21         05  order-amt       pic 9(4)v99. 
            22 procedure division. 
    


Appendix A
Compaq COBOL Reserved Words

The reserved words listed in this appendix are both the default reserved words and the words that are reserved only if activated by the COBOL command-line qualifier /RESERVED_WORDS=FOREIGN_EXTENSIONS or /RESERVED_WORDS=200X.

The XOPEN reserved words, which are reserved by default, can be deactivated by the /RESERVED_WORDS=NOXOPEN qualifier.

These three categories of reserved words, which are activated or deactivated by command-line qualifiers, are marked in this appendix as follows:
[FOREIGN] Reserved only if activated by /RESERVED_WORDS=FOREIGN_EXTENSIONS
[200X] Reserved only if activated by /RESERVED_WORDS=200X
[XOPEN] Reserved by default, but not reserved if deactivated by /RESERVED_WORDS=NOXOPEN

Reserved Words

ACCEPT
ACCESS
ADD
ADDRESS [FOREIGN]
ADVANCING
AFTER
ALL
ALLOWING
ALPHABET
ALPHABETIC
ALPHABETIC--LOWER
ALPHABETIC--UPPER
ALPHANUMERIC
ALPHANUMERIC--EDITED
ALSO
ALTER
ALTERNATE
AND
ANY
APPLY
ARE
AREA
AREAS
ASCENDING
ASSIGN
AT
AUTHOR
AUTO [XOPEN]
AUTOMATIC
AUTOTERMINATE

BACKGROUND-COLOR [XOPEN]
BATCH
BEFORE
BEGINNING
BELL [XOPEN]
BINARY
BINARY-CHAR [200X]
BINARY-DOUBLE [200X]
BINARY-LONG [200X]
BINARY-SHORT [200X]
BIT
BITS
BLANK
BLINK [XOPEN]
BLINKING
BLOCK
BOLD
BOOLEAN
BOTTOM
BY

CALL
CANCEL
CD
CF
CH
CHANGED [FOREIGN]
CHARACTER
CHARACTERS
CLASS
CLOCK-UNITS
CLOSE
COBOL
CODE
CODE-SET
COL [200X]
COLLATING
COLUMN
COMMA
COMMIT
COMMON
COMMUNICATION
COMP
COMP-1
COMP-2
COMP-3
COMP-4
COMP-5
COMP-6
COMP-X
COMPUTATIONAL
COMPUTATIONAL-1
COMPUTATIONAL-2
COMPUTATIONAL-3
COMPUTATIONAL-4
COMPUTATIONAL-5
COMPUTATIONAL-6
COMPUTATIONAL-X
COMPUTE
CONCURRENT
CONFIGURATION
CONNECT
CONTAIN
CONTAINS
CONTENT
CONTINUE
CONTROL
CONTROLS
CONVERSION
CONVERTING
COPY
CORE-INDEX [FOREIGN]
CORR
CORRESPONDING
COUNT
CRT
CURRENCY
CURRENT
CURSOR

DATA
DATE
DATE-COMPILED
DATE-WRITTEN
DAY
DAY-OF-WEEK
DB
DB-ACCESS-CONTROL-KEY
DB-CONDITION
DB-CURRENT-RECORD-ID
DB-CURRENT-RECORD-NAME
DB-EXCEPTION
DB-KEY
DB-RECORD-NAME
DB-SET-NAME
DB-STATUS
DB-UWA
DBCS [FOREIGN]
DBKEY
DE
DEBUG-CONTENTS
DEBUG-ITEM
DEBUG-LENGTH
DEBUG-LINE
DEBUG-NAME
DEBUG-NUMERIC-CONTENTS
DEBUG-SIZE
DEBUG-START
DEBUG-SUB
DEBUG-SUB-1
DEBUG-SUB-2
DEBUG-SUB-3
DEBUG-SUB-ITEM
DEBUG-SUB-N
DEBUG-SUB-NUM
DEBUGGING
DECIMAL-POINT
DECLARATIVES
DEFAULT
DELETE
DELIMITED
DELIMITER
DEPENDENCY
DEPENDING
DESCENDING
DESCRIPTOR
DESTINATION
DETAIL
DICTIONARY
DISABLE
DISCONNECT
DISP [FOREIGN]
DISPLAY
DISPLAY-1 [FOREIGN]
DISPLAY-6
DISPLAY-7
DISPLAY-9
DIVIDE
DIVISION
DOES
DOWN
DUPLICATE
DUPLICATES

ECHO
EDITING
EGI
EJECT [FOREIGN]
ELSE
EMI
EMPTY
ENABLE
END
END-ACCEPT
END-ADD
END-CALL
END-COMMIT
END-COMPUTE
END-CONNECT
END-DELETE
END-DISCONNECT
END-DIVIDE
END-ERASE
END-EVALUATE
END-FETCH
END-FIND
END-FINISH
END-FREE
END-GET
END-IF
END-KEEP
END-MODIFY
END-MULTIPLY
END-OF-PAGE
END-PERFORM
END-READ
END-READY
END-RECEIVE
END-RECONNECT
END-RETURN
END-REWRITE
END-ROLLBACK
END-SEARCH
END-START
END-STORE
END-STRING
END-SUBTRACT
END-UNSTRING
END-WRITE
ENDING
ENTER
ENTRY [FOREIGN]
ENVIRONMENT
EOL [XOPEN]
EOP
EOS [XOPEN]
EQUAL
EQUALS
ERASE [XOPEN]
ERROR
ESI
EVALUATE
EVERY
EXAMINE [FOREIGN]
EXCEEDS
EXCEPTION
EXCLUSIVE
EXHIBIT [FOREIGN]
EXIT
EXOR
EXTEND
EXTERNAL

FAILURE
FALSE
FD
FETCH
FILE
FILE-CONTROL
FILLER
FINAL
FIND
FINISH
FIRST
FLOAT-EXTENDED [200X]
FLOAT-LONG [200X]
FLOAT-SHORT [200X]
FOOTING
FOR
FOREGROUND-COLOR [XOPEN]
FREE
FROM
FULL [XOPEN]
FUNCTION

GENERATE
GET
GIVING
GLOBAL
GO
GOBACK [FOREIGN]
GREATER
GROUP

HEADING
HIGH-VALUE
HIGH-VALUES
HIGHLIGHT [XOPEN]

I-O
I-O-CONTROL
ID [FOREIGN]
IDENT
IDENTIFICATION
IF
IN
INCLUDING
INDEX
INDEXED
INDICATE
INITIAL
INITIALIZE
INITIATE
INPUT
INPUT-OUTPUT
INSPECT
INSTALLATION
INTO
INVALID
IS

JUST
JUSTIFIED

KANJI [FOREIGN]
KEEP
KEY

LABEL
LAST
LD
LEADING
LEFT
LENGTH
LESS
LIMIT
LIMITS
LINAGE
LINAGE-COUNTER
LINE
LINE-COUNTER
LINES
LINKAGE
LOCALLY
LOCK
LOCK-HOLDING
LOW-VALUE
LOW-VALUES
LOWLIGHT [XOPEN]

MANUAL
MATCH
MATCHES
MEMBER
MEMBERSHIP
MEMORY
MERGE
MESSAGE
MODE
MODIFY
MODULES
MOVE
MULTIPLE
MULTIPLY

NAMED [FOREIGN]
NATIVE
NEGATIVE
NEXT
NO
NON-NULL
NOT
NOTE [FOREIGN]
NULL
NUMBER
NUMERIC
NUMERIC-EDITED

OBJECT-COMPUTER
OCCURS
OF
OFF
OFFSET
OMITTED
ON
ONLY
OPEN
OPTIONAL
OPTIONS [200X]
OR
ORDER
OTHERWISE [FOREIGN]

PACKED-DECIMAL
PADDING
PAGE
PAGE-COUNTER
PASSWORD [FOREIGN]
PERFORM
PF
PH
PIC
PICTURE
PLUS
POINTER
POSITION
POSITIONING [FOREIGN]
POSITIVE
PREVIOUS
PRINTING
PRIOR
PROCEDURE
PROCEDURES
PROCEED
PROGRAM
PROGRAM-ID
PROTECTED
PURGE

QUEUE
QUOTE
QUOTES

RANDOM
RD
READ
READERS
READY
REALM
REALMS
RECEIVE
RECONNECT
RECORD
RECORD-NAME
RECORD-OVERFLOW [FOREIGN]
RECORDING [FOREIGN]
RECORDS
REDEFINES
REEL
REFERENCE
REFERENCE-MODIFIER
REFERENCES
REGARDLESS
RELATIVE
RELEASE
RELOAD [FOREIGN]
REMAINDER
REMARKS [FOREIGN]
REMOVAL
RENAMES
REORG-CRITERIA [FOREIGN]
REPLACE
REPLACING
REPORT
REPORTING
REPORTS
REQUIRED [XOPEN]
RERUN
RESERVE
RESET
RETAINING
RETRIEVAL
RETURN
RETURN-CODE [XOPEN]
RETURNING [FOREIGN]
REVERSE-VIDEO [XOPEN]
REVERSED
REWIND
REWRITE
RF
RH
RIGHT
RMS-CURRENT-FILENAME
RMS-CURRENT-STS
RMS-CURRENT-STV
RMS-FILENAME
RMS-STS
RMS-STV
ROLLBACK
ROUNDED
RUN

SAME
SCREEN [XOPEN]
SD
SEARCH
SECTION
SECURE [XOPEN]
SECURITY
SEGMENT
SEGMENT-LIMIT
SELECT
SEND
SENTENCE
SEPARATE
SEQUENCE
SEQUENCE-NUMBER
SEQUENTIAL
SERVICE [FOREIGN]
SET
SETS
SIGN
SIGNED [200X]
SIZE
SKIP1 [FOREIGN]
SKIP2 [FOREIGN]
SKIP3 [FOREIGN]
SORT
SORT-MERGE
SOURCE
SOURCE-COMPUTER
SPACE
SPACES
SPECIAL-NAMES
STANDARD
STANDARD-1
STANDARD-2
START
STATUS
STOP
STORE
STREAM
STRING
SUB-QUEUE-1
SUB-QUEUE-2
SUB-QUEUE-3
SUB-SCHEMA
SUBTRACT
SUCCESS
SUM
SUPPRESS
SYMBOLIC
SYNC
SYNCHRONIZED

TABLE
TALLYING
TAPE
TENANT
TERMINAL
TERMINATE
TEST
TEXT
THAN
THEN
THROUGH
THRU
TIME
TIMES
TO
TOP
TRACE [FOREIGN]
TRAILING
TRANSFORM [FOREIGN]
TRUE
TYPE

UNDERLINE [XOPEN]
UNDERLINED
UNEQUAL
UNIT
UNLOCK
UNSIGNED [200X]
UNSTRING
UNTIL
UP
UPDATE
UPDATERS
UPON
USAGE
USAGE-MODE
USE
USING

VALUE
VALUES
VARYING
VFU-CHANNEL

WAIT
WHEN
WHERE
WITH
WITHIN
WORDS
WORKING-STORAGE
WRITE
WRITERS

ZERO
ZEROES
ZEROS

+
-
*
/
**
>
< =
> =
< =


Previous Next Contents Index