[an error occurred while processing this directive]

HP OpenVMS Systems Documentation

Content starts here

HP COBOL
User Manual


Previous Contents Index

9.1.7 Multiple Sorting

A program can contain multiple sort files, multiple SORT statements, or both multiple sort files and multiple SORT statements. Example 9-4 uses two sort files to produce two reports with different sort sequences.

Example 9-4 Using Two Sort Files

.
.
.
DATA DIVISION.
FILE SECTION.
SD  SORT-FILE1.
01  SORT-REC-1.
    03  S1-KEY-1     PIC X(5).
    03  FILLER       PIC X(40).
    03  S1-KEY-2     PIC X(5).
    03  FILLER       PIC X(50).
SD  SORT-FILE2.
01  SORT-REC-2.
01  SORT-REC-2.
    03  FILLER       PIC X(20).
    03  S2-KEY-1     PIC X(10).
    03  FILLER       PIC X(10).
    03  S2-KEY-2     PIC X(10).
    03  FILLER       PIC X(50).
             .
             .
             .
PROCEDURE DIVISION.
000-SORT SECTION.
010-DO-FIRST-SORT.
    SORT SORT-FILE1 ON ASCENDING KEY
                   S1-KEY-1
                   S1-KEY-2
                   WITH DUPLICATES IN ORDER
                   USING INPUT-FILE
                   OUTPUT PROCEDURE IS 050-CREATE-REPORT-1
                                  THRU 300-DONE-REPORT-1.
020-DO-SECOND-REPORT.
    SORT SORT-FILE2 ON ASCENDING KEY
                   S2-KEY-1
                   ON DESCENDING KEY
                   S2-KEY-2
                   USING INPUT-FILE
                   OUTPUT PROCEDURE IS 400-CREATE-REPORT-2
                                  THRU 700-DONE-REPORT-2.
030-END-JOB.
    DISPLAY "PROGRAM ENDED".
    STOP RUN.
050-CREATE-REPORT-1 SECTION.
**********************************************************
*                                                        *
*                                                        *
*   Use the RETURN statement to read the sorted records. *
*                                                        *
*                                                        *
**********************************************************
300-DONE-REPORT-1 SECTION.
310-EXIT-REPORT-1.
    EXIT.
400-CREATE-REPORT-2 SECTION.
**********************************************************
*                                                        *
*                                                        *
*   Use the RETURN statement to read the sorted records. *
*                                                        *
*                                                        *
**********************************************************
700-DONE-REPORT-2 SECTION.
710-EXIT-REPORT.
    EXIT.

9.1.8 Sorting Variable-Length Records

If you specify the USING phrase and the input file contains variable-length records, the sort-file record must not be smaller than the smallest record, nor larger than the largest record, described in the input file.

If you specify the GIVING phrase and the output file contains variable-length records, the sort-file record must not be smaller than the smallest record, nor larger than the largest record, described in the output file.

9.1.9 Preventing I/O Aborts

All I/O errors detected during a sort can cause abnormal program termination. The Declarative USE AFTER STANDARD ERROR PROCEDURE, shown in Example 9-5, specifies error-handling procedures should I/O errors occur.

Example 9-5 The Declarative USE AFTER STANDARD ERROR PROCEDURE

PROCEDURE DIVISION.
DECLARATIVES.
SORT-FILE SECTION.
    USE AFTER STANDARD ERROR PROCEDURE ON INPUT-FILE.
SORT-ERROR.
    DISPLAY "I-O TYPE ERROR WHILE SORTING".
    DISPLAY "INPUT-FILE STATUS IS " INPUT-STATUS.
    STOP RUN.
END DECLARATIVES.
000-SORT SECTION.
010-DO-THE-SORT.
    SORT SORT-FILE ON DESCENDING KEY
                      S-KEY-1
                   WITH DUPLICATES IN ORDER
                   USING INPUT-FILE
                   GIVING OUTPUT-FILE.
    DISPLAY "END OF SORT".
    STOP RUN.

Note

The USE PROCEDURE phrase does not apply to Sort Description (SD) files.

9.1.10 Sorting Tables (Alpha, I64)

The SORT statement can be used to order the elements in a table. This is especially useful for tables used with SEARCH ALL. The table elements are sorted based on the keys as specified in the OCCURS for the table unless you override them by specifying keys in the SORT statement. If no key is specified, the table elements are the SORT keys.

