MainframeMaster

COBOL Tutorial

COBOL SORT and MERGE Operations

Progress0 of 0 lessons

Introduction to SORT and MERGE

SORT and MERGE operations are powerful features in COBOL that allow you to arrange data in a specific sequence and combine pre-ordered data sources. These operations are essential for reports, analyses, batch processing, and data preparation tasks that require ordered data.

Key Capabilities

  • Sort records based on one or multiple key fields
  • Specify ascending or descending sequence for each key
  • Process records before and/or after sorting
  • Sort data from files or generated within a program
  • Merge multiple pre-sorted files while maintaining sequence
  • Sort table elements within memory (in modern COBOL)

SORT vs. MERGE: When to Use Each

FeatureSORTMERGE
Primary purposeArrange unsorted data in specified sequenceCombine multiple pre-sorted files maintaining sequence
Input requirementCan work with unsorted dataInput files must already be sorted in same sequence
PerformanceMay require multiple passes through dataRequires only one pass through each input file
Typical use caseCreating ordered reports from raw dataCombining daily transaction files into weekly file

SORT Statement Syntax

The SORT statement is used to arrange records or table elements into a specified sequence based on key fields. It offers several variations to handle different input and output scenarios.

Basic Syntax

cobol
1
2
3
4
5
6
7
8
9
10
11
SORT file-name ON {ASCENDING|DESCENDING} KEY data-name-1 [data-name-2 ...] [ON {ASCENDING|DESCENDING} KEY data-name-3 [data-name-4 ...]] ... [WITH DUPLICATES IN ORDER] [COLLATING SEQUENCE IS alphabet-name] {[USING file-name-1 [file-name-2 ...]] [INPUT PROCEDURE IS procedure-name-1 [THRU|THROUGH procedure-name-2]] } {[GIVING file-name-3 [file-name-4 ...]] [OUTPUT PROCEDURE IS procedure-name-3 [THRU|THROUGH procedure-name-4]] }

The SORT statement requires at least one key field and must have either input (USING or INPUT PROCEDURE) and output (GIVING or OUTPUT PROCEDURE) specifications.

Key Components Explained

ComponentDescription
file-nameThe sort file defined in the FILE SECTION with SD entry
ASCENDING/DESCENDING KEYSpecifies the sort order for each key field
data-nameFields used as sort keys in the sort file record
WITH DUPLICATES IN ORDERMaintains relative order of records with identical keys (optional)
COLLATING SEQUENCESpecifies the character ordering for alphanumeric comparisons
USINGNames input files containing records to be sorted
INPUT PROCEDURENames procedures that select/modify records before sorting
GIVINGNames output files to receive sorted records
OUTPUT PROCEDURENames procedures that process records after sorting

Sort File Description

The sort file is defined in the FILE SECTION using an SD (Sort Description) entry:

cobol
1
2
3
4
5
6
7
8
DATA DIVISION. FILE SECTION. SD SORT-WORK-FILE. 01 SORT-RECORD. 05 SR-EMPLOYEE-ID PIC 9(5). 05 SR-EMPLOYEE-NAME PIC X(30). 05 SR-DEPARTMENT PIC X(15). 05 SR-SALARY PIC 9(7)V99.

  • SD (Sort Description) is used instead of FD for sort files
  • No physical file is associated with the SD entry
  • The sort file is a temporary work area managed by the sort utility
  • The record description defines the layout of records being sorted

Simple SORT Examples

Here are several examples of SORT operations, starting with basic usage and progressing to more complex scenarios.

