z/OS DFSORT: Getting Started
Previous topic | Next topic | Contents | Contact z/OS | Library | PDF


Sorting records

z/OS DFSORT: Getting Started
SC23-6880-00

The sample COBOL program in Figure 1 calls DFSORT to sort the bookstore master file (MASTER-FILE) by title in ascending order. The sorted master file is written to SORTED-MASTER-FILE.

Following is the JCL that calls the sample COBOL program:

//EXAMP    JOB  A492,PROGRAMMER
//BOOKS    EXEC PGM=COBOLPGM
//STEPLIB  DD   DSN=USER.PGMLIB,DISP=SHR
//SYSOUT   DD   SYSOUT=A
//MASTIN   DD   DSN=A123456.MASTER,DISP=OLD
//MASTOUT  DD   DSN=A123456.OUTB,DISP=(NEW,CATLG,DELETE),
//           SPACE=(CYL,(1,1)),UNIT=SYSDA
//PRINTFL  DD   SYSOUT=A
In contrast to the JCL for executing DFSORT by using a JCL EXEC statement with PGM=SORT or PGM=ICEMAN (see JCL for sorting data sets directly) the previous JCL has these differences:
  • The program name on the EXEC statement is that of the COBOL program.
  • The STEPLIB DD statement defines the library containing the COBOL program.
  • The name of the DD statement for the input file need not be SORTIN.
  • The name of the DD statement for the output file need not be SORTOUT.

Notice that the control field and order for the sort are specified in the COBOL program itself rather than with a SORT control statement. Figure 1 shows the sample COBOL program.

Figure 1. Sample COBOL Program with SORT Commands
 IDENTIFICATION DIVISION.
 PROGRAM-ID.
     COBOLPGM.
 ENVIRONMENT DIVISION.
 INPUT-OUTPUT SECTION.
 FILE-CONTROL.
     SELECT SD-FILE ASSIGN TO
     DUMMYNM.
     SELECT MASTER-FILE ASSIGN TO
     MASTIN.
     SELECT SORTED-MASTER-FILE ASSIGN TO
     MASTOUT.
     SELECT PRINT-FILE ASSIGN TO
     PRINTFL.
 DATA DIVISION.
 FILE SECTION.
 SD  SD-FILE
     DATA RECORD IS SD-RECORD.
 01  SD-RECORD.
  05 TITLE-IN   PICTURE X(75).
  05 AUTH-LN-IN   PICTURE X(15).
  05 AUTH-FN-IN   PICTURE X(15).
  05 PUB-IN    PICTURE X(4).
  05 COUR-DEPT-IN  PICTURE X(5).
  05 COUR-NO-IN   PICTURE X(5).
  05 COUR-NAM-IN   PICTURE X(25).
  05 INST-LN-IN   PICTURE X(15).
  05 INST-INIT-IN   PICTURE X(2).
  05 NO-STOCK-IN   PICTURE 9(8) BINARY.
  05 NO-SOLD-IN   PICTURE 9(8) BINARY.
  05 PRICE-IN   PICTURE 9(8) BINARY.
 FD  MASTER-FILE
     DATA RECORD IS MASTER-RECORD.
 01  MASTER-RECORD.
  05 FILLER    PICTURE X(173).

 FD  SORTED-MASTER-FILE
     DATA RECORD IS SORTED-MASTER-RECORD.
 01  SORTED-MASTER-RECORD.
  05 FILLER    PICTURE X(173).

 FD  PRINT-FILE
     DATA RECORD IS OUTPUT-REPORT-RECORD.
 01  OUTPUT-REPORT-RECORD.
  05 REPORT-OUT   PICTURE X(120).
  .
  .
  .

 PROCEDURE DIVISION.
  .
  .
  .

 SORT-ROUTINE SECTION.
     SORT SD-FILE
     ASCENDING KEY TITLE-IN
     USING MASTER-FILE
     GIVING SORTED-MASTER-FILE.
     IF SORT-RETURN > 0
     DISPLAY "SORT FAILED".
     .
     .
     .
SORT-REPORT SECTION.
     print a report on PRINT-FILE using SORTED-MASTER-FILE.
     .
     .
     .
     STOP RUN.

Go to the previous page Go to the next page




Copyright IBM Corporation 1990, 2014