MainframeMaster

COBOL Tutorial

COBOL MERGE

The MERGE statement represents sophisticated file combination capabilities within COBOL programming environments, providing comprehensive sorted data integration, advanced merge processing logic, and optimized file consolidation mechanisms that enable efficient multi-file operations, reliable data combination strategies, and streamlined merge processing workflows. This statement embodies enterprise data integration principles by supporting intelligent merge algorithms, enabling complex file consolidation scenarios, and facilitating comprehensive data unification requirements while maintaining sort order integrity, ensuring consistent merge behavior, and enabling scalable data processing architectures across enterprise applications requiring automated file combination, efficient merge operations, and reliable data consolidation throughout complex business integration scenarios.

MERGE Syntax and Structure

MERGE Statement Format
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
MERGE sort-file-name ON {ASCENDING | DESCENDING} KEY key-field-1 [key-field-2 ...] [ON {ASCENDING | DESCENDING} KEY key-field-n ...] [COLLATING SEQUENCE IS alphabet-name] USING file-name-1 file-name-2 [file-name-3 ...] {OUTPUT PROCEDURE IS procedure-name | GIVING file-name}. *> Sort Description (SD) entry required SD sort-file-name. 01 sort-record-name. 05 key-field-1 PIC X(n). 05 key-field-2 PIC 9(n). 05 other-fields PIC X(n). *> Examples: *> Basic merge operation MERGE CUSTOMER-MERGE-FILE ON ASCENDING KEY CUST-ID USING CUSTOMER-FILE-A CUSTOMER-FILE-B GIVING MERGED-CUSTOMER-FILE. *> Merge with output procedure MERGE SALES-MERGE-FILE ON ASCENDING KEY REGION-CODE ON DESCENDING KEY SALES-AMOUNT USING NORTH-SALES SOUTH-SALES EAST-SALES WEST-SALES OUTPUT PROCEDURE IS CONSOLIDATE-SALES. *> Multiple key merge MERGE EMPLOYEE-MERGE-FILE ON ASCENDING KEY DEPT-CODE ON ASCENDING KEY EMPLOYEE-ID COLLATING SEQUENCE IS ASCII-SEQUENCE USING ACTIVE-EMPLOYEES INACTIVE-EMPLOYEES GIVING COMPLETE-EMPLOYEE-FILE.
File Merging
Data Integration
Sort Operations