Example 1: Basic File Sort with USING and GIVING

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
IDENTIFICATION DIVISION. PROGRAM-ID. SIMPLESORT. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT UNSORTED-FILE ASSIGN TO 'UNSORTED.DAT' ORGANIZATION IS SEQUENTIAL. SELECT SORTED-FILE ASSIGN TO 'SORTED.DAT' ORGANIZATION IS SEQUENTIAL. SELECT SORT-WORK-FILE ASSIGN TO 'SORTWORK'. DATA DIVISION. FILE SECTION. FD UNSORTED-FILE. 01 UNSORTED-RECORD. 05 UR-CUSTOMER-ID PIC 9(6). 05 UR-CUSTOMER-NAME PIC X(30). 05 UR-BALANCE PIC 9(7)V99. FD SORTED-FILE. 01 SORTED-RECORD. 05 SR-CUSTOMER-ID PIC 9(6). 05 SR-CUSTOMER-NAME PIC X(30). 05 SR-BALANCE PIC 9(7)V99. SD SORT-WORK-FILE. 01 SORT-RECORD. 05 SORT-CUSTOMER-ID PIC 9(6). 05 SORT-CUSTOMER-NAME PIC X(30). 05 SORT-BALANCE PIC 9(7)V99. PROCEDURE DIVISION. MAIN-LOGIC. SORT SORT-WORK-FILE ON ASCENDING KEY SORT-CUSTOMER-ID USING UNSORTED-FILE GIVING SORTED-FILE DISPLAY "Sort completed successfully" STOP RUN.

This example shows a straightforward sort that reads records from UNSORTED-FILE, sorts them by customer ID in ascending order, and writes the sorted records to SORTED-FILE. The USING and GIVING clauses simplify the process by handling file I/O automatically.

Example 2: Multiple Sort Keys

cobol
1
2
3
4
5
6
7
* Sort on multiple keys with different sequencing SORT SORT-WORK-FILE ON ASCENDING KEY SORT-DEPARTMENT ON DESCENDING KEY SORT-SALARY ON ASCENDING KEY SORT-EMPLOYEE-NAME USING EMPLOYEE-FILE GIVING REPORT-FILE

This example sorts employee records first by department (A-Z), then by salary (highest to lowest) within each department, and finally by employee name (A-Z) for employees with the same department and salary.

Example 3: Sorting with Duplicate Handling

cobol
1
2
3
4
5
6
* Maintain the original order of records with identical keys SORT SORT-WORK-FILE ON ASCENDING KEY SORT-TRANSACTION-DATE WITH DUPLICATES IN ORDER USING TRANSACTION-FILE GIVING SORTED-TRANSACTION-FILE

The WITH DUPLICATES IN ORDER clause ensures that the relative order of records with identical keys is preserved. For example, if multiple transactions occurred on the same date, they will remain in their original sequence relative to each other.

INPUT PROCEDURE and RELEASE

An INPUT PROCEDURE gives you more control over which records are sorted and how they're prepared before sorting. This is useful when you need to filter records, transform data, or generate records programmatically.

INPUT PROCEDURE vs. USING

FeatureINPUT PROCEDUREUSING
ControlFull programmatic controlAutomatic file processing
Record selectionCan filter based on any criteriaAll records are included
Data transformationCan modify record contentRecords used as-is
ComplexityMore code requiredSimpler, more concise
PerformanceCan be more efficient by pre-filteringMay process unnecessary records

RELEASE Statement

In an INPUT PROCEDURE, the RELEASE statement sends records to the sort operation:

cobol
1
2
3
4
5
6
* Basic RELEASE statement RELEASE sort-record-name [FROM identifier] * Examples: RELEASE SORT-RECORD RELEASE SORT-RECORD FROM WORKING-RECORD

  • RELEASE transfers a record to the sort file for sorting
  • sort-record-name must be a record associated with the SD entry
  • The FROM option copies data from a working storage record
  • Each released record becomes part of the sort operation

