RAMESH KRISHNA REDDY mainframe discussion forum - cobol, db2,cics,jcl,file-aid,changeman,interview questions
Online Tutorials   | PREV  | TOP  | NEXT



DRONA SERIES
COBOL STUDY MATERIAL


COPY

Author : Kishore & Vasanta



   
 

COPY






COPY COPY Statement is compiler directive statement. This places the prewritten text in a COBOL program during compilation time. COPY statement in COBOL is Replaced at compile time, while other statements are executed at runtime. When a COPY statement is used in COBOL program, the source text is copied into the program from copy file/library before the program is compiled. This statement can appear in source program anywhere a character can appear. All COPY statements will be processed before source program compilation. For example COPYFILE contains following text 01 WS-COPYFIELD PIC 9(02) VALUE ZEROES. And we can include the above text in program using COPY statement. The resulting text in program will appear as follows in listing file. … DATA DIVISION. WORKING-STORAGE SECTION. *COPY COPYFILE. 01 WS-COPYFIELD PIC 9(02) VALUE ZEROES. 01 WS-INPUT PIC X(01). … If COPY statement is specified with SUPPRESS option, text in COPYFILE will not be displayed in listing file. If COPY is specified with REPLACING option, the text in COPYFILE will be replaced first, and then it will be copied into program. We can use REPLACING option to replace the string “COPYFIELD” with “WS- COPYFIELD” For example COPYFILE contains following text 01 COPYFIELD PIC 9(02) VALUE ZEROES. After compilation, listing will contain WS-COPYFIELD value included DATA DIVISION. WORKING-STORAGE SECTION. *COPY COPYFILE REPLACING COPYFIELD BY WS-COPYFIELD. <-- Commented out. 01 WS-COPYFIELD PIC 9(02) VALUE ZEROES. <-- New record inserted. .. 01 WS-INPUT PIC X(01). .. We can also use REPLACING option to replace part of string, i.e. “:TAG:” with “WS” For example COPYFILE contains following text 01 :TAG:-COPYFIELD PIC 9(02) VALUE ZEROES. During compilation process, COPY statement will be commented out and data from copy book will be inserted into the program. DATA DIVISION. WORKING-STORAGE SECTION. *COPY COPYFILE REPLACING ==:TAG:== BY ==WS==. <-- Commented out 01 WS-COPYFIELD PIC 9(02) VALUE ZEROES. <-- Newly inserted row .. 01 WS-INPUT PIC X(01). .. Operands in REPLACING option can be pseudo text, identifier or literal. Pseudo text is group of characters bounded by, but not included delimiters (“==”). Both delimiter characters must appear on one line. COPY statements can be nested. However, o Nested COPY statements cannot contain the REPLACING phrase, and a COPY statement with the REPLACING phrase cannot contain nested COPY statements. o Nested COPY statement cannot cause recursion But it is not advisbale to use nested COPY statements, as it will impact readability of the program. ------------- Article 2 -------------------------------------------------- COPY : In many programs usually files or Piece of code are accessed by more than one Program in the system. In addition, record structures and routines such as date validation routine are generally used by several programs. In these situations, it is important to ensure that each program has the same file description, record structure or code. Maintaining several copies of the same thing leads to errors and is also time consuming. Each time you modify one copy, you also need to modify all the other copies and each modification is an opportunity to introduce errors. To address all these issues, COBOL provides the COPY statement. The COPY statement inserts the code from specified copybook in copy library into the source program during compilation. Thus, unlike all other COBOL statements which gets executed during runtime, the COPY statement gets executed during the compile time. In addition to merely inserting a copybook from a copy library, the COPY statement can also modify the text as it is being inserted, by replacing words contained in the copybook. To facilitate, we must use the REPLACING BY clause. A COPY statement can be placed anywhere in the source program where a character string can be used. For example: COBOL program IDENTIFICATION DIVISION. PROGRAM-ID. COPYPRM. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. 77 WS-NAME PIC X(26) * COPY F040860 * PROCEDURE DIVISION. .. .. F040860 is copy book which stored in V2145.COBOL.COYBOOK It structure is 01 WS-RECORD. 05 WS-NUMBER PIC 9(09). 05 WS-NAME PIC X(10). 05 WS-LOB PIC X(03). Here in COBOL program after compilation, COBOL program contains this Code. During compilation process, compiler replaces COPY statement with the copybook content. IDENTIFICATION DIVISION. PROGRAM-ID. COPYPRM. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. 77 WS-NAME PIC X(26) * *COPY F040860 <-- Attention, commented out 01 WS-RECORD. <-- Newly inserted 05 WS-NUMBER PIC 9(09). <-- Newly inserted 05 WS-NAME PIC X(10). <-- Newly inserted 05 WS-LOB PIc X(03). <-- Newly inserted * PROCEDURE DIVISION. .. ..
    

NEXT CHAPTER TOPIC : COBOL


                                   



Previous chapter in COBOL tutorial Starting of COBOL tutorial Next chapter in COBOL tutorial


Visit COBOL books section in this site for good books




Home | Donations | Online Tutorials | Books | Entertainment | Contactme | privacy |  sql tutorial | jcl interview questions | JCL Tutorial | JCL Tutorial - chapter1 | JCL Tutorial - chapter2 | JCL Tutorial - chapter3 | JCL Tutorial - chapter4 | JCL Tutorial - chapter5 | JCL Tutorial - chapter6 | JCL Tutorial - chapter7 | JCL Tutorial - chapter8 | JCL Tutorial - chapter9 | JCL Tutorial - chapter10 | JCL Tutorial - chapter11