389
Chapter 15 ■ String Manipulation
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
390
Chapter 15 ■ String Manipulation
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
391
Chapter 15 ■ String Manipulation
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.
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.
392
Chapter 15 ■ String Manipulation
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"
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
393
Chapter 15 ■ String Manipulation
2. STRING SPACE, "See" DELIMITED BY SIZE
Source1 DELIMITED BY SPACES
INTO StringVar2 WITH POINTER StrPtr
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:)
______________________________________________________________
394
Chapter 15 ■ String Manipulation
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"
395
Chapter 15 ■ String Manipulation
4. INSPECT StringVar1 CONVERTING "WZQ" TO "abc"
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
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
396
Chapter 15 ■ String Manipulation
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
397
Chapter 16
Creating Large Systems
All the programs you have seen so far in this book have been small stand-alone programs. But a large software system is not usually written as a single monolithic program. Instead, it consists of a main program and many independently compiled subprograms, linked together to form one executable run-unit. In COBOL, a program that is invoked from another program is called a subprogram. In other languages, these might be called procedures or methods.
This chapter shows you how to create a software system that consists of a number of programs linked together into one executable run-unit. You see how to create contained (internal) and external subprograms and how to use the CALL verb to pass control to them. You discover how to pass data to a subprogram through its parameter list, and you learn about state memory and how to create subprograms that exhibit state memory and subprograms that do not. Because COBOL subprograms introduce a number of data-declaration issues, this chapter also examines the COPY verb and the IS GLOBAL and IS EXTERNAL clauses.
Subprograms and the COPY Verb
Prior to the ANS 74 version, a large software system written in COBOL consisted of a series of large monolithic programs that ran under the control of a Job Control Language. Each program in the series did a piece of work and then passed the resulting data to the next program through the medium of files. The Job Control Language controlled the order of execution of the programs and provided access to the required files. For instance, a validation program might validate the data in a file to create a validated file that was then passed to the next
program for processing.
The ANS 74 version of COBOL introduced external subprograms and the CALL and COPY verbs. These changes
allowed you to create software systems that consisted of the following:
• A main program
• Record, file, and table descriptions imported from a central source text library
• A number of independently compiled external subprograms
These elements were linked together to form one executable run-unit.
The ANS 85 version of COBOL improved on this by introducing the concept of contained subprograms. These subprograms are called contained because their source code is contained within the source code of the main program.
Contained subprograms are closed subroutines. They are very similar to the procedures or methods found in other languages. As you will discover, OO-COBOL methods are so similar to contained subprograms that once you have learned how to create one, the other requires little additional instruction.
It is easy to see how a system that consists of a main program and its contained subprograms can be compiled to create one executable image. It is perhaps not so obvious how a system that consists of a number of external subprograms, all independently compiled at different times, can be made into a single executable.
To create a single executable from a number of independently compiled programs, the object code (binary
compiled code) of the main program and the subprograms must be bound together by a special program called a linker. One purpose of the linker is to resolve the subprogram names (given in the PROGRAM-ID clause) into actual 399
Chapter 16 ■ Creating Large SyStemS
physical addresses so that the computer can find a particular subprogram when it is invoked. Nowadays many software development environments hide the linker step in this traditional sequence:
source code (.cbl) -> compiler -> object code (.obj) -> linker -> executable code (.exe)
A system that consists of a main program and linked subprograms requires a mechanism that allows one
Michael Coughlan Page 48