The MERGE statement combines two or more identically ordered files by selected ASCENDING or DESCENDING key fields.
Unlike SORT, MERGE doesn't allow you to manipulate the records before they are merged. Like SORT, MERGE does allow you to
modify records after they are merged via the OUTPUT PROCEDURE phrase.
Note: This manual entry includes code examples and highlights for first-time users following the General Rules section.
General Format
MERGE merge-file
{ KEY AREA IS key-table }
{ ON {ASCENDING } KEY {key-name} } ...
{DESCENDING}
[ COLLATING SEQUENCE IS alpha-name ]
USING {in-file} ...
{ OUTPUT PROCEDURE IS proc-name }
{ GIVING {out-file} ... }
proc-name has the following format:
start-proc [ {THRU } end-proc ]
{THROUGH}
Syntax Rules
- merge-file names a sort file described by an SD entry in the Data Division.
- key-table must name a data item that is not located in the record for
merge-file.
key-table may not be subordinate to an OCCURS clause, nor may it be reference modified.
- key-table must reference a data item whose size is an even multiple of 7.
key-table is processed as if it had the following structure:
01 KEY-TABLE.
03 MERGE-KEY OCCURS N TIMES.
05 KEY-ASCENDING PIC X COMP-X.
05 KEY-TYPE PIC X COMP-X.
05 KEY-OFFSET PIC XX COMP-X.
05 KEY-SIZE PIC XX COMP-X.
05 KEY-DIGITS PIC X COMP-X.
Typically, programs will declare
key-table with a similar format.
- key-name is a data item in the record description associated with
merge-file. It may not be subordinate to an OCCURS clause, nor may it be a group item containing variable occurrence data items. The
maximum number of keys allowed is 23.
- alpha-name is an
alphabet-name defined in the SPECIAL-NAMES paragraph of the Environment Division.
- in-file and
out-file are files described by FD entries in the Data Division. They may not be sort files. The maximum number of input and output
files allowed is 25.
- start-proc and
end-proc are paragraph or section names in the Procedure Division.
- A MERGE statement may not appear in Declaratives or in the input or output procedure of a SORT or MERGE statement.
- If
merge-file contains variable length records,
in-file records must not be smaller than the smallest record in
merge-file nor larger than the largest. If
merge-file contains fixed length records,
in-file records may not be larger than the size of
merge-file's records.
- If
out-file contains variable length records,
merge-file records must not be smaller than the smallest record in
out-file nor larger than the largest. If
out-file contains fixed length records,
merge-file records may not be larger than the size of
out-file's records.
- If
merge-file contains more than one record description,
key-name need appear in only one of them. The character positions referenced by
key-name are used as the key for all the file's records.
- If
out-file is an indexed file, the first
key-name must be ASCENDING and must specify the same character positions in its record as the primary record key for
out-file.
- THRU is an abbreviation for THROUGH.
General Rules
- The MERGE statement merges all the records in the in-file files into
merge-file and then either writes these records to each
out-file or makes these records available to the specified OUTPUT PROCEDURE.
- If
merge-file contains fixed length records, any shorter
in-file records are space-filled on the right to match the record size.
- If
out-file contains fixed length records, any shorter
merge-file records are space-filled on the right to match the record size.
- The first
key-name is the major key, and the next
key-name is the next most significant key. This pattern continues for each
key-name specified.
- The ASCENDING phrase specifies that key values are to be ordered from lowest to highest. The DESCENDING phrase specifies the
reverse ordering. Once ASCENDING or DESCENDING is specified, it applies to each
key-name until another ASCENDING or DESCENDING adjective is encountered.
- Use the KEY AREA option when you do not know the specifics of the merge key until the program is run. You can use this to
allow users to enter merge key specifications, typically in conjunction with some form of data dictionary.
- Your program must fill in a table of information that describes the merge keys. This table, key-table, should have the format
described by Syntax Rule 3 above. The number of merge keys is determined by the number of occurrences in the table. The keys
are listed in order of precedence: table entry 1 describes the highest precedence key, table entry 2 the second highest, and
so on. If you need to process a variable number of keys, use a variable-size table (by using OCCURS DEPENDING ON).
- For each key, you must specify the following information:
KEY-ASCENDING:
|
This should be 0 or 1. Enter 1 to have an ascending merge sequence, 0 for descending.
|
KEY-TYPE:
|
Describes the underlying data format. The allowed values are listed in the next rule.
|
KEY-OFFSET:
|
Describes the distance (in standard character positions) from the beginning of the merge record to the beginning of the key
field. The first field in a merge record is at offset 0.
|
KEY-SIZE:
|
Describes the size of the key field in standard character positions.
|
KEY-DIGITS:
|
This is used only for numeric keys. It describes the number of digits contained in the key (counting digits on both sides
of the decimal point).
|
- The KEY-TYPE field uses a code to describe the type and internal storage format of the data item. Select from the following
values:
0
|
Numeric edited
|
1
|
Unsigned numeric (DISPLAY)
|
2
|
Signed numeric (DISPLAY, trailing separate)
|
3
|
Signed numeric (DISPLAY, trailing combined)
|
4
|
Signed numeric (DISPLAY, leading separate)
|
5
|
Signed numeric (DISPLAY, leading combined)
|
6
|
Signed COMP-2
|
7
|
Unsigned COMP-2
|
8
|
Unsigned COMP-3
|
9
|
Signed COMP-3
|
10
|
COMP-6
|
11
|
Signed binary (COMP-1, COMP-4, COMP-X)
|
12
|
Unsigned binary (COMP-1, COMP-4, COMP-X)
|
13
|
Signed native (COMP-5, COMP-N)
|
14
|
Unsigned native (COMP-5, COMP-N)
|
15
|
Floating point (FLOAT, DOUBLE)
|
16
|
Alphanumeric
|
17
|
Alphanumeric (justified)
|
18
|
Alphabetic
|
19
|
Alphabetic (justified)
|
20
|
Alphanumeric edited
|
22
|
Group
|
This coding is the same one used by the C interface, and is also used by Acu4GL. When specifying the key type, you may safely
use "alphanumeric" for all nonnumeric keys. (The merge rules are the same for each of these types). For numeric data, however,
you must specify the correct type or you may get merging errors.
- The results are undefined if you provide invalid data in the key-table. If you fail to specify any keys (by specifying a table
whose size is zero), you receive a file error on
merge-file. Under the default file status codes, this is file error 94 with a secondary status of 63.
- For nonnumeric keys, the COLLATING SEQUENCE phrase establishes the ordering. If this phrase is omitted, the NATIVE collating
sequence is used. For numeric keys, the ordering is specified by the algebraic value of the key.
- When the contents of all key fields in one input record equal the contents of the key fields in another, the order of return:
- follows the order of the associated in-files in the MERGE statement
- causes all records with equal key values from one input file to be returned before any are returned from another
- The MERGE statement transfers all records from each
in-file to merge-file. When the MERGE statement executes,
in-file must not be open. The results of the MERGE statement are undefined if the
in-file records are not ordered according to the KEY clause of the MERGE statement.
- For each
in-file, the MERGE statement:
- opens the file as if it had been the object of an OPEN INPUT statement with no options. This occurs before any associated
output procedure executes.
- retrieves the records of the file and releases them to the merge operation. The retrieval is performed as if the program had
executed a READ statement with the NEXT and AT END phrases.
- closes the file as if it were the object of a CLOSE statement with no options. This occurs after any associated output procedure
has finished execution.
These actions cause any associated USE procedures to execute if an exception condition occurs.
- The OUTPUT PROCEDURE, if specified, is executed by the MERGE statement when the records are ready to be processed in merged
order. The statements in the range of the output procedure must contain one or more RETURN statements to retrieve the merged
records. Control is passed to the output procedure by the MERGE statement according to the rules of the PERFORM statement.
When the last statement of the output procedure is executed, control returns to the MERGE statement. The MERGE statement then
closes the in-files and terminates.
- If the MERGE statement is in a fixed segment, the range of the output procedure must be contained completely in the fixed
segments and no more than one independent segment. If the MERGE statement is in an independent segment, the range must be
completely contained in the fixed segments and the same independent segment.
- If the GIVING phrase is used, the MERGE statement writes all merged records to each out-file. Out-file must not be open when
the MERGE statement executes.
- The MERGE statement writes records to out-file with the following steps:
- out-file is opened as if it were the object of an OPEN OUTPUT statement with no options.
- Each merged record is retrieved and written to
out-file as if it were the object of a WRITE statement.
- out-file is closed as if it were the object of a CLOSE statement with no options.
- The implicit OPEN, WRITE, and CLOSE operations cause associated USE procedures to execute if an exception condition occurs.
If the MERGE statement tries to write beyond the boundaries of
out-file, the applicable USE procedure executes. If that procedure returns, or no USE procedure is specified, the processing of that
out-file terminates with an implied CLOSE operation.
- If
out-file is a relative file, the value of the RELATIVE KEY data item is updated to contain the record number of each record after
it is written.
- The MERGE statement updates the value of the FILE STATUS data item associated with merge-file.
- If a MERGE statement is executed in a wrong context, the runtime displays the error
Illegal MERGE. This error belongs to the class of
intermediate runtime errors that, upon occurrence, call installed error procedures. See CBL_ERROR_PROC in Appendix I. Library Routines for details.
Code Example 1
*Merge sales prospects lists.
MERGE NATIONAL-MERGE-FILE
ON ASCENDING KEY PROSPECT-CLASS
SALES-REP-NUMBER
USING WESTERN-REGION-FILE,
EASTERN-REGION-FILE,
SOUTHERN-REGION-FILE
GIVING NATIONAL-PROSPECT-FILE.
Code Example 2
*Merge sales prospects lists and use an
*OUTPUT PROCEDURE to do processing on the list
*before writing it to the output file.
MERGE NATIONAL-MERGE-FILE
ON ASCENDING KEY PROSPECT-CLASS
SALES-REP-NUMBER
USING WESTERN-REGION-FILE,
EASTERN-REGION-FILE,
SOUTHERN-REGION-FILE
OUTPUT PROCEDURE IS PROCESS-PROSPECT-LIST.
(An extended code sample of this example may be found at the end of this page.)
Highlights for First-time Users
- MERGE can be thought of as a specialized version of SORT that has been optimized to give better processing performance than
can be achieved using SORT. Bear in mind, however, that MERGE, like SORT, does all of its I/O on disk files and will, therefore,
take a variable amount of time to complete, depending on the size of the input files, the number of records in the files and
the speed of the disk subsystems.
- MERGE does not allow the use of an input procedure for manipulating records before they are merged.
- The files to be merged must have identical record formats and be identically ordered by the same key fields.
- The result of the merge may be written directly to an output file or made available to an output procedure.
- The output procedure may not reference any of the input files or their records. You can access the records contained in the
input files, in merged order, by using RETURN to fetch records from the merge file.
- The KEY AREA phrase is a means for defining the merge keys at runtime. When you use KEY AREA, it is not required that the
merge file record descriptor contain entries for potential sort keys. Definition of the sort key(s) in the merge file is handled
internally by the MERGE routine, using the key table. See syntax rules 2 and 3 and general rules 6 through 10.
- Summary of the merge process:
- At the beginning of the MERGE process all input files (in-files) and the temporary merge file (merge-file) are opened and positioned at the head of the file. The input files cannot already be open when the MERGE statement begins.
- The records of each input file are sequentially READ and released to the merge operation.
- When all of the records in all of the input files have been read, the input files are closed and MERGE completes its merging
process.
- Following merge processing, if OUTPUT PROCEDURE is specified, control is passed to the output procedure. In the output procedure,
each record in the merge file is fetched, in sort order, by the RETURN verb for processing. When the last statement of the
output procedure is executed, control returns to the MERGE statement.
- If the GIVING phrase is used, the merged records are written to the specified output file(s).
Extended code example 2:
IDENTIFICATION DIVISION.
PROGRAM-ID. SAMPLE-FILE-MERGE.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT WESTERN-REGION-FILE
ASSIGN TO ....
SELECT EASTERN-REGION-FILE
ASSIGN TO ....
SELECT SOUTHERN-REGION-FILE
ASSIGN TO ....
SELECT NATIONAL-PROSPECT-FILE
ASSIGN TO ....
SELECT NATIONAL-MERGE-FILE
ASSIGN TO ....
DATA DIVISION.
FILE SECTION.
FD WESTERN-REGION-FILE.
01 W-REGION-RECORD PIC X(30).
FD EASTERN-REGION-FILE.
01 E-REGION-RECORD PIC X(30).
FD SOUTHERN-REGION-FILE.
01 S-REGION-RECORD PIC X(30).
SD NATIONAL-MERGE-FILE.
01 SORT-DATA.
05 PROSPECT-NUMBER PIC X(5).
05 PROSPECT-NAME PIC X(7).
05 PROSPECT-CLASS PIC X.
05 ESTIMATED-VALUE PIC 9999V9.
05 SALES-REP-NUMBER PIC X(3).
05 SALES-REP-NAME PIC X(7).
05 FILLER PIC XX.
FD NATIONAL-PROSPECT-FILE.
01 NATIONAL-RECORD PIC X(30).
WORKING-STORAGE SECTION.
01 FLAGS.
05 MERGE-LIST-EMPTY PIC X VALUE "N".
88 NO-MORE-RECORDS VALUE "Y".
...
PROCEDURE DIVISION.
PROSPECT-LIST-MERGE-PROCEDURE.
MERGE NATIONAL-MERGE-FILE
ON ASCENDING KEY PROSPECT-CLASS
SALES-REP-NUMBER
USING WESTERN-REGION-FILE,
EASTERN-REGION-FILE,
SOUTHERN-REGION-FILE
OUTPUT PROCEDURE IS PROCESS-PROSPECT-LIST.
PROCESS-PROSPECT-LIST SECTION.
CREATE-NATIONAL-PROSPECT-FILE.
OPEN OUTPUT NATIONAL-PROSPECT-FILE.
RETURN NATIONAL-MERGE-FILE
AT END MOVE "Y" TO MERGE-LIST-EMPTY.
PERFORM UPDATE-PROSPECT-DATA
UNTIL NO-MORE-RECORDS.
CLOSE NATIONAL-PROSPECT-FILE.
GO TO EXIT-MERGE-OUTPUT-PROCESSING.
UPDATE-PROSPECT-DATA.
*do not write records tagged "TestRep"
IF SALES-REP-NAME NOT = "TestRep"
*write the record to the output file
WRITE NATIONAL-RECORD FROM SORT-DATA.
END-IF.
*fetch the next record
RETURN NATIONAL-MERGE-FILE
AT END MOVE "Y" TO MERGE-LIST-EMPTY.
EXIT-MERGE-OUTPUT-PROCESSING.
EXIT.