Example with INPUT PROCEDURE

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
IDENTIFICATION DIVISION. PROGRAM-ID. SORTWITHPROC. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT TRANSACTION-FILE ASSIGN TO 'TRANS.DAT' ORGANIZATION IS SEQUENTIAL. SELECT REPORT-FILE ASSIGN TO 'REPORT.DAT' ORGANIZATION IS SEQUENTIAL. SELECT SORT-WORK-FILE ASSIGN TO 'SORTWORK'. DATA DIVISION. FILE SECTION. FD TRANSACTION-FILE. 01 TRANSACTION-RECORD. 05 TR-TYPE PIC X. 88 VALID-TYPE VALUES 'S', 'P', 'I'. 05 TR-AMOUNT PIC 9(7)V99. 05 TR-CUSTOMER-ID PIC 9(6). 05 TR-DATE PIC 9(8). 05 TR-DESCRIPTION PIC X(30). FD REPORT-FILE. 01 REPORT-RECORD PIC X(80). SD SORT-WORK-FILE. 01 SORT-RECORD. 05 SORT-CUSTOMER-ID PIC 9(6). 05 SORT-DATE PIC 9(8). 05 SORT-TYPE PIC X. 05 SORT-AMOUNT PIC 9(7)V99. 05 SORT-DESCRIPTION PIC X(30). WORKING-STORAGE SECTION. 01 FLAGS. 05 EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. PROCEDURE DIVISION. MAIN-LOGIC. SORT SORT-WORK-FILE ON ASCENDING KEY SORT-CUSTOMER-ID ON ASCENDING KEY SORT-DATE INPUT PROCEDURE IS PROCESS-INPUT GIVING REPORT-FILE DISPLAY "Sort completed successfully" STOP RUN. PROCESS-INPUT SECTION. OPEN INPUT TRANSACTION-FILE READ TRANSACTION-FILE AT END SET END-OF-FILE TO TRUE END-READ PERFORM UNTIL END-OF-FILE * Only process valid transaction types and non-zero amounts IF VALID-TYPE AND TR-AMOUNT > 0 MOVE TR-CUSTOMER-ID TO SORT-CUSTOMER-ID MOVE TR-DATE TO SORT-DATE MOVE TR-TYPE TO SORT-TYPE MOVE TR-AMOUNT TO SORT-AMOUNT MOVE TR-DESCRIPTION TO SORT-DESCRIPTION RELEASE SORT-RECORD END-IF READ TRANSACTION-FILE AT END SET END-OF-FILE TO TRUE END-READ END-PERFORM CLOSE TRANSACTION-FILE .

This example demonstrates an INPUT PROCEDURE that filters transactions by:

  • Only selecting records with valid transaction types ('S', 'P', 'I')
  • Only including transactions with amounts greater than zero
  • Rearranging fields in the sort record to optimize sorting
Only records that meet these criteria are RELEASEd to the sort operation.

OUTPUT PROCEDURE and RETURN

An OUTPUT PROCEDURE gives you control over how sorted records are processed after the sort operation. This is useful for generating reports, performing calculations on ordered data, or further filtering the sorted results.

OUTPUT PROCEDURE vs. GIVING

FeatureOUTPUT PROCEDUREGIVING
ControlFull programmatic controlAutomatic file output
ProcessingCan perform additional logicSimply writes records to file
Output formatCan generate formatted reportsOutputs records as-is
Multiple destinationsCan write to multiple files conditionallyCan output to multiple files but all get the same data

RETURN Statement

In an OUTPUT PROCEDURE, the RETURN statement retrieves the next sorted record:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
* Basic RETURN statement RETURN sort-file-name [AT END imperative-statement-1] [NOT AT END imperative-statement-2] [END-RETURN] * Alternative format with INTO clause RETURN sort-file-name INTO identifier [AT END imperative-statement-1] [NOT AT END imperative-statement-2] [END-RETURN]

  • RETURN retrieves the next record from the sorted sequence
  • The AT END phrase detects when all records have been processed
  • The INTO option copies the record to a working storage area
  • END-RETURN is a scope terminator for inline conditionals