For the syntax and examples of table sorting, refer to the SORT statement description in the Procedure Division chapter of the HP COBOL Reference Manual. <>

9.1.11 Sorting at the Operating System Level

On OpenVMS an alternative to using the SORT statement within COBOL is to sort at the operating system level, using the bundled SORT utility, which you can access via the SORT, MERGE, and CONVERT DCL commands. <>

On Alpha and I64, you can choose between two sorting methods: Hypersort and SORT-32. (See Section 15.5.3 for more information on Hypersort and SORT-32.) SORT-32 is the default. Consult the DCL online help (type $HELP SORT) for details about the two methods, which have effects on optimization and other differences, and information about how to switch between SORT-32 and Hypersort. If you select Hypersort at DCL level, it will be in effect for a SORT statement within a COBOL program as well. <>

On Tru64 UNIX, Hypersort is the sole method available. <>

On OpenVMS VAX, SORT-32 is the sole method available. <>

See Appendix A for the record and key size limits with SORT-32 and Hypersort.

9.2 Merging Data with the MERGE Statement

The MERGE statement combines two or more identically sequenced files and makes their records available, in merged order, to an output procedure or to one or more output files. Use MERGE statement phrases the same way you use their SORT statement phrase equivalents. Note that the SORT phrases with DUPLICATES IN ORDER INPUT PROCEDURE are not allowed with MERGE.

In Example 9-6, district sales data is merged into one regional sales file.

Example 9-6 Using the MERGE Statement

     .
     .
     .
DATA DIVISION.
FILE SECTION.
SD  MERGE-FILE.
01  MERGE-REC.
    03  FILLER            PIC XX.
    03  M-PRODUCT-CODE    PIC X(10).
    03  FILLER            PIC X(88).
FD  DISTRICT1-SALES.
01  DISTRICT1-REC         PIC X(100).
FD  DISTRICT2-SALES.
01  DISTRICT2-REC         PIC X(100).
FD  REGION1-SALES.
01  REGION1-REC           PIC X(100).
PROCEDURE DIVISION.
000-MERGE-FILES.
    MERGE MERGE-FILE ON ASCENDING KEY M-PRODUCT-CODE
          USING DISTRICT1-SALES DISTRICT2-SALES
          GIVING REGION1-SALES.
    STOP RUN.

9.3 Sample Programs Using the SORT and MERGE Statements

The programs in Example 9-7, Example 9-8, Example 9-9, Example 9-10, Example 9-11, and Example 9-12 all show how to use the SORT and MERGE statements.

Example 9-7 shows how to use the SORT statement with the USING and GIVING phrases.

Example 9-7 Sorting a File with the USING and GIVING Phrases

IDENTIFICATION DIVISION.
PROGRAM-ID.            SORTA.
*************************************************
*   This program shows how to sort              *
*   a file with the USING and GIVING phrases    *
*   of the SORT statement. The fields to be     *
*   sorted are S-KEY-1 and S-KEY-2; they        *
*   contain account numbers and amounts. The    *
*   sort sequence is amount within account      *
*   number.                                     *
*   Notice that OUTPUT-FILE is a relative file. *
*************************************************
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT INPUT-FILE ASSIGN TO "INPFIL".
    SELECT OUTPUT-FILE ASSIGN TO "OUTFIL"
           ORGANIZATION IS RELATIVE.
    SELECT SORT-FILE ASSIGN TO "SRTFIL".
DATA DIVISION.
FILE SECTION.
SD  SORT-FILE.
01  SORT-REC.
    03  S-KEY-1.
        05  S-ACCOUNT-NUM      PIC X(8).
    03  FILLER                 PIC X(32).
    03  S-KEY-2.
        05  S-AMOUNT           PIC S9(5)V99.
    03  FILLER                 PIC X(53).
FD  INPUT-FILE
    LABEL RECORDS ARE STANDARD.
01  IN-REC                     PIC X(100).
FD  OUTPUT-FILE
    LABEL RECORDS ARE STANDARD.
01  OUT-REC                    PIC X(100).
PROCEDURE DIVISION.
000-DO-THE-SORT.
    SORT SORT-FILE ON ASCENDING KEY
                      S-KEY-1
                      S-KEY-2
         WITH DUPLICATES IN ORDER
         USING INPUT-FILE GIVING OUTPUT-FILE.

