CHAPTER 14

image

Sorting and Merging

If there is one thing you should have learned from the chapters on sequential files, it is that your processing options are very limited if a sequential file is not ordered. Solutions based on control breaks, and the file-update problem, are impossible unless the file is ordered on some key field. In previous chapters, I mentioned the very useful program design technique called beneficial wishful thinking in which, when you are confronted by a difficult programming problem, you imagine a set of circumstances under which the difficulty would be greatly reduced and then try to bring about that set of circumstances. In the context of sequential files, you will often find yourself confronted with problems that would be much easier to solve if the file was ordered. A solution based on the beneficial wishful thinking approach first puts the file into the required order.

In this chapter, you discover how to use the SORT verb to sort a sequential file in ascending or descending order. You learn how to use an INPUT PROCEDURE to filter or modify the records presented for sorting and how to use an OUTPUT PROCEDURE to process the sorted records instead of sending them directly to an output file. In addition, you see how to use the MERGE verb to merge the records in two or more ordered files to create a combined file with the records in the correct order.

SORTING

I noted in previous chapters that it is possible to apply processing to an ordered sequential file that is difficult, or impossible, when the file is unordered. In cases where you need to apply ordered processing to an unordered sequential file, part of the solution must be to sort the file. COBOL provides the SORT verb for this purpose.

The SORT verb is usually used to sort sequential files. Some programmers claim that the SORT verb is unnecessary, preferring to use an implementer-provided or “off-the-shelf” sort. However, one major advantage of using the SORT verb is that it enhances the portability of COBOL programs. Because the SORT verb is available in every COBOL compiler, when a program that uses SORT has to be moved to a different computer system, it can make the transition without requiring any changes to the SORT. This is rarely the case when programs rely on an implementer-supplied or bought-in sort.

Simple Sorting

The syntax for the simple SORT is given in Figure 14-1. This version of SORT takes the records in the InFileName file, sorts them on the WorkSortKey#$i key or keys, and writes the sorted records to the OutFileName file.

9781430262534_Fig14-01.jpg

Figure 14-1. Metalanguage for the simple version of SORT

Some example SORT statements are given in Example 14-1.

Example 14-1. Example SORT Statements

SORT WorkFile
     ON ASCENDING BookId-WF
                  AuthorName-WF
     USING BookSalesFileUS, BookSalesFileEU
     GIVING SortedBookSales
 
SORT WorkFile
     ON DESCENDING NCAP-Result-WF
        ASCENDING  ManfName-WF, VehicleName-WF
     USING NCAP-TestResultsFile
     GIVING Sorted-NCAP-TestResultsFile

Simple Sorting Notes

Consider the following:

  • SDWorkFileName identifies a temporary work file that the sort process uses as a kind of scratch pad for sorting. The file is defined in the FILE SECTION using a sort description (SD) rather than a file description (FD) entry. Even though the work file is a temporary file, it must still have associated SELECT and ASSIGN clauses in the ENVIRONMENT DIVISION. You can give this file any name you like; I usually call it WorkFile as I did in Example 14-1.
  • SDWorkFileName file is a sequential file with an organization of RECORD SEQUENTIAL. Because this is the default organization, it is usually omitted (see Listing 14-1).
  • Each WorkSortKey#$i identifies a field in the record of the work file. The sorted file will be ordered on this key field(s).
  • When more than one WorkSortKey#$i is specified, the keys decrease in significance from left to right (the leftmost key is the most significant, and the rightmost is the least significant).
  • InFileName and OutFileName are the names of the input and output files, respectively.
  • If more than one InFileName is specified, the files are combined (OutFileSize = InFile1Size + InFile2Size) and then sorted.
  • If more than one OutFileName is specified, then each file receives a copy of the sorted records.
  • If the DUPLICATES clause is used, then when the file has been sorted, the final order of records with duplicate keys (keys with the same value) is the same as that in the unsorted file. If no DUPLICATES clause is used, the order of records with duplicate keys is undefined.
  • AlphabetName is an alphabet name defined in the SPECIAL-NAMES paragraph of the ENVIRONMENT DIVISION. This clause is used to select the character set the SORT verb uses for collating the records in the file. The character set may be STANDARD-1 (ASCII), STANDARD-2 (ISO 646), NATIVE (may be defined by the system to be ASCII or EBCDIC; see your implementer manual), or user defined.
  • SORT can be used anywhere in the PROCEDURE DIVISION except in an INPUT PROCEDURE (SORT) or OUTPUT PROCEDURE (SORT or MERGE) or in the DECLARATIVES SECTION. The purpose of the INPUT PROCEDURE and OUTPUT PROCEDURE is explained later in this chapter, but an explanation of the DECLARATIVES SECTION has to wait until Chapter 18.
  • The records described for the input file (USING) must be able to fit into the records described for SDWorkFileName.
  • The records described for SDWorkFileName must be able to fit into the records described for the output file (GIVING).
  • The description of WorkSortKey#$i cannot contain an OCCURS clause (it cannot be a table), nor can it be subordinate to an entry that contains one.
  • The InFileName and OutFileName files are automatically opened by the SORT. When the SORT executes, they must not already be open.

How the Simple SORT Works

Figure 14-2 shows how the simple version of SORT works. In this case, the diagram uses the example in Listing 14-1 to illustrate the point. The sort process takes records from the unsorted BillableServicesFile, sorts them using WorkFile (the temporary work area), and, when the records have been sorted, sends them to SortedBillablesFile. After sorting, the records in the SortedBillablesFile will be ordered on ascending SubscriberId.

9781430262534_Fig14-02.jpg

Figure 14-2. Diagram showing how the simple SORT works

Simple Sorting Program

Universal Telecoms has subscribers all over the United States. Each month, the billable activities of these subscribers are gathered into a file. BillableServicesFile is an unordered sequential file. Each record has the following description:

image

A program is required to produce a report that shows the value of the billable services for each subscriber (see Listing 14-1). In the report, BillableValue is the sum of the ServiceCost fields for each subscriber. The report must be printed on ascending SubscriberId and have the following format:

Universal Telecoms Monthly Report
SubscriberId      BillableValue
 XXXXXXXXXX        XXXXXXXXXXX
 XXXXXXXXXX        XXXXXXXXXXX
 XXXXXXXXXX        XXXXXXXXXXX

Listing 14-1. A simple SORT applied to the BillableServicesFile

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing14-1.
AUTHOR. Michael Coughlan.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT WorkFile ASSIGN TO "WORK.TMP".
    
    SELECT BillableServicesFile  ASSIGN TO "Listing14-1.dat"
           ORGANIZATION LINE SEQUENTIAL.
    
    SELECT SortedBillablesFile   ASSIGN TO "Listing14-1.Srt"
               ORGANIZATION LINE SEQUENTIAL.
 
DATA DIVISION.
FILE SECTION.
 
FD  BillableServicesFile.
01  SubscriberRec-BSF     PIC X(17).
 
SD  WorkFile.
01  WorkRec.
    02 SubscriberId-WF    PIC 9(10).
    02 FILLER             PIC X(7).
 
FD  SortedBillablesFile.
01  SubscriberRec.
    88 EndOfBillablesFile   VALUE HIGH-VALUES.
    02 SubscriberId       PIC 9(10).
    02 ServiceType        PIC 9.
    02 ServiceCost        PIC 9(4)V99.
    
WORKING-STORAGE SECTION.
01 SubscriberTotal        PIC 9(5)V99.
 
01 ReportHeader           PIC X(33) VALUE "Universal Telecoms Monthly Report".
 
