CHAPTER 15

image

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

9781430262534_unFig15-01.jpg

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

9781430262534_Fig15-01.jpg

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.

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.

9781430262534_unFig15-02.jpg

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. Although it is not strictly string manipulation, I’d like to explore an alternative solution to Listing 15-3 here, because it allows me to introduce an aspect of condition names that you have not seen before. In the solution in Listing 15-4, TextLine is defined as an array of characters. A PERFORM is used to step through the array and, at each character, test whether it is a vowel or a consonant; whichever it is, the PERFORM then increments the appropriate total. The interesting part is the way you discover whether the character is a vowel or a consonant.

You may not have realized that a condition name can be set to monitor a table element. That is what the program in Listing 15-4 does. Once the condition names for vowels and consonants are set up, all the program needs to do is test which condition name is set to TRUE for the character under consideration and then increment the appropriate count.

Listing 15-4. Using a Table Element Condition to Count Vowels and Consonants

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing15-4.
AUTHOR. Michael Coughlan.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 TextLine.
   02 Letter           PIC X OCCURS 80 TIMES.
      88 Vowel         VALUE  "A" "E" "I" "O" "U".
      88 Consonant     VALUE  "B" "C" "D" "F" "G" "H" "J" "K" "L" "M" "N" "P"
                              "Q" "R" "S" "T" "V" "W" "X" "Y" "Z".
01 VowelCount          PIC 99 VALUE ZERO.
01 ConsonantCount      PIC 99 VALUE ZERO.
01 idx                 PIC 99.
PROCEDURE DIVISION.
Begin.
    DISPLAY "Enter text : " WITH NO ADVANCING
    ACCEPT TextLine
    MOVE FUNCTION UPPER-CASE(TextLine) TO TextLine
    PERFORM VARYING idx FROM 1 BY 1 UNTIL idx > 80
        IF Vowel(idx) ADD 1 TO VowelCount
          ELSE IF Consonant(idx) ADD 1 TO ConsonantCount
        END-IF
    END-PERFORM
    DISPLAY "The line contains " VowelCount " vowels and " ConsonantCount " consonants."
    STOP RUN.

9781430262534_unFig15-03.jpg

INSPECT .. REPLACING: Format 2

INSPECT..REPLACING replaces characters in the string with a replacement character. The metalanguage for this version of INSPECT is given in Figure 15-2.

9781430262534_Fig15-02.jpg

Figure 15-2. Metalanguage for INSPECT..REPLACING

This version of INSPECT works by scanning the source string SourceStr$i from left to right and replacing occurrences of all characters with a replacement character, or replacing specified characters with replacement characters:

  • The behavior of the INSPECT is modified by the LEADING, ALL, FIRST, BEFORE, and AFTER phrases. An ALL, LEADING, FIRST, or CHARACTERS phrase may only be followed by one BEFORE phrase and one AFTER phrase.
  • If Compare$il or Delim$il is a figurative constant, it is one character in size. But when Replace$il is a figurative constant, its size equals that of Compare$il.
  • The sizes of Compare$il and Replace$il must be equal.
  • When there is a CHARACTERS phrase, the size of ReplaceChar$il and the delimiter that may follow it (Delim$il) must be one character.

Modifying Phrases

Like INSPECT..TALLYING, the operation of INSPECT..REPLACING is governed by the modifying phrases used. The meaning of these phrases is as follows:

BEFORE: Designates the characters to the left of its 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 its 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.

ALL: Replaces all Compare$il characters with the Replace$il characters from the first matching valid character to the first invalid one.

FIRST: Causes only the first valid character(s) to be replaced.

INSPECT .. REPLACING Examples

The INSPECT..REPLACING statements in Example 15-2 work on the data in StringData to produce the results shown in the storage schematics. Assume that before each INSPECT executes, the value "FFFAFFFFFFQFFFZ" (shown in the Before row) is moved to StringData.

Example 15-2. Example INSPECT..REPLACING Statements with Results

  1. INSPECT StringData REPLACING ALL "F" BY "G"
            AFTER INITIAL "A" BEFORE INITIAL "Q"
  2. INSPECT StringData REPLACING ALL "F" BY "G"
            AFTER INITIAL "A" BEFORE INITIAL "Z"
  3. INSPECT StringData REPLACING FIRST "F" BY "G"
            AFTER INITIAL "A" BEFORE INITIAL "Q"
  4. INSPECT StringData REPLACING
            ALL "FFFF" BY "DOGS"
            AFTER INITIAL "A" BEFORE INITIAL "Z"
  5. INSPECT StringData REPLACING
            CHARACTERS BY "z" BEFORE INITIAL "Q"

9781430262534_unFig15-04.jpg

INSPECT: Format 3

The third format of INSPECT simply allows you to combine the operation of the two previous formats in one statement. Please see those formats for explanations and examples. The metalanguage for the third INSPECT format is shown in Figure 15-3. This format is executed as though two successive INSPECT statements are applied to SourceStr$i, the first being an INSPECT..TALLYING and the second an INSPECT.. REPLACING.

9781430262534_Fig15-03.jpg

Figure 15-3. Metalanguage for format 3 of INSPECT

INSPECT .. CONVERTING: Format 4

INSPECT..CONVERTING seems very similar to INSPECT..REPLACING but actually works quite differently. It is used to convert one list of characters to another list of characters on a character-per-character basis. The metalanguage for this version of INSPECT is given in Figure 15-4.

9781430262534_Fig15-04.jpg

Figure 15-4. Metalanguage for INSPECT..CONVERTING

Using INSPECT .. CONVERTING

INSPECT..CONVERTING works on individual characters. If any of the Compare$il list of characters are found in SourceStr$i, they are replaced by the characters in Convert$il on a one-for-one basis. For instance, in Figure 15-5, an F found in StringData is converted to z, X is converted to y, T is converted to a, and D is converted to b.

9781430262534_Fig15-05.jpg

Figure 15-5. INSPECT..CONVERTING showing the conversion strategy

The INSPECT..CONVERTING in Figure 15-5 is the equivalent of the following:

INSPECT StringData REPLACING
ALL "F" BY "z",
    "X" BY "y",
    "T" BY "a",
    "D" BY "b"

These are some rules for INSPECT..CONVERTING :

  • Compare$il and Convert$il must be equal in size.
  • When Convert$il is a figurative constant, its size equals that of Compare$il.
  • The same character cannot appear more than once in Compare$il, because each character in the Compare$il string is associated with a replacement character. For instance, INSPECT StringData CONVERTING "XTX" TO "abc" is not allowed because the system won’t know if X should be converted to a or c.

INSPECT .. CONVERTING Examples

You saw an example of INSPECT..CONVERTING in Listing 15-1, where it was used to convert text to uppercase. That example is repeated in Listing 15-3, but here it demonstrates that Compare$il and Convert$il can be either strings or data items containing string values.

Example 15-3. Using INSPECT..CONVERTING to Convert Text to Uppercase or Lowercase

DATA DIVISION.
WORKING-STORAGE SECTION.
01 TextLine         PIC X(60).
01 LowerCase        PIC X(26) VALUE "abcdefghijklmnopqrstuvwxyz".
01 UpperCase        PIC X(26) VALUE "ABCDEFGHIJKLMNOPQRSTUVWXYZ".
 