***********************************************************
*   At this point, you could transfer control to another  *
*   section of your program and continue processing.      *
***********************************************************
    DISPLAY "END OF PROGRAM SORTA".
    STOP RUN.

Example 9-8 shows how to use the USING and OUTPUT PROCEDURE phrases.

Example 9-8 Using the USING and OUTPUT PROCEDURE Phrases

IDENTIFICATION DIVISION.
PROGRAM-ID. SORTB.
**************************************************************
*   This program shows how to sort a file                    *
*   with the USING and OUTPUT PROCEDURE phrases              *
*   of the SORT statement. The program eliminates            *
*   duplicate records by adding their amounts to the         *
*   amount in the first record with the same account         *
*   number. Only records with unique account numbers         *
*   are written to the output file. The fields to be         *
*   sorted are S-KEY-1 and S-KEY-2; they contain account     *
*   numbers and amounts. The sort sequence is amount         *
*   within account number.                                   *
*   Notice that the organization of OUTPUT-FILE is indexed.  *
**************************************************************
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT INPUT-FILE ASSIGN TO "INPFIL".
    SELECT OUTPUT-FILE ASSIGN TO "OUTFIL"
           ORGANIZATION IS INDEXED.
    SELECT SORT-FILE ASSIGN TO "SRTFIL".
DATA DIVISION.
FILE SECTION.
SD  SORT-FILE.
01  SORT-REC.
    03  S-KEY-1.
        05  S-ACCOUNT-NUM      PIC X(8).
    03  FILLER                 PIC X(32).
    03  S-KEY-2.
        05  S-AMOUNT           PIC S9(5)V99.
    03  FILLER                 PIC X(53).
FD  INPUT-FILE
    LABEL RECORDS ARE STANDARD.
01  IN-REC                     PIC X(100).
FD  OUTPUT-FILE
    LABEL RECORDS ARE STANDARD
    ACCESS MODE IS SEQUENTIAL
    RECORD KEY IS OUT-KEY.
01  OUT-REC.
    03  OUT-KEY                PIC X(8).
    03  FILLER                 PIC X(92).
WORKING-STORAGE SECTION.
01  INITIAL-SORT-READ          PIC X   VALUE "Y".
01  SAVE-SORT-REC.
    03  SR-ACCOUNT-NUM         PIC X(8).
    03  FILLER                 PIC X(32).
    03  SR-AMOUNT              PIC S9(5)V99.
    03  FILLER                 PIC X(53).
PROCEDURE DIVISION.
000-START SECTION.
005-DO-THE-SORT.
    SORT SORT-FILE ON ASCENDING KEY
                      S-KEY-1
                      S-KEY-2
         USING INPUT-FILE
         OUTPUT PROCEDURE IS 300-CREATE-OUTPUT-FILE
                        THRU 600-DONE-CREATE.
************************************************************
*    At this point, you could transfer control to another  *
*    section of the program and continue processing.       *
************************************************************
    DISPLAY "END OF PROGRAM SORTB".
    STOP RUN.

300-CREATE-OUTPUT-FILE SECTION.
350-OPEN-OUTPUT.
    OPEN OUTPUT OUTPUT-FILE.
400-READ-SORT-FILE.
    RETURN SORT-FILE AT END
        PERFORM 500-WRITE-THE-OUTPUT
        CLOSE OUTPUT-FILE
        GO TO 600-DONE-CREATE.
    IF INITIAL-SORT-READ = "Y"
        MOVE SORT-REC TO SAVE-SORT-REC
        MOVE "N" TO INITIAL-SORT-READ
        GO TO 400-READ-SORT-FILE.
450-COMPARE-ACCOUNT-NUM.
    IF S-ACCOUNT-NUM = SR-ACCOUNT-NUM
        ADD S-AMOUNT TO SR-AMOUNT
        GO TO 400-READ-SORT-FILE.
500-WRITE-THE-OUTPUT.
    MOVE SAVE-SORT-REC TO OUT-REC.
    WRITE OUT-REC INVALID KEY
        DISPLAY "INVALID KEY " SR-ACCOUNT-NUM " SORTB ABORTED"
        CLOSE OUTPUT-FILE STOP RUN.
550-GET-A-REC.
    MOVE SORT-REC TO SAVE-SORT-REC.
    GO TO 400-READ-SORT-FILE.
600-DONE-CREATE SECTION.
650-EXIT-PARAGRAPH.
    EXIT.


Previous Next Contents Index