Example with OUTPUT PROCEDURE

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
IDENTIFICATION DIVISION. PROGRAM-ID. SORTSUMMARY. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT SALES-FILE ASSIGN TO 'SALES.DAT' ORGANIZATION IS SEQUENTIAL. SELECT REPORT-FILE ASSIGN TO 'SUMMARY.RPT' ORGANIZATION IS SEQUENTIAL. SELECT SORT-WORK-FILE ASSIGN TO 'SORTWORK'. DATA DIVISION. FILE SECTION. FD SALES-FILE. 01 SALES-RECORD. 05 SALES-REGION PIC X(2). 05 SALES-PRODUCT PIC X(10). 05 SALES-AMOUNT PIC 9(7)V99. 05 SALES-DATE PIC 9(8). FD REPORT-FILE. 01 REPORT-LINE PIC X(80). SD SORT-WORK-FILE. 01 SORT-RECORD. 05 SORT-REGION PIC X(2). 05 SORT-PRODUCT PIC X(10). 05 SORT-AMOUNT PIC 9(7)V99. 05 SORT-DATE PIC 9(8). WORKING-STORAGE SECTION. 01 WS-CURRENT-REGION PIC X(2) VALUE SPACES. 01 WS-REGION-TOTAL PIC 9(9)V99 VALUE ZEROS. 01 WS-GRAND-TOTAL PIC 9(9)V99 VALUE ZEROS. 01 WS-EOF-FLAG PIC X VALUE 'N'. 88 WS-END-OF-FILE VALUE 'Y'. 01 WS-DETAIL-LINE. 05 WS-REGION PIC X(2). 05 FILLER PIC X(6) VALUE SPACES. 05 WS-PRODUCT PIC X(10). 05 FILLER PIC X(5) VALUE SPACES. 05 WS-AMOUNT PIC $,$$$,$$$,$$9.99. 05 FILLER PIC X(5) VALUE SPACES. 05 WS-DATE PIC 99/99/9999. 01 WS-TOTAL-LINE. 05 FILLER PIC X(10) VALUE 'Region '. 05 WS-TOTAL-REGION PIC X(2). 05 FILLER PIC X(15) VALUE ' Total Sales: '. 05 WS-TOTAL-AMOUNT PIC $$$,$$$,$$$,$$9.99. 01 WS-HEADER. 05 FILLER PIC X(20) VALUE 'SALES SUMMARY REPORT'. 05 FILLER PIC X(60) VALUE SPACES. PROCEDURE DIVISION. MAIN-LOGIC. SORT SORT-WORK-FILE ON ASCENDING KEY SORT-REGION ON ASCENDING KEY SORT-PRODUCT USING SALES-FILE OUTPUT PROCEDURE IS GENERATE-REPORT DISPLAY "Report generation complete" STOP RUN. GENERATE-REPORT SECTION. OPEN OUTPUT REPORT-FILE WRITE REPORT-LINE FROM WS-HEADER WRITE REPORT-LINE FROM SPACES RETURN SORT-WORK-FILE AT END SET WS-END-OF-FILE TO TRUE END-RETURN * Save first region for grouping IF NOT WS-END-OF-FILE MOVE SORT-REGION TO WS-CURRENT-REGION END-IF PERFORM UNTIL WS-END-OF-FILE * Check for region change (control break) IF SORT-REGION NOT = WS-CURRENT-REGION * Print region total and reset MOVE WS-CURRENT-REGION TO WS-TOTAL-REGION MOVE WS-REGION-TOTAL TO WS-TOTAL-AMOUNT WRITE REPORT-LINE FROM WS-TOTAL-LINE WRITE REPORT-LINE FROM SPACES * Update region and reset total MOVE SORT-REGION TO WS-CURRENT-REGION MOVE ZEROS TO WS-REGION-TOTAL END-IF * Format and write detail line MOVE SORT-REGION TO WS-REGION MOVE SORT-PRODUCT TO WS-PRODUCT MOVE SORT-AMOUNT TO WS-AMOUNT * Format date from YYYYMMDD to MM/DD/YYYY STRING SORT-DATE(5:2) '/' SORT-DATE(7:2) '/' SORT-DATE(1:4) INTO WS-DATE WRITE REPORT-LINE FROM WS-DETAIL-LINE * Accumulate totals ADD SORT-AMOUNT TO WS-REGION-TOTAL ADD SORT-AMOUNT TO WS-GRAND-TOTAL RETURN SORT-WORK-FILE AT END SET WS-END-OF-FILE TO TRUE END-RETURN END-PERFORM * Print final region total MOVE WS-CURRENT-REGION TO WS-TOTAL-REGION MOVE WS-REGION-TOTAL TO WS-TOTAL-AMOUNT WRITE REPORT-LINE FROM WS-TOTAL-LINE WRITE REPORT-LINE FROM SPACES * Print grand total MOVE 'ALL' TO WS-TOTAL-REGION MOVE WS-GRAND-TOTAL TO WS-TOTAL-AMOUNT WRITE REPORT-LINE FROM WS-TOTAL-LINE CLOSE REPORT-FILE .