PROCEDURE DIVISION.
Begin.
    DISPLAY "Enter text : " WITH NO ADVANCING
    ACCEPT TextLine
 
    INSPECT TextLine CONVERTING
            "abcdefghijklmnopqrstuvwxyz" TO
            "ABCDEFGHIJKLMNOPQRSTUVWXYZ"
    DISPLAY "Entered text in upper case = " TextLine
 
    INSPECT TextLine CONVERTING UpperCase TO LowerCase
    DISPLAY "Entered text in lower case = " TextLine.

Sometimes when you want to process the words in a line of text, especially if you want to recognize the words, you may need to get rid of the punctuation marks. Example 15-4 uses INSPECT..CONVERTING to convert punctuation marks in the text to spaces. UNSTRING is then used to unpack the words from the text.

Example 15-4. Using INSPECT..CONVERTING to Convert Punctuation Marks to Spaces

ACCEPT TextLine
INSPECT TextLine CONVERTING ",.;:?!-_" TO SPACES
MOVE 1 TO UnstrPtr
PERFORM UNTIL EndOfText
   UNSTRING TextLine DELIMITED BY ALL SPACES
            INTO UnpackedWord
            WITH POINTER UnstrPtr
   DISPLAY UnpackedWord
END-PERFORM

The final example (Example 15-5) shows how you can use INSPECT..CONVERTING to implement a simple encoding mechanism. It converts the character 0 to character 5, 1 to 2, 2 to 9, 3 to 8, and so on. Conversion starts when the characters @> are encountered in the string and stops when <@ appears.

Example 15-5. Using INSPECT..CONVERTING to Implement an Encoding Mechanism

WORKING-STORAGE SECTION.
01 TextLine           PIC X(70).
 
01 UnEncodedText      PIC X(10) VALUE "0123456789".
 
01 EncodedText        PIC X(10) VALUE "5298317046".
 
PROCEDURE DIVISION.
Begin.
    DISPLAY "Text : "
          WITH NO ADVANCING
    ACCEPT TextLine
    INSPECT TextLine CONVERTING
        UnEncodedText  TO  EncodedText
        AFTER  INITIAL "@>"
        BEFORE INITIAL "<@"
      
    DISPLAY "Encoded   = " TextLine
    
    INSPECT TextLine CONVERTING
        EncodedText  TO  UnEncodedText
        AFTER  INITIAL "@>"
        BEFORE INITIAL "<@"
        
    DISPLAY "UnEncoded = " TextLine
 
    STOP RUN.

9781430262534_unFig15-05.jpg

String Concatenation

String concatenation involves joining the contents of two or more source strings or partial source strings to create a single destination string. In COBOL, string concatenation is done using the STRING verb. Before I discuss the STRING verb formally, let’s look at some examples to get a feel for what it can do.

The first example concatenates the entire contents of the identifiers String1 and String2 with the literal "LM051" and puts the resulting sting into DestString:

STRING String1, String2, "LM051" DELIMITED BY SIZE
    INTO DestString
END-STRING

The second example concatenates the entire contents of String1, the partial contents of String2 (all the characters up to the first space), and the partial contents of String3 (all the characters up to the word unique) and puts the concatenated string in DestString.

STRING
   String1 DELIMITED BY SIZE
   String2 DELIMITED BY SPACES
   String3 DELIMITED BY "unique"
INTO DestString
END-STRING

The STRING Verb

The metalanguage for the STRING verb is given in Figure 15-6.

9781430262534_Fig15-06.jpg

Figure 15-6. Metalanguage for the STRING verb

The STRING verb moves characters from the source string (SourceString$il) to the destination string (DestString$il). Data movement is from left to right. The leftmost character of the source string is moved to the leftmost position of the destination string, then the next-leftmost character of the source string is moved to the next-leftmost position of the destination string, and so on. Note that no space filling occurs; and unless characters in the destination string are explicitly overwritten, they remain undisturbed.

When a number of source strings are concatenated, characters are moved from the leftmost source string first until either that string is exhausted or the delimiter (Delim$il) is encountered in that string. When transfer from that source string finishes, characters are moved from the next-leftmost source string. This proceeds until either the strings are exhausted or the destination string is full. At that point, the STRING operation finishes.

The following rules apply to the operation of the STRING verb:

  • The ON OVERFLOW clause executes if valid characters remain to be transferred in the source string but the destination string is full.
  • When a WITH POINTER phrase is used, its value determines the starting character position for insertion into the destination string. As each character is inserted into the destination string, the pointer is incremented. When the pointer points beyond the end of the destination string, the STRING statement stops.
  • When the WITH POINTER phrase is used, then before the STRING statement executes, the program must set Pointer#i to an initial value greater than zero and less than the length of the destination string.
  • If the WITH POINTER phrase is not used, operation on the destination field starts from the leftmost position.
  • Pointer#imust be an integer item, and its description must allow it to contain a value one greater than the size of the destination string. For instance, a pointer declared as PIC 9 is too small if the destination string is ten characters long.
  • The DELIMITED BY SIZE clause causes the whole of the sending field to be added to the destination string.
  • Where a literal can be used, you can use a figurative constant (such as SPACES) except for the ALL literal figurative constant.
  • When a figurative constant is used, it is one character in size.
  • The destination item DestString$i must be either an elementary data item without editing symbols or the JUSTIFIED clause.
  • Data movement from a particular source string ends when one of the following occurs:
    • The end of the source string is reached.
    • The end of the destination string is reached.
    • The delimiter is detected.
  • The STRING statement ends when one of the following is true:
    • All the source strings have been processed.
    • The destination string is full.
    • The pointer points outside the string.

String Concatenation Example

Example 15-6 shows how you can build a destination string a piece at a time by executing several separate STRING statements. Each time a STRING statement executes, the current value of StrPtr governs where the characters from the source string are inserted into the destination string.

Example 15-6. STRING Examples Showing How to Use the WITH POINTER Phrase

DATA DIVISION.
WORKING-STORAGE SECTION.
01 DayStr     PIC XX VALUE "5".
01 MonthStr   PIC X(9) VALUE "September".
01 YearStr    PIC X(4) VALUE "2013".
01 DateStr    PIC X(16) VALUE ALL "@".
01 StrPtr     PIC 99.
 
PROCEDURE DIVISION.
Begin.
DISPLAY DateStr
MOVE 1 TO StrPtr
STRING DayStr  DELIMITED BY SPACES
       ","     DELIMITED BY SIZE
       INTO DateStr WITH POINTER StrPtr
END-STRING
DISPLAY DateStr
 
STRING MonthStr DELIMITED BY SPACES
       ","     DELIMITED BY SIZE
       INTO DateStr WITH POINTER StrPtr
END-STRING
DISPLAY DateStr
 
STRING YearStr  DELIMITED BY SIZE
       INTO DateStr WITH POINTER StrPtr
END-STRING
DISPLAY DateStr.

9781430262534_unFig15-06.jpg

String Splitting

String splitting involves chopping a string into a number of smaller strings. In COBOL, string splitting is done using the UNSTRING verb. Before I discuss the UNSTRING verb formally, let’s look at some examples to see what UNSTRING can do.

The first example uses UNSTRING to break a customer name into its three constituent parts: first name, middle name, and surname. For instance, the string “John Joseph Ryan” is broken into the three strings “John”, “Joseph”, and “Ryan”:

UNSTRING CustomerName DELIMITED BY ALL SPACES
    INTO FirstName, SecondName, Surname
END-UNSTRING

The second example breaks an address string (where the parts of the address are separated from one another by commas) into separate address lines. The address lines are stored in a six-element table. Not all addresses have six parts exactly, but you can use the TALLYING clause to discover how many parts there are:

