Your Browser is not longer supported

Please use Google Chrome, Mozilla Firefox or Microsoft Edge to view the page correctly
Loading...

{{viewport.spaceProperty.prod}}

SORT statement

Function

Format 1

Sorting records.
The SORT statement is used to sort records either created in an input procedure or contained in a file according to a data items (set of specified keys).
The sorted records are released to an output procedure or entered in a file.

Format 2

Sorting tables.
The SORT statement causes table elements to be arranged according to a user-defined collating sequence.

Format 1 Sorting records


SORT sort-file-name

{ON {DESCENDING | ASCENDING} {KEY | KEY-YY } {data-name-1}... }...

[WITH DUPLICATES IN ORDER]

[COLLATING SEQUENCE IS alphabet-name]

{INPUT PROCEDURE IS paragraph-name-1 [{THRU | THROUGH} paragraph-name-2] | USING {file-name-1}...}

{OUTPUT PROCEDURE IS paragraph-name-3 [{THRU | THROUGH} paragraph-name-4] | GIVING {file-name-2}...}


Syntax rules

  1. The SORT statement may be specified anywhere in the Procedure Division except

    • in DECLARATIVES and

    • in input/output procedures which belong to a SORT statement.

  2. sort-file-name must be described in a sort-file description (SD) entry in the Data Division.

  3. sort-file-name must correspond to the sort-file-name defined in the SELECT clause (format 2).

  4. data-name-1... are key data-names. A key is that part of a record which is used as a basis for sorting. Keys must be defined in a record description belonging to an SD entry. They are subject to the following rules:

    1. The data items must not be of variable length.

    2. Key data-names may be qualified (see section "Qualification").

    3. When two or more record descriptions are supplied, the keys need only be described in one of these descriptions. The byte positions addressed by the key in the record description are also regarded as a key in all other data descriptions of the file.

    4. A key must not be defined with an OCCURS clause and must not be subordinate to a data item defined with an OCCURS clause.

    5. If the sort file referenced by file-name-1 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.

    6. A maximum of 64 keys may be specified for any file.

    7. A key must begin within the first 4096 bytes of the record.

    8. Keys for sorting purposes are always listed from left to right in order of significance, regardless of whether they are ascending or descending. Hence, the first specification of data-name-1 is the principal key and the second specification of data-name-1 the subsidiary key.

    9. The maximum length of a key which can be processed by SORT depends on the format of the key. The maximum length is 16 bytes for the packed decimal format (PD), the length of the record for a character-string, and 256 bytes for all other formats.

    10. The keys following the KEY-YY specification must be defined either with PIC 99 USAGE DISPLAY or USAGE PACKED-DECIMAL (see chapter "Report Writer" ).

  5. file-name-1..., file-name-2... must be defined in a file description (FD) entry in the DATA DIVISION.

  6. The record length of records from input files passed to the SORT operation are governed by the following rules: If the sort file has a fixed length record format, program execution is terminated if the record is too long. If the record is too short, the missing spaces will be filled with blanks. If the sort file has a variable length record format, the input records are accepted without any alteration of their length. This length must be within the range specified for the sort file in the RECORD clause (see section "RECORD clause").

  7. At least one ASCENDING/DESCENDING phrase must be specified in a SORT statement.

  8. No pair of file-names in the same SORT statement may be specified in the SAME SORT AREA or SAME SORT-MERGE AREA clause.

  9. 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 data item associated with the prime record key for that file.