This example demonstrates an OUTPUT PROCEDURE that:

  • Generates a formatted sales report from sorted data
  • Implements control breaks to show subtotals by region
  • Reformats dates from YYYYMMDD to MM/DD/YYYY
  • Calculates running totals for each region and a grand total
  • Formats numeric amounts with proper currency notation
The OUTPUT PROCEDURE gives complete control over how the sorted data is processed and presented.

MERGE Statement

The MERGE statement combines two or more sorted files into a single sorted file, maintaining the specified sequence. This is particularly useful for consolidating periodic transaction files or combining partitioned data.

MERGE Syntax

cobol
1
2
3
4
5
6
7
8
MERGE file-name ON {ASCENDING|DESCENDING} KEY data-name-1 [data-name-2 ...] [ON {ASCENDING|DESCENDING} KEY data-name-3 [data-name-4 ...]] ... [COLLATING SEQUENCE IS alphabet-name] USING file-name-1 file-name-2 [file-name-3 ...] {[GIVING file-name-4 [file-name-5 ...]] [OUTPUT PROCEDURE IS procedure-name-1 [THRU|THROUGH procedure-name-2]] }

  • Key components are similar to the SORT statement
  • USING requires at least two input files (must already be sorted)
  • No INPUT PROCEDURE option is available for MERGE
  • Output can be directed to files with GIVING or processed with OUTPUT PROCEDURE

Requirements for MERGE

RequirementDescription
Pre-sorted filesInput files must already be sorted in the same sequence as specified in the MERGE statement
Compatible recordsAll files must have compatible record formats with identical key fields
Key specificationsThe keys specified must match the sequence used when the input files were sorted
Minimum filesAt least two input files are required for a MERGE operation

Example: Basic MERGE Operation

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
IDENTIFICATION DIVISION. PROGRAM-ID. BASICMERGE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT DAILY-TRANS-1 ASSIGN TO 'DAY1.DAT' ORGANIZATION IS SEQUENTIAL. SELECT DAILY-TRANS-2 ASSIGN TO 'DAY2.DAT' ORGANIZATION IS SEQUENTIAL. SELECT DAILY-TRANS-3 ASSIGN TO 'DAY3.DAT' ORGANIZATION IS SEQUENTIAL. SELECT WEEKLY-TRANS ASSIGN TO 'WEEK.DAT' ORGANIZATION IS SEQUENTIAL. SELECT MERGE-WORK-FILE ASSIGN TO 'MERGEWORK'. DATA DIVISION. FILE SECTION. FD DAILY-TRANS-1. 01 DAILY-RECORD-1 PIC X(100). FD DAILY-TRANS-2. 01 DAILY-RECORD-2 PIC X(100). FD DAILY-TRANS-3. 01 DAILY-RECORD-3 PIC X(100). FD WEEKLY-TRANS. 01 WEEKLY-RECORD PIC X(100). SD MERGE-WORK-FILE. 01 MERGE-RECORD. 05 MR-TRANSACTION-ID PIC 9(8). 05 MR-CUSTOMER-ID PIC 9(6). 05 MR-TRANS-DATE PIC 9(8). 05 MR-TRANS-TYPE PIC X(2). 05 MR-AMOUNT PIC 9(7)V99. 05 MR-DESCRIPTION PIC X(50). 05 FILLER PIC X(17). PROCEDURE DIVISION. MAIN-LOGIC. MERGE MERGE-WORK-FILE ON ASCENDING KEY MR-CUSTOMER-ID ON ASCENDING KEY MR-TRANS-DATE USING DAILY-TRANS-1 DAILY-TRANS-2 DAILY-TRANS-3 GIVING WEEKLY-TRANS DISPLAY "Merge completed successfully" STOP RUN.

This example merges three daily transaction files (all pre-sorted by customer ID and transaction date) into a single weekly file, maintaining the same sort order. The MERGE statement assumes all files have compatible records and are already correctly sorted.

MERGE with OUTPUT PROCEDURE