01 SubjectHeader          PIC X(31) VALUE "SubscriberId      BillableValue".
 
01 SubscriberLine.
   02 PrnSubscriberId     PIC 9(10).
   02 FILLER              PIC X(8) VALUE SPACES.
   02 PrnSubscriberTotal  PIC $$$,$$9.99.
    
01 PrevSubscriberId       PIC 9(10).
    
 
PROCEDURE DIVISION.
Begin.
    SORT WorkFile ON ASCENDING KEY SubscriberId-WF
           USING BillableServicesFile
           GIVING SortedBillablesFile
    DISPLAY ReportHeader
    DISPLAY SubjectHeader
    OPEN INPUT SortedBillablesFile
    READ SortedBillablesFile
      AT END SET EndOfBillablesFile TO TRUE
    END-READ
    PERFORM UNTIL EndOfBillablesFile
       MOVE SubscriberId TO PrevSubscriberId, PrnSubscriberId
       MOVE ZEROS TO SubscriberTotal
       PERFORM UNTIL SubscriberId NOT EQUAL TO PrevSubscriberId
          ADD ServiceCost TO SubscriberTotal
          READ SortedBillablesFile
               AT END SET EndOfBillablesFile TO TRUE
          END-READ
       END-PERFORM
       MOVE SubscriberTotal TO PrnSubscriberTotal
       DISPLAY SubscriberLine
    END-PERFORM
    CLOSE SortedBillablesFile
    STOP RUN.

Program Notes

I have kept this program simple for reasons of clarity and space, and because you will meet a more fully worked version of the program when I explore advanced versions of the SORT. Because the SORT uses a disk-based WorkFile, it is slower than purely RAM-bound operations. You should be aware of this whenever you are considering using SORT. You should probably use SORT only when no practical RAM-based solution is available; and even then, you should ensure that only the data items required in the sorted file are sorted. This may involve leaving out some of the records or changing the record size.

