You are on page 1of 4

3/24/2018 The American Programmer.com COBOL compare and audit two files.

wo files. produce output files with added, deleted, and changed

The American Programmer

Home > COBOL > COBOL Compare Program


Home

Books on Mainframe
Programming COBOL logic to compare two sorted input
Mainframe Manuals and
Tutorials
files and determine what changed: audit
System Abend codes,
function
Sqlcodes, VSAM/QSAM
codes Input files must be sorted! This model program uses a 5
Everything about the IBM character record key, in the first 5 characters of the
AS/400 Midrange Computer - record.
iSeries You have two input files. They are a current and a
Everything about CICS previous. In other words, versions of the same file.
You want to know if records were added, deleted, or
Cobol programs, manuals, changed.
books
Run this program with the two files:
Sample Cobol code: The Simple,
Single File COBOL Program
it produces 4 output files:
Sample Cobol code: The Simple,
ADDS, DELETES, CHANGES, FULL.
Single File Report COBOL Program If you don't want one or more of the output files, then
with Record Count or Final Totals
Sample Cobol code: The Simple,
dummy them out.
Single File Report COBOL Program The logic is deceptively simple. (Change it at your own
with Record Count or Final Totals
risk.)
Sample Cobol code: The Sequence
Check COBOL Program
Sample Cobol code: The Record 000100 IDENTIFICATION DIVISION.
Selection COBOL Program 000110* Compares 2 input files. produces 4 output files:
Sample Cobol code: The Edit or * adds - records that were added
Validate COBOL Program * dels - records that were deleted
Sample Cobol code: The The One * chgs - records that were changed
Level Subtotal (Control Break)
COBOL Program * requires use of a record key
Sample Cobol code: The Three
* in this progm first 5 chars
Level Subtotal (Control Break) * full - the old file (prev)
COBOL Program * with added records
Sample Cobol code: The Sequential * without deleted records
File, Batch Update COBOL Program
* with changes applied
Sample Cobol code: The COBOL * The first 5 characters of each file are a record key
Sort
* Both input files must be sorted ascending,
Sample Cobol code: The CASE
Structure: COBOL EVALUATE * on the record key (first 5 characters)
Sample Cobol code: Direct * Obviously both input files must be the same length,
Subscripting in COBOL * and have the same fields.
Sample Cobol code: The Sequential, * (in other words, both input files are the SAME FILE,
or Serial Search in COBOL * but produced at different times)
Sample Cobol code: The Binary * Don't complain about the style.
Search in COBOL * This style was very popular at one time. It works.
Sample Cobol code: Loading a Table 000200 PROGRAM-ID. 'COMPARE'.
from a Sequential File in a COBOL
program 000300 ENVIRONMENT DIVISION.
Sample Cobol code: The VSAM File 000400 CONFIGURATION SECTION.
Read Sequentially in a COBOL 000500 INPUT-OUTPUT SECTION.
program 000600 FILE-CONTROL.
Sample Cobol code: The VSAM 000700 SELECT PREV-IN ASSIGN PREV.
KSDS, Read Randomly in a COBOL
program 000800 SELECT CURR-IN ASSIGN CURR.
Sample Cobol code: The VSAM File, 000900 SELECT ADDS-OUT ASSIGN ADDS.
Read Randomly in a COBOL program 001000 SELECT DELS-OUT ASSIGN DELS.
Sample Cobol code: VSAM Initial 001100 SELECT CHGS-OUT ASSIGN CHGS.
Load in a COBOL program 001200* FULL IS LIKE A NEW MASTER -
Sample Cobol code: VSAM File 001300* PREV + ADDS
Maintenance (Add, Change, Delete) in
a COBOL program
001400* - DELS
001500* WITH CHANGED RECORDS FROM CURR
Sample Cobol code: VSAM Read
Sequentially, with START, in a COBOL 001600 SELECT FULL-OUT ASSIGN FULL.
program 001700
Sample Cobol code: Creating a 001800 DATA DIVISION.
http://theamericanprogrammer.com/cobol/compare.audit.two.files.shtml 1/4
3/24/2018 The American Programmer.com COBOL compare and audit two files. produce output files with added, deleted, and changed
Variable Format File in a COBOL 001900 FILE SECTION.
program
002000
Sample Cobol code: Reading a
Variable Format File in a COBOL 002100 FD PREV-IN
program 002200 BLOCK CONTAINS 0 RECORDS
Sample Cobol code: Creating a 002300 LABEL RECORDS ARE STANDARD
Variable Format File with Occurs 002400 DATA RECORD IS PREV-REC.
Depending On in a COBOL program
002500
Sample Cobol code: COBOL 002600 01 PREV-REC.
Reading a Variable Format File with
Occurs Depending On, in a COBOL 002700 05 PREV-KEY PIC X(05).
program 002800 05 FILLER PIC X(75).
Sample Cobol code: COBOL The 002900
Table Load with Occurs Depending
On
003000 FD CURR-IN
003100 BLOCK CONTAINS 0 RECORDS
Sample Cobol/DB2 code: Singleton
Select 003200 LABEL RECORDS ARE STANDARD
Sample Cobol code: logic to 003300 DATA RECORD IS CURR-REC.
compare two sorted input files 003400
Sample Cobol code: logic to merge 003500 01 CURR-REC.
two sorted input files into one 003600 05 CURR-KEY PIC X(05).
Sample Cobol code: Illustrates how 003700 05 FILLER PIC X(75).
Occurs Depending On (ODO) works
003800
Manuals on the COBOL 003900 FD ADDS-OUT
programming language.
004000 BLOCK CONTAINS 0 RECORDS
Books on Cobol
004100 LABEL RECORDS ARE STANDARD
Abend Codes from Cobol programs 004200 DATA RECORD IS ADDS-REC.
004300
Everything about DB2 and 004400 01 ADDS-REC PIC X(80).
SQL 004500
004600 FD DELS-OUT
Everything about IMS
004700 BLOCK CONTAINS 0 RECORDS
Everything about Java and 004800 LABEL RECORDS ARE STANDARD
JavaScript 004900 DATA RECORD IS DELS-REC.
005000
Everything about JCL and 005100 01 DELS-REC PIC X(80).
JES 005200
005300 FD CHGS-OUT
Everything about REXX
005400 BLOCK CONTAINS 0 RECORDS
Everything about zOS, 005500 LABEL RECORDS ARE STANDARD
VSAM, Tivoli, Assembler 005600 DATA RECORD IS CHGS-REC.
005700
Everything about TSO, ISPF, 005800 01 CHGS-REC PIC X(80).
Spufi 005900
006000 FD FULL-OUT
Site Map and Site Search
006100 BLOCK CONTAINS 0 RECORDS
006200 LABEL RECORDS ARE STANDARD
006300 DATA RECORD IS FULL-REC.
006400
006500 01 FULL-REC PIC X(80).
006600
006700 WORKING-STORAGE SECTION.
006800 01 ADDS-REC-WS PIC X(80).
006900 01 DELS-REC-WS PIC X(80).
007000 01 CHGS-REC-WS PIC X(80).
007100 01 FULL-REC-WS PIC X(80).
007200 01 COUNTERS.
007300 05 PREV-CNT COMP-3 PIC 9(07) VALUE 0.
007400 05 CURR-CNT COMP-3 PIC 9(07) VALUE 0.
007500 05 ADDS-CNT COMP-3 PIC 9(07) VALUE 0.
007600 05 DELS-CNT COMP-3 PIC 9(07) VALUE 0.
007700 05 CHGS-CNT COMP-3 PIC 9(07) VALUE 0.
007800 05 FULL-CNT COMP-3 PIC 9(07) VALUE 0.
007900
008600 PROCEDURE DIVISION.
008700
008800 P0000-MAIN-PROCESS.
008900 PERFORM P0100-OPEN-FILES THRU P0100-EXIT.
009000
009100 PERFORM P0210-READ-PREV-INPUT THRU P0210-EXIT.
009200 PERFORM P0220-READ-CURR-INPUT THRU P0220-EXIT.
009300
009400 PERFORM P0300-COMPARE-INPUT THRU P0300-EXIT
009600 UNTIL (PREV-KEY EQUAL HIGH-VALUES) AND