UNSTRING CustAddress DELIMITED BY ","
    INTO AdrLine(1), AdrLine(2), AdrLine(3),
        AdrLine(4), AdrLine(5), AdrLine(6)
    TALLYING IN AdrLinesUsed
END-UNSTRING

The final example breaks a simple comma-delimited record into its constituent parts. Because the fields are not fixed length, they need to be validated for length—and that requires finding out how long each field is. The COUNT IN clause, which counts the number of characters transferred to a particular destination field, is used to determine the actual length of the field:

UNSTRING SupplierRec DELIMITED BY ","
    INTO Supplier-Code    COUNT IN SuppCodeCount
         Supplier-Name    COUNT IN SuppNameCount
         Supplier-Address COUNT IN SuppAdrCount
END-UNSTRING

The UNSTRING Verb

The metalanguage for the UNSTRING verb is given in Figure 15-7.

9781430262534_Fig15-07.jpg

Figure 15-7. Metalanguage for the UNSTRING verb

UNSTRING copies characters from the source string to the destination string until a condition is encountered that terminates data movement. When data movement ends for a particular destination string, the next destination string becomes the receiving area, and characters are copied into it until once again a terminating condition is encountered. Characters are copied from the source string to the destination strings according to the rules for MOVE, with space filling or truncation as necessary.

Strictly speaking, END-UNSTRINGis only required to delimit the scope of the OVERFLOW statement block. You will notice, however, that I have a tendency to use it to indicate the end of every UNSTRING statement. This is just a personal preference.

Data-Movement Termination

When you use the DELIMITED BY clause, data movement from the source string to the current destination string ends when either of the following occurs:

  • A delimiter is encountered in the source string
  • The end of the source string is reached

When the DELIMITED BY clause is not used, data movement from the source string to the current destination string ends when either of these is true:

  • The destination string is full.
  • The end of the source string is reached.

UNSTRING Termination

The UNSTRING statement terminates in the following cases:

  • All the characters in the source string have been examined.
  • All the destination strings have been processed.
  • Some error condition is encountered (such as the pointer pointing outside the source string).

UNSTRING Clauses