Comprehensive MERGE Examples

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
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
IDENTIFICATION DIVISION. PROGRAM-ID. MERGE-DEMONSTRATION. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. *> Input files to be merged SELECT CUSTOMER-FILE-A ASSIGN TO "CUST-A.DAT" ORGANIZATION IS SEQUENTIAL FILE STATUS IS WS-STATUS-A. SELECT CUSTOMER-FILE-B ASSIGN TO "CUST-B.DAT" ORGANIZATION IS SEQUENTIAL FILE STATUS IS WS-STATUS-B. SELECT CUSTOMER-FILE-C ASSIGN TO "CUST-C.DAT" ORGANIZATION IS SEQUENTIAL FILE STATUS IS WS-STATUS-C. *> Output merged file SELECT MERGED-CUSTOMERS ASSIGN TO "MERGED.DAT" ORGANIZATION IS SEQUENTIAL FILE STATUS IS WS-MERGE-STATUS. *> Sort work file for merge SELECT SORT-WORK ASSIGN TO "SORTWORK" ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. *> Input file structures FD CUSTOMER-FILE-A. 01 CUSTOMER-RECORD-A. 05 CUST-ID-A PIC X(8). 05 CUST-NAME-A PIC X(30). 05 CUST-TYPE-A PIC X(10). 05 CUST-BALANCE-A PIC 9(8)V99. 05 CUST-REGION-A PIC X(5). FD CUSTOMER-FILE-B. 01 CUSTOMER-RECORD-B. 05 CUST-ID-B PIC X(8). 05 CUST-NAME-B PIC X(30). 05 CUST-TYPE-B PIC X(10). 05 CUST-BALANCE-B PIC 9(8)V99. 05 CUST-REGION-B PIC X(5). FD CUSTOMER-FILE-C. 01 CUSTOMER-RECORD-C. 05 CUST-ID-C PIC X(8). 05 CUST-NAME-C PIC X(30). 05 CUST-TYPE-C PIC X(10). 05 CUST-BALANCE-C PIC 9(8)V99. 05 CUST-REGION-C PIC X(5). FD MERGED-CUSTOMERS. 01 MERGED-CUSTOMER-RECORD. 05 MERGED-CUST-ID PIC X(8). 05 MERGED-CUST-NAME PIC X(30). 05 MERGED-CUST-TYPE PIC X(10). 05 MERGED-CUST-BALANCE PIC 9(8)V99. 05 MERGED-CUST-REGION PIC X(5). 05 MERGED-SOURCE-FILE PIC X(1). *> Sort file description for merge SD CUSTOMER-SORT-FILE. 01 CUSTOMER-SORT-RECORD. 05 SORT-CUST-ID PIC X(8). 05 SORT-CUST-NAME PIC X(30). 05 SORT-CUST-TYPE PIC X(10). 05 SORT-CUST-BALANCE PIC 9(8)V99. 05 SORT-CUST-REGION PIC X(5). 05 SORT-SOURCE-FILE PIC X(1). WORKING-STORAGE SECTION. *> File status variables 01 WS-FILE-STATUS. 05 WS-STATUS-A PIC X(2). 05 WS-STATUS-B PIC X(2). 05 WS-STATUS-C PIC X(2). 05 WS-MERGE-STATUS PIC X(2). *> Processing statistics 01 WS-MERGE-STATISTICS. 05 WS-RECORDS-FROM-A PIC 9(8) VALUE 0. 05 WS-RECORDS-FROM-B PIC 9(8) VALUE 0. 05 WS-RECORDS-FROM-C PIC 9(8) VALUE 0. 05 WS-TOTAL-MERGED PIC 9(8) VALUE 0. 05 WS-DUPLICATES-FOUND PIC 9(6) VALUE 0. 05 WS-REGIONAL-COUNTS. 10 WS-NORTH-COUNT PIC 9(6) VALUE 0. 10 WS-SOUTH-COUNT PIC 9(6) VALUE 0. 10 WS-EAST-COUNT PIC 9(6) VALUE 0. 10 WS-WEST-COUNT PIC 9(6) VALUE 0. *> Work variables 01 WS-WORK-VARIABLES. 05 WS-PREVIOUS-CUST-ID PIC X(8) VALUE SPACES. 05 WS-CURRENT-TOTAL PIC 9(10)V99 VALUE 0. 05 WS-REGION-TOTAL PIC 9(10)V99 VALUE 0. PROCEDURE DIVISION. MAIN-MERGE-PROCESSING. DISPLAY "=== COBOL MERGE DEMONSTRATION ===" DISPLAY SPACES PERFORM INITIALIZE-MERGE-PROCESS PERFORM DEMONSTRATE-BASIC-MERGE PERFORM DEMONSTRATE-COMPLEX-MERGE PERFORM DEMONSTRATE-OUTPUT-PROCEDURE PERFORM DISPLAY-MERGE-STATISTICS DISPLAY "=== MERGE DEMO COMPLETE ===" STOP RUN. INITIALIZE-MERGE-PROCESS. DISPLAY "Initializing merge demonstration..." *> Create sample input files (simulation) PERFORM CREATE-SAMPLE-FILES DISPLAY "Sample files created:" DISPLAY " Customer File A: North region customers" DISPLAY " Customer File B: South region customers" DISPLAY " Customer File C: East/West region customers" DISPLAY " All files pre-sorted by Customer ID" DISPLAY SPACES. CREATE-SAMPLE-FILES. *> This would normally be external data *> Simulating pre-sorted input files DISPLAY " Creating sample sorted input files..." DISPLAY " File A: 1000 North region records" DISPLAY " File B: 1500 South region records" DISPLAY " File C: 800 East/West region records" DISPLAY " Total records to merge: 3300". DEMONSTRATE-BASIC-MERGE. DISPLAY "=== BASIC MERGE OPERATION ===" DISPLAY SPACES DISPLAY "Performing basic merge with GIVING clause..." *> Basic merge using GIVING OPEN OUTPUT MERGED-CUSTOMERS MERGE CUSTOMER-SORT-FILE ON ASCENDING KEY SORT-CUST-ID USING CUSTOMER-FILE-A CUSTOMER-FILE-B CUSTOMER-FILE-C GIVING MERGED-CUSTOMERS CLOSE MERGED-CUSTOMERS *> Simulate successful merge MOVE 1000 TO WS-RECORDS-FROM-A MOVE 1500 TO WS-RECORDS-FROM-B MOVE 800 TO WS-RECORDS-FROM-C COMPUTE WS-TOTAL-MERGED = WS-RECORDS-FROM-A + WS-RECORDS-FROM-B + WS-RECORDS-FROM-C DISPLAY "Basic merge completed:" DISPLAY " Records from File A: " WS-RECORDS-FROM-A DISPLAY " Records from File B: " WS-RECORDS-FROM-B DISPLAY " Records from File C: " WS-RECORDS-FROM-C DISPLAY " Total merged records: " WS-TOTAL-MERGED DISPLAY SPACES. DEMONSTRATE-COMPLEX-MERGE. DISPLAY "=== COMPLEX MERGE WITH MULTIPLE KEYS ===" DISPLAY SPACES DISPLAY "Performing multi-key merge operation..." *> Complex merge with multiple sort keys MERGE CUSTOMER-SORT-FILE ON ASCENDING KEY SORT-CUST-REGION ON DESCENDING KEY SORT-CUST-BALANCE ON ASCENDING KEY SORT-CUST-ID USING CUSTOMER-FILE-A CUSTOMER-FILE-B CUSTOMER-FILE-C OUTPUT PROCEDURE IS PROCESS-COMPLEX-MERGE DISPLAY "Complex merge completed with multiple keys:" DISPLAY " Primary key: Region (ascending)" DISPLAY " Secondary key: Balance (descending)" DISPLAY " Tertiary key: Customer ID (ascending)" DISPLAY " Regional distribution processed" DISPLAY SPACES. PROCESS-COMPLEX-MERGE. 01 WS-REGION-PROCESSING. 05 WS-CURRENT-REGION PIC X(5) VALUE SPACES. 05 WS-REGION-RECORD-COUNT PIC 9(6) VALUE 0. 05 WS-REGION-BALANCE-TOTAL PIC 9(10)V99 VALUE 0. PERFORM RETURN-NEXT-RECORD PERFORM UNTIL CUSTOMER-SORT-RECORD = HIGH-VALUES *> Process each merged record PERFORM PROCESS-MERGED-RECORD PERFORM RETURN-NEXT-RECORD END-PERFORM PERFORM FINALIZE-REGION-PROCESSING. RETURN-NEXT-RECORD. RETURN CUSTOMER-SORT-FILE AT END MOVE HIGH-VALUES TO CUSTOMER-SORT-RECORD NOT AT END ADD 1 TO WS-TOTAL-MERGED END-RETURN. PROCESS-MERGED-RECORD. *> Check for region change IF SORT-CUST-REGION NOT = WS-CURRENT-REGION IF WS-CURRENT-REGION NOT = SPACES PERFORM DISPLAY-REGION-SUMMARY END-IF MOVE SORT-CUST-REGION TO WS-CURRENT-REGION MOVE 0 TO WS-REGION-RECORD-COUNT MOVE 0 TO WS-REGION-BALANCE-TOTAL END-IF *> Accumulate region statistics ADD 1 TO WS-REGION-RECORD-COUNT ADD SORT-CUST-BALANCE TO WS-REGION-BALANCE-TOTAL *> Check for duplicates IF SORT-CUST-ID = WS-PREVIOUS-CUST-ID ADD 1 TO WS-DUPLICATES-FOUND DISPLAY " Duplicate customer ID: " SORT-CUST-ID END-IF MOVE SORT-CUST-ID TO WS-PREVIOUS-CUST-ID *> Count by region EVALUATE SORT-CUST-REGION WHEN "NORTH" ADD 1 TO WS-NORTH-COUNT WHEN "SOUTH" ADD 1 TO WS-SOUTH-COUNT WHEN "EAST" ADD 1 TO WS-EAST-COUNT WHEN "WEST" ADD 1 TO WS-WEST-COUNT END-EVALUATE. DISPLAY-REGION-SUMMARY. DISPLAY " Region: " WS-CURRENT-REGION DISPLAY " Records: " WS-REGION-RECORD-COUNT DISPLAY " Total Balance: $" WS-REGION-BALANCE-TOTAL COMPUTE WS-CURRENT-TOTAL = WS-REGION-BALANCE-TOTAL / WS-REGION-RECORD-COUNT DISPLAY " Average Balance: $" WS-CURRENT-TOTAL. FINALIZE-REGION-PROCESSING. *> Display final region if any IF WS-CURRENT-REGION NOT = SPACES PERFORM DISPLAY-REGION-SUMMARY END-IF. DEMONSTRATE-OUTPUT-PROCEDURE. DISPLAY "=== MERGE WITH OUTPUT PROCEDURE ===" DISPLAY SPACES DISPLAY "Demonstrating merge with custom output processing..." *> Merge with output procedure for custom processing MERGE CUSTOMER-SORT-FILE ON ASCENDING KEY SORT-CUST-ID USING CUSTOMER-FILE-A CUSTOMER-FILE-B OUTPUT PROCEDURE IS CUSTOM-OUTPUT-PROCESSING DISPLAY "Output procedure merge completed" DISPLAY "Custom processing applied to merged data" DISPLAY SPACES. CUSTOM-OUTPUT-PROCESSING. 01 WS-OUTPUT-CONTROL. 05 WS-OUTPUT-COUNTER PIC 9(8) VALUE 0. 05 WS-HIGH-VALUE-CUSTOMERS PIC 9(6) VALUE 0. 05 WS-VIP-THRESHOLD PIC 9(8)V99 VALUE 10000.00. OPEN OUTPUT MERGED-CUSTOMERS PERFORM RETURN-FOR-OUTPUT PERFORM UNTIL CUSTOMER-SORT-RECORD = HIGH-VALUES ADD 1 TO WS-OUTPUT-COUNTER *> Custom processing logic PERFORM APPLY-BUSINESS-RULES PERFORM WRITE-PROCESSED-RECORD PERFORM RETURN-FOR-OUTPUT END-PERFORM CLOSE MERGED-CUSTOMERS DISPLAY "Custom output processing summary:" DISPLAY " Records processed: " WS-OUTPUT-COUNTER DISPLAY " VIP customers: " WS-HIGH-VALUE-CUSTOMERS DISPLAY " VIP threshold: $" WS-VIP-THRESHOLD. RETURN-FOR-OUTPUT. RETURN CUSTOMER-SORT-FILE AT END MOVE HIGH-VALUES TO CUSTOMER-SORT-RECORD END-RETURN. APPLY-BUSINESS-RULES. *> Identify high-value customers IF SORT-CUST-BALANCE >= WS-VIP-THRESHOLD ADD 1 TO WS-HIGH-VALUE-CUSTOMERS *> Could apply special processing here END-IF *> Additional business logic could be applied *> - Credit limit adjustments *> - Customer category updates *> - Regional pricing modifications. WRITE-PROCESSED-RECORD. *> Move data to output record MOVE SORT-CUST-ID TO MERGED-CUST-ID MOVE SORT-CUST-NAME TO MERGED-CUST-NAME MOVE SORT-CUST-TYPE TO MERGED-CUST-TYPE MOVE SORT-CUST-BALANCE TO MERGED-CUST-BALANCE MOVE SORT-CUST-REGION TO MERGED-CUST-REGION MOVE SORT-SOURCE-FILE TO MERGED-SOURCE-FILE WRITE MERGED-CUSTOMER-RECORD. DISPLAY-MERGE-STATISTICS. DISPLAY "=== FINAL MERGE STATISTICS ===" DISPLAY SPACES DISPLAY "Overall merge processing results:" DISPLAY " Total records merged: " WS-TOTAL-MERGED DISPLAY " Duplicate IDs found: " WS-DUPLICATES-FOUND DISPLAY "Regional distribution:" DISPLAY " North region: " WS-NORTH-COUNT " customers" DISPLAY " South region: " WS-SOUTH-COUNT " customers" DISPLAY " East region: " WS-EAST-COUNT " customers" DISPLAY " West region: " WS-WEST-COUNT " customers" COMPUTE WS-CURRENT-TOTAL = WS-NORTH-COUNT + WS-SOUTH-COUNT + WS-EAST-COUNT + WS-WEST-COUNT DISPLAY " Total verified: " WS-CURRENT-TOTAL " customers" DISPLAY "Merge operation benefits:" DISPLAY " ✓ Efficient combination of pre-sorted files" DISPLAY " ✓ Maintained sort order throughout process" DISPLAY " ✓ Custom processing during merge" DISPLAY " ✓ Duplicate detection and handling" DISPLAY " ✓ Regional analysis and reporting" DISPLAY SPACES. *> ================================================== *> UTILITY PROCEDURES FOR MERGE OPERATIONS *> ================================================== MERGE-UTILITIES. VALIDATE-INPUT-FILES-SORTED. *> Validate that input files are properly sorted *> This would check sort order before merge DISPLAY "Validating input file sort order..." DISPLAY " Customer File A: ✓ Sorted by Customer ID" DISPLAY " Customer File B: ✓ Sorted by Customer ID" DISPLAY " Customer File C: ✓ Sorted by Customer ID". PREPARE-MERGE-ENVIRONMENT. *> Set up merge environment and work files DISPLAY "Preparing merge environment..." DISPLAY " Sort work space: Allocated" DISPLAY " Output file: Ready" DISPLAY " Memory buffers: Initialized". PERFORM-MERGE-VALIDATION. *> Post-merge validation DISPLAY "Performing post-merge validation..." DISPLAY " Output file sort order: ✓ Verified" DISPLAY " Record count accuracy: ✓ Verified" DISPLAY " Data integrity: ✓ Verified". CLEANUP-MERGE-RESOURCES. *> Clean up merge resources DISPLAY "Cleaning up merge resources..." DISPLAY " Sort work files: Released" DISPLAY " Temporary storage: Freed" DISPLAY " File handles: Closed". HANDLE-MERGE-ERRORS. *> Error handling for merge operations DISPLAY "Merge error handling:" DISPLAY " Input file status: " WS-STATUS-A " " WS-STATUS-B " " WS-STATUS-C DISPLAY " Output file status: " WS-MERGE-STATUS DISPLAY " Error recovery procedures available".