http://theamericanprogrammer.com/cobol/compare.audit.two.files.shtml 2/4
3/24/2018 The American Programmer.com COBOL compare and audit two files. produce output files with added, deleted, and changed
009700 (CURR-KEY EQUAL HIGH-VALUES).
009800
009900 PERFORM P0999-NORMAL-EOJ THRU P0999-EXIT.
010000
010100 GOBACK.
010200
010300 P0100-OPEN-FILES.
010400 OPEN INPUT PREV-IN
010500 CURR-IN
010600 OUTPUT ADDS-OUT
010700 DELS-OUT
010800 CHGS-OUT
010900 FULL-OUT.
011000
011100 P0100-EXIT. EXIT.
011200
011300 P0210-READ-PREV-INPUT.
011400 READ PREV-IN
011500 AT END
011600 MOVE HIGH-VALUES TO PREV-KEY
011700 GO TO P0210-EXIT.
011800 ADD +1 TO PREV-CNT.
011900
012000 P0210-EXIT. EXIT.
012100
012200 P0220-READ-CURR-INPUT.
012300 READ CURR-IN
012400 AT END
012500 MOVE HIGH-VALUES TO CURR-KEY
012600 GO TO P0220-EXIT.
012700
012800 ADD +1 TO CURR-CNT.
012900
013000 P0220-EXIT. EXIT.
013100
013200 P0300-COMPARE-INPUT.
013300
013400*** DELETED
013500 IF CURR-KEY GREATER THAN PREV-KEY
013600 PERFORM P0910-WRITE-DELETE-RECORD THRU P0910-EXIT
013700 IF PREV-KEY NOT EQUAL HIGH-VALUES
013800 PERFORM P0210-READ-PREV-INPUT THRU P0210-EXIT
013900 GO TO P0300-EXIT
014000 ELSE
014100 GO TO P0300-EXIT.
014200
014300*** ADDED
014400 IF CURR-KEY LESS THAN PREV-KEY
014500 PERFORM P0920-WRITE-ADD-RECORD THRU P0920-EXIT
014600 IF CURR-KEY NOT EQUAL HIGH-VALUES
014700 PERFORM P0220-READ-CURR-INPUT THRU P0220-EXIT
014800 GO TO P0300-EXIT
014900 ELSE
015000 GO TO P0300-EXIT.
015100
015200*** MATCHED
015300 IF CURR-REC NOT EQUAL PREV-REC
015400 PERFORM P0930-WRITE-CHANGE-RECORD THRU P0930-EXIT
015500 ELSE
015600 PERFORM P0935-WRITE-FULLUP-RECORD THRU P0935-EXIT.
015700
015800 IF PREV-KEY NOT EQUAL HIGH-VALUES
015900 PERFORM P0210-READ-PREV-INPUT THRU P0210-EXIT.
016000
016100 IF CURR-KEY NOT EQUAL HIGH-VALUES
016200 PERFORM P0220-READ-CURR-INPUT THRU P0220-EXIT.
016300
016400 P0300-EXIT. EXIT.
016500
016600 P0910-WRITE-DELETE-RECORD.
016700 WRITE DELS-REC FROM PREV-REC

