BCS COBOL Internal Sort Example


There are those times when you will need the COBOL sort verb to order data generated or used by a COBOL application. The remainder of this article addresses the idiosyncrasies of the COBOL sort verb employing the using and giving option. This is the simplest approach of using COBOL internal sort.
The using input and output procedures of the SORT verb allows for heavy modification of data passed into the sort and data passed out of the sort. This technique will be discussed further in another article.
Below you will notice a sample COBOL program that employs the using and giving option of COBOL.
[codesyntax lang=”cobol”]

                IDENTIFICATION DIVISION.
       PROGRAM-ID. 'SORTUG-EXAMPLE-COBOLSORT'.
       AUTHOR. ARCH BROOKS.
       INSTALLATION. BROOKS COMPUTING SYSTEMS.
       DATE-WRITTEN. WDATE.
       DATE-COMPILED.
      *
      *COMMENTS ARE HERE.
      *
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER. IBM-390-X.
       OBJECT-COMPUTER. IBM-390-X.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
           SELECT INPUTFILE ASSIGN TO UT-S-INP001.
           SELECT OUTPUTFILE ASSIGN TO UT-S-INP001.
           SELECT SORTWORK ASSIGN TO UT-S-WORKFILE.
       DATA DIVISION.
       FILE SECTION.
       FD INPUTFILE
           RECORDING MODE IS F
           BLOCK CONTAINS 0 CHARACTERS
           RECORD CONTAINS 80 CHARACTERS
           LABEL RECORDS ARE STANDARD
           DATA RECORD IS TARGFILEREC.
       01  INPUTFILEREC PIC X(80).
       FD OUTPUTFILE
           RECORDING MODE IS F
           BLOCK CONTAINS 0 CHARACTERS
           RECORD CONTAINS 80 CHARACTERS
           LABEL RECORDS ARE STANDARD
           DATA RECORD IS TARGFILEREC.
       01  OUTPUTFILEREC PIC X(80).
       SD  SORTWORK
           DATA RECORD IS SORTRECORD.
       01  SORTRECORD.
           05  MEMNAME PIC X(8).
           05  DSNAME PIC X(72).
       PROCEDURE DIVISION.
           SORT SORTWORK ON ASCENDING MEMNAME
               ON ASCENDING DSNAME
               USING INPUTFILE
               GIVING OUTPUTFILE.
           GOBACK.

[/codesyntax]
The next step in the process is to provide the execution JCL that would be required.
[codesyntax lang=”text”]

//AMBCOB JOB The job card info goes here
/*JOBPARM L=99
//STEP0001 EXEC PGM=SORTUG
//STEPLIB DD DISP=SHR,DSN=Your.LOAD
//INP001 DD DISP=SHR,DSN=your.pds.CNTL(DS01)
//SORTWORK DD UNIT=VIO,SPACE=(CYL,(1,1)),DISP=(,PASS)

[/codesyntax]
This should be enough information to begin using the COBOL internal sort.   Please feel free to comment or make suggestions about this article.
Mr. Arch Brooks, Software Engineer, Brooks Computing Systems authored this article.

Leave a Reply

Your email address will not be published. Required fields are marked *