Michael Coughlan

Home > Other > Michael Coughlan > Page 44


  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:

  Field

  Type Length

  Value

  ProductCode

  X

  6

  –

  ValueOfSale

  9

  6

  0–9999.99

  The record description for the summary file is shown next:

  Field

  Type Length

  Value

  ProductCode

  X

  6

  –

  TotalValueOfSale

  9

  8

  0–999999.99

  355

  Chapter 14 ■ Sorting and Merging

  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:

  Field

  Type

  Length

  Value

  GuestName

  X

  20

  –

  CountryName

  X

  20

  –

  GuestComment

  X

  40

  –

  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 *****

  356

  Chapter 14 ■ Sorting and Merging

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

  357

  Chapter 14 ■ Sorting and Merging

  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
<
br />   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

  358

  Chapter 14 ■ Sorting and Merging

  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.

  359

  Chapter 15

  String Manipulation

  In many languages, string manipulation is achieved by using a library of string functions or, as in Java, the methods of a String class. COBOL also uses a library of string-manipulation functions, but most string manipulation is done using reference modification and the three string-handling verbs: STRING, UNSTRING, and INSPECT.

  This chapter starts by examining the string-handling verbs. These verbs allow you to count and replace

  characters, and concatenate and split strings. You are then introduced to reference modification, which lets you treat any string as an array of characters. Finally, you learn about the intrinsic functions used for string and date manipulation.

  The INSPECT Verb

  The INSPECT verb has four formats;

  • The first format is used for counting characters in a string.

  • The second replaces a group of characters in a string with another group of characters.

  • The third combines both operations in one statement.

  • The fourth format converts each character in a set of characters to its corresponding character

  in another set of characters.

  Before starting a formal examination of the INSPECT formats, let’s get a feel for how the verb operates by looking at a short program (see Listing 15-1). The program accepts a line of text from the user and then counts and displays how many times each letter of the alphabet occurs in the text.

  Listing 15-1. Finding the Number of Times Each Letter Occurs in a Line of Text

  IDENTIFICATION DIVISION.

  PROGRAM-ID. Listing15-1.

  AUTHOR. Michael Coughlan.

  DATA DIVISION.

  WORKING-STORAGE SECTION.

  01 TextLine PIC X(80).

  01 LowerCase PIC X(26) VALUE "abcdefghijklmnopqrstuvwxyz".

  01 UpperCase VALUE "ABCDEFGHIJKLMNOPQRSTUVWXYZ".

  02 Letter PIC X OCCURS 26 TIMES.

  361

  Chapter 15 ■ String Manipulation

  01 idx PIC 99.

  01 LetterCount PIC 99

  01 PrnLetterCount PIC Z9.

  PROCEDURE DIVISION.

  Begin.

  DISPLAY "Enter text : " WITH NO ADVANCING

  ACCEPT TextLine

  INSPECT TextLine

  CONVERTING LowerCase TO UpperCase

  PERFORM VARYING idx FROM 1 BY 1 UNTIL idx > 26

  MOVE ZEROS TO LetterCount

  INSPECT TextLine TALLYING LetterCount FOR ALL Letter(idx)

  IF LetterCount > ZERO

  MOVE LetterCount TO PrnLetterCount

  DISPLAY "Letter " Letter(idx) " occurs " PrnLetterCount " times"

  END-IF

  END-PERFORM

  STOP RUN.

  The program gets a line of text from the user. It then uses INSPECT..CONVERTING to convert all the characters to their uppercase equivalents.

  The UpperCase data item in this program does double duty. It is used in INSPECT CONVERTING as an ordinary

  alphanumeric data item, but it is also defined as a 26-element prefilled table of letters. Using this table, the PERFORM

  loop supplies the letters one at a time to INSPECT..TALLYING, which counts the number of times each letter occurs in TextLine. It stores the count in LetterCount. If the letter occurred in TextLine, then the count is displayed.

  There are some interesting things to note about this program. First, since intrinsic functions were introduced in the ANS 85 version of COBOL, is it no longer necessary to use INSPECT.. CONVERTING to convert characters to uppercase. Nowadays you can use the UPPER-CASE function. This function has the added benefit that it can do the conversion without changing the original text. Second, you don’t actually need to hold the letters of the alphabet as a table. Reference modification allows you to treat any alphanumeric data item as a table of characters. Listing 15-2

  shows a version of the program that incorporates these modernizations.

  Listing 15-2. Modernized Version of the Program in Listing 15-1

  IDENTIFICATION DIVISION.

  PROGRAM-ID. Listing15-2.

  AUTHOR. Michael Coughlan.

  DATA DIVISION.

  WORKING-STORAGE SECTION.

  01 TextLine PIC X(80).

  01 Letters PIC X(26) VALUE "ABCDEFGHIJKLMNOPQRSTUVWXYZ".

  01 LetterPos PIC 99.

  01 LetterCount PIC 99.

  01 PrnLetterCount PIC Z9.

  362

  Chapter 15 ■ String Manipulation

  PROCEDURE DIVISION.

  Begin.

  DISPLAY "Enter text : " WITH NO ADVANCING

  ACCEPT TextLine

  PERFORM VARYING LetterPos FROM 1 BY 1 UNTIL LetterPos > 26

  MOVE ZEROS TO LetterCount

  INSPECT FUNCTION UPPER-CASE(TextLine)

  TALLYING LetterCount FOR ALL Letters(LetterPos:1)

  IF LetterCount > ZERO

  MOVE LetterCount TO PrnLetterCount

  DISPLAY "Letter " Letters(LetterPos:1) " occurs " PrnLetterCount " times"

  END-IF

  END-PERFORM

  STOP RUN.

  INSPECT .. TALLYING: Format 1

  INSPECT..TALLYING counts the number of occurrences of a character in a string. The metalanguage for this version of INSPECT is given in Figure 15-1.

  Figure 15-1. Metalanguage for INSPECT..TALLYING

  This version of INSPECT works by scanning the source string SourceStr$i from left to right, counting the

  occurrences of all characters or just a specified character:

  • The behavior of INSPECT is modified by the LEADING, ALL, BEFORE, and AFTER phrases. An ALL,

  LEADING, or CHARACTERS phrase may only be followed by one BEFORE and one AFTER phrase.

  • As indicated by the ellipsis after the final bracket, you can use a number of counters—each

  with its own modifying phrases—with an INSPECT..TALLYING statement.

  • If Compare$il or Delim$il is a figurative constant, it is one character in size.

  Modifying Phrases

  The operation of INSPECT is governed by the modifying phrases used. The meaning of these phrases is as follows: BEFORE: Designates the characters to the left of the associated delimiter (Delim$il) as valid.

  If the delimiter is not present in SourceStr$i, then using the BEFORE phrase implies that all

  the characters are valid.

  AFTER: Designates the characters to the right of the associated delimiter (Delim$il) as valid.

  If the delimiter is not present in the SourceStr$i, then using the AFTER phrase implies that

  there are no valid characters in the string.

  363

  Chapter 15 ■ String Manipulation

  ALL: Counts all Compare$il characters