cobol
1
2
3
4
5
6
7
8
9
10
* Merge with OUTPUT PROCEDURE for processing merged records MERGE MERGE-WORK-FILE ON ASCENDING KEY MR-REGION-CODE ON ASCENDING KEY MR-BRANCH-CODE ON ASCENDING KEY MR-TRANSACTION-DATE USING NORTHEAST-FILE SOUTHEAST-FILE MIDWEST-FILE WEST-FILE OUTPUT PROCEDURE IS GENERATE-SUMMARY-REPORT * The OUTPUT PROCEDURE would use RETURN statements similar to the SORT example * to process the merged records in sequence

This example merges regional transaction files and uses an OUTPUT PROCEDURE to generate a summary report. The procedure would use RETURN statements to retrieve the merged records and process them as needed.

Key Differences: SORT vs. MERGE

FeatureSORTMERGE
Input requirementsCan sort unsorted dataRequires pre-sorted input files
INPUT PROCEDURESupportedNot available
Number of input sourcesCan work with a single fileRequires at least two input files
Processing algorithmTypically uses multiple passesSingle-pass algorithm
Processing efficiencyLess efficient for large datasetsMore efficient when inputs are pre-sorted

Performance Considerations

The performance of SORT and MERGE operations can significantly impact batch processing times, especially when working with large volumes of data. Here are key considerations and optimization techniques.

Memory and Resource Allocation

  • Use SORT-CORE-SIZE special register to allocate memory (if available)
  • Specify sort work file size in JCL or environment settings
  • Pre-allocate sufficient temporary space for sort work files
  • For very large sorts, ensure adequate disk space is available
  • Consider multi-step processes for extremely large datasets

The more memory allocated to a sort operation, the fewer disk I/O operations required, which can dramatically improve performance for large datasets.

Key Selection and Design

  • Minimize the number and size of key fields
  • Place frequently used sort keys early in the record structure
  • Use binary or packed-decimal formats for numeric keys
  • Consider pre-formatting complex keys (like dates) for direct comparison
  • Limit the total key length to reduce comparison overhead

Input/Output Optimization

  • Pre-filter data with INPUT PROCEDURE to reduce volume
  • Use the simplest form (USING/GIVING) when possible
  • Consider fixed-length records for better performance
  • Use appropriate blocking factors for input and output files
  • Consider compressing data before sorting very large files
  • For mainframes, use efficient file organizations (VSAM, etc.)

Reducing the volume of data to be sorted through pre-filtering is often the single most effective optimization technique.

Platform-Specific Optimizations

PlatformOptimization Techniques
Mainframe
  • Use DFSORT parameters in JCL
  • Configure sort exit routines
  • Consider SMS-managed storage for work files
  • Use appropriate REGION size in JCL
Distributed Systems
  • Use runtime environment variables for sort settings
  • Place sort work files on separate physical drives
  • Consider multi-threaded sort utilities if available
  • Use memory-optimized sort settings for modern hardware

Exercises

Exercise 1: Basic File Sort

Write a complete COBOL program that:

  • Sorts a customer file by customer name in ascending order
  • Uses USING and GIVING clauses (no procedures)
  • Includes all necessary division headers and file definitions

Solution
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
IDENTIFICATION DIVISION. PROGRAM-ID. CUSTSORTER. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO 'CUSTDATA.DAT' ORGANIZATION IS SEQUENTIAL. SELECT SORTED-CUSTOMER-FILE ASSIGN TO 'SORTCUST.DAT' ORGANIZATION IS SEQUENTIAL. SELECT SORT-WORK-FILE ASSIGN TO 'SORTWORK'. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(6). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(50). 05 CUSTOMER-PHONE PIC X(14). FD SORTED-CUSTOMER-FILE. 01 SORTED-RECORD PIC X(100). SD SORT-WORK-FILE. 01 SORT-RECORD. 05 SORT-CUSTOMER-ID PIC 9(6). 05 SORT-CUSTOMER-NAME PIC X(30). 05 SORT-CUST-ADDRESS PIC X(50). 05 SORT-CUST-PHONE PIC X(14). PROCEDURE DIVISION. MAIN-LOGIC. SORT SORT-WORK-FILE ON ASCENDING KEY SORT-CUSTOMER-NAME USING CUSTOMER-FILE GIVING SORTED-CUSTOMER-FILE DISPLAY "Customer file has been sorted by name" STOP RUN.

