COBOL Tutorial

COBOL COPY Statement Quick Reference

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.

What is a Copybook?

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:

  • Record layout definitions (data structures)
  • File descriptions for the ENVIRONMENT DIVISION
  • Reusable procedure code
  • Common working storage definitions
  • Standard error handling routines

Basic Syntax

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
*> 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".

How COPY Works

When the COBOL compiler encounters a COPY statement, it:

  • Searches the specified library (or SYSLIB) for the copybook member
  • Reads the copybook contents
  • If REPLACING is specified, performs text replacements
  • Inserts the processed copybook text into your program, replacing the entire COPY statement
  • Continues compilation with the expanded source code

This happens before the actual compilation, so the compiler sees the expanded code as if you had typed it directly.

Simple COPY Example

Let's say you have a copybook called EMPREC that contains an employee record layout:

Copybook: EMPREC

cobol
1
2
3
4
5
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).

Using the Copybook in Your Program

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
IDENTIFICATION 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.

What the Compiler Sees

After processing the COPY statement, the compiler sees:

cobol
1
2
3
4
5
6
01 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).

REPLACING Phrase

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.

Basic REPLACING Example

Suppose you have a generic record copybook that uses a prefix:

Copybook: GENREC

cobol
1
2
3
05 :PREFIX:-ID PIC 9(05). 05 :PREFIX:-NAME PIC X(30). 05 :PREFIX:-AMOUNT PIC 9(07)V99.

Using REPLACING to Customize

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
IDENTIFICATION 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.

Replacing Multiple Items

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
IDENTIFICATION 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.

Replacing Identifiers

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
*> 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).

Complete Example: File Record Layout

Here's a complete example showing how COPY is typically used for file record layouts:

Copybook: CUSTOMER-REC (stored in library)

cobol
1
2
3
4
5
6
7
8
9
10
11
05 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".

Program Using the Copybook

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
IDENTIFICATION 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.

Step-by-Step Guide: Creating and Using a Copybook

Advanced REPLACING Techniques

Partial Word Replacement

Use pseudo-text delimiters == to replace parts of words:

cobol
1
2
3
4
5
6
7
8
9
10
*> 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).

Replacing Level Numbers

cobol
1
2
3
4
5
*> 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

Replacing PICTURE Clauses

cobol
1
2
3
4
5
6
7
8
*> 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.

Nested COPY Statements

COPY statements can be nested - a copybook can contain another COPY statement. However, there are important rules:

  • No circular recursion allowed (copybook A cannot include copybook B if B includes A)
  • Only one COPY statement in a nested chain can have the REPLACING phrase
  • The REPLACING phrase applies to all nested copybooks
cobol
1
2
3
4
5
6
7
8
9
10
*> 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

Library Specification

By default, the compiler searches SYSLIB for copybooks. You can specify a different library:

cobol
1
2
3
4
5
6
7
8
*> 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

Best Practices

  • Use meaningful copybook names: Choose names that clearly indicate the copybook's purpose (e.g., CUSTOMER-REC, EMPLOYEE-FILE-DESC)
  • Document copybooks: Include comments in copybooks explaining their purpose and usage
  • Version control: Keep copybooks in version-controlled libraries to track changes
  • Standardize prefixes: Use consistent naming conventions in copybooks to make REPLACING easier
  • Test after changes: When modifying a copybook, recompile all programs that use it
  • Avoid deep nesting: Limit nested COPY statements to maintain readability
  • Use REPLACING judiciously: Don't overuse REPLACING - sometimes separate copybooks are clearer
  • Keep copybooks focused: Each copybook should have a single, clear purpose

Common Use Cases

File Record Layouts

The most common use - defining record structures for files. All programs reading/writing the same file use the same copybook, ensuring consistency.

File Descriptions

Standard file descriptions in the ENVIRONMENT DIVISION can be stored in copybooks and reused across multiple programs.

Working Storage Definitions

Common working storage items like counters, switches, and temporary variables can be centralized in copybooks.

Error Handling Routines

Standard error handling code can be stored in copybooks and included in multiple programs for consistency.

Key Takeaways

  • COPY statement includes prewritten code (copybooks) from libraries into your program at compile time
  • Copybooks promote code reuse, consistency, and maintainability
  • REPLACING phrase allows customization of copybook content for different uses
  • Copybooks are typically stored in PDS libraries and referenced via SYSLIB in JCL
  • COPY statements can be nested, but circular recursion is not allowed
  • The compiler processes COPY statements before compilation, expanding them inline
  • Common uses include record layouts, file descriptions, and reusable procedure code

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!

Test Your Knowledge

1. What is the primary purpose of the COPY statement in COBOL?

  • To copy files from disk to memory
  • To include prewritten code sections (copybooks) from a library into your program
  • To duplicate program code
  • To create backup copies of programs

2. What happens when the compiler processes a COPY statement?

  • The copybook is executed at runtime
  • The COPY statement is replaced with the contents of the copybook during compilation
  • The copybook is loaded into memory
  • The copybook is compiled separately

3. What is the correct syntax for a COPY statement with REPLACING?

  • COPY copybook-name REPLACING "old" WITH "new"
  • COPY copybook-name REPLACING "old" BY "new"
  • COPY copybook-name REPLACE "old" BY "new"
  • COPY copybook-name SUBSTITUTE "old" FOR "new"

4. Where is the copybook library typically specified?

  • In the COPY statement itself
  • In the JCL SYSLIB or COPYLIB DD statement
  • In the COBOL program header
  • In a configuration file

5. What is a common use case for the REPLACING phrase?

  • To fix errors in copybooks
  • To customize copybook content for different programs by replacing identifiers
  • To delete unwanted code from copybooks
  • To rename copybooks

6. Can a copybook contain another COPY statement?

  • No, COPY statements cannot be nested
  • Yes, but only one level deep
  • Yes, COPY statements can be nested, but circular recursion is not allowed
  • Yes, with unlimited nesting levels