from the first matching valid character to the first

  invalid one.

  LEADING: Counts leading Compare$il characters from the first matching valid character

  encountered to the first nonmatching or invalid character.

  INSPECT .. TALLYING Examples

  Example 15-1 shows some example INSPECT statements, and Listing 15-3 presents a small program. The program’s task is to count the number of vowels and the number of consonants in a line of text entered by the user.

  Example 15-1. Some INSPECT..TALLYING Example Statements

  INSPECT TextLine TALLYING UnstrPtr FOR LEADING SPACES.

  INSPECT TextLine TALLYING

  eCount FOR ALL "e" AFTER INITIAL "start"

  BEFORE INITIAL "end".

  INSPECT TextLine TALLYING

  aCount FOR ALL "a"

  eCount FOR ALL "e"

  oCount FOR ALL "o"

  INSPECT FUNCTION REVERSE(TextLine) TALLYING

  TrailingSpaces FOR LEADING SPACES

  COMPUTE StrLength = FUNCTION LENGTH(TextLine) - TrailingSpaces

  Listing 15-3. Counting Vowels and Consonants

  IDENTIFICATION DIVISION.

  PROGRAM-ID. Listing15-3.

  AUTHOR. Michael Coughlan.

  DATA DIVISION.

  WORKING-STORAGE SECTION.

  01 TextLine PIC X(80).

  01 VowelCount PIC 99 VALUE ZERO.

  01 ConsonantCount PIC 99 VALUE ZERO.

  PROCEDURE DIVISION.

  Begin.

  DISPLAY "Enter text : " WITH NO ADVANCING

  ACCEPT TextLine

  INSPECT FUNCTION UPPER-CASE(TextLine) TALLYING

  VowelCount FOR ALL "A" "E" "I" "O" "U"

  ConsonantCount FOR ALL

  "B" "C" "D" "F" "G" "H" "J" "K" "L" "M" "N" "P"

  "Q" "R" "S" "T" "V" "W" "X" "Y" "Z"

  DISPLAY "The line contains " VowelCount " vowels and "

  ConsonantCount " consonants."

  STOP RUN.

  364

  Chapter 15 ■ String Manipulation

  Programmatic Detour

  There are a number of ways to solve the problem of finding the number of vowels and consonants in a line of text.

 

‹ Prev