Exercise 2: Using INPUT PROCEDURE

Modify the program from Exercise 1 to:

  • Use an INPUT PROCEDURE instead of USING
  • Filter out any customers with blank names
  • Convert all customer names to uppercase before sorting
  • Keep the GIVING clause the same

Solution
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
IDENTIFICATION DIVISION. PROGRAM-ID. CUSTSORTER. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO 'CUSTDATA.DAT' ORGANIZATION IS SEQUENTIAL. SELECT SORTED-CUSTOMER-FILE ASSIGN TO 'SORTCUST.DAT' ORGANIZATION IS SEQUENTIAL. SELECT SORT-WORK-FILE ASSIGN TO 'SORTWORK'. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(6). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(50). 05 CUSTOMER-PHONE PIC X(14). FD SORTED-CUSTOMER-FILE. 01 SORTED-RECORD PIC X(100). SD SORT-WORK-FILE. 01 SORT-RECORD. 05 SORT-CUSTOMER-ID PIC 9(6). 05 SORT-CUSTOMER-NAME PIC X(30). 05 SORT-CUST-ADDRESS PIC X(50). 05 SORT-CUST-PHONE PIC X(14). WORKING-STORAGE SECTION. 01 EOF-FLAG PIC X VALUE 'N'. 88 END-OF-FILE VALUE 'Y'. 01 RECORD-COUNTER PIC 9(6) VALUE ZERO. 01 SKIPPED-COUNTER PIC 9(6) VALUE ZERO. PROCEDURE DIVISION. MAIN-LOGIC. SORT SORT-WORK-FILE ON ASCENDING KEY SORT-CUSTOMER-NAME INPUT PROCEDURE IS PROCESS-CUSTOMERS GIVING SORTED-CUSTOMER-FILE DISPLAY "Customer file has been sorted by name" DISPLAY RECORD-COUNTER " valid records processed" DISPLAY SKIPPED-COUNTER " invalid records skipped" STOP RUN. PROCESS-CUSTOMERS SECTION. OPEN INPUT CUSTOMER-FILE READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE END-READ PERFORM UNTIL END-OF-FILE * Skip records with blank customer names IF CUSTOMER-NAME NOT = SPACES * Convert name to uppercase (simplified conversion for example) INSPECT CUSTOMER-NAME CONVERTING 'abcdefghijklmnopqrstuvwxyz' TO 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' * Copy record to sort file MOVE CUSTOMER-ID TO SORT-CUSTOMER-ID MOVE CUSTOMER-NAME TO SORT-CUSTOMER-NAME MOVE CUSTOMER-ADDRESS TO SORT-CUST-ADDRESS MOVE CUSTOMER-PHONE TO SORT-CUST-PHONE * Send to sort RELEASE SORT-RECORD ADD 1 TO RECORD-COUNTER ELSE ADD 1 TO SKIPPED-COUNTER END-IF READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE END-READ END-PERFORM CLOSE CUSTOMER-FILE .

Exercise 3: MERGE Operation

Write a COBOL program that:

  • Merges three monthly inventory files (MONTH1.DAT, MONTH2.DAT, MONTH3.DAT)
  • Orders records by item number (ascending) and transaction date (ascending)
  • Uses an OUTPUT PROCEDURE to calculate and display the total quantity of each item
  • Writes the merged records to a QUARTER.DAT file

