Function
The MERGE statement creates a sort-file into which records are accepted from two or more similarly sorted input files. It merges the records in the sort-file on the basis of a set of specified data items (keys) and, once this merge operation is finished, makes each record from the sort-file available to an output procedure or to output files.
Format
MERGE sort-file-name
{ON {DESCENDING | ASCENDING} {KEY | KEY-YY } {data-name-1}... }...
[COLLATING SEQUENCE IS alphabet-name]
USING {file-name-1}...
{ OUTPUT PROCEDURE IS section-name-1 [{THRU | THROUGH} section-name-2]
|GIVING {file-name-2}...
}
Syntax rules
sort-file-name must be defined in a sort-file description (SD) entry in the Data Division.
sort-file-name must correspond to the sort-file-name defined in the SELECT clause (format 2).
The file names specified in the USING phrase must not be specified in the GIVING phrase.
data-name-1... are key data-names. A key is that part of a record which is used as a basis for sorting. Key data-names must be defined in a record description belonging to an SD description entry. They are subject to the following rules:
The data items identified by key data-names must not be of variable length.
The data-names describing the keys may be qualified (see section "Qualification").
When two or more record descriptions are supplied, the keys need only be described in one of these descriptions. If a key is defined in more than one record description, the descriptions of that key must be identical, and must ensure that the key appears in the same position within each record.
A key must not be defined with an OCCURS clause and must not be subordinate to a data item defined with an OCCURS clause.
If the sort-file contains variable length records, all the data items identified by key data-names must be contained within the first n character positions of the record, where n equals the minimum record size specified for the sort-file.
A maximum of 64 keys may be specified for any file.
Each key must lie within the first 4096 bytes.
Keys are always listed from left to right in the order of their decreasing significance, regardless of whether they are ascending or descending. Hence, the first occurrence of data-name-1 would be the principal sort-key and the second occurrence of data-name-1 the subsidiary key.
A key, when expressed as a packed decimal, may have no more than 16 digits.
The keys following the KEY-YY specification must be defined either with PIC 99 USAGE DISPLAY or USAGE PACKED-DECIMAL.
section-name-1 identifies the first or only section in the output procedure. section-name-2 identifies the last section in the output procedure. It is required only if the output procedure consists of more than one section.
file-name-1..., file-name-2... must be defined in a file description (FD) entry in the Data Division.
The size of the records that can be passed to a MERGE operation or written to an output file is dependent on the record format of the sort-file (variable or fixed) and will be discussed in more detail in the "General rules" when the USING/GIVING phrases are mentioned.
At least one ASCENDING/DESCENDING phrase must be specified in a MERGE statement.
The MERGE statement may be written anywhere in the program except
in the declaratives area,
in an input/output procedure belonging to a SORT/MERGE statement.
The sort- and input-files named in the MERGE statement must not be specified together in the same SAME AREA, SAME SORT AREA or SAME SORT-MERGE AREA (see section "SAME AREA clause").
- If file-name-2 references an indexed file, the first specification of data-name-1 must be associated with an ASCENDING phrase and the data item referenced by that data-name-1 must occupy the same character positions in its record as the record key occupies within the file referenced by file-name-2.
General rules
- The collating sequence is set by means of the ASCENDING/DESCENDING option:
When ASCENDING is specified, sorting proceeds from the lowest to the highest value of the key, i.e. in ascending order.
When DESCENDING is specified, sorting proceeds from the highest to the lowest value of the key, i.e. in descending order.
The collating sequence is governed by the same rules as apply to the comparison of operands in a relation condition (see section "Relation condition").
When, according to the rules for the comparison of operands in a relation condition, the contents of all the key data items of one record are equal to the contents of the corresponding key data items of one or more other records, the order of return of these records:
Follows the order of the associated input files as specified in the MERGE statement.
Is such that all records associated with one input file are returned prior to the return of records from another input file.
When the program is executed, the collating sequence for the comparison of alphanumeric sort items is set as follows:
If COLLATING SEQUENCE has been specified in the MERGE statement, this entry is used as a sort criterion.
If COLLATING SEQUENCE was not specified in the MERGE statement, the program-specific collating sequence will be used (see section "OBJECT-COMPUTER paragraph").
The national (native) collating sequence is used for comparisons of national collating sequences.
- All records from the input files (file-name-1...) are transferred to the sort-file designated by sort-file-name. At the start of execution of the MERGE statement, the input files must not be in the open mode. The MERGE statement is executed for each of the referenced files in the following way:
The processing of the file is initiated. The initiation is performed as if an OPEN INPUT statement had been executed.
The logical records are obtained and released to the merge operation. Each record is obtained as if a READ statement with the NEXT and the AT END phrases had been executed. If the input file contains the RECORD clause with the DEPENDING phrase, the associated DEPENDING ON data item will not be provided for this READ operation. Relative files must be described in the FILE CONTROL paragraph with ACCESS MODE IS SEQUENTIAL.
If the sort-file contains variable length records, the size which the record had when it was input is used as the length for a record when it is transferred to a MERGE operation. This length must be within the range defined for the sort-file in the RECORD clause (see section "RECORD clause"). If the sort-file has a fixed length record format, records shorter than the specified format length will be supplied with blanks, longer records will not be permitted.The processing of the file is terminated. The termination is performed as if a CLOSE statement without optional phrases had been executed.
These implicit functions are performed such that any associated USE AFTER EXCEPTION/ERROR procedures are executed.
OUTPUT PROCEDURE indicates that the Procedure Division contains an output procedure to process records after they have been merged. If OUTPUT PROCEDURE is specified, control passes to it after the sort-file has been processed by the MERGE statement. During RETURN statement processing, the output procedure accepts the records from the sort-file. The compiler inserts a return mechanism at the end of the last section of the output procedure. When control passes to the last statement in the output procedure, the return mechanism provides for termination of the sort, and then passes control to the statement following the MERGE statement.
The following rules apply to the output procedure, which is a self-contained section within the Procedure Division:
It must consist of one or more sections that are written consecutively.
It must contain at least one RETURN statement, to make merged records available for processing.
It must not lead to execution of a MERGE, RELEASE, or SORT statement.
It may include any procedures needed to select, modify, or copy records.
A branch may be made from the output procedure if the programmer makes sure that a transfer of this type is followed by a return to the output procedure in order to effect a proper exit from this procedure (i.e. to processing its last statement).
A branch may be made from points outside an output procedure to procedure names within that procedure if the branch does not involve a RETURN statement or the end of the output procedure.
When the OUTPUT PROCEDURE phrase is used, control is passed from the specified procedure as though a format-1 PERFORM statement is executing. That is, all sections constituting the procedure are executed once, and execution of the procedure is terminated after its last statement has been processed. Thus, any procedure may be terminated by using an EXIT statement.
If MERGE statements are supplied in segmented programs, the following restrictions apply:
If a MERGE statement appears in a section which is outside any independent segment, then all input or output procedures referred to by that MERGE statement must be either wholly contained within one fixed segment, or wholly contained in a single independent segment.
If a MERGE statement appears in an independent segment, then all input or output procedures referred to by that MERGE statement must be either wholly contained within one fixed segment, or wholly contained in the same independent segment as the MERGE statement.
These restrictions do not apply to the compiler discussed in this manual.
If the GIVING phrase is specified, all the merged records are written on the output file (file-name-3...). At the start of execution of the MERGE statement, the output file must not be in the open mode. The MERGE statement is executed for each of the referenced files in the following way:
The processing of the file is initiated. The initiation is performed as if an OPEN statement with the OUTPUT phrase had been executed.
The merged logical records are returned and written onto the output file as if a WRITE statement without any optional phrases had been executed. The length of these records must be within the range defined for the output file (see section "RECORD clause").
For a relative file, the relative key data item for the first record returned contains the value 1; for the second record returned, the value 2, etc. After execution of the MERGE statement, the content of the relative data item indicates the last record returned to the file. The file must be defined in the FILE-CONTROL paragraph with ACCESS MODE IS SEQUENTIAL.The processing of the file is terminated. The termination is performed as if a CLOSE statement without optional phrases had been executed. If the output file contains the RECORD clause with DEPENDING ON phrase, the associated DEPENDING ON data item is not evaluated when a record is written. The current record length is used instead.
Example 8-53
IDENTIFICATION DIVISION. PROGRAM-ID. MERGE1. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT INPUT-FILE-1 ASSIGN TO "INPUT-FILE-1". SELECT INPUT-FILE-2 ASSIGN TO "INPUT-FILE-2". SELECT OUTPUT-FILE-1 ASSIGN TO "OUTPUT-FILE-1". SELECT OUTPUT-FILE-2 ASSIGN TO "OUTPUT-FILE-2". SELECT SORT ASSIGN TO "SORTWK". DATA DIVISION. FILE SECTION. FD INPUT-FILE-1 LABEL RECORD STANDARD. 01 INPUT-RECORD-1. 02 I10 PIC X. 02 I11 PIC 9(4). 02 I12 PIC 9(4). 02 I13 PIC 9(4). FD INPUT-FILE-2 LABEL RECORD STANDARD. 01 INPUT-RECORD-2. 02 I20 PIC X. 02 I21 PIC 9(4). 02 I22 PIC 9(4). 02 I23 PIC 9(4). FD OUTPUT-FILE-1 LABEL RECORD STANDARD. 01 O1RECORD PIC X(13). FD OUTPUT-FILE-2 LABEL RECORD STANDARD. 01 O2RECORD PIC X(13). SD SORT LABEL RECORD STANDARD. 01 SRECORD. 02 S0 PIC X. 02 S1 PIC 9(4). 02 S2 PIC 9(4). 02 S3 PIC 9(4). PROCEDURE DIVISION. MAIN SECTION. H01. MERGE SORT ON ASCENDING S1 S2 S3 (1) USING INPUT-FILE-1 INPUT-FILE-2 | GIVING OUTPUT-FILE-1 OUTPUT-FILE-2. (1) H02. STOP RUN.
(1) | The records of two files sorted in the same way are output to two identical files in a sorted sequence. |
All files are sorted in ascending order in accordance with the sort terms S1 S2 S3.
Example 8-54
IDENTIFICATION DIVISION. PROGRAM-ID. MERGE2. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT INPUT-FILE-1 ASSIGN TO "INPUT-FILE-1". SELECT INPUT-FILE-2 ASSIGN TO "INPUT-FILE-2". SELECT OUTPUT-FILE-1 ASSIGN TO "OUTPUT-FILE-1". SELECT OUTPUT-FILE-2 ASSIGN TO "OUTPUT-FILE-2". SELECT SORT ASSIGN TO "SORTWK". DATA DIVISION. FILE SECTION. FD INPUT-FILE-1 LABEL RECORD STANDARD. 01 INPUT-RECORD-1. 02 I10 PIC X. 02 I11 PIC 9(4). 02 I12 PIC 9(4). 02 I13 PIC 9(4). FD INPUT-FILE-2 LABEL RECORD STANDARD. 01 INPUT-RECORD-2. 02 I20 PIC X. 02 I21 PIC 9(4). 02 I22 PIC 9(4). 02 I23 PIC 9(4). FD OUTPUT-FILE-1 LABEL RECORD STANDARD. 01 O1RECORD PIC X(13). FD OUTPUT-FILE-2 LABEL RECORD STANDARD. 01 O2RECORD PIC X(13). SD SORT LABEL RECORD STANDARD. 01 SRECORD. 02 S0 PIC X. 02 S1 PIC 9(4). 02 S2 PIC 9(4). 02 S3 PIC 9(4). WORKING-STORAGE SECTION. 01 MERGE-STATUS PIC X VALUE LOW-VALUE. 88 MERGE-END VALUE HIGH-VALUE. PROCEDURE DIVISION. MAIN SECTION. H01. OPEN OUTPUT OUTPUT-FILE-1 OUTPUT-FILE-2. H02. MERGE SORT ON ASCENDING S1 S2 S3 (1) USING INPUT-FILE-1 INPUT-FILE-2 | OUTPUT PROCEDURE IS OUT1. (1) H03. CLOSE OUTPUT-FILE-1 OUTPUT-FILE-2. STOP RUN. . . . OUT1 SECTION. 001. PERFORM UNTIL MERGE-END (2) RETURN SORT | AT END | SET MERGE-END TO TRUE | NOT AT END | WRITE 01RECORD FROM SRECORD | WRITE 02RECORD FROM SRECORD (2) END-RETURN END-PERFORM.
(1) | The records from the files sorted in the same way are transferred to the sort file in their sorted order. Control then passes to the output procedure (OUT1 SECTION). |
(2) | The sort file is taken record by record and written to the output files. |