In this instance, sorting the file does seem to be the only viable option. There are millions of telephone subscribers, and, in the course of a month, they make many calls and send hundreds of texts. So BillableServicesFile contains tens of millions, or hundreds of millions, of records. In COBOL, the only possible RAM-based solution (you can't create dynamic structures like trees or linked lists pre–ISO 2002) would be to use a table (one element per subscriber) to sum the subscribers’ ServiceCost fields. That solution has many problems. The array would have to contain millions of elements, you would have to ensure that the elements were in SubscriberId order, and, because new subscribers are constantly joining, the table would have to be redimensioned every time the program ran.

You may wonder why the example uses different record descriptions for the three files when the records are identical. The reason is that although the records are identical, they are used in different ways in the program, and the granular data descriptions reflect way the records are used.

The input file is used only by the SORT, so while you have to define how much storage a record will occupy you never need to refer to the individual fields. You could fully define the record as follows:

01  UnsortedSubcriberRec.
    02 SubscriberId       PIC 9(10).
    02 ServiceType        PIC 9.
    02 ServiceCost        PIC 9(4)V99

But then you would either have to use slightly different field names for the sorted file or qualify them using references such as SubscriberId OF SubscriberRec.

In WorkFile, only the data items on which the file is to be sorted (mentioned in the KEY phrase) need to be explicitly defined. In this case, the only item that must be explicitly identified is SubscriberId-WF.

The sorted file is normally the file that the program uses to do whatever work is required. This generally means that all, or nearly all, of the data items are mentioned by name in the program; and, hence, they have to be declared. Normally, the record description for this file fully defines the record.

Using Multiple Keys

If you examine the SORT metalanguage in Figure 14-1, you will realize not only that can a file be sorted on a number of keys but also that one key can be ascending while another is descending. This is illustrated in Table 14-1 and Example 14-2. The table contains student results that have been sorted into descending StudentId order within ascending GPA order. Notice that GPA is the major key and that StudentId is only in descending sequence within GPA. This is because the first key named in a SORT statement is the major key, and keys become less significant with each successive declaration.

Example 14-2. SORT with One Key Descending and Another Ascending

SORT WorkFile ON DESCENDING GPA
                 ASCENDING  StudentId
                 USING   StudentResultsFile
                 GIVING  SortedStudentsResultsFile

Table 14-1. Ascending StudentId within Descending GPA

9781430262534_unFig14-01.jpg

SORT with Procedures

The simple version of SORT takes the records from InFileName, sorts them, and then outputs them to OutFileName. Sometimes, however, not all the records in the unsorted file are required in the sorted file, or not all the data items in the unsorted file record are required in the record of the sorted file. For instance, suppose the specification for the Universal Telecoms Monthly Report changes so that you are only required to show the value of the voice calls made by subscribers. In that situation, the text records (ServiceType = 1) are not required in the sorted file. Similarly, if the specification changes so that the number of texts and phone calls is required rather than their value, you do not need the ServiceCost data item in sorted file records. In both cases, processing must be applied, to eliminate unwanted records or alter their format, before the records are submitted to the sort process. This processing is achieved by specifying INPUT PROCEDURE with SORT.

Sometimes, to reduce the number of files that have to be declared, you may find it useful to process the records directly from the sort process instead of creating a sorted file and then processing that. For instance, you could create the Universal Telecoms Monthly Report directly instead of creating a sorted file and then processing the sorted file to create the report. Such processing is accomplished by using OUTPUT PROCEDURE with SORT.

An INPUT PROCEDURE is a block of code that consists of one or more sections or paragraphs that execute, having been passed control by SORT. When the block of code has finished, control reverts to SORT. An OUTPUT PROCEDURE works in a similar way.

Figure 14-3 gives the metalanguage for the full SORT including the INPUT PROCEDURE and the OUTPUT PROCEDURE.

9781430262534_Fig14-03.jpg

Figure 14-3. Metalanguage for the full version of the SORT verb

INPUT PROCEDURE Notes

You should consider the following when using an INPUT PROCEDURE:

  • The block of code specified by the INPUT PROCEDURE allows you to select which records, and what format of records, are submitted to the sort process. Because an INPUT PROCEDURE executes before the SORT sorts the records, only the data that is actually required in the sorted file is sorted.
  • When you use an INPUT PROCEDURE, it replaces the USING phrase. The ProcedureName in the INPUT PROCEDURE phrase identifies a block of code that uses the RELEASE verb to supply records to the sort process. The INPUT PROCEDURE must contain at least one RELEASE statement to transfer the records to the work file (identified by SDWorkFileName).
  • The INPUT PROCEDURE finishes before the sort process sorts the records supplied to it by the procedure. That's why the records are RELEASEd to the work file. They are stored there until the INPUT PROCEDURE finishes, and then they are sorted.
  • Neither an INPUT PROCEDURE nor an OUTPUT PROCEDURE can contain a SORT or MERGE statement.
  • The pre–ANS 85 COBOL rules for the SORT verb stated that the INPUT PROCEDURE and OUTPUT PROCEDURE had to be self-contained sections of code and could not be entered from elsewhere in the program.
  • In the ANS 85 version of COBOL, the INPUT PROCEDURE and OUTPUT PROCEDURE can be any contiguous group of paragraphs or sections. The only restriction is that the range of paragraphs or sections used must not overlap.

OUTPUT PROCEDURE Notes

You should consider the following when using an OUTPUT PROCEDURE:

  • An OUTPUT PROCEDURE retrieves sorted records from the work file using the RETURN verb. An OUTPUT PROCEDURE must contain at least one RETURN statement to get the records from the work file.
  • An OUTPUT PROCEDURE only executes after the file has been sorted.
  • If you use an OUTPUT PROCEDURE, the SORT..GIVING phrase cannot be used.

How an INPUT PROCEDURE Works

A simple SORT works by taking records from the USING file, sorting them, and then writing them to the GIVING file. When an INPUT PROCEDURE is used, there is no USING file, so the sort process has to get its records from the INPUT PROCEDURE. The INPUT PROCEDURE uses the RELEASE verb to supply the records to the work file of the SORT, one at a time.

Although an INPUT PROCEDURE usually gets the records it supplies to the sort process from an input file, the records can originate from anywhere. For instance, if you wanted to sort the elements of a table, you could use INPUT PROCEDURE to send the elements, one at a time, to the sort process (see Listing 14-7, in the section “Sorting Tables Program”). Or, if you wanted to sort the records as they were entered by the user, you could use INPUT PROCEDURE to get the records from the user and supply them to the sort process (see Listing 14-3, later in this section). When an INPUT PROCEDURE gets its records from an input file, it can select which records to send to the sort process and can even alter the structure of the records before they are sent.

Creating an INPUT PROCEDURE

When you use an INPUT PROCEDURE, a RELEASE verb must be used to send records to the work file associated with SORT. The work file is declared in an SD entry in the FILE SECTION. RELEASE is a special verb used only in INPUT PROCEDUREs to send records to the work file. It is the equivalent of a WRITE command and works in a similar way. The metalanguage for the RELEASE verb is given in Figure 14-4.

9781430262534_Fig14-04.jpg

Figure 14-4. Metalanguage for the RELEASE verb

A template for an INPUT PROCEDURE that gets records from an input file and releases them to the SORT work file is given in Example 14-3. Notice that the work file is not opened in the OUTPUT PROCEDURE. The work file is automatically opened by the SORT.

Example 14-3. INPUT PROCEDURE File-Processing Template

OPEN INPUT InFileName
READ InFileName RECORD
PERFORM UNTIL TerminatingCondition
    RELEASE SDWorkRec
    READ InFileName RECORD
END-PERFORM
CLOSE InFileName

Using an INPUT PROCEDURE to Select Records

Suppose that the specification for the Universal Telecoms Monthly Report is changed so that only the value of the voice calls made by subscribers is required. Figure 14-5 shows how you can use an INPUT PROCEDURE between the input file and the sort process to filter out the unwanted text (ServiceType = 1) records. Listing 14-2 implements the specification change and also produces a more fully worked version. In this program, the report is written to a print file rather than just displayed on the computer screen.

9781430262534_Fig14-05.jpg

Figure 14-5. INPUT PROCEDURE used to select the voice call records

Listing 14-2. Using an INPUT PROCEDURE to Select Only Voice Calls Records

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing14-2.
AUTHOR. Michael Coughlan.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT WorkFile ASSIGN TO "WORK.TMP".
    
    SELECT BillableServicesFile  ASSIGN TO "Listing14-2.dat"
           ORGANIZATION LINE SEQUENTIAL.
    
    SELECT SortedCallsFile   ASSIGN TO "Listing14-2.Srt"
               ORGANIZATION LINE SEQUENTIAL.
                
    SELECT PrintFile  ASSIGN TO "Listing14-2.prn"
               ORGANIZATION LINE SEQUENTIAL.
 
DATA DIVISION.
FILE SECTION.
FD  BillableServicesFile.
01  SubscriberRec-BSF.
    88 EndOfBillableServicesFile VALUE HIGH-VALUES.
    02 FILLER           PIC X(10).
    02 FILLER           PIC 9.
       88 VoiceCall     VALUE 2.
    02 FILLER           PIC X(6).
 
SD  WorkFile.
01  WorkRec.
    02 SubscriberId-WF    PIC 9(10).
    02 FILLER             PIC X(7).
 
FD  SortedCallsFile.
01  SubscriberRec.
    88 EndOfCallsFile   VALUE HIGH-VALUES.
    02 SubscriberId       PIC 9(10).
    02 ServiceType        PIC 9.
    02 ServiceCost        PIC 9(4)V99.
 
FD PrintFile.
01 PrintRec               PIC X(40).
    
WORKING-STORAGE SECTION.
01 SubscriberTotal        PIC 9(5)V99.
 
01 ReportHeader           PIC X(33) VALUE "Universal Telecoms Monthly Report".
 
01 SubjectHeader          PIC X(31) VALUE "SubscriberId      BillableValue".
 
01 SubscriberLine.
   02 PrnSubscriberId     PIC 9(10).
   02 FILLER              PIC X(8) VALUE SPACES.
   02 PrnSubscriberTotal  PIC $$$,$$9.99.
    
01 PrevSubscriberId       PIC 9(10).
    
PROCEDURE DIVISION.
Begin.
    SORT WorkFile ON ASCENDING KEY SubscriberId-WF
           INPUT PROCEDURE IS SelectVoiceCalls
           GIVING SortedCallsFile
    OPEN OUTPUT PrintFile
    OPEN INPUT SortedCallsFile
    WRITE PrintRec FROM ReportHeader AFTER ADVANCING PAGE
    WRITE PrintRec FROM SubjectHeader AFTER ADVANCING 1 LINE
 
    READ SortedCallsFile
      AT END SET EndOfCallsFile TO TRUE
    END-READ
    PERFORM UNTIL EndOfCallsFile
       MOVE SubscriberId TO PrevSubscriberId, PrnSubscriberId
       MOVE ZEROS TO SubscriberTotal
       PERFORM UNTIL SubscriberId NOT EQUAL TO PrevSubscriberId
          ADD ServiceCost TO SubscriberTotal
          READ SortedCallsFile
               AT END SET EndOfCallsFile TO TRUE
          END-READ
       END-PERFORM
       MOVE SubscriberTotal TO PrnSubscriberTotal
       WRITE PrintRec FROM SubscriberLine AFTER ADVANCING 1 LINE
    END-PERFORM
    CLOSE SortedCallsFile, PrintFile
    STOP RUN.
 
SelectVoiceCalls.
    OPEN INPUT BillableServicesFile
    READ BillableServicesFile
         AT END SET EndOfBillableServicesFile TO TRUE
    END-READ
    PERFORM UNTIL EndOfBillableServicesFile
       IF VoiceCall
          RELEASE WorkRec FROM SubscriberRec-BSF
       END-IF
       READ BillableServicesFile
            AT END SET EndOfBillableServicesFile TO TRUE
       END-READ
    END-PERFORM
    CLOSE BillableServicesFile.

The file declarations are once more of interest. Because only the voice call records are released to the work file, you need to be able to detect which records are voice call records. To do this, you cannot declare SubscriberRec-BSF as an undifferentiated group of 17 characters, as in Listing 14-1. Instead, you isolate the ServiceType character position so that you can monitor it with the condition name VoiceCall. Because you never refer to ServiceType in the PROCEDURE DIVISION, you do not explicitly name it but instead give it the generic name FILLER.

Using an INPUT PROCEDURE to Modify Records

In addition to selecting which records to send to be sorted, you can also use an INPUT PROCEDURE to modify the records before releasing them to the sort process. Suppose the specification for the Universal Telecoms Monthly Report is changed again. Now you are now required to count the number of calls made and the number of texts sent by each subscriber. Because sorting is a slow, disk-based process, every effort should be made to reduce the amount of data that has to be sorted. The ServiceCost data item is not required to produce the report, so you do not need to include it in the records sent to the work file. You can use an INPUT PROCEDURE to modify the input record so that only the required data items are submitted to the SORT.

Listing 14-3 implements the specification change, and Figure 14-6 shows how the INPUT PROCEDURE sits between the input file and the sort process to modify the records before they are released to the work file.

Listing 14-3. Using an INPUT PROCEDURE to Modify the Record Structure

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing14-3.
AUTHOR. Michael Coughlan.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT WorkFile ASSIGN TO "WORK.TMP".
    
    SELECT BillableServicesFile  ASSIGN TO "Listing14-3.dat"
           ORGANIZATION LINE SEQUENTIAL.
    
    SELECT SortedSubscriberFile   ASSIGN TO "Listing14-3.Srt"
               ORGANIZATION LINE SEQUENTIAL.
                
    SELECT PrintFile  ASSIGN TO "Listing14-3.prn"
               ORGANIZATION LINE SEQUENTIAL.
 
DATA DIVISION.
FILE SECTION.
FD  BillableServicesFile.
01  SubscriberRec-BSF.
    88 EndOfBillableServicesFile VALUE HIGH-VALUES.
    02 SubscriberId-BSF   PIC 9(10).
    02 ServiceType-BSF    PIC 9.
    02 FILLER             PIC X(6).
 
SD  WorkFile.
01  WorkRec.
    02 SubscriberId-WF    PIC 9(10).
    02 ServiceType-WF     PIC 9.
 
FD  SortedSubscriberFile.
01  SubscriberRec.
    88 EndOfCallsFile   VALUE HIGH-VALUES.
    02 SubscriberId       PIC 9(10).
    02 ServiceType        PIC 9.
       88 VoiceCall       VALUE 2.
 
FD PrintFile.
01 PrintRec               PIC X(40).
    
WORKING-STORAGE SECTION.
01 CallsTotal             PIC 9(4).
 
01 TextsTotal             PIC 9(5).
 
01 ReportHeader           PIC X(33) VALUE "Universal Telecoms Monthly Report".
 
01 SubjectHeader          PIC X(31) VALUE "SubscriberId    Calls     Texts".
 
01 SubscriberLine.
   02 PrnSubscriberId     PIC 9(10).
   02 FILLER              PIC X(6) VALUE SPACES.
   02 PrnCallsTotal       PIC Z,ZZ9.
   02 FILLER              PIC X(4) VALUE SPACES.
   02 PrnTextsTotal       PIC ZZ,ZZ9.
    
01 PrevSubscriberId       PIC 9(10).
    
PROCEDURE DIVISION.
Begin.
    SORT WorkFile ON ASCENDING KEY SubscriberId-WF
           INPUT PROCEDURE IS ModifySubscriberRecords
           GIVING SortedSubscriberFile
    OPEN OUTPUT PrintFile
    OPEN INPUT SortedSubscriberFile
    WRITE PrintRec FROM ReportHeader AFTER ADVANCING PAGE
    WRITE PrintRec FROM SubjectHeader AFTER ADVANCING 1 LINE
 
    READ SortedSubscriberFile
      AT END SET EndOfCallsFile TO TRUE
    END-READ
    PERFORM UNTIL EndOfCallsFile
       MOVE SubscriberId TO PrevSubscriberId, PrnSubscriberId
       MOVE ZEROS TO CallsTotal, TextsTotal
       PERFORM UNTIL SubscriberId NOT EQUAL TO PrevSubscriberId
          IF VoiceCall ADD 1 TO CallsTotal
             ELSE ADD 1 TO TextsTotal
          END-IF
          READ SortedSubscriberFile
               AT END SET EndOfCallsFile TO TRUE
          END-READ
       END-PERFORM
       MOVE CallsTotal TO PrnCallsTotal
       MOVE TextsTotal TO PrnTextsTotal
       WRITE PrintRec FROM SubscriberLine AFTER ADVANCING 1 LINE
    END-PERFORM
    CLOSE SortedSubscriberFile, PrintFile
    STOP RUN.
 
ModifySubscriberRecords.
    OPEN INPUT BillableServicesFile
    READ BillableServicesFile
         AT END SET EndOfBillableServicesFile TO TRUE
    END-READ
    PERFORM UNTIL EndOfBillableServicesFile
       MOVE SubscriberId-BSF TO SubscriberId-WF
       MOVE ServiceType-BSF  TO ServiceType-WF
       RELEASE WorkRec
       READ BillableServicesFile
            AT END SET EndOfBillableServicesFile TO TRUE
       END-READ
    END-PERFORM
    CLOSE BillableServicesFile.

9781430262534_Fig14-06.jpg

Figure 14-6. Using an INPUT PROCEDURE to modify the subscriber records

As before, the record declarations are of some interest. For reasons of clarity, I chose to explicitly identify the data items in SubscriberRec-BSF that are being preserved in WorkRec. You may, on consideration of the character positions, wonder if you could simply move SubscriberRec-BSF to WorkRec and let MOVE truncation eliminate the unwanted data. If those are your thoughts, then you are correct. You could save yourself some typing by doing that.

Feeding SORT from the Keyboard

As I mentioned earlier, and as you can see from Figure 14-5 and Figure 14-6, when an INPUT PROCEDURE is used, it is responsible for supplying records to the sort process. The records supplied can come from anywhere. They can come from a file, a table, or (as in this example) directly from the user.

The program in Listing 14-4 gets records directly from the user, sorts them on ascending StudentId, and then outputs them to SortedStudentFile. The diagram in Figure 14-7 represents the process. Note that the sort process only sorts the file when the INPUT PROCEDURE has finished.

Listing 14-4. Feeding SORT from the Keyboard

IDENTIFICATION DIVISION.
PROGRAM-ID.  Lsiting14-4.
AUTHOR.  Michael Coughlan.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT StudentFile ASSIGN TO "Listing14-4.DAT"
           ORGANIZATION IS LINE SEQUENTIAL.
 
    SELECT WorkFile ASSIGN TO "WORK.TMP".
 
DATA DIVISION.
FILE SECTION.
FD StudentFile.
01 StudentDetails      PIC X(32).
* The StudentDetails record has the description shown below.
* But in this program I don't actually need to refer to any
* of the items in the record and so have described it as PIC X(32)
* 01 StudentDetails
*    02  StudentId       PIC 9(8).
*    02  StudentName.
*        03 Surname      PIC X(8).
*        03 Initials     PIC XX.
*    02  DateOfBirth.
*        03 YOBirth      PIC 9(4).
*        03 MOBirth      PIC 9(2).
*        03 DOBirth      PIC 9(2).
*    02  CourseCode      PIC X(5).
*    02  Gender          PIC X.
 
SD WorkFile.
01 WorkRec.
   88 EndOfInput         VALUE SPACES.
   02 FILLER             PIC X(8).
   02 SurnameWF          PIC X(8).
   02 FILLER             PIC X(16).
 
PROCEDURE DIVISION.
Begin.
   SORT WorkFile ON ASCENDING KEY SurnameWF
        INPUT PROCEDURE IS GetStudentDetails
        GIVING StudentFile
   STOP RUN.
 
GetStudentDetails.
    DISPLAY "Use the template below"
    DISPLAY "to enter your details."
    DISPLAY "Enter spaces to end.".
    DISPLAY "NNNNNNNNSSSSSSSSIIYYYYMMDDCCCCCG".
    ACCEPT  WorkRec.
    PERFORM UNTIL EndOfInput
       RELEASE WorkRec
       ACCEPT WorkRec
    END-PERFORM.

9781430262534_unFig14-02.jpg

9781430262534_Fig14-07.jpg

Figure 14-7. Supplying SORT records directly from the user

OUTPUT PROCEDURE

An INPUT PROCEDURE allows you to filter, or alter, records before they are supplied to the sort process. This can substantially reduce the amount of data that has to be sorted. An OUTPUT PROCEDURE has no such advantage. An OUTPUT PROCEDURE only executes when the sort process has already sorted the file.

Nevertheless, an OUTPUT PROCEDURE is useful when you don’t need to preserve the sorted file. For instance, if you are sorting records to produce a one-off report, you can use an OUTPUT PROCEDURE to create the report directly, without first having to create a file containing the sorted records. This saves you the effort of having to define an unnecessary file. An OUTPUT PROCEDURE is also useful when you want to alter the structure of the records written to the sorted file. For instance, if you were required to produce a summary file from the sorted records, you could use an OUTPUT PROCEDURE to summarize the sorted records and then write each of the summary records to summary file. The resulting file would contain summary records, rather than the detail records contained in the unsorted file.

How the OUTPUT PROCEDURE Works

A simple SORT takes the records from the unsorted input file, sorts them, and then outputs them to the sorted output file. As Figure 14-8 shows, the OUTPUT PROCEDURE breaks the connection between the SORT and the output file. The OUTPUT PROCEDURE uses the RETURN verb to retrieve sorted records from the work file. It may then send the retrieved records to the output file, but it doesn’t have to. Once the OUTPUT PROCEDURE has retrieved the sorted records from the work file, it can do whatever it likes with them. For instance, it can summarize them, alter them, put them into a table, display them on the screen, or send them to the output file. When the OUTPUT PROCEDURE does send the sorted records to an output file, it can control which records, and what type of records, appear in the file.

9781430262534_Fig14-08.jpg

Figure 14-8. Using an OUTPUT PROCEDURE TO summarize records

Creating an OUTPUT PROCEDURE

When you use an OUTPUT PROCEDURE, you must use the RETURN verb to retrieve records from the work file associated with the SORT. RETURN is a special verb used only in OUTPUT PROCEDUREs. It is the equivalent of the READ verb and works in a similar way. The metalanguage for the RETURN verb is given in Figure 14-9.

9781430262534_Fig14-09.jpg

Figure 14-9. Metalanguage for the RETURN verb

Example 4-4 shows an operational template for an OUTPUT PROCEDURE that gets records from the work file and writes them to an output file. Notice that the work file is not opened in the OUTPUT PROCEDURE; the work file is automatically opened by the SORT.

Example 14-4. OUTPUT PROCEDURE File-Processing Template

OPEN OUTPUT OutFile
RETURN SDWorkFile RECORD
PERFORM UNTIL TerminatingCondition
   Setup OutRec
   WRITE OutRec
   RETURN SDWorkFile RECORD
END-PERFORM
CLOSE OutFile

Using an OUTPUT PROCEDURE to Produce a Summary File

The example in Listing 14-5 returns to the specification for the Universal Telecoms Monthly Report. However, the specification has been changed again. This time, instead of producing a report, you are required to produce a summary file. The summary file is a sequential file, ordered on ascending SubscriberId. Each subscriber record in the summary file summarizes all the records in BillableServicesFile for that subscriber. Each record in the file has the following description:

image

Listing 14-5. Using an OUTPUT PROCEDURE to Create a Summary File

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing14-5.
AUTHOR. Michael Coughlan.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT WorkFile ASSIGN TO "WORK.TMP".
    
    SELECT BillableServicesFile  ASSIGN TO "Listing14-5.dat"
           ORGANIZATION LINE SEQUENTIAL.
    
    SELECT SortedSummaryFile   ASSIGN TO "Listing14-5.Srt"
               ORGANIZATION LINE SEQUENTIAL.
 
DATA DIVISION.
FILE SECTION.
FD  BillableServicesFile.
01  SubscriberRec-BSF     PIC X(17).
 
SD  WorkFile.
01  WorkRec.
    88 EndOfWorkFile      VALUE HIGH-VALUES.
    02 SubscriberId-WF    PIC 9(10).
    02 FILLER             PIC 9.
       88 TextCall        VALUE 1.
       88 VoiceCall       VALUE 2.
    02 ServiceCost-WF     PIC 9(4)V99.
 
FD  SortedSummaryFile.
01  SummaryRec.
    02 SubscriberId       PIC 9(10).
    02 CostOfTexts        PIC 9(4)V99.
    02 CostOfCalls        PIC 9(6)V99.
    
PROCEDURE DIVISION.
Begin.
    SORT WorkFile ON ASCENDING KEY SubscriberId-WF
           USING BillableServicesFile
           OUTPUT PROCEDURE IS CreateSummaryFile
    STOP RUN.
 
CreateSummaryFile.
    OPEN OUTPUT SortedSummaryFile
    RETURN WorkFile
      AT END SET EndOfWorkFile TO TRUE
    END-RETURN
    PERFORM UNTIL EndOfWorkFile
       MOVE ZEROS TO CostOfTexts, CostOfCalls
       MOVE SubscriberId-WF TO SubscriberId
       PERFORM UNTIL SubscriberId-WF NOT EQUAL TO SubscriberId
          IF VoiceCall
             ADD ServiceCost-WF TO CostOfCalls
           ELSE
             ADD ServiceCost-WF TO CostOfTexts
          END-IF
          RETURN WorkFile
             AT END SET EndOfWorkFile TO TRUE
          END-RETURN
       END-PERFORM
       WRITE SummaryRec
    END-PERFORM
    CLOSE SortedSummaryFile.

Figure 14-8 illustrates the process of producing the summary file. The SORT takes records from BillableServicesFile and sorts them, and then the OUTPUT PROCEDURE summarizes them and writes the summary records to SortedSummaryFile.

The data items in BillableServicesFile are not referred to in the program and so are not explicitly defined, although the storage they require is reserved (PIC X(17)). For reasons of brevity, and because it would obscure the core logic, the program does not check the data for validity.

Some Interesting Programs

You have seen how you can use an INPUT PROCEDURE to process records before they are sent to a SORT and how you can use an OUTPUT PROCEDURE to process the sorted records. But each was used in isolation. You can achieve some interesting results by using them in concert.

Sorting Student Records into Date-of-Entry Order

Suppose there exists an unordered sequential file of student records, and each record in the file has the following description:

image

StudentId is a number that consists of two digits representing the year of entry followed by six other digits. Write a program to sort StudentFile on the “real” ascending StudentId.

This specification presents an interesting issue. It says that the file should be ordered on the “real” ascending StudentId. This means the IDs of students who entered the university after the year 2000 should appear after those of students who entered the university before 2000. This is a problem because you can't just sort the records in ascending StudentId order, as is demonstrated in Figure 14-10.

9781430262534_Fig14-10.jpg

Figure 14-10. Showing the real StudentId sort order

How can this be done? Listing 14-6 solves the problem by using an INPUT PROCEDURE to alter StudentId to add the millennium to the date-of-entry part. Then the altered records are sorted, and the OUTPUT PROCEDURE strips off the millennium digits.

Listing 14-6. Using INPUT PROCEDURE and OUTPUT PROCEDURE in Concert

IDENTIFICATION DIVISION.
PROGRAM-ID.  Listing14-6.
AUTHOR.  Michael Coughlan.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT UnsortedStudentsFile ASSIGN TO "Listing14-6.DAT"
        ORGANIZATION IS LINE SEQUENTIAL.
 
    SELECT WorkFile ASSIGN TO "Workfile.tmp".
 
    SELECT SortedStudentsFile  ASSIGN TO "Listing14-6.srt"
                ORGANIZATION IS LINE SEQUENTIAL.
 
DATA DIVISION.
FILE SECTION.
FD UnsortedStudentsFile.
01 StudentRecUF.
   88  EndOfUnsortedFile  VALUE HIGH-VALUES.
   02  StudentIdUF.
       03 MillenniumUF   PIC 99.
       03 FILLER         PIC 9(5).
   02  RecBodyUF         PIC X(14).
 
SD WorkFile.
01 StudentRecWF.
   88  EndOfWorkFile  VALUE HIGH-VALUES.
   02  FullStudentIdWF.
       03 MillenniumWF   PIC 99.
       03 StudentIdWF    PIC 9(7).
   02  RecBodyWF         PIC X(14).
 
FD SortedStudentsFile.
01 StudentRecSF.
   02  StudentIdSF       PIC 9(7).
   02  RecBodySF         PIC X(14).
 
PROCEDURE DIVISION.
Begin.
   SORT WorkFile ON ASCENDING KEY FullStudentIdWF
       INPUT PROCEDURE  IS AddInMillennium
       OUTPUT PROCEDURE IS RemoveMillennium
   STOP RUN.
 
AddInMillennium.
   OPEN INPUT UnsortedStudentsFile
   READ UnsortedStudentsFile
      AT END SET EndOfUnsortedFile TO TRUE
   END-READ
   PERFORM UNTIL EndOfUnsortedFile
      MOVE RecBodyUF TO RecBodyWF
      MOVE StudentIDUF   TO StudentIdWF
      IF MillenniumUF < 70
         MOVE 20 TO MillenniumWF
      ELSE
         MOVE 19 TO MillenniumWF
      END-IF
      RELEASE StudentRecWF
      READ UnsortedStudentsFile
        AT END SET EndOfUnsortedFile TO TRUE
      END-READ
   END-PERFORM
   CLOSE UnsortedStudentsFile.
 
RemoveMillennium.
   OPEN OUTPUT SortedStudentsFile
   RETURN WorkFile
      AT END SET EndOfWorkFile TO TRUE
   END-RETURN
   PERFORM UNTIL EndOfWorkFile
      MOVE RecBodyWF   TO RecBodySF
      MOVE StudentIdWF TO StudentIdSF
      WRITE StudentRecSF
      RETURN WorkFile
        AT END SET EndOfWorkFile TO TRUE
      END-RETURN
   END-PERFORM
   CLOSE SortedStudentsFile.

Sorting Tables

Versions of COBOL before ISO 2002 did not allow you to apply a SORT to a table. But it was possible to work around this restriction by using an INPUT PROCEDURE to release table elements to the work file and an OUTPUT PROCEDURE to get the sorted element-records from the work file and put them back into the table. The process is illustrated in Figure 14-11; see Listing 14-7.

9781430262534_Fig14-11.jpg

Figure 14-11. Using INPUT PROCEDURE and OUTPUT PROCEDURE to sort a table

Listing 14-7. Sorting a Table Using INPUT PROCEDURE and OUTPUT PROCEDURE

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing14-7.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 CountyTable.
   02 TableValues.
      03 FILLER  PIC X(16)  VALUE "kilkenny 0080421".
      03 FILLER  PIC X(16)  VALUE "laois    0058732".
      03 FILLER  PIC X(16)  VALUE "leitrim  0025815".
      03 FILLER  PIC X(16)  VALUE "tipperary0140281".
      03 FILLER  PIC X(16)  VALUE "waterford0101518".
      03 FILLER  PIC X(16)  VALUE "westmeath0072027".
      03 FILLER  PIC X(16)  VALUE "carlow   0045845".
      03 FILLER  PIC X(16)  VALUE "wicklow  0114719".
      03 FILLER  PIC X(16)  VALUE "cavan    0056416".
      03 FILLER  PIC X(16)  VALUE "clare    0103333".
      03 FILLER  PIC X(16)  VALUE "meath    0133936".
      03 FILLER  PIC X(16)  VALUE "monaghan 0052772".
      03 FILLER  PIC X(16)  VALUE "offaly   0063702".
      03 FILLER  PIC X(16)  VALUE "roscommon0053803".
      03 FILLER  PIC X(16)  VALUE "sligo    0058178".
      03 FILLER  PIC X(16)  VALUE "cork     0448181".
      03 FILLER  PIC X(16)  VALUE "donegal  0137383".
      03 FILLER  PIC X(16)  VALUE "dublin   1122600".
      03 FILLER  PIC X(16)  VALUE "galway   0208826".
      03 FILLER  PIC X(16)  VALUE "wexford  0116543".
      03 FILLER  PIC X(16)  VALUE "kerry    0132424".
      03 FILLER  PIC X(16)  VALUE "kildare  0163995".
      03 FILLER  PIC X(16)  VALUE "limerick 0175529".
      03 FILLER  PIC X(16)  VALUE "longford 0031127".
      03 FILLER  PIC X(16)  VALUE "louth    0101802".
      03 FILLER  PIC X(16)  VALUE "mayo     0117428".
   02 FILLER REDEFINES TableValues.
      03   CountyDetails OCCURS 26 TIMES
           INDEXED BY Cidx.
           04 CountyName   PIC X(9).
           04 CountyPop    PIC 9(7).
 
01 PrnCountyPop            PIC Z,ZZZ,ZZ9.
 
PROCEDURE DIVISION.
Begin.
   DISPLAY "County name order"
   SORT CountyDetails ON ASCENDING KEY CountyName
   PERFORM DisplayCountyTotals
           VARYING Cidx FROM 1 BY 1 UNTIL Cidx GREATER THAN 26.
 
   DISPLAY SPACES
   DISPLAY "County population order"
   SORT CountyDetails ON DESCENDING KEY CountyPop
   PERFORM DisplayCountyTotals
           VARYING Cidx FROM 1 BY 1 UNTIL Cidx GREATER THAN 26.
 
   STOP RUN.
 
DisplayCountyTotals.
   MOVE CountyPop(Cidx) TO PrnCountyPop
   DISPLAY CountyName(Cidx) " is " PrnCountyPop

9781430262534_unFig14-03.jpg

Sorting Tables: ISO 2002 Changes

Listing 14-7 shows how to sort a table using an INPUT PROCEDURE and an OUTPUT PROCEDURE. The problem with this solution is the work file. The sort operation, being bound to a file on backing storage, is comparatively slow. Sorting the table would be faster if it could be done wholly in memory.

Sorting a table directly in memory is exactly what the ISO 2002 version of COBOL now allows. The metalanguage for this SORT format is given in Figure 14-12, and Listing 14-8 shows how you can use this format to sort the County table from Listing 14-7.

9781430262534_Fig14-12.jpg

Figure 14-12. Metalanguage for the ISO 2002 version of SORT

Listing 14-8. Applying SORT Directly to a Table

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing14-8.
*> ISO 2002 Applying the SORT to a table
DATA DIVISION.
WORKING-STORAGE SECTION.
01 CountyTable.
   02 TableValues.
      03 FILLER  PIC X(16)  VALUE "kilkenny 0080421".
      03 FILLER  PIC X(16)  VALUE "laois    0058732".
      03 FILLER  PIC X(16)  VALUE "leitrim  0025815".
      03 FILLER  PIC X(16)  VALUE "tipperary0140281".
      03 FILLER  PIC X(16)  VALUE "waterford0101518".
      03 FILLER  PIC X(16)  VALUE "westmeath0072027".
      03 FILLER  PIC X(16)  VALUE "carlow   0045845".
      03 FILLER  PIC X(16)  VALUE "wicklow  0114719".
      03 FILLER  PIC X(16)  VALUE "cavan    0056416".
      03 FILLER  PIC X(16)  VALUE "clare    0103333".
      03 FILLER  PIC X(16)  VALUE "meath    0133936".
      03 FILLER  PIC X(16)  VALUE "monaghan 0052772".
      03 FILLER  PIC X(16)  VALUE "offaly   0063702".
      03 FILLER  PIC X(16)  VALUE "roscommon0053803".
      03 FILLER  PIC X(16)  VALUE "sligo    0058178".
      03 FILLER  PIC X(16)  VALUE "cork     0448181".
      03 FILLER  PIC X(16)  VALUE "donegal  0137383".
      03 FILLER  PIC X(16)  VALUE "dublin   1122600".
      03 FILLER  PIC X(16)  VALUE "galway   0208826".
      03 FILLER  PIC X(16)  VALUE "wexford  0116543".
      03 FILLER  PIC X(16)  VALUE "kerry    0132424".
      03 FILLER  PIC X(16)  VALUE "kildare  0163995".
      03 FILLER  PIC X(16)  VALUE "limerick 0175529".
      03 FILLER  PIC X(16)  VALUE "longford 0031127".
      03 FILLER  PIC X(16)  VALUE "louth    0101802".
      03 FILLER  PIC X(16)  VALUE "mayo     0117428".
   02 FILLER REDEFINES TableValues.
      03   CountyDetails OCCURS 26 TIMES
           INDEXED BY Cidx.
           04 CountyName   PIC X(9).
           04 CountyPop    PIC 9(7).
 
01 PrnCountyPop            PIC Z,ZZZ,ZZ9.
 
PROCEDURE DIVISION.
Begin.
   DISPLAY "County name order"
   SORT CountyDetails ON ASCENDING KEY CountyName
   PERFORM DisplayCountyTotals
           VARYING Cidx FROM 1 BY 1 UNTIL Cidx GREATER THAN 26.
            
   DISPLAY SPACES
   DISPLAY "County population order"
   SORT CountyDetails ON ASCENDING KEY CountyPop
   PERFORM DisplayCountyTotals
           VARYING Cidx FROM 1 BY 1 UNTIL Cidx GREATER THAN 26.
 
   STOP RUN.
 
DisplayCountyTotals.
   MOVE CountyPop(Cidx) TO PrnCountyPop
   DISPLAY CountyName(Cidx) " is " PrnCountyPop.

image Note  For full details, read your implementer manual.

Merging Files

It is often useful to combine two or more files into a single large file. If the files are unordered, this is easy to accomplish because you can simply append the records in one file to the end of the other. But if the files are ordered, the task is somewhat more complicated—especially if there are more than two files—because you must preserve the ordering in the combined file.

In COBOL, instead of having to write special code every time you want to merge files, you can use the MERGE verb. MERGE takes a number of files, all ordered on the same key values, and combines them based on those key values. The combined file is then sent to an output file or an OUTPUT PROCEDURE.

MERGE Verb

The metalanguage for the MERGE verb is given in Figure 14-13. It should be obvious from the metalanguage that MERGE shares many of same declarations required for SORT. Just like SORT, MERGE uses a temporary work file that must be defined using an SD entry in the FILE SECTION. Also just as with SORT, the KEY field (on which the files are merged) must be a data item declared in the work file. And just as with SORT, you can use an OUTPUT PROCEDURE to get records from the work file before sending them to their ultimate destination. Unlike with SORT, however, no INPUT PROCEDURE is permitted.

9781430262534_Fig14-13.jpg

Figure 14-13. Metalanguage for the MERGE verb

MERGE Notes

You should consider the following when using MERGE:

  • The results of the MERGE verb are predictable only when the records in the USING files are ordered as described in the KEY clause associated with the MERGE. For instance, if the MERGE statement has an ON DESCENDING KEY StudentId clause, then all the USING files must be ordered on descending StudentId.
  • As with SORT, SDWorkFileName is the name of a temporary file, with an SD entry in the FILE SECTION, SELECT and ASSIGN entries in the INPUT-OUTPUT SECTION, and an organization of RECORD SEQUENTIAL.
  • Each MergeKeyIdentifier identifies a field in the record of the work file. The merged files are ordered on this key field(s).
  • When more than one MergeKeyIdentifier is specified, the keys decrease in significance from left to right (the leftmost key is most significant, and the rightmost is least significant).
  • InFileName and MergedFileName are the names of the input file to be merged and the resulting combined file produced by the MERGE, respectively. These files are automatically opened by the MERGE. When the MERGE executes, they must not be already open.
  • AlphabetName is an alphabet name defined in the SPECIAL-NAMES paragraph of the ENVIRONMENT DIVISION. This clause is used to select the character set the SORT verb uses for collating the records in the file. The character set may be STANDARD-1 (ASCII), STANDARD-2 (ISO 646), NATIVE (may be defined by the system to be ASCII or EBCDIC; see your implementer manual), or user defined.
  • MERGE can use an OUTPUT PROCEDURE and the RETURN verb to get merged records from SDWorkFileName.
  • The OUTPUT PROCEDURE executes only after the files have been merged and must contain at least one RETURN statement to get the records from SortFile.

Merging Province Sales Files

Listing 14-9 is an example program that uses MERGE to combine four sequential files, each ordered on ascending ProductCode. The program is based on the following specification.

Listing 14-9. Merging ProvinceSales Files and Producing a Sales Summary File

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing14-9.
AUTHOR. Michael Coughlan.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT UlsterSales    ASSIGN TO "Listing14-9ulster.dat"
           ORGANIZATION IS LINE SEQUENTIAL.
 
    SELECT ConnachtSales  ASSIGN TO "Listing14-9connacht.dat"
           ORGANIZATION IS LINE SEQUENTIAL.
 
    SELECT MunsterSales   ASSIGN TO "Listing14-9munster.dat"
           ORGANIZATION IS LINE SEQUENTIAL.
 
    SELECT LeinsterSales  ASSIGN TO "Listing14-9leinster.dat"
           ORGANIZATION IS LINE SEQUENTIAL.
 
    SELECT SummaryFile    ASSIGN TO "Listing14-9.sum"
               ORGANIZATION IS LINE SEQUENTIAL.
                
    SELECT WorkFile       ASSIGN TO "WORK.TMP".
 
DATA DIVISION.
FILE SECTION.
FD  UlsterSales.
01  FILLER                 PIC X(12).
 
FD  ConnachtSales.
01  FILLER                 PIC X(12).
 
FD  MunsterSales.
01  FILLER                 PIC X(12).
 
FD  LeinsterSales.
01  FILLER                 PIC X(12).
 
FD  SummaryFile.
01  SummaryRec.
    02 ProductCode-SF      PIC X(6).
    02 TotalSalesValue     PIC 9(6)V99.
    
SD  WorkFile.
01  WorkRec.
    88 EndOfWorkfile       VALUE HIGH-VALUES.
    02 ProductCode-WF      PIC X(6).
    02 ValueOfSale-WF      PIC 9999V99.
 
PROCEDURE DIVISION.
Begin.
    MERGE WorkFile ON ASCENDING KEY ProductCode-WF
       USING UlsterSales, ConnachtSales, MunsterSales, LeinsterSales
       OUTPUT PROCEDURE IS SummarizeProductSales
        
    STOP RUN.
 
SummarizeProductSales.
    OPEN OUTPUT SummaryFile
    RETURN WorkFile
       AT END SET EndOfWorkfile TO TRUE
    END-RETURN
    
    PERFORM UNTIL EndOfWorkFile
       MOVE ZEROS TO TotalSalesValue
       MOVE ProductCode-WF TO ProductCode-SF
       PERFORM UNTIL ProductCode-WF NOT EQUAL TO ProductCode-SF
          ADD ValueOfSale-WF TO TotalSalesValue
          RETURN WorkFile
             AT END SET EndOfWorkfile TO TRUE
          END-RETURN
       END-PERFORM
       WRITE SummaryRec
    END-PERFORM
    CLOSE SummaryFile.

Every month, the TrueValue head office receives a file from its branch in each of the four provinces of Ireland. Each file records the sales made in that province. A program is required that will combine these four files and, from them, produce a summary file that records the total value of the sales of each product sold by the company. The summary file must be ordered on ascending ProductCode. The record description for each of the four files is as follows:

image

The record description for the summary file is shown next:

image

Summary

This chapter explored the SORT and MERGE verbs. You discovered how to define the work file that SORT uses as a temporary scratch pad when sorting. You saw how to create an INPUT PROCEDURE to filter or alter the records sent to the work file and how to create an OUTPUT PROCEDURE to get and process the sorted records from the work file. You also learned that you can use the INPUT PROCEDURE and OUTPUT PROCEDURE in concert to achieve interesting results: you can sort a table by using an INPUT PROCEDURE to get the elements from the table and release them to the work file and an OUTPUT PROCEDURE to retrieve the sorted element-records from the work file and place them back in the table. In addition, the ISO 2002 version of COBOL allows you to sort a table directly. Finally, you saw how to use the MERGE verb to combine identically ordered files into one file that preserves the ordering.

The next chapter introduces COBOL string handling. In many other languages, string manipulation is achieved by using a library of string functions. In COBOL, string manipulation uses intrinsic functions, reference modification, and the STRING, UNSTRING, and INSPECT verbs.

PROGRAMMING EXERCISE 1

Visitors to an Irish web site are asked to fill in a guestbook form. The form requests the name of the visitor, their country of origin, and a comment. These fields are stored as a fixed length record in GuestBookFile. GuestBookFile is an unordered sequential file, each record of which has the following description:

image

You are required to write a program to print a report that shows the number of visitors from each foreign (non-Irish) country. The report must be printed in ascending CountryName sequence. Because the records in GuestBookFile are not in any particular order, before the report can be printed, the file must be sorted by CountryName. The report template is as follows:

    Foreign Guests Report
Country               Visitors
XXXXXXXXXXXXXXXXXXXX   XXXXXX
XXXXXXXXXXXXXXXXXXXX   XXXXXX
XXXXXXXXXXXXXXXXXXXX   XXXXXX
XXXXXXXXXXXXXXXXXXXX   XXXXXX
XXXXXXXXXXXXXXXXXXXX   XXXXXX
XXXXXXXXXXXXXXXXXXXX   XXXXXX
XXXXXXXXXXXXXXXXXXXX   XXXXXX
XXXXXXXXXXXXXXXXXXXX   XXXXXX
XXXXXXXXXXXXXXXXXXXX   XXXXXX
XXXXXXXXXXXXXXXXXXXX   XXXXXX
XXXXXXXXXXXXXXXXXXXX   XXXXXX
XXXXXXXXXXXXXXXXXXXX   XXXXXX

  ***** End of report *****

PROGRAMMING EXERCISE 1: ANSWER

Because only foreign visitors are of interest, there is no point in sorting the entire file. An INPUT PROCEDURE is used to select only the records of visitors from foreign (non-Irish) countries. An OUTPUT PROCEDURE is used to create the report.

When you examine the fields of a GuestBookFile record, notice that, for the purposes of this report, GuestName and GuestComment are irrelevant. The only field you need for the report is the CountryName field. So in addition to selecting only foreign guests, the INPUT PROCEDURE alters the structure of the records supplied to the sort process. Because the new records are only 20 characters in size, rather than 80 characters, the amount of data that has to be sorted is substantially reduced.

Listing 14-10. Using an INPUT PROCEDURE to Modify and Filter the Records in the Input File

IDENTIFICATION DIVISION.
PROGRAM-ID.  Listing14-10.
AUTHOR.  Michael Coughlan.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
   SELECT GuestBookFile
          ASSIGN TO "Listing14-10.Dat"
          ORGANIZATION IS LINE SEQUENTIAL.
 
   SELECT WorkFile
          ASSIGN TO "Work.Tmp".
 
   SELECT ForeignGuestReport
          ASSIGN TO "Listing14-10.rpt"
          ORGANIZATION IS LINE SEQUENTIAL.
 
DATA DIVISION.
FILE SECTION.
FD GuestBookFile.
01 GuestRec.
   88  EndOfFile  VALUE HIGH-VALUES.
   02  GuestNameGF         PIC X(20).
   02  CountryNameGF       PIC X(20).
       88 CountryIsIreland VALUE "IRELAND".
   02  GuestCommentGF      PIC X(40).
 
SD WorkFile.
01 WorkRec.
   88 EndOfWorkFile        VALUE HIGH-VALUES.
   02 CountryNameWF        PIC X(20).
 
FD ForeignGuestReport.
01 PrintLine               PIC X(38).
 
WORKING-STORAGE SECTION.
01 Heading1                PIC X(25)
         VALUE "    Foreign Guests Report".
          
01 Heading2.
   02 FILLER               PIC X(22) VALUE "Country".
   02 FILLER               PIC X(8)  VALUE "Visitors".
 
01 CountryLine.
   02 PrnCountryName       PIC X(20).
   02 PrnVisitorCount      PIC BBBZZ,ZZ9.
 
01 ReportFooting           PIC X(27)
         VALUE "  ***** End of report *****".
 
01 VisitorCount            PIC 9(5).
 
PROCEDURE DIVISION.
Begin.
   SORT WorkFile ON ASCENDING CountryNameWF
        INPUT PROCEDURE IS SelectForeignGuests
        OUTPUT PROCEDURE IS PrintGuestsReport.
 
   STOP RUN.
 
PrintGuestsReport.
   OPEN OUTPUT ForeignGuestReport
   WRITE PrintLine FROM Heading1
         AFTER ADVANCING PAGE
   WRITE PrintLine FROM Heading2
         AFTER ADVANCING 1 LINES
    
   RETURN WorkFile
        AT END SET EndOfWorkfile TO TRUE
   END-RETURN
   PERFORM PrintReportBody UNTIL EndOfWorkfile
 
   WRITE PrintLine FROM ReportFooting
         AFTER ADVANCING 2 LINES
   CLOSE ForeignGuestReport.
    
PrintReportBody.
   MOVE CountryNameWF TO PrnCountryName
   MOVE ZEROS TO VisitorCount
   PERFORM UNTIL CountryNameWF NOT EQUAL TO PrnCountryName
      ADD 1 TO VisitorCount
      RETURN WorkFile
         AT END SET EndOfWorkfile TO TRUE
      END-RETURN
   END-PERFORM
   MOVE VisitorCount TO PrnVisitorCount
   WRITE PrintLine FROM CountryLine
         AFTER ADVANCING 1 LINE.
 
SelectForeignGuests.
   OPEN INPUT GuestBookFile.
   READ GuestBookFile
      AT END SET EndOfFile TO TRUE
   END-READ
   PERFORM UNTIL EndOfFile
      IF NOT CountryIsIreland
         MOVE CountryNameGF TO CountryNameWF
         RELEASE WorkRec
      END-IF
      READ GuestBookFile
        AT END SET EndOfFile TO TRUE
      END-READ
   END-PERFORM
   CLOSE GuestBookFile.
..................Content has been hidden....................

You can't read the all page of ebook, please click here login for view all page.
Reset
3.15.142.21