General rules

  1. The collating sequence is set by means of the ASCENDING/DESCENDING option:

    1. When ASCENDING is specified, the sorted sequence will be from the lowest to the highest value of the key, i.e. in ascending order.

    2. When DESCENDING is specified, the sorted sequence will be 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 "Relation conditions".

  2. If DUPLICATES is specified and several records have the same contents in all of their sort items, then the order of return of these records is as follows:

    1. If no input procedure is specified, the records are returned in the order in which the associated files were specified in the SORT statement. If records with identical sort item contents exist in one and the same file, the records are returned in the order in which they were entered.

    2. If an input procedure is specified, the records are returned in the order in which they left the input procedure.

  3. If DUPLICATES is not specified and several records have the same contents in all of their items, then the order of return of these records is undefined.

  4. When the program is executed, the collating sequence for the comparison of alphanumeric sort items is set as follows:

    1. If COLLATING SEQUENCE has been specified in the SORT statement, this entry is used as a sort criterion.

    2. If COLLATING SEQUENCE was not specified in the SORT 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.

  5. INPUT PROCEDURE indicates that the Procedure Division contains an input procedure to process records prior to sorting. If INPUT PROCEDURE is specified, control passes to it when the input section of the SORT program is ready to accept the first record. During RELEASE statement processing the input procedure releases records to the sort-file (see section "RELEASE statement"). The compiler inserts a return mechanism at the end of the last section in the input procedure, i.e. once the last statement in the input procedure has been processed the input procedure is terminated and the released records will be sorted in the sort-file. The following rules apply to the input procedure, which is a self-contained section within the Procedure Division:

    1. It must consist of one or more sections that are written consecutively.

    2. It must contain at least one RELEASE statement so that records can be released to the sort-file (see section "RELEASE statement").

    3. It must not lead to the execution of a MERGE, RETURN, or SORT statement.

    4. It may include any procedures needed to select, modify or copy records.

    5. It is permitted to leave the input procedure if the programmer makes sure that a transfer from the input procedure is followed by a return to it, in order to effect a proper exit from this procedure (i.e. processing its last statement).

    6. It is permitted to branch from points outside an input procedure to procedure-names within that procedure if such a branch does not involve a RELEASE statement or the end of the input procedure.

  6. An input procedure, when specified, is processed before the records in the sort-file are sorted.

  7. If the USING phrase is specified, all the records in the input files (file-name-1...) are transferred to the sort file referenced by sort-file-name. The input files must not be in the open mode when execution of the SORT statement begins. The execution of the SORT statement for each of the named files consists of the following phases:

    1. The processing of the file is initiated. The initiation is performed as if an OPEN statement with the INPUT phrase had been executed.

    2. The logical records are obtained and released to the sort operation. Each record is obtained as if a READ statement with the NEXT RECORD and the AT END phrases had been executed. For a relative file, the content of the relative key data item is undefined after the execution of the SORT statement if file-name-1 is not additionally referenced in the GIVING phrase. A relative file must be defined in the FILE CONTROL paragraph with ACCESS MODE IS SEQUENTIAL.

    3. The processing of the file is terminated. The termination is performed as if a CLOSE statement without optional phrases had been executed. This termination is performed before the sort operation begins.

    These implicit functions are performed such that any associated USE AFTER EXCEPTION/ERROR procedures are executed; however, the execution of such a USE procedure must not cause the execution of any statement manipulating the input files or their record area declarations.
  8. OUTPUT PROCEDURE means that the Procedure Division contains an output procedure in which records are processed after sorting. If OUTPUT PROCEDURE is specified, control is passed to the output procedure after the sort-file has been processed by the SORT command. 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 in the output procedure, i.e. once the last statement in the output procedure has been executed the procedure is terminated and control passes to the statement that follows the SORT statement.
    The following rules apply to the output procedure, which is a self-contained section within the Procedure Division:

    1. It must consist of one or more sections that are written consecutively and that do not form part of an input procedure.

    2. It must contain at least one RETURN statement to make the sorted records available for processing (see section "RETURN statement").

    3. It must not lead to the execution of a MERGE, RELEASE, or SORT statement.

    4. It may include any procedures needed to select, modify, or copy records before they are transferred.

    5. It is permitted to leave the output procedure if the programmer makes sure that a transfer from the output procedure is followed by a return to it, in order to effect a proper exit from this procedure (i.e. processing its last statement).

    6. It is permitted to branch from points outside an output procedure to procedurenames within that procedure if such a branch does not involve a RETURN statement or the end of the output procedure.

  9. When the INPUT PROCEDURE or OUTPUT PROCEDURE phrase is used, a branch is performed in the program as if it were a format-1 PERFORM statement. This means that all sections that form the procedure are run once and procedure execution terminates once the last statement has been processed. Thus, either procedure (or both) may be terminated by an EXIT statement.

  10. If GIVING file-name-2... is specified, all the sorted records are written on the output file (file-name-2).
    The output file must not be in the open mode when execution of the SORT statement begins. The SORT statement is executed for each of the referenced files in the following way:

    1. The processing of the file is initiated. The initiation is performed as if an OPEN statement with the OUTPUT phrase had been executed. This initiation is performed after the execution of any input procedure.

    2. The sorted 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 SORT 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.

    3. 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; however, the execution of such a USE procedure must not cause the execution of any statement manipulating the input files or their record area declarations. On the first attempt to write beyond the externally defined boundaries of the file, any USE AFTER STANDARD EXCEPTION/ERROR procedure specified for the file is executed; if control is returned from this USE procedure or if no such USE procedure was specified, the processing of the file is terminated, as described in c) above.

  11. Since the SORT statement is not directed at individual records, it does not conform to the standard input/output statements (READ, WRITE, etc.). The READ statement, when executing, reads a single record; likewise, the WRITE statement writes an individual record. The SORT statement, on the other hand, does not treat an individual record but an entire file. Thus, this entire file must be placed at the disposal of SORT, either via the USING phrase or by repeated use of the RELEASE statement within an input procedure, before SORT can function. The SORT routine alters the sequence of the records within the file, and hence the first record returned by the SORT routine is, as a rule, not the first record released to the routine. SORT cannot provide any output before it has received the whole of the input.

