The COPY statement is a powerful COBOL feature that allows you to include prewritten code sections (called copybooks) from a library into your program during compilation. This promotes code reuse, consistency, and maintainability by centralizing common data structures, file descriptions, and procedures.
A copybook is a prewritten section of COBOL source code stored in a library (typically a PDS - Partitioned Data Set on mainframes). Copybooks usually contain:
1234567891011121314*> Simple COPY statement COPY copybook-name. *> COPY with library specification COPY copybook-name OF library-name. *> COPY with REPLACING phrase COPY copybook-name REPLACING operand-1 BY operand-2. *> COPY with multiple replacements COPY copybook-name REPLACING "old-text-1" BY "new-text-1" "old-text-2" BY "new-text-2".
When the COBOL compiler encounters a COPY statement, it:
This happens before the actual compilation, so the compiler sees the expanded code as if you had typed it directly.
Let's say you have a copybook called EMPREC that contains an employee record layout:
1234505 EMP-NUM PIC 9(05). 05 EMP-NAME PIC X(30). 05 EMP-DEPARTMENT PIC X(20). 05 EMP-SALARY PIC 9(07)V99. 05 EMP-HIRE-DATE PIC 9(08).
1234567891011121314IDENTIFICATION DIVISION. PROGRAM-ID. EMPLOYEE-PROGRAM. DATA DIVISION. WORKING-STORAGE SECTION. 01 EMPLOYEE-RECORD. COPY EMPREC. PROCEDURE DIVISION. MAIN-LOGIC. *> The copybook is expanded here during compilation *> You can now use EMP-NUM, EMP-NAME, etc. in your program MOVE 12345 TO EMP-NUM MOVE "JOHN SMITH" TO EMP-NAME DISPLAY "Employee: " EMP-NAME STOP RUN.
After processing the COPY statement, the compiler sees:
12345601 EMPLOYEE-RECORD. 05 EMP-NUM PIC 9(05). 05 EMP-NAME PIC X(30). 05 EMP-DEPARTMENT PIC X(20). 05 EMP-SALARY PIC 9(07)V99. 05 EMP-HIRE-DATE PIC 9(08).
The REPLACING phrase allows you to customize copybook content by replacing text when it's copied into your program. This is useful when you want to reuse a copybook structure but with different field names.
Suppose you have a generic record copybook that uses a prefix:
12305 :PREFIX:-ID PIC 9(05). 05 :PREFIX:-NAME PIC X(30). 05 :PREFIX:-AMOUNT PIC 9(07)V99.
1234567891011121314151617IDENTIFICATION DIVISION. PROGRAM-ID. CUSTOMER-PROGRAM. DATA DIVISION. WORKING-STORAGE SECTION. 01 CUSTOMER-RECORD. COPY GENREC REPLACING ==:PREFIX:== BY ==CUST==. *> This expands to: *> 05 CUST-ID PIC 9(05). *> 05 CUST-NAME PIC X(30). *> 05 CUST-AMOUNT PIC 9(07)V99. PROCEDURE DIVISION. MAIN-LOGIC. MOVE 10001 TO CUST-ID MOVE "ACME CORP" TO CUST-NAME STOP RUN.
1234567891011121314151617IDENTIFICATION DIVISION. PROGRAM-ID. EMPLOYEE-PROGRAM. DATA DIVISION. WORKING-STORAGE SECTION. 01 EMPLOYEE-RECORD. COPY GENREC REPLACING ==:PREFIX:== BY ==EMP==. *> This expands to: *> 05 EMP-ID PIC 9(05). *> 05 EMP-NAME PIC X(30). *> 05 EMP-AMOUNT PIC 9(07)V99. PROCEDURE DIVISION. MAIN-LOGIC. MOVE 20001 TO EMP-ID MOVE "JANE DOE" TO EMP-NAME STOP RUN.
12345678910111213*> Copybook contains: *> 01 CUSTOMER-DATA. *> 05 CUST-ID PIC 9(05). *> 05 CUST-NAME PIC X(30). *> In your program: COPY CUSTOMER-REC REPLACING CUSTOMER-DATA BY EMPLOYEE-DATA CUST BY EMP. *> This expands to: *> 01 EMPLOYEE-DATA. *> 05 EMP-ID PIC 9(05). *> 05 EMP-NAME PIC X(30).
Here's a complete example showing how COPY is typically used for file record layouts:
123456789101105 CUSTOMER-NUMBER PIC 9(08). 05 CUSTOMER-NAME PIC X(40). 05 CUSTOMER-ADDRESS PIC X(60). 05 CUSTOMER-CITY PIC X(30). 05 CUSTOMER-STATE PIC X(02). 05 CUSTOMER-ZIP PIC X(10). 05 CUSTOMER-PHONE PIC X(15). 05 CUSTOMER-BALANCE PIC S9(07)V99 COMP-3. 05 CUSTOMER-STATUS PIC X(01). 88 ACTIVE-CUSTOMER VALUE "A". 88 INACTIVE-CUSTOMER VALUE "I".
123456789101112131415161718192021222324252627282930313233343536IDENTIFICATION DIVISION. PROGRAM-ID. PROCESS-CUSTOMERS. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS WS-FILE-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. COPY CUSTOMER-REC. WORKING-STORAGE SECTION. 01 WS-FILE-STATUS PIC X(02). 01 WS-END-OF-FILE PIC X(01) VALUE "N". 88 END-OF-FILE VALUE "Y". PROCEDURE DIVISION. MAIN-LOGIC. OPEN INPUT CUSTOMER-FILE PERFORM UNTIL END-OF-FILE READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE NOT AT END IF ACTIVE-CUSTOMER DISPLAY "Processing: " CUSTOMER-NAME *> Process active customer END-IF END-READ END-PERFORM CLOSE CUSTOMER-FILE STOP RUN.
Use pseudo-text delimiters == to replace parts of words:
12345678910*> Copybook contains: *> 05 :PREFIX:-ID PIC 9(05). *> 05 :PREFIX:-NAME PIC X(30). *> Replace the prefix part only COPY RECORD REPLACING ==:PREFIX:== BY ==CUST==. *> Results in: *> 05 CUST-ID PIC 9(05). *> 05 CUST-NAME PIC X(30).
12345*> Copybook has level 01, change to 05 COPY RECORD REPLACING == 01 == BY == 05 ==. *> Note: Be careful with spaces to avoid replacing *> numbers in PICTURE clauses
12345678*> Copybook contains: *> 05 AMOUNT PIC 9(07)V99. *> Replace the entire PICTURE clause COPY RECORD REPLACING ==PIC 9(07)V99== BY ==PIC 9(10)V99==. *> Results in: *> 05 AMOUNT PIC 9(10)V99.
COPY statements can be nested - a copybook can contain another COPY statement. However, there are important rules:
12345678910*> Main program COPY MAIN-REC. *> MAIN-REC copybook contains: *> 05 HEADER-FIELDS. *> COPY HEADER-REC. *> 05 DETAIL-FIELDS. *> COPY DETAIL-REC. *> This is valid nesting - no circular references
By default, the compiler searches SYSLIB for copybooks. You can specify a different library:
12345678*> Use default library (SYSLIB) COPY EMPREC. *> Specify a specific library COPY EMPREC OF MYLIB. *> In JCL, you would have: *> //MYLIB DD DSN=YOUR.SPECIFIC.LIBRARY,DISP=SHR
The most common use - defining record structures for files. All programs reading/writing the same file use the same copybook, ensuring consistency.
Standard file descriptions in the ENVIRONMENT DIVISION can be stored in copybooks and reused across multiple programs.
Common working storage items like counters, switches, and temporary variables can be centralized in copybooks.
Standard error handling code can be stored in copybooks and included in multiple programs for consistency.
Explain It Like I'm 5 Years Old:
Imagine you have a favorite recipe card that you use to make cookies. Instead of writing the whole recipe every time you want to make cookies, you just write "COPY COOKIE-RECIPE" and the recipe appears! That's what COPY does in COBOL. You write your code once (like a recipe), save it in a special library (like a recipe box), and whenever you need it, you just say "COPY" and the code appears in your program. If you want to make chocolate chip cookies instead of regular cookies, you can use REPLACING to change "sugar" to "chocolate chips" - same recipe, but customized!
1. What is the primary purpose of the COPY statement in COBOL?
2. What happens when the compiler processes a COPY statement?
3. What is the correct syntax for a COPY statement with REPLACING?
4. Where is the copybook library typically specified?
5. What is a common use case for the REPLACING phrase?
6. Can a copybook contain another COPY statement?