Solution
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
IDENTIFICATION DIVISION. PROGRAM-ID. INVMERGER. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT MONTH1-FILE ASSIGN TO 'MONTH1.DAT' ORGANIZATION IS SEQUENTIAL. SELECT MONTH2-FILE ASSIGN TO 'MONTH2.DAT' ORGANIZATION IS SEQUENTIAL. SELECT MONTH3-FILE ASSIGN TO 'MONTH3.DAT' ORGANIZATION IS SEQUENTIAL. SELECT QUARTER-FILE ASSIGN TO 'QUARTER.DAT' ORGANIZATION IS SEQUENTIAL. SELECT MERGE-WORK-FILE ASSIGN TO 'MERGEWORK'. DATA DIVISION. FILE SECTION. FD MONTH1-FILE. 01 MONTH1-RECORD PIC X(80). FD MONTH2-FILE. 01 MONTH2-RECORD PIC X(80). FD MONTH3-FILE. 01 MONTH3-RECORD PIC X(80). FD QUARTER-FILE. 01 QUARTER-RECORD PIC X(80). SD MERGE-WORK-FILE. 01 MERGE-RECORD. 05 MR-ITEM-NUMBER PIC 9(6). 05 MR-TRANS-DATE PIC 9(8). 05 MR-QUANTITY PIC S9(5). 05 MR-DESCRIPTION PIC X(30). 05 MR-LOCATION PIC X(5). 05 MR-STATUS PIC X(1). 05 FILLER PIC X(25). WORKING-STORAGE SECTION. 01 WS-CURRENT-ITEM PIC 9(6) VALUE ZEROS. 01 WS-ITEM-TOTAL PIC S9(7) VALUE ZEROS. 01 WS-RECORD-COUNT PIC 9(6) VALUE ZEROS. 01 WS-EOF-FLAG PIC X VALUE 'N'. 88 WS-END-OF-FILE VALUE 'Y'. PROCEDURE DIVISION. MAIN-LOGIC. MERGE MERGE-WORK-FILE ON ASCENDING KEY MR-ITEM-NUMBER ON ASCENDING KEY MR-TRANS-DATE USING MONTH1-FILE MONTH2-FILE MONTH3-FILE OUTPUT PROCEDURE IS PROCESS-MERGED-DATA DISPLAY "Merge completed - " WS-RECORD-COUNT " records processed" STOP RUN. PROCESS-MERGED-DATA SECTION. OPEN OUTPUT QUARTER-FILE RETURN MERGE-WORK-FILE AT END SET WS-END-OF-FILE TO TRUE END-RETURN IF NOT WS-END-OF-FILE MOVE MR-ITEM-NUMBER TO WS-CURRENT-ITEM MOVE ZEROS TO WS-ITEM-TOTAL END-IF PERFORM UNTIL WS-END-OF-FILE * Check for item number change IF MR-ITEM-NUMBER NOT = WS-CURRENT-ITEM DISPLAY "Item " WS-CURRENT-ITEM ": Total quantity = " WS-ITEM-TOTAL MOVE MR-ITEM-NUMBER TO WS-CURRENT-ITEM MOVE ZEROS TO WS-ITEM-TOTAL END-IF * Accumulate quantity for current item ADD MR-QUANTITY TO WS-ITEM-TOTAL * Write the record to the output file WRITE QUARTER-RECORD FROM MERGE-RECORD ADD 1 TO WS-RECORD-COUNT RETURN MERGE-WORK-FILE AT END SET WS-END-OF-FILE TO TRUE END-RETURN END-PERFORM * Display the last item's total IF WS-RECORD-COUNT > 0 DISPLAY "Item " WS-CURRENT-ITEM ": Total quantity = " WS-ITEM-TOTAL END-IF CLOSE QUARTER-FILE .

Test Your Knowledge

1. What is the primary purpose of the SORT statement in COBOL?

  • To convert data between different formats
  • To arrange records or table elements in a specified sequence
  • To find specific records in a file
  • To combine two tables into one

2. What is the difference between a SORT and MERGE operation?

  • SORT works with one input source while MERGE combines multiple already-sorted input sources
  • SORT is only for numeric data, while MERGE works with any data type
  • SORT can only sort in ascending order, while MERGE can sort in either direction
  • MERGE is deprecated in modern COBOL

3. In a SORT statement, what does the USING clause specify?

  • The fields to be used as sort keys
  • The memory allocation for the sort operation
  • The input file(s) for the sort operation
  • The collating sequence to be used

4. What is an INPUT PROCEDURE in relation to SORT?

  • A procedure that defines how to interpret input data formats
  • A procedure executed for each record before it is released to the sort operation
  • A procedure that validates input before sorting
  • A procedure that creates index files for faster sorting

5. What statement is used to send a record to the sort operation from within an INPUT PROCEDURE?

  • WRITE
  • MOVE
  • RELEASE
  • SEND

Frequently Asked Questions