Examples of file SORT

Example 8-74

Sort processing with one output file

IDENTIFICATION DIVISION.
PROGRAM-ID.
SORT1.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT MASTER-FILE ASSIGN TO "MASTER-FILE".
    SELECT OUTPUT-FILE ASSIGN TO "OUTPUT-FILE".
    SELECT SORT-FILE ASSIGN TO "SORTWK".
DATA DIVISION.
FILE SECTION.
FD  MASTER-FILE LABEL RECORD STANDARD.
01  MASTER-RECORD.
    02  E0            PIC X.
    02  E1            PIC 9(4). 
    02  E2            PIC 9(4).
    02  E3            PIC 9(4).
FD  OUTPUT-FILE LABEL RECORD STANDARD.
01  OUTPUT-RECORD. 
    02  A0            PIC X. 
    02  A1            PIC 9(4).
    02  A2            PIC 9(4).
    02  A3            PIC 9(4).
SD  SORT-FILE LABEL RECORD STANDARD.
01  SORT-RECORD.
    02  S0             PIC X.
    02  S1             PIC 9(4).
    02  S2             PIC 9(4).
    02  S3             PIC 9(4). 
PROCEDURE DIVISION.
P1 SECTION. 
SORTING.
    SORT SORT-FILE ASCENDING S1 S2 S3                 (1)
                                                       |
         USING MASTER-FILE GIVING OUTPUT-FILE.        (1) 
    STOP RUN.

(1)

The sort operation takes place in the following stages:

  1. The records are released from the input file MASTER-FILE to the SORT-FILE.

  2. The records are sorted in the sort-file according to ascending S1, or (in those records with identical S1) according to ascending S2, or (in records with identical S1 and S2) according to ascending S3.

  3. The records are released from the sort-file to the OUTPUT-FILE.

Example 8-75

Sort processing with two output files

IDENTIFICATION DIVISION.
PROGRAM-ID. SORT2.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT MASTER-FILE ASSIGN TO "MASTER-FILE".
    SELECT OUTPUT-FILE-1 ASSIGN TO "OUTPUT-FILE-1".
    SELECT OUTPUT-FILE-2 ASSIGN TO "OUTPUT-FILE-2".
    SELECT SORT-FILE ASSIGN TO "SORTWK".
DATA DIVISION.
FILE SECTION.
FD  MASTER-FILE LABEL RECORD STANDARD.
01  INPUT-RECORD.
    02  E0           PIC X.
    02  E1           PIC 9(4).
    02  E2           PIC 9(4).
    02  E3           PIC 9(4).
FD  OUTPUT-FILE-1 LABEL RECORD STANDARD.
01  OUTPUT-RECORD-1 PIC X(13).
FD  OUTPUT-FILE-2 LABEL RECORD STANDARD.
01  OUTPUT-RECORD-2 PIC X(13).
SD  SORT-FILE LABEL RECORD STANDARD.
01  SORT-RECORD.
    02  S0           PIC X.
    02  S1           PIC 9(4).
    02  S2           PIC 9(4).
    02  S3           PIC 9(4).
WORKING-STORAGE SECTION.
01  INPUT-STATUS PIC X VALUE LOW-VALUE.
    88  INPUT-END VALUE HIGH-VALUE.
01  SORT-STATUS PIC X VALUE LOW-VALUE.
    88  SORT-END VALUE HIGH-VALUE.
PROCEDURE DIVISION.
MAIN SECTION.
M1.
    OPEN INPUT MASTER-FILE OUTPUT OUTPUT-FILE-1 OUTPUT-FILE-2.
    SORT SORT-FILE ASCENDING S1 S2 S3              (1)
         INPUT PROCEDURE IPROC                      |
         OUTPUT PROCEDURE OPROC.                   (1)
    CLOSE MASTER-FILE OUTPUT-FILE-1 OUTPUT-FILE-2.
