SORT Statement


The SORT statement is a powerful statement used for sorting files internally within the program. It's mainly useful in batch processing, where large amounts of data need to be sorted before further processing.

The SORT operation differs from other programming languages because it can work directly on input and output files without loading the data. It can be coded anywhere in the procedure division except in the declarative portion.

Syntax -

1----+----2----+----3----+----4----+----5----+----6
  SORT work-file-1 ON ASCENDING|DESCENDING KEY key-1
       [ASCENDING|DESCENDING KEY key-2 ...]
       [USING input-file1]
       [GIVING output-file]
       [COLLATING SEQUENCE IS alphabet-name]
       [USING input-file2 ...]
       [INPUT PROCEDURE IS para-1 THRU para-2]
       [OUTPUT PROCEDURE IS para-3 THRU para-4]
Note! All statements coded in [ ] are optional.

Parameters -

  • work-file-1 - The name of the sort work file. It's a logical file and does not correspond to any physical file.
  • ASCENDING|DESCENDING KEY - Specifies the sort order. You can sort on multiple keys.
  • key-1, key-2, ... - The data item(s) on which to sort.
  • USING input-file1, input-file2, ... - The name of the input file to be sorted.
  • GIVING output-file - The name of the output file where the sorted data will be written.
  • COLLATING SEQUENCE IS alphabet-name USING file-4 ... - Optional. Defines the sequence in which data is sorted. For instance, specify an EBCDIC or ASCII collating sequence.
  • INPUT PROCEDURE - Optional. A procedure is executed for each record of the input file before sorting.
  • OUTPUT PROCEDURE - Optional. A procedure is executed for each record of the sorted file.

Files used in sort process -

Three files are used in the sorting process −

  • Input file
  • Work file
  • Output file

Sort processing steps -

  • It opens work file in I-O mode, input file in INPUT mode, and output file in OUTPUT mode.
  • Transfers the records from input file to the work file.
  • Sorts the sort file based on the order coded with key-1.
  • Transfers the sorted records from work file to output file.
  • Closes the input, output files and releases (deletes) the work-file.

Practical Example -


Scenario - Let us assume we have an employee file that contains employee information unsorted. The file should be sorted based on the employee number (1-5 characters) in ascending order.

Input (MATEPK.EMPFILE.NSINPUT1) -

----+----1----+----2----+----3----+----4----+--
E0004EMPLOYEE4     TL   DEPT1LOC1 0000050000
E0002EMPLOYEE2     MGR  DEPT1LOC1 0000080000
E0006EMPLOYEE6     SE   DEPT1LOC1 0000034000
E0001EMPLOYEE1     DIR       LOC1 0000100000

Code -

----+----1----+----2----+----3----+----4----+----5----+
       IDENTIFICATION DIVISION.
       PROGRAM-ID. SORTFLS.
       AUTHOR. MTH.

       ENVIRONMENT DIVISION.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
           SELECT EMPFILE1 ASSIGN TO INPUT1.
           SELECT EMPFILEO ASSIGN TO OUTPUT1.
           SELECT WORKFILE ASSIGN TO WORK1.

       DATA DIVISION. 
       FILE SECTION.
       FD EMPFILE1
           RECORD CONTAINS 47 CHARACTERS
           DATA RECORD EMP-REC1
           RECORDING MODE F.
       01 EMP-REC1.
          COPY EMPREC.
       FD EMPFILEO 
           RECORD CONTAINS 47 CHARACTERS 
           DATA RECORD EMP-RECO 
           RECORDING MODE F.
       01 EMP-RECO.
          COPY EMPREC.
       SD WORKFILE
           RECORD CONTAINS 47 CHARACTERS 
           DATA RECORD WORK-REC
           RECORDING MODE F.
       01 WORK-REC.
          05 WORK-EMP-NUM     PIC 9(05).
          05 WORK-REM-REC     PIC X(42).

       PROCEDURE DIVISION.
           SORT WORKFILE
             ON ASCENDING KEY WORK-EMP-NUM 
                USING EMPFILE1
                GIVING EMPFILEO.
           STOP RUN.

JCL -

///MATEPKRJ JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID
//*
//STEP01  EXEC PGM=SORTFLS
//STEPLIB  DD  DSN=MATEPK.COBOL.LOADLIB,DISP=SHR
//INPUT1   DD  DSN=MATEPK.EMPFILE.NSINPUT1,DISP=SHR
//OUTPUT1  DD  DSN=MATEPK.EMPFILE.NSOUT1,
//            DISP=(NEW,CATLG,DELETE),
//            SPACE=(TRK,(3,2),RLSE),
//            UNIT=SYSDA,
//            DCB=(DSORG=PS,RECFM=FB,LRECL=47,BLKSIZE=470)
//WORK1    DD  DSN=&&TEMP,
//            DISP=(NEW,DELETE,DELETE),
//            SPACE=(CYL,(10,5),RLSE),
//            UNIT=SYSDA,
//            DCB=(DSORG=PS,RECFM=FB,LRECL=47,BLKSIZE=470)
//SYSOUT   DD  SYSOUT=*

Output (MATEPK.EMPFILE.NSOUT1) -

----+----1----+----2----+----3----+----4----+--
E0001EMPLOYEE1     DIR       LOC1 0000100000
E0002EMPLOYEE2     MGR  DEPT1LOC1 0000080000
E0004EMPLOYEE4     TL   DEPT1LOC1 0000050000
E0006EMPLOYEE6     SE   DEPT1LOC1 0000034000

Explaining Example -

In the above example, SORT statement sorts the input file records based on the employee number (1-5 bytes) and writes into the output file.