COBOL SORT Statement - Quick Reference
The SORT statement in COBOL is used to arrange records in a specified order using the COBOL SORT utility. It provides efficient external sorting capabilities for large datasets that cannot be sorted in memory.
Primary Use
Sort records in files using external sort utility
Division
PROCEDURE DIVISION
File Type
Sequential files with SD definition
Performance
External sorting for large datasets
Overview
The SORT statement is a powerful COBOL feature that uses the external SORT utility to arrange records in a specified order. It is designed for processing large datasets that cannot be sorted in memory and provides efficient external sorting capabilities. SORT works with sequential files and uses temporary sort-merge files managed by the SORT utility.
Syntax
1234567SORT sort-file-name ON ASCENDING KEY sort-key-1 [sort-key-2 ...] ON DESCENDING KEY sort-key-3 [sort-key-4 ...] [USING input-file-1 [input-file-2 ...]] [GIVING output-file-1 [output-file-2 ...]] [INPUT PROCEDURE procedure-name-1 [THROUGH procedure-name-2]] [OUTPUT PROCEDURE procedure-name-3 [THROUGH procedure-name-4]]
Practical Examples
Basic SORT Operation
12345678910111213141516171819202122232425262728293031323334353637383940414243* Basic SORT with single key IDENTIFICATION DIVISION. PROGRAM-ID. BASIC-SORT-EXAMPLE. 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. SD SORT-WORK-FILE. 01 SORT-RECORD. 05 SORT-EMPLOYEE-ID PIC X(6). 05 SORT-EMPLOYEE-NAME PIC X(25). 05 SORT-SALARY PIC 9(8)V99. FD UNSORTED-FILE. 01 UNSORTED-RECORD. 05 UNSORTED-EMPLOYEE-ID PIC X(6). 05 UNSORTED-EMPLOYEE-NAME PIC X(25). 05 UNSORTED-SALARY PIC 9(8)V99. FD SORTED-FILE. 01 SORTED-RECORD. 05 SORTED-EMPLOYEE-ID PIC X(6). 05 SORTED-EMPLOYEE-NAME PIC X(25). 05 SORTED-SALARY PIC 9(8)V99. PROCEDURE DIVISION. MAIN-LOGIC. * Sort by employee ID in ascending order SORT SORT-WORK-FILE ON ASCENDING KEY SORT-EMPLOYEE-ID USING UNSORTED-FILE GIVING SORTED-FILE DISPLAY "Sort completed successfully" STOP RUN.
Explanation: This example demonstrates a basic SORT operation that sorts employee records by employee ID in ascending order. The SORT statement uses the SORT-WORK-FILE (defined with SD) as temporary storage, reads from UNSORTED-FILE, and writes the sorted results to SORTED-FILE. The ON ASCENDING KEY clause specifies the sort order and key field.
Multi-Key SORT Operation
1234567891011121314151617181920212223242526272829303132333435363738394041424344454647* Multi-key SORT with mixed ordering IDENTIFICATION DIVISION. PROGRAM-ID. MULTI-KEY-SORT-EXAMPLE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT SALES-FILE ASSIGN TO "SALES.DAT" ORGANIZATION IS SEQUENTIAL. SELECT SORTED-SALES-FILE ASSIGN TO "SORTED-SALES.DAT" ORGANIZATION IS SEQUENTIAL. SELECT SORT-WORK-FILE ASSIGN TO "SORTWORK". DATA DIVISION. FILE SECTION. SD SORT-WORK-FILE. 01 SORT-RECORD. 05 SORT-REGION PIC X(2). 05 SORT-SALESPERSON PIC X(25). 05 SORT-SALES-AMOUNT PIC 9(8)V99. 05 SORT-DATE PIC X(8). FD SALES-FILE. 01 SALES-RECORD. 05 SALES-REGION PIC X(2). 05 SALES-SALESPERSON PIC X(25). 05 SALES-AMOUNT PIC 9(8)V99. 05 SALES-DATE PIC X(8). FD SORTED-SALES-FILE. 01 SORTED-SALES-RECORD. 05 SORTED-REGION PIC X(2). 05 SORTED-SALESPERSON PIC X(25). 05 SORTED-SALES-AMOUNT PIC 9(8)V99. 05 SORTED-DATE PIC X(8). PROCEDURE DIVISION. MAIN-LOGIC. * Sort by region (ascending), then by sales amount (descending) SORT SORT-WORK-FILE ON ASCENDING KEY SORT-REGION ON DESCENDING KEY SORT-SALES-AMOUNT USING SALES-FILE GIVING SORTED-SALES-FILE DISPLAY "Multi-key sort completed successfully" STOP RUN.
Explanation: This example demonstrates a multi-key SORT operation that sorts sales records first by region in ascending order, then by sales amount in descending order within each region. This creates a report where regions are ordered alphabetically, and within each region, salespeople are ordered by their sales amounts from highest to lowest.
SORT with INPUT PROCEDURE
12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364* SORT with INPUT PROCEDURE for data filtering IDENTIFICATION DIVISION. PROGRAM-ID. SORT-INPUT-PROC-EXAMPLE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT MASTER-FILE ASSIGN TO "MASTER.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. SD SORT-WORK-FILE. 01 SORT-RECORD. 05 SORT-CUSTOMER-ID PIC X(10). 05 SORT-CUSTOMER-NAME PIC X(30). 05 SORT-BALANCE PIC 9(8)V99. 05 SORT-STATUS PIC X(1). FD MASTER-FILE. 01 MASTER-RECORD. 05 MASTER-CUSTOMER-ID PIC X(10). 05 MASTER-CUSTOMER-NAME PIC X(30). 05 MASTER-BALANCE PIC 9(8)V99. 05 MASTER-STATUS PIC X(1). FD SORTED-FILE. 01 SORTED-RECORD. 05 SORTED-CUSTOMER-ID PIC X(10). 05 SORTED-CUSTOMER-NAME PIC X(30). 05 SORTED-BALANCE PIC 9(8)V99. 05 SORTED-STATUS PIC X(1). WORKING-STORAGE SECTION. 01 WS-EOF-FLAG PIC X(1) VALUE 'N'. PROCEDURE DIVISION. MAIN-LOGIC. * Sort with INPUT PROCEDURE to filter active customers SORT SORT-WORK-FILE ON ASCENDING KEY SORT-CUSTOMER-NAME INPUT PROCEDURE SELECT-ACTIVE-CUSTOMERS GIVING SORTED-FILE DISPLAY "Sort with input procedure completed" STOP RUN. SELECT-ACTIVE-CUSTOMERS. OPEN INPUT MASTER-FILE PERFORM UNTIL WS-EOF-FLAG = 'Y' READ MASTER-FILE AT END MOVE 'Y' TO WS-EOF-FLAG NOT AT END * Only include active customers (status = 'A') IF MASTER-STATUS = 'A' MOVE MASTER-RECORD TO SORT-RECORD RELEASE SORT-RECORD END-IF END-READ END-PERFORM CLOSE MASTER-FILE.
Explanation: This example demonstrates SORT with an INPUT PROCEDURE that filters data before sorting. The SELECT-ACTIVE-CUSTOMERS procedure reads the master file and only releases records for active customers (status = 'A') to the sort operation. This allows for data filtering and transformation before the actual sorting occurs, making the SORT operation more efficient by processing only relevant data.
SORT with OUTPUT PROCEDURE
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384* SORT with OUTPUT PROCEDURE for custom processing IDENTIFICATION DIVISION. PROGRAM-ID. SORT-OUTPUT-PROC-EXAMPLE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT INPUT-FILE ASSIGN TO "INPUT.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. SD SORT-WORK-FILE. 01 SORT-RECORD. 05 SORT-DEPARTMENT PIC X(3). 05 SORT-EMPLOYEE-ID PIC X(6). 05 SORT-SALARY PIC 9(8)V99. 05 SORT-YEARS-SERVICE PIC 99. FD INPUT-FILE. 01 INPUT-RECORD. 05 INPUT-DEPARTMENT PIC X(3). 05 INPUT-EMPLOYEE-ID PIC X(6). 05 INPUT-SALARY PIC 9(8)V99. 05 INPUT-YEARS-SERVICE PIC 99. FD REPORT-FILE. 01 REPORT-RECORD. 05 REPORT-LINE PIC X(80). WORKING-STORAGE SECTION. 01 WS-EOF-FLAG PIC X(1) VALUE 'N'. 01 WS-DEPARTMENT-TOTAL PIC 9(10)V99 VALUE ZERO. 01 WS-CURRENT-DEPT PIC X(3) VALUE SPACES. PROCEDURE DIVISION. MAIN-LOGIC. * Sort with OUTPUT PROCEDURE for custom report generation SORT SORT-WORK-FILE ON ASCENDING KEY SORT-DEPARTMENT ON DESCENDING KEY SORT-SALARY USING INPUT-FILE OUTPUT PROCEDURE GENERATE-DEPARTMENT-REPORT DISPLAY "Sort with output procedure completed" STOP RUN. GENERATE-DEPARTMENT-REPORT. OPEN OUTPUT REPORT-FILE PERFORM UNTIL WS-EOF-FLAG = 'Y' RETURN SORT-WORK-FILE AT END MOVE 'Y' TO WS-EOF-FLAG NOT AT END * Check for department change IF SORT-DEPARTMENT NOT = WS-CURRENT-DEPT * Write department total if not first department IF WS-CURRENT-DEPT NOT = SPACES MOVE WS-DEPARTMENT-TOTAL TO REPORT-LINE WRITE REPORT-RECORD END-IF * Start new department MOVE SORT-DEPARTMENT TO WS-CURRENT-DEPT MOVE ZERO TO WS-DEPARTMENT-TOTAL MOVE "Department: " TO REPORT-LINE(1:12) MOVE SORT-DEPARTMENT TO REPORT-LINE(13:3) WRITE REPORT-RECORD END-IF * Add salary to department total ADD SORT-SALARY TO WS-DEPARTMENT-TOTAL * Write employee record MOVE SORT-EMPLOYEE-ID TO REPORT-LINE(1:6) MOVE SORT-SALARY TO REPORT-LINE(20:10) WRITE REPORT-RECORD END-RETURN END-PERFORM * Write final department total IF WS-CURRENT-DEPT NOT = SPACES MOVE WS-DEPARTMENT-TOTAL TO REPORT-LINE WRITE REPORT-RECORD END-IF CLOSE REPORT-FILE.
Explanation: This example demonstrates SORT with an OUTPUT PROCEDURE that generates a custom report during the sort output phase. The GENERATE-DEPARTMENT-REPORT procedure processes sorted records and creates a department summary report with totals. It tracks department changes and accumulates salary totals, showing how OUTPUT PROCEDURE can be used for custom processing of sorted data.
Best Practices and Considerations
Important Considerations
- Always define sort files with SD statements in the FILE SECTION
- Ensure sufficient disk space for sort-merge files
- Use appropriate sort keys for optimal performance
- Consider using INPUT/OUTPUT procedures for data filtering and custom processing
- Test sort operations with various data sizes and key combinations
Advantages
- Efficient external sorting for large datasets
- Uses optimized SORT utility
- Supports multiple sort keys with different orders
- Provides INPUT/OUTPUT procedures for custom processing
- Handles datasets too large for memory sorting
Limitations
- Requires temporary disk space
- Limited to sequential file processing
- Performance depends on disk I/O speed
- Cannot sort in memory like table operations
- Requires proper file definitions and error handling
Performance Tips
- • Choose sort keys carefully to minimize sort complexity
- • Use INPUT PROCEDURE to filter data before sorting
- • Ensure adequate disk space for sort-merge files
- • Monitor sort performance and resource usage
- • Consider using OUTPUT PROCEDURE for custom processing
Test Your Knowledge
1. What is the primary purpose of the SORT statement in COBOL?
- To sort data in memory
- To sort records in files using external sort utility
- To sort programs
- To sort memory
2. In which COBOL division is the SORT statement typically used?
- IDENTIFICATION DIVISION
- ENVIRONMENT DIVISION
- DATA DIVISION
- PROCEDURE DIVISION
3. What is the relationship between SORT and SD statements?
- They are unrelated
- SD defines the sort file, SORT uses it
- SORT defines the file, SD uses it
- They are the same thing
4. Can SORT be used with all file types?
- Yes, with all file types
- No, only with sequential files
- No, only with indexed files
- Only with specific file types
5. What is the difference between SORT and internal table sorting?
- They are the same thing
- SORT uses external utility, table sorting uses memory
- SORT is faster than table sorting
- SORT is obsolete, table sorting is modern
Related Concepts
SD Statement
Understanding SD statements for sort-merge file definitions.
SORT-MERGE Statement
Using SORT-MERGE for combining sorted files.
File Processing
Complete guide to file processing in COBOL.
Data Organization
Data organization and sorting techniques.
External Sort Utility
Understanding the COBOL SORT utility.