ME.
    STOP RUN.
IPROC SECTION.
IP0.
    PERFORM UNTIL INPUT-END                        (2)
      READ INPUT                                    |
      AT END                                        |
        SET INPUT-END TO TRUE                       |
      NOT AT END                                    |
        IF E0 NOT = "C"                             |
          THEN                                      |
          RELEASE SORT-RECORD FROM INPUT-RECORD     |
        END-IF                                      |
      END-READ                                      |
    END-PERFORM.                                   (2)
OPROC SECTION.
A0.
    PERFORM UNTIL SORT-END                         (3)
      RETURN SORT-FILE                              |
      AT END                                        |
        SET SORT-END TO TRUE                        |
      NOT AT END                                    |
        IF S0 = "A"                                 |
        THEN                                        |
          WRITE OUTPUT-RECORD-1 FROM SORT-RECORD    |
        ELSE                                        |
          WRITE OUTPUT-RECORD-2 FROM SORT-RECORD    |
        END-IF                                      |
      END-RETURN                                    |
    END-PERFORM.                                   (3)

(1)
 

  1. Control passes to the input procedure (IPROC SECTION).

  2. The records in the sort-file are sorted in ascending order according to S1 S2 S3.

  3. Control passes to the output procedure (OPROC SECTION).

(2)
 

A record is read from the input file. Only those records without a "C" in their first character position are to be processed. If the INPUT-RECORD is valid, it is released to the sort-file as SORT-RECORD. This process continues until the end of the input-file is encountered. Control then returns to the SORT statement.

(3)
 
 
 

A record is released from the sort-file. If its first character position contains an "A", it is written to the first output file (OUTPUT-FILE-1). All other records are written to the second output file (OUTPUT-FILE-2). When all the records in the sort-file have been processed, the statement following the SORT statement is executed.

Format 2 Sorting tables


SORT data-name-2 {ON {ASCENDING | DESCENDING} {KEY | KEY-YY} {data-name-1}... }...

[WITH DUPLICATES IN ORDER]

[COLLATING SEQUENCE IS alphabet-name]

[USING data-name-3]


Syntax rules

  1. The SORT statement may be used anywhere in the Procedure Division except in DECLARATIVES and input and output procedures that belong to a SORT statement.

  2. data-name-2 and data-name-3, if USING is specified, specify the table to be sorted.data-name-1... denotes one or more data items to be used as sort keys (key fields).

  3. The record specified by data-name-2 must be defined in a data description entry, and is subject to the following rules:

    1. data-name-2 may be qualified.

    2. The data description entry for data-name-2 must contain an OCCURS clause, i.e. be defined as a a table element.

    3. If the table specified by data-name-2 is subordinate to a table (multidimensional table), then data-name-2 must be defined as an indexable table, i.e. an index name must be specified in the data description entry for the superordinate table by means of the INDEXED-BY phrase. Before execution of the SORT statement, the indexname must be supplied with the desired element number (see section "Indexing").

  4. The key fields specified by data-name-1 must be defined in the data description entry for data-name-2, where the following rules apply:

    1. data-name-1 is either the same as data-name-2 or the same as a data item subordinate to data-name-2.
    2. data-name-1 may be qualified.

    3. If data-name-1 refers to a data item subordinate to data-name-2, then the description of this data item must neither contain an OCCURS clause itself nor be subordinate to a data item whose description contains an OCCURS clause.

    4. data-name-1 must not refer to a data item whose description contains a SIGN clause.

    5. If the data item specified by data-name-1 is defined as a signed numeric, it must not comprise more than 16 digits.

    6. The keys following the KEY-YY specification must be defined either with PIC 99 USAGE DISPLAY or with USAGE PACKED-DECIMAL.

  5. For data-name-3, the same rules apply as for data-name-2.

  6. If the USING phrase is used, both, data-name-2 and data-name-3 must be described as national data items or as alphanumeric resp. alphabetic data items.