http://theamericanprogrammer.com/cobol/compare.audit.two.files.shtml 3/4
3/24/2018 The American Programmer.com COBOL compare and audit two files. produce output files with added, deleted, and changed
016800 ADD +1 TO DELS-CNT.
016900
017000 P0910-EXIT. EXIT.
017100
017200 P0920-WRITE-ADD-RECORD.
017300 WRITE ADDS-REC FROM CURR-REC
017310 WRITE FULL-REC FROM CURR-REC
017400 ADD +1 TO FULL-CNT.
017500
017600 P0920-EXIT. EXIT.
017700
017800 P0930-WRITE-CHANGE-RECORD.
017900 WRITE CHGS-REC FROM CURR-REC
017910 WRITE FULL-REC FROM CURR-REC
018000 ADD +1 TO FULL-CNT.
018100
018200 P0930-EXIT. EXIT.
018300
018400 P0935-WRITE-FULLUP-RECORD.
018500 WRITE FULL-REC FROM CURR-REC
018600 ADD +1 TO FULL-CNT.
018700
018800 P0935-EXIT. EXIT.
018900
019000 P0940-WRITE-COUNTS-RECORD.
019200 DISPLAY 'ADDS-CNT' ADDS-CNT.
019300 DISPLAY 'DELS-CNT' DELS-CNT.
019400 DISPLAY 'CHGS-CNT' CHGS-CNT.
019500 DISPLAY 'FULL-CNT' FULL-CNT.
019600
019610 P0940-EXIT. EXIT.
019620
019700 P0999-NORMAL-EOJ.
019800
019900 PERFORM P0940-WRITE-COUNTS-RECORD THRU P0940-EXIT.
020000
020100 CLOSE PREV-IN
020200 CURR-IN
020300 ADDS-OUT
020400 DELS-OUT
020500 CHGS-OUT
020600 FULL-OUT.
020700
020800 P0999-EXIT. EXIT.

Learn how to use all the features of COBOL: COBOL


Programming Books

| Home | Books for Computer Professionals | Privacy | Terms |


| Site Map and Site Search | Programming Manuals and Tutorials | The REXX Files | Top of Page |

http://theamericanprogrammer.com/cobol/compare.audit.two.files.shtml 4/4

You might also like