Michael Coughlan

Home > Other > Michael Coughlan > Page 42


  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.

  336

  Chapter 14 ■ Sorting and Merging

  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

  337

  Chapter 14 ■ Sorting and Merging

  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.

  338

  Chapter 14 ■ Sorting and Merging

  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.

  339

  Chapter 14 ■ Sorting and Merging

  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 PrevSub
scriberId, 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.

  340

  Chapter 14 ■ Sorting and Merging

  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".

  341

  Chapter 14 ■ Sorting and Merging

  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.

  342

  Chapter 14 ■ Sorting and Merging

  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.

  343

  Chapter 14 ■ Sorting and Merging

  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.

  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

  344

  Chapter 14 ■ Sorting and Merging

  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 subsc
riber record in the summary file summarizes all the records in BillableServicesFile for that subscriber. Each record in the file has the following description:

  Field

  Type Length

  Value

  SubscriberId

  9

  10

  –

  CostOfTexts

  9

  6

  0.10–9999.99

  CostOfCalls

  9

  8

  0.10–999999.99

  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.

  345

 

‹ Prev