General rules

  1. The key words ASCENDING and DESCENDING apply to all subsequent data-name-1 specifications up to the next key word ASCENDING or DESCENDING.

  2. The data items specified by data-name-1 are the sort keys. The sort keys are used hierarchically from left to right for sort processing, irrespective of whether ASCENDING or DESCENDING is specified. The first instance of data-name-1 is thus the main sort key, the second instance of data-name-1 is the next most significant sort key etc.

  3. If DUPLICATES is specified and two or more table elements are found to match in respect of all their key fields, then the relative sequence of these table elements will not be changed by sort processing.

  4. If DUPLICATES is not specified and two or more table elements are found to match in respect of all their key fields, then the relative sequence of these table elements will be undefined after sort processing.

  5. The collating sequence that is used in comparing the alphanumeric key fields is defined as follows on commencement of execution of the SORT statement:

    1. If COLLATING SEQUENCE is specified in the SORT statement, this specification serves as the criterion for the collating sequence,

    2. If COLLATING SEQUENCE is not specified in the SORT statement, the program-specific collating sequence is used (see section "OBJECT-COMPUTER paragraph" ).

    The national (native) collating sequence is used for comparisons of national collating sequences.

  6. The table elements sorted in accordance with the ASCENDING/DESCENDING KEY phrases are stored in the table specified by data-name-2.
  7. The table elements are sorted through comparison of the contents of the data items defined as sort keys, in accordance with the rules for relation conditions:

    1. If the contents of the compared key fields differ and the ASCENDING phrase is in effect, then the table element whose key field contains the lower value has the lower element number.

    2. If the contents of the compared key fields differ and the DESCENDING phrase is in effect, then the table element whose key field contains the higher value has the lower element number.

    3. If the contents of the compared key fields are the same, the next sort key specified is used for the comparison.

  8. Sort keys specified in the SORT statement take priority over any sort keys that may be specified in the data description entry for data-name-2.

  9. By specifying USING data-name-3, a second table can be used for sort processing.
    In this case, the elements of the table specified by data-name-3 are sorted as described above and then transferred to the table specified by data-name-2 in accordance with the rules for the MOVE statement. Note the following with regard to the transfer of the individual table elements:
    If the "sending" element is shorter than the "receiving" element, it is padded with blanks;
    if it is longer, it is truncated.

  10. Transfer of the sorted data-name-3 table elements to the data-name-2 table ends with the last sorted table element (data-name-3) or on reaching the number of table elements for data-name-2. This means that if the data-name-3 table contains more elements than the data-name-2 table, the excess elements are not transferred. If it contains fewer elements, the excess elements of the data-name-2 table are retained unchanged.

  11. Sort processing does not change the contents of the data-name-3 table.

Example 8-76

Sorting a table

IDENTIFICATION DIVISION.
PROGRAM-ID. TABSORT.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SPECIAL-NAMES.
    TERMINAL IS T.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 NAMETAB.
   02 TAB-ELEM OCCURS 10 TIMES.
      03 FORENAME    PIC X(8).
      03 FILLER      PIC X(3) VALUE SPACES.
      03 NAME        PIC X(10).
PROCEDURE DIVISION.
SINGLE SECTION.
INITIALIZATION.
    MOVE "PETER" TO FORENAME (1) MOVE "KRAUS" TO NAME (1).
    MOVE "JANE" TO FORENAME (2) MOVE "FONDA" TO NAME (2).
    MOVE "PETER" TO FORENAME (3) MOVE "FONDA" TO NAME (3).
    MOVE "KARL" TO FORENAME (4) MOVE "KRAUS" TO NAME (4).
    MOVE "UWE" TO FORENAME (5) MOVE "SEELER" TO NAME (5).
    MOVE "WALT" TO FORENAME (6) MOVE "DISNEY" TO NAME (6).
    MOVE "CLARA" TO FORENAME (7) MOVE "WIECK" TO NAME (7).
    MOVE "LEONID" TO FORENAME (8) MOVE "KOGAN" TO NAME (8).
    MOVE "ERICH" TO FORENAME (9) MOVE "FROMM" TO NAME (9).
    MOVE "ELVIS" TO FORENAME (10) MOVE "PRESLEY" TO NAME (10).
    DISPLAY NAMETAB UPON T.
SORTING.
    SORT TAB-ELEM ON ASCENDING KEY NAME FORENAME.
END.
    STOP RUN.

The following table is output with AID %DISPLAY TABELLE


Sorted table:

Element number
(1)            |WALT    |   |DISNEY
(2)            |JANE    |   |FONDA
(3)            |PETER   |   |FONDA
(4)            |ERICH   |   |FROMM
(5)            |LEONID  |   |KOGAN
(6)            |KARL    |   |KRAUS
(7)            |PETER   |   |KRAUS
(8)            |ELVIS   |   |PRESLEY
(9)            |UWE     |   |SEELER
(10)           |CLARA   |   |WIECK