MERGE vs SORT Comparison

MERGE Operation
  • • Combines pre-sorted files
  • • More efficient for sorted inputs
  • • Requires multiple input files
  • • Maintains sort order
SORT Operation
  • • Sorts unsorted data
  • • Can handle single input source
  • • More CPU intensive
  • • Creates sorted output

Interactive Tutorial

Hands-On Exercise: Implementing File Merge
Practice using MERGE for combining sorted customer files

Exercise 1: Basic Three-File Merge

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
SD CUSTOMER-MERGE-FILE. 01 CUSTOMER-MERGE-RECORD. 05 CUST-ID PIC X(8). 05 CUST-NAME PIC X(30). 05 CUST-BALANCE PIC 9(8)V99. 05 CUST-REGION PIC X(5). PROCEDURE DIVISION. MERGE-CUSTOMER-FILES. MERGE CUSTOMER-MERGE-FILE ON ASCENDING KEY CUST-ID USING NORTH-CUSTOMERS SOUTH-CUSTOMERS WEST-CUSTOMERS GIVING CONSOLIDATED-CUSTOMERS DISPLAY "Merged three regional customer files" DISPLAY "Output sorted by Customer ID".

Exercise 2: Merge with Output Processing

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
MERGE SALES-MERGE-FILE ON ASCENDING KEY REGION-CODE ON DESCENDING KEY SALES-AMOUNT USING Q1-SALES Q2-SALES Q3-SALES Q4-SALES OUTPUT PROCEDURE IS PROCESS-ANNUAL-SALES. PROCESS-ANNUAL-SALES. PERFORM RETURN-SALES-RECORD PERFORM UNTIL SALES-MERGE-RECORD = HIGH-VALUES *> Calculate running totals ADD SALES-AMOUNT TO REGION-TOTAL ADD SALES-AMOUNT TO ANNUAL-TOTAL *> Check for region change IF REGION-CODE NOT = PREVIOUS-REGION PERFORM DISPLAY-REGION-TOTAL MOVE REGION-CODE TO PREVIOUS-REGION MOVE 0 TO REGION-TOTAL END-IF PERFORM WRITE-ANNUAL-RECORD PERFORM RETURN-SALES-RECORD END-PERFORM.

Best Practices

Knowledge Check

Test Your Understanding

Question 1: MERGE Requirements

What are the key requirements for using the MERGE statement?

Answer: MERGE requires: 1) All input files must be pre-sorted on the same key sequence, 2) SD (Sort Description) entry for the merge file, 3) Proper key specification with ASCENDING/DESCENDING, and 4) Either GIVING clause or OUTPUT PROCEDURE to handle results.

Question 2: MERGE vs SORT

When should you use MERGE instead of SORT?

Answer: Use MERGE when you have multiple already-sorted files to combine. MERGE is more efficient than SORT for this scenario because it doesn't need to sort the data, just combine the sorted sequences.

Question 3: Output Processing

What's the advantage of using OUTPUT PROCEDURE with MERGE?

Answer: OUTPUT PROCEDURE allows custom processing of merged records before writing to output, including duplicate detection, business rule application, calculations, filtering, and custom formatting. GIVING writes records directly without processing.

Related Pages