As you can see by examining the metalanguage, the operation of UNSTRING is modified by a number of clauses. These clauses affect the operation of UNSTRING as follows:

  • DELIMITED BY: When the DELIMITED BY clause is used, characters are examined in the source string and copied to the current destination string until one of the specified delimiters is encountered in the source string or the end the source string is reached. If there is not enough room in the destination string to take all the characters sent to it from the source string, the remaining characters are truncated/lost. When the delimiter is encountered in the source string, the next destination string becomes current, and characters are transferred into it from the source string. Delimiters are not transferred or counted in CharCounter#i.
  • ON OVERFLOW: When ON OVERFLOW activates, the statement block following it is executed. ON OVERFLOW activates if
    • The unstring pointer (Pointer#i) is not pointing to a character position within the source string when UNSTRING executes (that is, Pointer#i is 0 or is greater than the size of the string).
    • All the destination strings have been processed, but there are still valid unexamined characters in the source string.
  • The statements following NOT ON OVERFLOW are executed if UNSTRING is about to terminate successfully.
  • COUNT IN: The COUNT IN clause is associated with a particular destination string and holds a count of the number of characters passed to the destination string, regardless of whether they were truncated.
  • DELIMITER IN: A DELIMITER IN clause is associated with a particular destination string. HoldDelim$i holds the delimiter that was encountered in the source string. If the DELIMITER IN phrase is used with the ALL phrase, then only one occurrence of the delimiter is moved to HoldDelim$i.
  • TALLYING IN: Only one TALLYING clause can be used with each UNSTRING. It holds a count of the number of destination strings affected by the UNSTRING operation.
  • WITH POINTER: When the WITH POINTER clause is used, the Pointer#i data item holds the position of the next non-delimiter character to be examined in the source string. Pointer#i must be large enough to hold a value one greater than the size of the source string, because when UNSTRING ends, it will be pointing to one character position beyond the end of the string.
  • ALL: When the ALL phrase is used, contiguous delimiters are treated as if only one delimiter had been encountered. If ALL is not used, contiguous delimiters result in spaces being sent to some of the destination strings.

Notes on UNSTRING

Bear the following in mind when you use UNSTRING:

  • Where a literal can be used, any figurative constant can be used except the ALL literal figurative constant.
  • When a figurative constant is used, it is one character long.
  • The delimiter is moved into HoldDelim$i according to the rules for MOVE.
  • The DELIMITER IN and COUNT IN phrases may be specified only if the DELIMITED BY phrase is used.

Language Knowledge Examples

This section presents a number of UNSTRING examples. These are not real-world examples but are rather intended to show how UNSTRING and its clauses operate.

UNSTRING: Demonstrating the COUNT IN Clause

Listing 15-5 demonstrates how to chop a string into separate strings based on a delimiter and how to keep a count of the number of characters transferred to each destination string. Note that DestStr2 is larger than the data copied to it and so is space filled. DestStr3 is too small to hold the characters transferred to it, so they are truncated; but the count still notes how many characters were transferred (08). The count for DestStr4 seems incorrect, but the literal assigned to xString is not long enough to fill it and so it is space filled. When UNSTRING copies “of sweet silent” to DestStr4, it copies these trailing spaces; they can’t all fit into DestStr4 and so are truncated but counted.

Listing 15-5. UNSTRING Example 1

IDENTIFICATION DIVISION.
PROGRAM-ID.  Listing15-5.
AUTHOR.  Michael Coughlan.
 
DATA DIVISION.
WORKING-STORAGE SECTION.
01 xString       PIC X(45) VALUE "When,to the,sessions,of sweet silent".
01 DestinationStrings.
   02 DestStr1   PIC X(4).
   02 DestStr2   PIC X(10).
   02 DestStr3   PIC X(3).
   02 DestStr4   PIC X(18).
 
01 CharCounts.
   02 CCount     PIC 99  OCCURS 4 TIMES.
 
PROCEDURE DIVISION.
Begin.
    UNSTRING xString delimited by ","
        INTO DestStr1 COUNT IN CCount(1)
             DestStr2 COUNT IN CCount(2)
             DestStr3 COUNT IN CCount(3)
             DestStr4 COUNT IN CCount(4)
    END-UNSTRING
              
    DISPLAY DestStr1 " = " CCount(1)
    DISPLAY DestStr2 " = " CCount(2)
    DISPLAY DestStr3 " = " CCount(3)
    DISPLAY DestStr4 " = " CCount(4)
    STOP RUN.

9781430262534_unFig15-07.jpg

UNSTRING: Demonstrating ON OVERFLOW and the Effect of Delimiters

Listing 15-6 contains three UNSTRING examples. Example 2 demonstrates the activation of the ON OVERFLOW clause. Because no delimiter is specified, all the text in DateStr is eligible for transfer; and as each destination item is filled, the next one becomes the current target. There are not enough destination items to take all the data: the remaining characters (“19” and the trailing spaces) are eligible for transfer, but there are no destination strings left to take them. So, ON OVERFLOW activates, and the message “Characters unexamined” is displayed.

Listing 15-6. The ON OVERFLOW Clause and the Effect of Delimiters

IDENTIFICATION DIVISION.
PROGRAM-ID.  Listing15-6.
AUTHOR.  Michael Coughlan.
 
DATA DIVISION.
WORKING-STORAGE SECTION.
01 DateStr       PIC X(15).
 
01 DateRec.
   02 DayStr     PIC XX.
   02 MonthStr   PIC XX.
   02 YearStr    PIC X(4).
 
PROCEDURE DIVISION.
Begin.
*>Unstring example 2
    MOVE "19-08-2012" TO DateStr
    UNSTRING DateStr INTO DayStr, MonthStr, YearStr
          ON OVERFLOW DISPLAY "Characters unexamined"
    END-UNSTRING
    DISPLAY DayStr SPACE MonthStr SPACE YearStr
    DISPLAY "__________________________"
    DISPLAY SPACES
    
*>Unstring example 3
    MOVE "25-07-2013lost" TO DateStr.
    UNSTRING DateStr DELIMITED BY "-"
          INTO DayStr, MonthStr, YearStr
          ON OVERFLOW DISPLAY "Characters unexamined"
    END-UNSTRING.
    DISPLAY DayStr SPACE MonthStr SPACE YearStr
    DISPLAY "__________________________"
    DISPLAY SPACES
    
*>Unstring example 4
    MOVE "30end06end2014" TO DateStr
    UNSTRING DateStr DELIMITED BY "end"
        INTO DayStr, MonthStr, YearStr
        ON OVERFLOW DISPLAY "Characters unexamined"
    END-UNSTRING
    DISPLAY DayStr SPACE MonthStr SPACE YearStr
    
    STOP RUN.

9781430262534_unFig15-08.jpg

Example 3 demonstrates the difference when a delimiter is specified. ON OVERFLOW does not activate in this case because all the characters have been copied to the destination strings. UNSTRING tries to copy “2013lost” into YearStr, but because there is not sufficient room, some of the transferred characters are truncated.

Example 4 demonstrates that the delimiter does not have to be a single character. It can be a word or any other group of characters.

UNSTRING: The Effect of the ALL Delimiter

Listing 15-7 also contains three UNSTRING examples. Example 5 demonstrates the use of the ALL delimiter, which treats successive occurrences of a delimiter as one occurrence. This is contrasted with Example 6, where the same delimiter configuration is used but the ALL phrase is omitted. In this example, each occurrence of the delimiter is treated as separate instance; the result is shown in the following storage schematic.

9781430262534_unFig15-09.jpg

Listing 15-7. The ALL Delimiter and the DELIMITER IN Phrase

IDENTIFICATION DIVISION.
PROGRAM-ID.  Listing15-7.
AUTHOR.  Michael Coughlan.
 
DATA DIVISION.
WORKING-STORAGE SECTION.
01 DateStr       PIC X(15).
 
01 DateRec.
   02 DayStr     PIC XX.
   02 MonthStr   PIC XX.
   02 YearStr    PIC X(4).
 
01 Delims.
   02 HoldDelim OCCURS 3 TIMES PIC X.
 
PROCEDURE DIVISION.
Begin.
*>Unstring example 5
    MOVE "15---07--2013" TO DateStr.
    UNSTRING DateStr DELIMITED BY ALL "-"
       INTO DayStr, MonthStr, YearStr
       ON OVERFLOW DISPLAY "Characters unexamined"
    END-UNSTRING
    DISPLAY DayStr SPACE MonthStr SPACE YearStr
    DISPLAY "__________________________"
    DISPLAY SPACES
    
*>Unstring example 6
    MOVE "15---07--2013" TO DateStr.
    UNSTRING DateStr DELIMITED BY "-"
       INTO DayStr
            MonthStr
            YearStr
       ON OVERFLOW DISPLAY "Characters unexamined"
    END-UNSTRING
    DISPLAY DayStr SPACE MonthStr SPACE YearStr
    DISPLAY "__________________________"
    DISPLAY SPACES
    
*>Unstring example 7
    MOVE "15/07-----2013@" TO DateStr
    UNSTRING DateStr DELIMITED BY "/" OR "@" OR ALL "-"
       INTO DayStr   DELIMITER in HoldDelim(1)
            MonthStr DELIMITER in HoldDelim(2)
            YearStr  DELIMITER in HoldDelim(3)
       ON OVERFLOW DISPLAY "Characters unexamined"
    END-UNSTRING
    DISPLAY HoldDelim(1) " delimits " DayStr
    DISPLAY HoldDelim(2) " delimits " MonthStr
DISPLAY HoldDelim(3) " delimits " YearStr
  
    STOP RUN.

9781430262534_unFig15-10.jpg

Example 7 shows how you can use the DELIMITER IN clause to store a delimiter that causes character transfer to cease for a particular destination field.

String-Splitting Program

The examples so far have shown you aspects of the UNSTRING verb’s operation. Listing 15-8 is a more real-world example. The problem specification is as follows: Write a program that accepts a person’s full name from the user and reduces it to the initials of the first and middle names followed by the surname. For instance, William Henry Ford Power becomes W. H. F. Power.

Listing 15-8. UNSTRING and STRING Used in Combination

IDENTIFICATION DIVISION.
PROGRAM-ID.  Listing15-8.
AUTHOR.  Michael Coughlan.
 
DATA DIVISION.
WORKING-STORAGE SECTION.
01 OldName      PIC X(80).
 
01 TempName.
   02 NameInitial  PIC X.
   02 FILLER       PIC X(19).
    
01 NewName         PIC X(30).
    
01 UnstrPtr        PIC 99.
   88 NameProcessed VALUE 81.
 
01 StrPtr          PIC 99.
 
PROCEDURE DIVISION.
ProcessName.
   DISPLAY "Enter a name - " WITH NO ADVANCING
   ACCEPT OldName
   MOVE 1 TO UnstrPtr, StrPtr
   UNSTRING OldName DELIMITED BY ALL SPACES
      INTO TempName WITH POINTER UnstrPtr
   END-UNSTRING
   PERFORM UNTIL NameProcessed
      STRING NameInitial "." SPACE DELIMITED BY SIZE
         INTO NewName WITH POINTER StrPtr
      END-STRING
      UNSTRING OldName DELIMITED BY ALL SPACES
         INTO TempName WITH POINTER UnstrPtr
      END-UNSTRING
   END-PERFORM
   STRING TempName DELIMITED BY SIZE
         INTO NewName WITH POINTER StrPtr
   END-STRING
   DISPLAY "Processed name = " NewName
   STOP RUN.

Reference Modification

Reference modification is a special COBOL facility that allows you to treat any USAGE IS DISPLAY item as if it were an array of characters but it defines access to the characters in a special way. To access substrings using reference modification, as shown in the metalanguage in Figure 15-8, you must specify the following:

  • The name of the data item (DataItemName) to be referenced
  • The start-character position of the substring (StartPos)
  • The number of characters in the substring (SubStrLength)

9781430262534_Fig15-08.jpg

Figure 15-8. Metalanguage syntax for reference modification

The metalanguage syntax is modified by the following sematic rules:

  • StartPos is the character position of the first character in the substring, and SubStrLength is the number of characters in the substring. StartPos and SubStrLength must each be a positive integer or an expression that evaluates to one.
  • DataItemName can be subscripted and/or qualified.
  • DataItemName can be the alphanumeric value returned by a function.
  • As indicated by the square brackets, SubStrLength may be omitted, in which case the substring from StartPos to the end of the string is assumed.
  • You can use reference modification almost anywhere an alphanumeric data item is permitted.

To get a feel for the way reference modification works, let’s look at some examples. You start with some abstract examples and then see how you can use reference modification in a more practical situation.

The three DISPLAYs in Example 15-7 use reference modification to display substrings of xString. The storage schematic shows how each example extracts the substring from xString:

  • DISPLAY xString(11:5) displays a substring of five characters starting at the position of the eleventh character.
  • DISPLAY xString(17:SubStrSize) demonstrates that you can use a numeric data item in place of the literal and displays eight characters starting with the seventeenth.
  • DISPLAY xString(StartPos:) shows that when you omit SubStrLength, the substring consists of the characters from the start character to the end of the string.

Example 15-7. Extracting a Substring Using Reference Modification

9781430262534_unFig15-11.jpg

The two DISPLAY statements in Example 15-8 demonstrate the other ways of defining the substring. The MOVE statement shows how you can use reference modification to insert characters into a string:

  • DISPLAY xString(12:SubstrSize - 5) shows that you can use an arithmetic expression as SubStrLength.
  • DISPLAY FUNCTION UPPER-CASE(xString)(Startpos - 7 : 4) demonstrates that you can apply reference modification to a function result. It also shows that StartPos may be an arithmetic expression.
  • MOVE " text insert " TO XString(31:6) demonstrates how to use reference modification to insert text into a string. Note that the SubStrLength given specifies the number of characters in the string that will be overwritten. For instance, in this example only 6 characters are overwritten, even though there are 13 characters in the moved text.

Example 15-8. Applying Reference Modification to an Alphanumeric String

9781430262534_unFig15-12.jpg

Example 15-9 shows how to apply reference modification to the numeric data item nString and the edited numeric data item enString:

  • In nString, reference modification is used to display the dollars and cents parts of a numeric value.
  • In enString, reference modification is used to overwrite the check-security asterisks with the @ symbol. Note that ALL "@" is a figurative constant that is used to fill the four character positions specified by the reference modifier.

Example 15-9. Applying Reference Modification to Numeric Data Items

9781430262534_unFig15-13.jpg

Intrinsic Functions

User-defined functions of one sort or another are a standard part of many programming languages. The ANS 85 version of COBOL does not support user-defined functions, but it has introduced a library of standard functions called intrinsic functions.

Intrinsic functions fall into three broad categories: date functions, numeric functions, and string functions. Because this chapter is about string manipulation, I discuss the string functions in some detail. I also look at the date functions and some of the numeric functions that I have found particularly useful. For the remaining functions you should consult your implementer manual.

Using Intrinsic Functions

Like a function in another language, an intrinsic function is replaced by the function result in the position where the function occurs. Wherever you can use a literal, you can use an intrinsic function that returns a result of the same type.

An intrinsic function consists of three parts:

  • The start of the function is signalled by the FUNCTION keyword.
  • The FUNCTION keyword is followed by the name of the function.
  • The name of the function is immediately followed by a bracketed list of parameters or arguments.
  • The intrinsic function template is
    FUNCTION FunctionName(Parameter)

    where FunctionName is the name of the function and Parameter is one or more parameters/arguments supplied to the function.

For instance, the following examples show how to use intrinsic functions in a number of different contexts. In some cases, the result of the function is assigned to a data item; in others (as in the first example), it is used directly in the place of a literal or data item. Sometimes the parameters/arguments are numeric, and other times they are alphabetic. Some functions use only one parameter, others take multiple parameters, and still others do not require a parameter:

DISPLAY FUNCTION UPPER-CASE("this will be in upper case").
MOVE FUNCTION ORD("A") TO OrdPos
MOVE FUNCTION RANDOM(SeedValue) TO RandomNumber
MOVE FUNCTION RANDOM TO NextRndNumber
COMPUTE Result = FUNCTION MOD(25, 10)
MOVE FUNCTION ORD-MAX(12 23 03 78 65) TO MaxOrdPos

When you use intrinsic functions, you must bear in mind a number of things:

  • Intrinsic functions return a result of Alphanumeric, Numeric (includes integer), or Integer (does not allow the decimal point).
  • The result returned by an alphanumeric function has an implicit usage of DISPLAY. This is why the result returned by FUNCTION UPPER-CASE may be used directly with the DISPLAY verb.
  • Intrinsic functions that return a numeric value are always considered to be signed and can only be used in an arithmetic expression or a MOVE statement.
  • Intrinsic functions that return a non-integer numeric value can’t be used where an integer value is required.

String Functions

Table 15-1 lists the intrinsic functions that allow manipulation of strings. The table uses the parameter name to indicate the type of the parameter required, as follows:

Alpha indicates Alphanumeric.

Num indicates any Numeric.

PosNum indicates a positive Numeric.

Int indicates any Integer.

PosInt indicates a positive Integer.

Any indicates that the parameter may be of any type.

Table 15-1. String Functions, Grouped by Type of Operation

Function Name

Result Type

Comment

CHAR(PosInt)

Alphanumeric

Returns the character in the collating sequence at ordinal position PosInt.

ORD(Alpha)

Integer

Returns the ordinal position of character Alpha.

ORD-MAX({Any}...)

Integer

Returns the ordinal position of whichever parameter in the list has the highest value. All parameters must be of the same type. The parameter list may be replaced by an array. If an array is used, the reserved word ALL may be used as the array subscript to indicate all the elements of the array.

ORD-MIN({Any}...)

Integer

Returns the ordinal position of whichever parameter in the list has the lowest value. All parameters must be of the same type. The parameter list may be replaced by an array.

LENGTH(Any)

Integer

Returns the number of characters in the data item Any. Not as useful as it sounds. It returns the value given in the item’s picture clause. For instance, Length(StrItem) returns 18 if the picture clause is PIC X(18).

REVERSE(Alpha)

Alphanumeric

Returns a character string with the characters in Alpha reversed.

LOWER-CASE(Alpha)

Alphanumeric

Returns a character string with the characters in Alpha changed to their lowercase equivalents.

UPPER-CASE(Alpha)

Alphanumeric

Returns a character string with the characters in Alpha changed to their uppercase equivalents.

If a function takes a parameter list (indicated by {Any}... in the function definition), the parameter list may be replaced by an array. The reserved word ALL is used as the array subscript to indicate all the elements of the array.

For instance, the ORD-MAX function may take a parameter list, or you can use an array as the parameter, as shown in the following example:

MOVE FUNCTION ORD-MAX(12 23 03 78 65) TO OrdPos
or
MOVE FUNCTION ORD-MAX(IntElement(ALL)) TO OrdPos

String Intrinsic Function Examples

Listing 15-9 solves no specific problem. It merely consists of a number of intrinsic function examples.

Listing 15-9. String Manipulation with Intrinsic Functions

IDENTIFICATION DIVISION.
PROGRAM-ID.  Listing15-9.
AUTHOR.  Michael Coughlan.
*> Intrinsic Function examples
 
DATA DIVISION.
WORKING-STORAGE SECTION.
01 OrdPos        PIC 99.
 
01 TableValues   VALUE "123411457429130938637306851419883522700467".
    02 Num       PIC 99 OCCURS 21 TIMES.
    
01 idx           PIC 9.
    
01 xString       PIC X(45)
                 VALUE "This string is 33 characters long".
              
01 xWord         PIC X(10).
    
01 CharCount     PIC 99.
 
01 TextLength    PIC 99.
        
PROCEDURE DIVISION.
Begin.
*> eg1. In the ASCII collating sequence W has a code of 87 but an ordinal
*> position of 88.
   DISPLAY "eg1. The character in position 88 is = " FUNCTION CHAR(88)
  
*> eg2. Using ordinal positions to spell out my name
   DISPLAY SPACES
   DISPLAY "eg2. My name is " FUNCTION CHAR(78)  FUNCTION CHAR(106)
                              FUNCTION CHAR(108) FUNCTION CHAR(102)
 
*> eg3. Finding the ordinal position of a particular character
   DISPLAY SPACES
   MOVE FUNCTION ORD("A") TO OrdPos
   DISPLAY "eg3. The ordinal position of A is = " OrdPos
 
*> eg4. Using CHAR and ORD in combination to display the sixth letter of thealphabet
   DISPLAY SPACES
   DISPLAY "eg4. The sixth letter of the alphabet is "
           FUNCTION CHAR(FUNCTION ORD("A") + 5)
            
*> eg5. Finding the position of the highest value in a list of parameters
   DISPLAY SPACES
   MOVE FUNCTION ORD-MAX("t" "b" "x" "B" "4" "s" "b") TO OrdPos
   DISPLAY "eg5. Highest character in the list is at pos " OrdPos
  
*> eg6. Finding the position of the lowest value in a list of parameters
   DISPLAY SPACES
   MOVE FUNCTION ORD-MIN("t" "b" "x" "B" "4" "s" "b") TO OrdPos
   DISPLAY "eg6. Lowest character in the list is at pos " OrdPos
    
*> eg7.Finding the position of the highest value in a table
   DISPLAY SPACES
   MOVE FUNCTION ORD-MAX(Num(ALL)) TO OrdPos
   DISPLAY "eg7. Highest value in the table is at pos "
           OrdPos
    
*> eg8. Finding the highest value in a table
   DISPLAY SPACES
   DISPLAY "eg8. Highest value in the table = " Num(FUNCTION ORD-MAX(Num(ALL)))
    
*> eg9. Finds the top three values in a table by finding the top
*> overwrites it with zeros to remove it from consideration
*> then finds the next top and so on
   DISPLAY SPACES
   DISPLAY "eg9."
   PERFORM VARYING idx FROM 1 BY 1 UNTIL idx > 3
      DISPLAY "TopPos " idx " = " Num(FUNCTION ORD-MAX(Num(ALL)))
      MOVE ZEROS TO Num(FUNCTION ORD-MAX(Num(ALL)))
   END-PERFORM
    
*> eg10. Finding the length of a string
   DISPLAY SPACES
   DISPLAY "eg10. The length of xString is " FUNCTION LENGTH(xString) " characters"
    
*> eg11. Finding the length of the text in a string
   DISPLAY SPACES
   INSPECT FUNCTION REVERSE(xString) TALLYING CharCount
          FOR LEADING SPACES
   COMPUTE TextLength = FUNCTION LENGTH(xString) - CharCount
   DISPLAY "eg11. The length of text in xString is " TextLength " characters"
 
*> eg12. Discover if a word is a palindrome
   DISPLAY SPACES
   DISPLAY "eg12."
   MOVE ZEROS TO CharCount
   DISPLAY "Enter a word - " WITH NO ADVANCING
   ACCEPT xWord
   INSPECT FUNCTION REVERSE(xWord)        TALLYING CharCount FOR LEADING SPACES
   IF FUNCTION UPPER-CASE(xWord(1:FUNCTION LENGTH(xWord) - CharCount)) EQUAL TO
      FUNCTION UPPER-CASE(FUNCTION REVERSE(xWord(1:FUNCTION LENGTH(xWord)- CharCount)))
      DISPLAY xWord " is a palindrome"
     ELSE
      DISPLAY xWord " is not a palindrome"
   END-IF
   STOP RUN.

9781430262534_unFig15-14.jpg

9781430262534_unFig15-15.jpg

9781430262534_unFig15-16.jpg

Program Explanation

These examples build on one another so that although the early ones are straightforward, the later ones are somewhat more complex and require explanation. One thing you will realize from these examples is that COBOL’s intrinsic functions are not as effective as functions in other languages. For one thing, the requirement to precede every intrinsic function with the word FUNCTION makes nesting functions cumbersome. For another, the function library is incomplete. You often have to use INSPECT, UNSTRING, and STRING to compensate for omissions. On the other hand, not being able to nest functions deeply may be a good thing. For instance, eg12 would require more typing but would be easier to understand and debug if coded as follows:

*>eg12. Discover if a word is a palindrome
  DISPLAY SPACES
  DISPLAY "eg12."
  MOVE ZEROS TO CharCount
  DISPLAY "Enter a word - " WITH NO ADVANCING
  ACCEPT xWord
 
  INSPECT FUNCTION REVERSE(xWord) TALLYING CharCount
          FOR LEADING SPACES
 
  MOVE FUNCTION UPPER-CASE(xWord) TO xWord
 
  COMPUTE TextLength = FUNCTION LENGTH(xWord) - CharCount
  
  IF xWord(1:TextLength) EQUAL TO FUNCTION REVERSE(xWord(1:TextLength))
     DISPLAY xWord " is a palindrome"
    ELSE
     DISPLAY xWord " is not a palindrome"
  END-IF

Let’s look at how these examples work:

  • eg1 uses the CHAR function to return the eighty-eighth character (W) of the ASCII collating sequence. In most languages, you would be required to supply the ASCII value, whereas in COBOL you supply the ordinal position. If you are used to dealing with ASCII values, the ordinal position will seem to be off by one: for example, the ASCII value of W is 87.
  • eg2 uses the CHAR function to display the name Mike.
  • eg3 demonstrates that the ORD function is the opposite of CHAR. Whereas CHAR returns the character at the ordinal position supplied, ORD returns the ordinal position of the character supplied. As you no doubt know, A is ASCII value 65, but its ordinal position is returned as 66.
  • eg4 is the first use of nested functions. CHAR and ORD are used in combination. ORD("A") returns the position of the first letter in the alphabet, and the sixth is five letters on from that.
  • eg5 and eg6 demonstrate using the ORD-MAX function to find the position of the highest value in the supplied list.
  • eg7 demonstrates how to use ORD-MAX to find the position of the highest value in a table.
  • eg8 uses nesting and ORD-MAX to find the highest value in a table.
  • Eg9 uses the techniques demonstrated in eg7 and eg8 to find the top three values in a table. Each time through the loop, the highest value is found, displayed, and then overwritten with zeros to remove it from consideration the next time around. This solution does have the drawback of destroying some of the values in the table.
  • eg10 and eg11: one problem COBOL has is that alphanumeric data items are fixed in length, so if the text does not fill the data item, the data item is space-filled to the right. For certain kinds of processing, this is a problem. eg10 shows how to get the length of a data item, and eg11 shows how to use the length of the data item to get the length of the text in that data item.
  • eg12 brings together much of the material covered in this chapter. The task is to discover whether a word entered by the user is a palindrome (reads the same backward as forward). As I noted earlier, the nesting of functions makes the program much more difficult to understand.

    This is the algorithm: using the technique of eg11, find the actual length of the word. Use reference modification to select only the word from the data item xWord, change it to uppercase, and compare it to a reversed, uppercased, version of the word. If they are equal, then the word is a palindrome.

DATE Functions

Date functions are a homogeneous group of functions that are often very useful. Table 15-2 lists the functions. The table uses the same parameter type indicators as Table 15-1 (Alpha, Num, PosNum, Int, PosInt, Any).

Table 15-2. Date Functions

Function Name

Result Type

Comment

CURRENT-DATE

Alphanumeric

Returns a 21-character string representing the current date and time, and the difference between the local time and Greenwich Mean Time. The format of the string is YYYYMMDDHHMMsshhxhhmm, where YYYY is the year, MM is the month, DD is the day of the month, HH is the hour (24-hour time), MM is the minutes, ss is the seconds, and hh is the hundredths of a second. In addition, xhhmm is the number of hours and minutes the local time is ahead of or behind GMT ( x = + or - or 0). If x = 0, the hardware cannot provide this information.

DATE-OF-INTEGER(PosInt)

Integerof the form YYYYMMDDD

Converts the integer date PosInt (representing the number of days that have passed since Dec 31, 1600 in the Gregorian calendar) to a standard date. Returns the standard date in the form YYYYMMDD. This function can be useful when you are calculating the number of days between two dates.

DAY-OF-INTEGER(PosInt)

Integer of the form YYYYDDD

Converts the integer date PosInt(representing the number of days that have passed since Dec 31, 1600 in the Gregorian calendar) to a standard date of the form YYYYDDD (sometimes called a Julian date).

INTEGER-OF-DATE(PosInt)

Integer

Converts the standard date PosInt (in the form YYYYMMDD) into the equivalent integer date. If PosInt is not a valid date, then zeros are returned.

INTEGER-OF-DAY(PosInt)

Integer

Converts the standard date PosInt (in the form YYYYDDD—a Julian date) into the equivalent integer date.

WHEN-COMPILED

Integer

Returns the date and time the program was compiled. Uses the same format as CURRENT-DATE.

DATE Examples

Like the previous listing, Listing 15-10 solves no specific problem but is instead a collection of examples that show how to use intrinsic functions to manipulate dates.

Listing 15-10. Using Intrinsic Functions to Manipulate Dates

IDENTIFICATION DIVISION.
PROGRAM-ID.  Listing15-10.
AUTHOR.  Michael Coughlan.
*> Date Functions
 
DATA DIVISION.
WORKING-STORAGE SECTION.
01 DateAndTimeNow.
    02 DateNow.
       03 YearNow              PIC 9(4).
       03 MonthNow             PIC 99.
       03 DayNow               PIC 99.
    02 TimeC.
       03 HourNow              PIC 99.
       03 MinNow               PIC 99.
       03 SecNow               PIC 99.
       03 FILLER               PIC 99.
    02 GMT.
       03 GMTDiff              PIC X.
          88 GMTNotSupported  VALUE "0".
       03 GMTHours             PIC 99.
       03 GMTMins              PIC 99.
 
01  BillDate                   PIC 9(8).
01  DateNowInt                 PIC 9(8).
01  DaysOverdue                PIC S999.
01  NumOfDays                  PIC 999.
 
01  IntFutureDate              PIC 9(8).
01  FutureDate                 PIC 9(8).
01  DisplayDate REDEFINES FutureDate.
    02 YearD                   PIC 9999.
    02 MonthD                  PIC 99.
    02 DayD                    PIC 99.
    
01 DateCheck                   PIC 9(8) VALUE ZEROS.
   88 DateIsNotValid           VALUE ZEROS.
   88 DateIsValid              VALUE 1 THRU 99999999.
    
PROCEDURE DIVISION.
Begin.
*> eg1 This example gets the current date and displays
*> the constituent parts.
   DISPLAY "eg1 - get the current date"
   MOVE FUNCTION CURRENT-DATE TO DateAndTimeNow
   DISPLAY "Current Date is "
           MonthNow "/" DayNow "/" YearNow
   DISPLAY "Current Time is "
            HourNow ":" MinNow ":" SecNow
   IF GMTNotSupported
       DISPLAY "This computer cannot supply the time"
       DISPLAY "difference between local and GMT."
     ELSE
       DISPLAY "The local time is - GMT "
                 GMTDiff GMTHours ":" GMTMins
   END-IF.
 
*> eg2. In this example bills fall due 30 days
*> from the billing date.
   DISPLAY SPACES
   DISPLAY "eg2 - find the difference between two dates"
   DISPLAY "Enter the date of the bill (yyyymmdd) - " WITH NO ADVANCING
   ACCEPT BillDate
   MOVE DateNow TO DateNowInt
   COMPUTE DaysOverDue =
           (FUNCTION INTEGER-OF-DATE(DateNowInt))
         - (FUNCTION INTEGER-OF-DATE(BillDate) + 30)
 
   EVALUATE TRUE
      WHEN DaysOverDue > ZERO
           DISPLAY "This bill is overdue."
      WHEN DaysOverDue = ZERO
           DISPLAY "This bill is due today."
      WHEN DaysOverDue < ZERO
           DISPLAY "This bill is not yet due."
   END-EVALUATE
 
*> eg3. This example displays the date NumOfDays days
*> from the current date
   DISPLAY SPACES
   DISPLAY "eg3 - find the date x days from now"
   DISPLAY "Enter the number of days - " WITH NO ADVANCING
   ACCEPT NumOfDays
   COMPUTE IntFutureDate = FUNCTION INTEGER-OF-DATE(DateNowInt) + NumOfDays + 1
   MOVE FUNCTION DATE-OF-INTEGER(IntFutureDate) TO FutureDate
   DISPLAY "The date in " NumOfDays " days time will be "
            MonthD "/" DayD "/" YearD
            
*> eg4. This takes advantage of the fact that DATE-OF-INTEGER
*> requires a valid date to do some easy date validation
    
   DISPLAY SPACES
   DISPLAY "eg4 - validate the date"
   PERFORM WITH TEST AFTER UNTIL DateIsValid
      DISPLAY "Enter a valid date (yyyymmdd) - " WITH NO ADVANCING
      ACCEPT DateNowInt
      COMPUTE DateCheck = FUNCTION INTEGER-OF-DATE(DateNowInt)
      IF DateIsNotValid
         DISPLAY DateNowInt " is not a valid date"
         DISPLAY SPACES
      END-IF
   END-PERFORM
   DISPLAY "Thank you! " DateNowInt " is a valid date."
 
   STOP RUN.

9781430262534_unFig15-17.jpg

DATE Program Explanation

Most of these examples are straightforward and require little explanation. Only eg2 and eg4 should present any difficulty:

  • eg2 calculates the difference between the due date (bill date + 30) and today’s date and, by subtracting one from the other, determines whether the bill is overdue (more than 30 days old).
  • eg4 invokes the INTEGER-OF-DATE function for the sole purpose of checking whether the date is valid. If an invalid date is supplied to INTEGER-OF-DATE, the function returns zeros.

Summary

This chapter introduced COBOL string manipulation. You discovered how to use INSPECT to count, convert, and replace characters in a string. You saw how to use the STRING verb to concatenate strings and UNSTRING to split a string into substrings. In addition to learning the basics of the string-handling verbs, you saw how to augment their capabilities by using reference modification and intrinsic functions.

All the examples you have examined so far have been small, stand-alone programs. But in a large COBOL system, the executables usually consist of a number of programs, separately compiled and linked together to produce a single run unit. In the next chapter, you learn how to use contained and external subprograms to create a single run unit from a number of COBOL programs. COBOL subprograms introduce a number of data-declaration issues, so Chapter 16 also examines the COPY verb and the IS GLOBAL and IS EXTERNAL clauses.

LANGUAGE KNOWLEDGE EXERCISES

Ah! Exercise time again. Now, where did you put your 2B pencil?

Q1  Assume that for each INSPECT statement,StringVar1 has the value shown in the Ref row of the following table. Show what value StringVar1 holds after each INSPECT statement is executed:

  1. INSPECT StringVar1 REPLACING LEADING "W" BY "6"
  2. INSPECT StringVar1 REPLACING ALL "W" BY "7"         AFTER INITIAL "Z" BEFORE INITIAL "Q"
  3. INSPECT StringVar1 REPLACING ALL "WW" BY "me" BEFORE INITIAL "ZZ"
  4. INSPECT StringVar1 CONVERTING "WZQ" TO "abc"

9781430262534_unFig15-18.jpg

Q2  Assume that for each STRING statement, StringVar2 has the value shown in the Ref row of the following table. Show what value StringVar2 holds after each STRING statement is executed:

01 Source1   PIC X(10) VALUE "the grass".
01 Source2   PIC X(6)  VALUE "is ris".
01 StrPtr    PIC 99    VALUE 3.

  1. STRING Source2 DELIMITED BY SPACES
           SPACE DELIMITED BY SIZE
           Source1 DELIMITED BY SIZE
           INTO StringVar2
  2. STRING SPACE, "See" DELIMITED BY SIZE
           Source1 DELIMITED BY SPACES
           INTO StringVar2 WITH POINTER StrPtr

9781430262534_unFig15-19.jpg

Q3  A four-line poem is accepted into StringVar3 as a single line of text. Each line of the poem is separated from the others by a comma. Using the declarations that follow, write an UNSTRING statement to unpack the poem into individual poem lines and then display each poem line as well the number of characters in the line. For instance, given the poem

"I eat my peas with honey,I've done it all my life,It makes the peas taste funny,But it keeps them on the knife,"

Display

24 - I eat my peas with honey
24 – I've done it all my life
29 - It makes the peas taste funny
30 - But it keeps them on the knife
01 StringVar3        PIC X(120).
01 PoemLine OCCURS 4 TIMES.
   02 PLine          PIC X(40)
   02 CCount         PIC 99.

Q4  Given these strings, write what will be displayed by the following DISPLAY statement:

01  Str1   PIC X(25)   VALUE "I never saw a purple cow".
01  Str2   PIC X(25)   VALUE "I never hope to see one".

DISPLAY Str3((36 - 12) + 1:)
DISPLAY Str1(1:2) Str2(9:5) Str2(1:7) Str2(16:4) Str1(12:)

______________________________________________________________

Q5  Given the following string description, write what will be displayed by the following DISPLAY statement:

01 Str3       PIC X(36) VALUE "abcdefghijklmnopqrstuvwxyz0123456789".

DISPLAY Str3((36 - 12) + 1:)

______________________________________________________________

Q6  Given the following ACCEPT statement, using INSPECT, reference modification, and intrinsic functions, write a set of statements to discover the actual size of the string entered and store it in StrSize. Hint: The actual string is followed by trailing spaces:

01 Str4    PIC X(60).
01 StrSize PIC 99.

ACCEPT Str4.

___________________________________________________________________

___________________________________________________________________

___________________________________________________________________

___________________________________________________________________

___________________________________________________________________

Q7  Given Str4 and the ACCEPT statement in Q6, write statements to trim any leading spaces from the string entered and then store the trimmed string back in Str4.

___________________________________________________________________

___________________________________________________________________

___________________________________________________________________

___________________________________________________________________

___________________________________________________________________

___________________________________________________________________

LANGUAGE KNOWLEDGE EXERCISES: ANSWERS

Q1  Assume that for each INSPECT statement, StringVar1 has the value shown in the Ref row of the following table. Show what value StringVar1 holds after each INSPECT statement is executed:

  1. INSPECT StringVar1 REPLACING LEADING "W" BY "6"
  2. INSPECT StringVar1 REPLACING ALL "W" BY "7"

          AFTER INITIAL "Z" BEFORE INITIAL "Q"

  3. INSPECT StringVar1 REPLACING ALL "WW" BY "me" BEFORE INITIAL "ZZ"
  4. INSPECT StringVar1 CONVERTING "WZQ" TO "abc"

9781430262534_unFig15-20.jpg

Q2  Assume that for each STRING statement, StringVar2 has the value shown in the Ref row of the following table. Show what value StringVar2 holds after each STRING statement is executed:

01 Source1   PIC X(10) VALUE "the grass".
01 Source2   PIC X(6)  VALUE "is ris".
01 StrPtr    PIC 99    VALUE 3.

  1. STRING Source2 DELIMITED BY SPACES
           SPACE DELIMITED BY SIZE
           Source1 DELIMITED BY SIZE
           INTO StringVar2
    STRING SPACE, "See" DELIMITED BY SIZE
           Source1 DELIMITED BY SPACES
           INTO StringVar2 WITH POINTER StrPtr

9781430262534_unFig15-21.jpg

Q3  A four-line poem is accepted into StringVar3 as a single line of text. Each line of the poem is separated from the others by a comma. Using the declarations that follow, write an UNSTRING statement to unpack the poem into individual poem lines and then display each poem line as well the number of characters in the line. For instance, given the poem

"I eat my peas with honey,I've done it all my life,It makes the peas taste funny,But it keeps them on the knife,"

Display

24 - I eat my peas with honey
24 – I've done it all my life
29 - It makes the peas taste funny
30 - But it keeps them on the knife

01 StringVar3        PIC X(120).
01 PoemLine OCCURS 4 TIMES.
   02 PLine          PIC X(40)
   02 CCount         PIC 99.
UNSTRING StringVar3 DELIMITED BY "," INTO
         PLine(1) COUNT IN CCount(1)
         PLine(2) COUNT IN CCount(2)
         PLine(3) COUNT IN CCount(3)
         PLine(4) COUNT IN CCount(4)
END-UNSTRING

Q4  Given these strings, write what will be displayed by the following DISPLAY statement:

01  Str1   PIC X(25)   VALUE "I never saw a purple cow".
01  Str2   PIC X(25)   VALUE "I never hope to see one".

DISPLAY Str3((36 - 12) + 1:)
DISPLAY Str1(1:2) Str2(9:5) Str2(1:7) Str2(16:4) Str1(12:)

I hope I never see a purple cow

Q5  Given the following string description, write what will be displayed by the following DISPLAY statement:

01 Str3       PIC X(36) VALUE "abcdefghijklmnopqrstuvwxyz0123456789".

DISPLAY Str3((36 - 12) + 1:)
yz0123456789

Q6  Given the following ACCEPT statement, using INSPECT, reference modification, and intrinsic functions, write a set of statements to discover the actual size of the string entered and store it in StrSize. Hint: The actual string is followed by trailing spaces:

01 Str4         PIC X(60).
01 StrSize      PIC 99.
01 NumOfChars   PIC 99.

ACCEPT Str4.

ACCEPT Str4.
INSPECT FUNCTION REVERSE(Str4) TALLYING NumOfChars
          FOR LEADING SPACES
COMPUTE StrSize = (60 - NumOfChars)
DISPLAY Str4(1:StrSize) ": is " StrSize " characters in size."

Q7  Given Str4 and the ACCEPT statement in Q6, write statements to trim any leading spaces from the string entered and then store the trimmed string back in Str4.

DISPLAY "Old string is - " Str4
MOVE 1 TO NumOfChars
INSPECT Str4 TALLYING NumOFChars FOR LEADING SPACES
MOVE Str4(NumOfChars :) TO Str4
DISPLAY "New string is - " Str4

..................Content has been hidden....................

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