BudiBadu Logo
Samplebadu

COBOL by Example: Merge

COBOL 2002

Merging pre-sorted files efficiently with MERGE statement, combining multiple input streams into single sorted output, using zipper algorithm for optimal performance, and processing batch transactions from distributed sources.

Code

       IDENTIFICATION DIVISION.
       PROGRAM-ID. MERGE-DEMO.
       
       ENVIRONMENT DIVISION.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
           SELECT FILE-A   ASSIGN TO "fileA.dat".
           SELECT FILE-B   ASSIGN TO "fileB.dat".
           SELECT WORK-F   ASSIGN TO "work.tmp".
           SELECT OUT-F    ASSIGN TO "merged.dat".
           
       DATA DIVISION.
       FILE SECTION.
       FD  FILE-A. 01 REC-A PIC X(20).
       FD  FILE-B. 01 REC-B PIC X(20).
       FD  OUT-F.  01 REC-O PIC X(20).
       
       SD  WORK-F.
       01  WORK-REC.
           05  KEY-VAL PIC 9(5).
           05  DATA-VAL PIC X(15).
           
       PROCEDURE DIVISION.
           MERGE WORK-F
               ON ASCENDING KEY KEY-VAL
               USING FILE-A, FILE-B
               GIVING OUT-F.
           STOP RUN.

Explanation

The MERGE statement combines multiple files that are already sorted into a single sorted output file. It is more efficient than sorting a combined dataset because it simply "zippers" the streams together, comparing the next record from each file and picking the lowest one.

Like SORT, it requires an SD (Sort/Merge Description) to define the record layout and keys used for the comparison. The input files must be sorted on the same keys as the merge operation; otherwise, the results will be unpredictable.

This operation is fundamental in batch processing, where "transaction" files from different sources (e.g., different bank branches) need to be combined into a master transaction file for nightly processing.

Code Breakdown

8
SELECT WORK-F. Defines the temporary workspace for the merge logic.
17
SD WORK-F. Sort/Merge Description. Defines the structure of the records being merged.
23
MERGE WORK-F. Initiates the merge process.
24
ON ASCENDING KEY KEY-VAL. The field used to compare records. Both input files must be pre-sorted by this key.
25
USING FILE-A, FILE-B. The input files. You can merge more than two files if needed.
26
GIVING OUT-F. The final destination for the merged stream.