CHAPTER 16

image

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 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 program to invoke another and to pass data to it. In many programming languages, the procedure or function call serves this purpose. In COBOL, the CALL verb is used to invoke one program from another.

The CALL Verb

The CALL verb is used to transfer control (program execution) to an external, independently compiled subprogram or a contained subprogram. When the subprogram terminates, control reverts to the statement after CALL. The metalanguage for the CALL verb is given in Figure 16-1.

9781430262534_Fig16-01.jpg

Figure 16-1. Metalanguage for the CALL verb

Some notes relating to the metalanguage follow:

  • BY REFERENCE and BY CONTENT are parameter-passing mechanisms. BY REFERENCE is the default and so is sometimes omitted (hence the square brackets).
  • If the called program has not been linked (does not exist in the executable image), the statements following ON EXCEPTION execute. Otherwise, the program terminates abnormally.
  • If the CALL passes parameters, then the called subprogram must have a USING phrase after the PROCEDURE DIVISION header and a LINKAGE SECTION to describe the parameters that are passed.
  • The CALL statement may only have a USING phrase if the PROCEDURE DIVISION header of the called subprogram also has a USING phrase.
  • Both USING phrases must have the same number of parameters.
  • Unlike some languages, COBOL does not check the type of the parameters passed to a called subprogram. It is your responsibility to make sure that only parameters of the correct type and size are passed.
  • As shown in Figure 16-2, the parameters passed from the calling program to the called subprogram correspond by position, not by name. That is, the first parameter in the USING phrase of the CALL corresponds to the first parameter in the USING phase of the called program, and so on.

9781430262534_Fig16-02.jpg

Figure 16-2. CALL parameters correspond by position not name

  • Implementers often extend CALL by introducing BY VALUE parameter passing and by including a GIVING phrase. These are nonstandard extensions.

Parameter-Passing Mechanisms

As you can see from the metalanguage in Figure 16-1, the CALL verb has two parameter-passing mechanisms: BY REFERENCE and BY CONTENT. You should use BY REFERENCE only when the called subprogram needs to pass data back to the caller. You should always use BY CONTENT when data needs to be passed to, but not received from, the called program.

It is a principle of good program design that you should not expose a subprogram to more data than it needs in order to work. If you pass your data BY REFERENCE, the possibility exists that it may be corrupted by the called subprogram. When you pass data BY CONTENT, there is no possibility of that happening.

Figure 16-3 and Figure 16-4 show how each of these mechanisms works.

9781430262534_Fig16-03.jpg

Figure 16-3. The CALL..BY REFERENCE parameter-passing mechanism

9781430262534_Fig16-04.jpg

Figure 16-4. The CALL..BY CONTENT parameter-passing mechanism

CALL..BY REFERENCE

When data is passed BY REFERENCE, the address of the data item is supplied to the called subprogram (see Figure 16-3). Therefore, any changes made to the data item in the subprogram are also made to the data item in the main program, because both items refer to the same memory location.

CALL..BY CONTENT

When a parameter is passed BY CONTENT, a copy of the data item is made, and the address of the copy is supplied to subprogram (see Figure 16-4). Any changes made to the data item in the subprogram affect only the copy.

Subprograms

I have said that a subprogram is just a program that is invoked by another program rather than by the user/operator. In most ways, this is true. A subprogram may have all the divisions, sections, and paragraphs that a program has, but subprograms may also have additional sections and phrases. In addition, because it is contained within the source text of a containing program, a contained subprogram is not quite the same as an external subprogram (one whose source code is in a document separate from the main program source).

Example 16-1 is a template for a subprogram that shows the additional sections and clauses in bold. The subprogram in Example 16-1 might be invoked with a CALL statement such as this:

CALL "ValidateCheckDigit" USING BY CONTENT StudentId
                                BY REFERENCE CKD-Result

Note that the CALL uses a literal value to identify the subprogram being invoked and that therefore the name is enclosed in quotes. This is the usual way a subprogram is invoked, because when you write a program, you usually know which subprogram you want to call. If you wanted to choose dynamically which program to call, you would use a data item to hold the program name. For instance:

DISPLAY "Enter the subprogram name - " WITH NO ADVANCING
ACCEPT SubprogramName
CALL SubprogramName

Example 16-1. Subprogram Template

IDENTIFICATION DIVISION.
PROGRAM-ID. ValidateCheckDigitIS INITIAL.
DATA DIVISION.
WORKING-STORAGE SECTION.
:     :     :     :     :     :     :
:     :     :     :     :     :     :
LINKAGE SECTION.
01 NumToValidate        PIC 9(7).
01 Result               PIC 99.
 
PROCEDURE DIVISIONUSING NumToValidate, Result.
Begin.
:     :     :     :     :     :     :
:     :     :     :     :     :     :
   EXIT PROGRAM.

Note that the name given in the CALL statement (ValidateCheckDigit) corresponds to the name given in the PROGRAM-ID of the called program. The main purpose of the PROGRAM-ID clause is to identify programs in a run-unit (the group of programs that have been compiled and linked into one executable image). The CALL transfers control from one program in the run-unit to another.

In this template, the IS INITIAL clause is attached to the PROGRAM-ID. I discuss the IS INITIAL clause and the problem of state memory, which it solves, in the next section.

This template uses a LINKAGE SECTION. A LINKAGE SECTION (which comes after the WORKING-STORAGE SECTION) is always required if parameters are passed to a subprogram. The LINKAGE SECTION is used to define the parameters and reserve storage for them. If a LINKAGE SECTION is required, then the subprogram’s PROCEDURE DIVISION header requires a USING phrase. The USING phrase matches the actual parameters of the CALL (by position in the parameter list) to the formal parameters in the subprogram.

image Note  You probably know what I mean by actual parameters and formal parameters; but in case you don’t, here is an explanation. Any useful subprogram is likely to be called from a number of different places and for different purposes. For instance, the check-digit validation subprogram might be called by various programs to validate NewStudentId, OldStudentId, GraduatedStudentId, TransferStudentId, or even (because it validates any seven-digit number) StockId. These data-item names are the names of the actual parameters that are passed to the subprogram. When you write the subprogram, you don’t always know the names of the data items that will be passed as parameters (a maintenance programmer, for instance, might write a new routine and call your subprogram); and in any case, there are multiple names—which do you choose? So, the name that you use in the subprogram is a placeholder (or formal parameter) for the actual parameter that is passed to the subprogram.

The EXIT PROGRAM statement in Example 16-1 stops the execution of the subprogram and transfers control back to the caller. You place the EXIT PROGRAM statement where you would normally place STOP RUN. The difference between STOP RUN and an EXIT PROGRAM statement is that STOP RUN causes the entire run-unit to stop (even if STOP RUN is encountered in a subprogram) instead of just the subprogram.

Contained Subprograms

As I explained earlier, a contained subprogram is a program contained within the source code of another program. When you use contained subprograms, the END PROGRAM header is required to delimit the scope of each subprogram and to wrap your subprograms within the scope of the main (container) program. The END PROGRAM header has this format: END PROGRAM ProgramIdName.

Example 16-2 shows the ValidateCheckDigit subprogram implemented as a contained subprogram. In this instance, it is contained within a main program called CheckDigitDrv.

Example 16-2. Outline of a Main Program and Its Contained Subprogram

IDENTIFICATION DIVISION.
PROGRAM-ID. CheckDigitDrv.
:     :     :     :     :     :     :
:     :     :     :     :     :     :
    CALL "ValidateCheckDigit" USING BY CONTENT StockId
                                    BY REFERENCE CKD-Result
:     :     :     :     :     :     :
:     :     :     :     :     :     :
 
IDENTIFICATION DIVISION.
PROGRAM-ID. ValidateCheckDigit IS INITIAL.
:     :     :     :     :     :     :
:     :     :     :     :     :     :
PROCEDURE DIVISION USING NumToValidate, Result.
:     :     :     :     :     :     :
:     :     :     :     :     :     :
END PROGRAM ValidateCheckDigit.
END PROGRAM CheckDigitDrv.

Contained Subprograms vs. External Subprograms

I mentioned that contained subprograms are not quite the same as external subprograms. You have already seen one difference: the END PROGRAM header. Another difference is the visibility of data. In an external subprogram, it is obvious that it can’t see data declared in the main program or other subprograms (although this is not entirely true, as you will see when you examine the IS EXTERNAL clause), because it is a separate, independent program. But because the text of a contained subprogram is contained within the text of the main (container) program, you may wonder whether the subprogram can see the data declared in the main program and whether the main program can see the data declared in the subprogram. In COBOL, data declared in a subprogram cannot be seen outside it, and data declared in the main (containing) program cannot be seen in the subprogram, unless … unless what? For the answer, you have to wait for the explanation of the IS GLOBAL clause later in this chapter.

An issue that does not arise in relation to external subprograms but is a burning issue for contained subprograms is invokability. Contained subprograms can be nested: that is, a contained subprogram may itself contain a subprogram. So the question arises, can a nested subprogram be called from anywhere? Or are there restrictions? Sadly, there are restrictions. A contained subprogram can only be called by its immediate parent (container) program or by a subprogram at the same level. Even this isn’t entirely true; a subprogram can only be called by a subprogram (sibling) at the same level if the called program uses the IS COMMON PROGRAM clause (see the next section) in its PROGRAM-ID.

State Memory and the IS INITIAL Phrase

The first time a subprogram is called, it is in its initial state: all files are closed, and the data items are initialized to their VALUE clauses. The next time the subprogram is called, it remembers its state from the previous call. Any files that were opened are still open, and any data items that were assigned values still contain those values.

Although it can be useful for a subprogram to remember its state from call to call, systems that contain subprograms with state memory are often less reliable and more difficult to debug than those that do not. A subprogram that does not have state memory is predictable, because for the same input value, it produces the same result. Subprograms that have state memory are more difficult to debug because they may produce different results for the same input values.

You can force a subprogram into its initial state each time it is called by including the IS INITIAL clause in the PROGRAM-ID. The metalanguage for the IS INITIAL clause is given in Figure 16-5. Note that INITIAL is only one of the clauses that can be attached to the PROGRAM-ID. IS COMMON PROGRAM may also be applied to a subprogram. I examine the IS COMMON PROGRAM clause in more detail later in the chapter.

9781430262534_Fig16-05.jpg

Figure 16-5. Metalanguage for the IS COMMON and IS INITIAL clauses

Listing 16-1 has a dual purpose. It shows how contained subprograms are created and used, and it demonstrates the difference between a subprogram that has state memory and one that does not. The listing consists of a main program and two subprograms named Steady and Dynamic. Steady is so named because every time you call it with the same parameter values, it produces the same results. But Dynamic, because it remembers its state from the previous call, produces different results when it is called with the same input values.

Listing 16-1. State Memory Demonstration with Steady and Dynamic

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing16-1.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 Increment      PIC 99 VALUE ZERO.
   88 EndOfData   VALUE ZERO.
 
PROCEDURE DIVISION.
Begin.
*> Demonstrates the difference between Steady
*> and Dynamic.  Entering a zero ends the iteration
   DISPLAY "Enter an increment value (0-99) - " WITH NO ADVANCING
   ACCEPT Increment
   PERFORM UNTIL EndOfData
      CALL "Steady"  USING BY CONTENT Increment
      CALL "Dynamic" USING BY CONTENT Increment
      DISPLAY SPACES
      DISPLAY "Enter an increment value (0-99) - " WITH NO ADVANCING
      ACCEPT Increment
   END-PERFORM
   STOP RUN.
 
IDENTIFICATION DIVISION.
PROGRAM-ID. Dynamic.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 RunningTotal   PIC 9(5) VALUE ZERO.
01 PrnTotal       PIC ZZ,ZZ9.
 
LINKAGE SECTION.
01 ValueToAdd     PIC 99.
PROCEDURE DIVISION USING ValueToAdd.
Begin.
   ADD ValueToAdd TO RunningTotal
   MOVE RunningTotal TO PrnTotal
   DISPLAY "Dynamic total = " PrnTotal
   EXIT PROGRAM.
END PROGRAM Dynamic.
 
IDENTIFICATION DIVISION.
PROGRAM-ID. Steady IS INITIAL.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 RunningTotal   PIC 9(5) VALUE ZERO.
01 PrnTotal       PIC ZZ,ZZ9.
 
LINKAGE SECTION.
01 ValueToAdd  PIC 99.
PROCEDURE DIVISION USING ValueToAdd .
Begin.
   ADD ValueToAdd  TO RunningTotal
   MOVE RunningTotal TO PrnTotal
   DISPLAY "Steady total  = " PrnTotal
   EXIT PROGRAM.
END PROGRAM Steady.
END PROGRAM Listing16-1.

9781430262534_unFig16-01.jpg

Notice that each time Steady is passed the same value, it produces the same result; but each time Dynamic is passed the same value, it produces a different result, because it remembers the state of the data items from the previous invocation. Sometimes, such as when you need to keep a running total, you want the subprogram to have state memory. But as a rule, unless you explicitly want a subprogram to remember its state, you should use the IS INITIAL phrase to set the program to its initial state each time it is called.

The CANCEL Verb

A program may need state memory only part of the time. That is, it needs to be reset to its initial state periodically. In COBOL, you can do this using the CANCEL verb. The metalanguage for the CANCEL verb is given in Figure 16-6.

9781430262534_Fig16-06.jpg

Figure 16-6. Metalanguage for the CANCEL verb

When the CANCEL command is executed, the memory space occupied by the subprogram is freed. If the subprogram is called again, it is in its initial state (all files declared in the subprogram are closed, and all data items are initialized to their VALUE clauses). As shown in Example 16-3, you can use the CANCEL verb to force Dynamic to act like Steady.

Example 16-3. Using the CANCEL Verb to Force Dynamic to Act Like Steady

DISPLAY "First  Call"
CALL "Dynamic" USING BY CONTENT 77.
CANCEL "Dynamic"
DISPLAY SPACES
DISPLAY "Second Call"
CALL " Dynamic" USING BY CONTENT 77.

9781430262534_unFig16-02.jpg

The IS GLOBAL Clause

I noted earlier that data declared in a contained subprogram cannot be seen in the main (containing) program, and data declared in the main program cannot be seen inside a contained subprogram. In general, this is true; but sometimes you may want to share a data item with a number of contained subprograms. For instance, consider the program fragments in Example 16-4. This program produces a report showing the purchases of new automobiles in the United States. The data is accumulated in a table and then printed.

The program is partitioned into a main program and two subprograms. One subprogram adds the value of each new car purchase to the appropriate state in the table. The other subprogram prints the report when the new car purchases have been processed. Both subprograms need access to the table. The table cannot be declared local to the subprogram because any local declarations cannot be seen outside the subprogram. So the table must be declared in the outer scope: the main (container) program. The problem then is how to allow the table to be seen by the subprograms.

One approach might be to pass the table through the parameter list. The problem with this approach is that there is a lot of data in the table, and every time AddToStateTotal is called, the table must be passed. A better solution is to make the table visible inside the subprograms. You can do this using the IS GLOBAL clause. Any data item to which the IS GLOBAL clause is attached is visible within the subordinate subprograms.

Example 16-4. Program Outline Showing the Use of the IS GLOBAL Clause

IDENTIFICATION DIVISION.
PROGRAM-ID. CarPurchasesReport.
  :     :     :     :     :     :     :
01 StateTable IS GLOBAL.
   02 State OCCURS 50 TIMES.
      03 TotalCarPurchases    PIC 9(9)V99.
  :     :     :     :     :     :     :
PROCEDURE DIVISION.
        :     :     :     :     :     :
    CALL AddToStateTotal USING BY CONTENT StateNo, ValueOfCarPurchase
        :     :     :     :     :     :
    CALL PrintTotalCarPurchases
    STOP RUN.
 
IDENTIFICATION DIVISION.
PROGRAM-ID. AddToStateTotal.
  :     :     :     :     :     :     :
END-PROGRAM AddToStateTotal.
 
IDENTIFICATION DIVISION.
PROGRAM-ID. PrintTotalCarPurchases.
  :     :     :     :     :     :     :
END PROGRAM PrintTotalCarPurchases.
END PROGRAM CarPurchasesReport.

The IS COMMON PROGRAM Clause

I mentioned earlier that a contained subprogram can only be called by its immediate parent (container) program or by a subprogram at the same level. I noted that even then, a contained subprogram can call a subprogram at the same level only if the subprogram to be called uses the IS COMMON PROGRAM clause in its PROGRAM-ID. You already saw the metalanguage for the IS COMMON PROGRAM clause in Figure 16-5, but it is repeated here for convenience:

pg407.jpg

When IS COMMON PROGRAM is attached to the PROGRAM-ID clause of a contained subprogram, that subprogram may be invoked by any subprograms at the same level (siblings) but only by them. As you can see from the metalanguage, both the COMMON and INITIAL clauses may be used in combination. The words IS and PROGRAM are noise words that may be omitted. The IS COMMON PROGRAM clause can be used only in nested programs.

Example Programs and Their Subprograms

Listing 16-2, Listing 16-3, and Listing 16-4 are programs that consist of simple examples to demonstrate some of the issues discussed so far. Listing 16-5 is a more practical example that implements a game to test your knowledge of the American states. Listing 16-6 is a demonstrator for the external subprogram used by Listing 16-5.

External Subprogram

Listing 16-2 is an example program that calls an external subprogram to validate Student IDs. It is followed by the external subprogram Listing 16-2sub, which applies check-digit validation to any seven-digit number supplied to it.

Listing 16-2. Creating and Calling an External Subprogram

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing16-2.
AUTHOR.  Michael Coughlan.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 StudentId              PIC 9(7).
    
01 ValidationResult       PIC 9.
   88 ValidStudentId      VALUE ZERO.
   88 InvalidStudentId    VALUE 1.
    
PROCEDURE DIVISION.
Begin.
    PERFORM 3 TIMES
       DISPLAY "Enter a Student Id : " WITH NO ADVANCING
       ACCEPT StudentId
       CALL "ValidateCheckDigit" USING BY CONTENT StudentID
                                       BY REFERENCE ValidationResult
       IF ValidStudentId
          DISPLAY "The Student id - " StudentId " - is valid"
        ELSE
          DISPLAY "The Student id - " StudentId " - is not valid"
       END-IF
       DISPLAY SPACES
    END-PERFORM
    STOP RUN.

Listing 16-2sub. The ValidateCheckDigit External Subprogram

IDENTIFICATION DIVISION.
PROGRAM-ID. ValidateCheckDigit IS INITIAL.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 SumOfNums            PIC 9(5).
01 Quotient             PIC 9(5).
01 CalcResult           PIC 99.
 
LINKAGE SECTION.
01 NumToValidate.
   02  D1               PIC 9.
   02  D2               PIC 9.
   02  D3               PIC 9.
   02  D4               PIC 9.
   02  D5               PIC 9.
   02  D6               PIC 9.
   02  D7               PIC 9.
 
01 Result               PIC 9.
   88 InvalidCheckDigit VALUE 1.
   88 ValidCheckDigit   VALUE 0.
 
PROCEDURE DIVISION USING NumToValidate, Result.
*> Returns a Result of 1 (invalid check digit) or 0 (valid check digit)
Begin.
   COMPUTE SumOfNums = (D1 * 7) + (D2 * 6) + (D3 * 5) + (D4 * 4) +
                       (D5 * 3) + (D6 * 2) + (D7).
   DIVIDE SumOfNums BY 11 GIVING Quotient REMAINDER CalcResult
   IF CalcResult EQUAL TO ZERO
      SET ValidCheckDigit TO TRUE
    ELSE
      SET InvalidCheckDigit TO TRUE
   END-IF
   EXIT PROGRAM.

9781430262534_unFig16-03.jpg

Parameter Passing and Data Visibility

Listing 16-3 is an abstract example that demonstrates how to create contained subprograms. It shows the various kinds of parameters and parameter-passing mechanisms you can use and demonstrates the visibility of any data item declared with the IS GLOBAL clause.

Listing 16-3. Contained Subprograms and Parameter Passing and Data Visibility

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing16-3.
AUTHOR.  Michael Coughlan.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 DaysOfTheWeek  VALUE "MonTueWedThuFriSatSun" IS GLOBAL.
   02 DayName     PIC XXX OCCURS 7 TIMES.
 
01 Parameters.
   02 Number1             PIC 9(3)  VALUE 456.
   02 Number2             PIC 9(3)  VALUE 321.
   02 FirstString         PIC X(20) VALUE "First parameter  = ".
   02 SecondString        PIC X(20) VALUE "Second parameter = ".
   02 Result              PIC 9(6)  USAGE IS COMP.
   02 DiscountTable VALUE "12430713862362".
      03 Discount         PIC 99 OCCURS 7 TIMES.
 
01 PrnResult              PIC ZZZ,ZZ9.
 
PROCEDURE DIVISION.
DemoParameterPassing.
    DISPLAY "FirstString  value is - " FirstString
    DISPLAY "SecondString value is - " SecondString
    
    CALL "MultiplyNums"
         USING BY CONTENT Number1, Number2, FirstString,
               BY REFERENCE SecondString, Result
               BY CONTENT DiscountTable
                
    DISPLAY SPACES
    DISPLAY "FirstString  value is - " FirstString
    DISPLAY "SecondString value is - " SecondString
    MOVE Result TO PrnResult
    DISPLAY "COMP value is " PrnResult
    STOP RUN.
                          
IDENTIFICATION DIVISION.
PROGRAM-ID. MultiplyNums.
AUTHOR. Michael Coughlan.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 idx              PIC 9.
 
LINKAGE SECTION.
01 Param1           PIC 9(3).
01 Param2           PIC 9(3).
01 Answer           PIC 9(6) USAGE IS COMP.
01 StrA             PIC X(20).
01 StrB             PIC X(20).
01 TableIn.
   02 TNum    PIC 99 OCCURS 7 TIMES.
 
PROCEDURE DIVISION USING Param1, Param2, StrA, StrB, Answer, TableIn.
Begin.
    DISPLAY SPACES
    DISPLAY ">>> In the MultiplyNums subprogram"
    DISPLAY StrA Param1
    DISPLAY StrB Param2
    MULTIPLY Param1 BY Param2 GIVING Answer.
    
*>  Displays table values. One passed as a parameter and the other global
    DISPLAY SPACES
    PERFORM VARYING idx FROM 1 BY 1 UNTIL idx > 7
       DISPLAY DayName(idx) " discount is  " Tnum(idx) "%"
    END-PERFORM
    
*>  Transfer control to a subprogram contained within MultiplyNums
    CALL "InnerSubProg"
    
*>  Demonstrates the difference between BY CONTENT and BY REFERENCE.
    MOVE "VALUE OVERWRITTEN" TO StrA
    MOVE "VALUE OVERWRITTEN" TO StrB
    DISPLAY SPACES
    DISPLAY "<<<< Leaving MultiplyNums"
    EXIT PROGRAM.
 
IDENTIFICATION DIVISION.
PROGRAM-ID. InnerSubProg.
AUTHOR. Michael Coughlan.
PROCEDURE DIVISION.
Begin.
*>  Demonstrates that the GLOBAL data item is even visible here
    DISPLAY SPACES
    DISPLAY ">>>> In InnerSubProg"
    DISPLAY "Days of the week = " DaysOfTheWeek
    DISPLAY "<<<< Leaving InnerSubProg"
    EXIT PROGRAM.
    
END PROGRAM InnerSubProg.
END PROGRAM MultiplyNums.
END PROGRAM LISTING16-3.

9781430262534_unFig16-04.jpg

The first displayed items show the current value of the two strings in the main program. There is a purpose to this. One string is passed BY REFERENCE and the other BY CONTENT. When these strings are displayed after the CALL has executed, the one passed BY REFERENCE has been corrupted. The lesson should be obvious.

In addition to normal numeric items, one of the parameters is a USAGE IS COMP data item. It holds the result of multiplying the two numbers Param1 and Param2. One thing I must stress here is that the description of numeric items in the main program must be the same as the description in the LINKAGE SECTION. If you describe an item as signed in the subprogram, it must be signed in the main program. If it is a USAGE IS COMP item in the subprogram, it must be the same in the main program. Be aware that the complier provides you with absolutely no protection in this regard. It is up to you to make sure the data types and sizes correspond. Working with COBOL subprograms is akin to driving down a twisty mountain road with no protection barrier—one mistake, and you plunge into the abyss.

The percentage displays are used to show that an array can be passed as a parameter. But in this example I also take the opportunity to show that the DaysOfTheWeek table, which is declared as GLOBAL in the outer scope (main program), is also visible inside the contained subprogram.

Just to emphasize the visibility of GLOBAL data items, the subprogram InnerSubProg is nested within the subprogram MultiplyNums. Even in InnerSubProg, the DaysOfTheWeek table is visible.

Using IS COMMON PROGRAM

Listing 16-4 shows that the program to be called can be assigned at runtime. In this example, instead of using a literal value as the target of the CALL, a data item containing the name of the subprogram to be called is used. The name of the subprogram is supplied by the user. Because the user is supplying the name of the program, there is a possibility that they will get the name wrong; the ON EXCEPTION clause is used to make sure the named program exists.

Listing 16-4. Creating and Using a COMMON Subprogram

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing16-4.
AUTHOR.  Michael Coughlan.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 Operation              PIC XXX.
01 NumericValue           PIC 999.
   88 EndOfData           VALUE ZEROS.
    
01 FILLER                 PIC 9.
   88 ValidSubprogName    VALUE ZERO.
   88 InvalidSubprogName  VALUE 1.
PROCEDURE DIVISION.
Begin.
    PERFORM 3 TIMES
       SET ValidSubprogName TO TRUE
       DISPLAY SPACES
       DISPLAY "Enter the required operation (Dec or Inc) : " WITH NO ADVANCING
       ACCEPT Operation
       DISPLAY "Enter a three digit value : " WITH NO ADVANCING
       ACCEPT NumericValue
       PERFORM UNTIL EndofData OR InvalidSubprogName
          CALL Operation USING BY CONTENT NumericValue
               ON EXCEPTION     DISPLAY Operation " is not a valid operation"
                                SET InvalidSubprogName TO TRUE
               NOT ON EXCEPTION SET ValidSubprogName   TO TRUE
                                DISPLAY "Enter a three digit value : "
                                        WITH NO ADVANCING
                                ACCEPT NumericValue
          END-CALL
       END-PERFORM
       CANCEL Operation
       END-PERFORM
       STOP RUN.
 
IDENTIFICATION DIVISION.
PROGRAM-ID. Inc.
AUTHOR. Michael Coughlan.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 RunningTotal     PIC S9(5) VALUE ZEROS.
 
LINKAGE SECTION.
01 ValueIn          PIC 9(3).
 
PROCEDURE DIVISION USING ValueIn.
Begin.
    ADD ValueIn TO RunningTotal
    CALL "DisplayTotal" USING BY CONTENT RunningTotal
    EXIT PROGRAM.
END PROGRAM Inc.
  
IDENTIFICATION DIVISION.
PROGRAM-ID. Dec.
AUTHOR. Michael Coughlan.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 RunningTotal     PIC S9(5) VALUE ZEROS.
 
LINKAGE SECTION.
01 ValueIn          PIC 9(3).
 
PROCEDURE DIVISION USING ValueIn.
Begin.
    SUBTRACT ValueIn FROM RunningTotal
    CALL "DisplayTotal" USING BY CONTENT RunningTotal
    EXIT PROGRAM.
END PROGRAM Dec.
 
IDENTIFICATION DIVISION.
PROGRAM-ID. DisplayTotal IS COMMON INITIAL PROGRAM.
AUTHOR. Michael Coughlan.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 PrnValue    PIC +++,++9.
 
LINKAGE SECTION.
01 ValueIn          PIC S9(5).
 
PROCEDURE DIVISION USING ValueIn.
Begin.
    MOVE ValueIn TO PrnValue
    DISPLAY "The current value is " PrnValue
    EXIT PROGRAM.
END PROGRAM DisplayTotal.
END PROGRAM LISTING16-4.

9781430262534_unFig16-05.jpg

In this example, both Inc and Dec display RunningTotal via a CALL to their sibling program DisplayTotal, which has the IS COMMON PROGRAM clause.

A Practical Example

In Chapter 13, I introduced a table that held the codes, names, and capitals of all the states in America. You might have thought at the time that that information could prove useful in a number of programs. In the next example I take that table, expand it to include the population of each state and from it create an external subprogram called GetStateInfo. Listing 16-5 and Listing 16-6 both use GetStateInfo, but in different ways. Listing 16-5 is a game that uses GetStateInfo to test your knowledge of the American states. Listing 16-6 simply returns the other information about a state when you give it one piece of information, such as the state name.

GetStateInfo External Subprogram

Before examining Listing 16-5 and Listing 16-6, let’s look at the external subprogram that both of these programs call (see Listing 16-5sub).

Listing 16-5sub. External Subprogram to Supply Information About the States

IDENTIFICATION DIVISION.
PROGRAM-ID.  GetStateInfo IS INITIAL.
AUTHOR.  Michael Coughlan.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 StatesTable.
   02 StateValues.
      03 FILLER PIC X(38)  VALUE "ALAlabama       Montgomery    04822023".
      03 FILLER PIC X(38)  VALUE "AKAlaska        Juneau        00731449".
      03 FILLER PIC X(38)  VALUE "AZArizona       Phoenix       06553255".
      03 FILLER PIC X(38)  VALUE "ARArkansas      Little Rock   02949131".
      03 FILLER PIC X(38)  VALUE "CACalifornia    Sacramento    38041430".
      03 FILLER PIC X(38)  VALUE "COColorado      Denver        05187582".
      03 FILLER PIC X(38)  VALUE "CTConnecticut   Hartford      03590347".
      03 FILLER PIC X(38)  VALUE "DEDelaware      Dover         00917092".
      03 FILLER PIC X(38)  VALUE "FLFlorida       Tallahassee   19317568".
      03 FILLER PIC X(38)  VALUE "GAGeorgia       Atlanta       09919945".
      03 FILLER PIC X(38)  VALUE "HIHawaii        Honolulu      01392313".
      03 FILLER PIC X(38)  VALUE "IDIdaho         Boise         01595728".
      03 FILLER PIC X(38)  VALUE "ILIllinois      Springfield   12875255".
      03 FILLER PIC X(38)  VALUE "INIndiana       Indianapolis  06537334".
      03 FILLER PIC X(38)  VALUE "IAIowa          Des Moines    03074186".
      03 FILLER PIC X(38)  VALUE "KSKansas        Topeka        02885905".
      03 FILLER PIC X(38)  VALUE "KYKentucky      Frankfort     04380415".
      03 FILLER PIC X(38)  VALUE "LALouisiana     Baton Rouge   04601893".
      03 FILLER PIC X(38)  VALUE "MEMaine         Augusta       01329192".
      03 FILLER PIC X(38)  VALUE "MDMaryland      Annapolis     05884563".
      03 FILLER PIC X(38)  VALUE "MAMassachusetts Boston        06646144".
      03 FILLER PIC X(38)  VALUE "MIMichigan      Lansing       09883360".
      03 FILLER PIC X(38)  VALUE "MNMinnesota     Saint Paul    05379139".
      03 FILLER PIC X(38)  VALUE "MSMississippi   Jackson       02984926".
      03 FILLER PIC X(38)  VALUE "MOMissouri      Jefferson City06021988".
      03 FILLER PIC X(38)  VALUE "MTMontana       Helena        01005141".
      03 FILLER PIC X(38)  VALUE "NENebraska      Lincoln       01855525".
      03 FILLER PIC X(38)  VALUE "NVNevada        Carson City   02758931".
      03 FILLER PIC X(38)  VALUE "NHNew Hampshire Concord       01320718".
      03 FILLER PIC X(38)  VALUE "NJNew Jersey    Trenton       08864590".
      03 FILLER PIC X(38)  VALUE "NMNew Mexico    Santa Fe      02085538".
      03 FILLER PIC X(38)  VALUE "NYNew York      Albany        19570261".
      03 FILLER PIC X(38)  VALUE "NCNorth CarolinaRaleigh       09752073".
      03 FILLER PIC X(38)  VALUE "NDNorth Dakota  Bismarck      00699628".
      03 FILLER PIC X(38)  VALUE "OHOhio          Columbus      11544225".
      03 FILLER PIC X(38)  VALUE "OKOklahoma      Oklahoma City 03814820".
      03 FILLER PIC X(38)  VALUE "OROregon        Salem         03899353".
      03 FILLER PIC X(38)  VALUE "PAPennsylvania  Harrisburg    12763536".
      03 FILLER PIC X(38)  VALUE "RIRhode Island  Providence    01050292".
      03 FILLER PIC X(38)  VALUE "SCSouth CarolinaColumbia      04723723".
      03 FILLER PIC X(38)  VALUE "SDSouth Dakota  Pierre        00833354".
      03 FILLER PIC X(38)  VALUE "TNTennessee     Nashville     06456243".
      03 FILLER PIC X(38)  VALUE "TXTexas         Austin        26059203".
      03 FILLER PIC X(38)  VALUE "UTUtah          Salt Lake City02855287".
      03 FILLER PIC X(38)  VALUE "VTVermont       Montpelier    00626011".
      03 FILLER PIC X(38)  VALUE "VAVirginia      Richmond      08185867".
      03 FILLER PIC X(38)  VALUE "WAWashington    Olympia       06897012".
      03 FILLER PIC X(38)  VALUE "WVWest Virginia Charleston    01855413".
      03 FILLER PIC X(38)  VALUE "WIWisconsin     Madison       05726398".
      03 FILLER PIC X(38)  VALUE "WYWyoming       Cheyenne      00576412".
   02 FILLER REDEFINES StateValues.
      03 State OCCURS 50 TIMES
               INDEXED BY StateIdx.
         04 StateCode     PIC XX.
         04 StateName     PIC X(14).
         04 StateCapital  PIC X(14).
         04 StatePop      PIC 9(8).
          
LINKAGE SECTION.
01 StateNum-IO         PIC 99.
   88 ValidStateNum    VALUE 1 THRU 50.
01 StateCode-IO        PIC XX.
01 StateName-IO        PIC X(14).
01 StateCapital-IO     PIC X(14).
01 StatePop-IO         PIC 9(8).
01 ErrorFlag           PIC 9.
   88  NoErrorFound    VALUE ZERO.
   88  InvalidStateNum VALUE 1.
   88  NoSearchItems   VALUE 2.
   88  NoSuchStateCode VALUE 3.
   88  NoSuchStateName VALUE 4.
   88  NoSuchCapital   VALUE 5.
 
PROCEDURE DIVISION USING StateNum-IO, StateCode-IO, StateName-IO,
                         StateCapital-IO, StatePop-IO, ErrorFlag.
Begin.
   SET NoErrorFound TO TRUE
   SET StateIdx TO 1
   EVALUATE            TRUE
     WHEN StateNum-IO      NOT EQUAL ZEROS  PERFORM SearchUsingStateNum
     WHEN StateCode-IO     NOT EQUAL SPACES PERFORM SearchUsingStateCode
     WHEN StateName-IO     NOT EQUAL SPACES PERFORM SearchUsingStateName
     WHEN StateCapital-IO  NOT EQUAL SPACES PERFORM SearchUsingStateCapital
     WHEN OTHER SET NoSearchItems TO TRUE
   END-EVALUATE
   EXIT PROGRAM.
      
SearchUsingStateNum.
   IF NOT ValidStateNum SET InvalidStateNum TO TRUE
     ELSE
       MOVE StateCode(StateNum-IO)    TO StateCode-IO
       MOVE StateName(StateNum-IO)    TO StateName-IO
       MOVE StateCapital(StateNum-IO) TO StateCapital-IO
       MOVE StatePop(StateNum-IO)     TO StatePop-IO
   END-IF.
 
SearchUsingStateCode.
   SEARCH State
       AT END SET NoSuchStateCode TO TRUE
       WHEN FUNCTION UPPER-CASE(StateCode(StateIdx)) EQUAL TO
            FUNCTION UPPER-CASE(StateCode-IO)
            SET StateNum-IO  TO StateIdx
            MOVE StateCode(StateIdx)    TO StateCode-IO
            MOVE StateName(StateIdx)    TO StateName-IO
            MOVE StateCapital(StateIdx) TO StateCapital-IO
            MOVE StatePop(StateIdx)     TO StatePop-IO
    END-SEARCH.
        
SearchUsingStateName.
   SEARCH State
       AT END SET NoSuchStateName TO TRUE
       WHEN FUNCTION UPPER-CASE(StateName(StateIdx)) EQUAL TO
            FUNCTION UPPER-CASE(StateName-IO)
            SET StateNum-IO  TO StateIdx
            MOVE StateCode(StateIdx)    TO StateCode-IO
            MOVE StateName(StateIdx)    TO StateName-IO
            MOVE StateCapital(StateIdx) TO StateCapital-IO
            MOVE StatePop(StateIdx)     TO StatePop-IO
    END-SEARCH.
 
SearchUsingStateCapital.
   SEARCH State
       AT END SET NoSuchCapital TO TRUE
       WHEN FUNCTION UPPER-CASE(StateCapital(StateIdx)) EQUAL TO
            FUNCTION UPPER-CASE(StateCapital-IO)
            SET StateNum-IO  TO StateIdx
            MOVE StateCode(StateIdx)    TO StateCode-IO
            MOVE StateName(StateIdx)    TO StateName-IO
            MOVE StateCapital(StateIdx) TO StateCapital-IO
            MOVE StatePop(StateIdx)     TO StatePop-IO
    END-SEARCH.

This program takes as parameters StateNum-IO, StateCode-IO, StateName-IO, StateCapital-IO, StatePop-IO, and ErrorFlag. Whichever of the first four parameters has a value is used as the search term to find the other information about the state. For instance, if StateName-IO has a value, then that is used as the search term to find the state number, state code, state capital, and state population.

If an error condition is detected, such as none of the fields having a value, then the appropriate error condition is set; this results in an error code being returned in the ErrorFlag parameter. If ErrorFlag contains zero, then no error was detected. The errors detected are given by the following condition names:

   88  NoErrorFound    VALUE ZERO.
   88  InvalidStateNum VALUE 1.
   88  NoSearchItems   VALUE 2.
   88  NoSuchStateCode VALUE 3.
   88  NoSuchStateName VALUE 4.
   88  NoSuchCapital   VALUE 5.

The State Knowledge Game

Listing 16-5 is a game to test your knowledge of the names, codes, capitals, and populations of American states. It uses the GetStateInfo external subprogram.

Listing 16-5. A Game to Test Your Knowledge of American States

IDENTIFICATION DIVISION.
PROGRAM-ID.  Listing16-5.
AUTHOR.  Michael Coughlan.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 Parameters.
   02 StateNum      PIC 99.
   02 StateCode     PIC XX.
   02 StateName     PIC X(14).
   02 StateCapital  PIC X(14).
   02 StatePop      PIC 9(8).
   02 ErrorFlag     PIC 9.
 
01 idx  PIC 99.
 
01 CurrentTime.
   02 FILLER        PIC 9(4).
   02 Seed          PIC 9(4).
01 RandState        PIC 99.
01 RandChoice       PIC 9.
  
01 Answer           PIC X(14).
01 PopAnswer        PIC 9(8).
01 MinPop           PIC 9(8).
01 MaxPop           PIC 9(8).
01 PrnStatePop      PIC ZZ,ZZZ,ZZ9.
01 StrLength        PIC 99.
    
PROCEDURE DIVISION.
Begin.
   ACCEPT CurrentTime FROM TIME
   COMPUTE RandState = FUNCTION RANDOM(Seed)
   PERFORM 8 TIMES
      COMPUTE RandState  = (FUNCTION RANDOM * 50) + 1
      COMPUTE RandChoice = (FUNCTION RANDOM * 4) + 1
      CALL "GetStateInfo"
           USING BY REFERENCE  RandState, StateCode, StateName,
                               StateCapital, StatePop, ErrorFlag
      EVALUATE RandChoice
        WHEN      1   PERFORM TestCapitalFromState
        WHEN      2   PERFORM TestCodeFromState
        WHEN      3   PERFORM TestPopFromState
        WHEN      4   PERFORM TestStateFromCapital
      END-EVALUATE
      DISPLAY SPACES
   END-PERFORM
   STOP RUN.
 
TestCapitalFromState.
   CALL "GetStringLength" USING BY CONTENT StateName
                                BY REFERENCE StrLength
   DISPLAY "What is the capital of " StateName(1:StrLength) "? "
           WITH NO ADVANCING
   ACCEPT Answer
   IF FUNCTION UPPER-CASE(Answer) = FUNCTION UPPER-CASE(StateCapital)
      DISPLAY "That is correct"
    ELSE
      DISPLAY "That is incorrect.  The capital of " StateName(1:StrLength)
              " is " StateCapital
   END-IF.
  
TestCodeFromState.
   CALL "GetStringLength" USING BY CONTENT StateName
                                BY REFERENCE StrLength
   DISPLAY "What is the state code for " StateName(1:StrLength) "? "
           WITH NO ADVANCING
   ACCEPT Answer
   IF FUNCTION UPPER-CASE(Answer) = FUNCTION UPPER-CASE(StateCode)
      DISPLAY "That is correct"
    ELSE
      DISPLAY "That is incorrect.  The code for " StateName(1:StrLength)
              " is " StateCode
   END-IF.
 
TestPopFromState.
   CALL "GetStringLength" USING BY CONTENT StateName
                                BY REFERENCE StrLength
   DISPLAY "What is the population of " StateName(1:StrLength) "? "
           WITH NO ADVANCING
   ACCEPT PopAnswer
   COMPUTE MinPop = PopAnswer - (PopAnswer * 0.25)
   COMPUTE MaxPop = PopAnswer + (PopAnswer * 0.25)
   MOVE StatePop TO PrnStatePop
   IF StatePop > MinPop AND < MaxPop
      DISPLAY "That answer is close enough.  The actual population is "  PrnStatePop
    ELSE
      DISPLAY "That is incorrect.  The population of " StateName(1:StrLength)
              " is " PrnStatePop
   END-IF.
 
TestStateFromCapital.
   CALL "GetStringLength" USING BY CONTENT StateCapital
                                BY REFERENCE StrLength
   DISPLAY "Of what state is " StateCapital(1:StrLength) " the capital? "
           WITH NO ADVANCING
   ACCEPT Answer
   IF FUNCTION UPPER-CASE(Answer) = FUNCTION UPPER-CASE(StateName)
      DISPLAY "That is correct"
    ELSE
      DISPLAY "That is incorrect.  The state for " StateCapital(1:StrLength)
              " is " StateName
   END-IF.
 
IDENTIFICATION DIVISION.
PROGRAM-ID.  GetStringLength IS INITIAL.
AUTHOR.  Michael Coughlan.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 CharCount       PIC 99 VALUE ZEROS.
 
LINKAGE SECTION.
01 StringParam     PIC X(14).
01 StringLength    PIC 99.
 
PROCEDURE DIVISION USING StringParam, StringLength.

Begin.
   INSPECT FUNCTION REVERSE(StringParam) TALLYING CharCount
          FOR LEADING SPACES
   COMPUTE StringLength = 14 - CharCount
   EXIT PROGRAM.
END PROGRAM GetStringLength.
END PROGRAM Listing16-5.

9781430262534_unFig16-06.jpg

This program contains a number of interesting features. First, it uses the RANDOM intrinsic function. The first time RANDOM is invoked, it generates a sequence of pseudo-random numbers using the current time as a seed. Subsequent uses of RANDOM return instances of those numbers.

The program gets two random numbers: one to choose which state to ask about and the other to choose what kind of question to ask. Once the program has chosen the number of the state to ask about, it uses the CALL verb to get all the other information about the state. Depending on what question is asked, the program gets an answer from the user and then compares it with state information returned by the CALL.

Although most answers must be exact, conversion to uppercase is done so the letter case of the answer is not an issue. And because you can’t expect users to know the exact population of a state, any answer within 25 percent (higher or lower) of the actual value is accepted as correct.

An interesting problem is caused by displaying state names and capitals when the text does not fill the data item. In that case, the data item is space filled, which causes unsightly output when the text is be displayed. For instance, a question about the capital of Delaware might display as follows:

: Of what state is Dover         the capital?

To solve this issue, reference modification is used to slice out the actual text. To enable this slicing, the program calculates the length of the text. Because this operation is performed a number of times, it is removed to the contained subprogram GetStringLength.

Getting State Information

Listing 16-6 also uses the subprogram GetStateInfo, but in a more straightforward way. When the user provides a piece of information, such as a state name, the program displays all the other information about the state. The state number and the state code are two of the items displayed and you might think that having both of these items in the table is redundant. However, the importance of the state code is obvious and when I wrote the game in Listing 16-5 the state number proved useful because it made it easy to select the state at random. One other advantage of the state number is that you can use it to dump out all the values in the table (see Example 16-5).

Example 16-5. Fragment Showing How to Display the State Table Values

PERFORM VARYING idx FROM 1 BY 1 UNTIL idx > 50
    MOVE idx TO StateNum
    CALL "GetStateInfo"
        USING BY REFERENCE  StateNum, StateCode, StateName,
                            StateCapital, StatePop, ErrorFlag
    DISPLAY StateNum ". " StateCode SPACE StateName
            SPACE StateCapital SPACE StatePop
END-PERFORM

Listing 16-6. Using the GetStateInfo Subprogram as Intended

IDENTIFICATION DIVISION.
PROGRAM-ID.  Listing16-6.
AUTHOR.  Michael Coughlan.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 Parameters.
   02 StateNum      PIC 99.
   02 StateCode     PIC XX.
   02 StateName     PIC X(14).
   02 StateCapital  PIC X(14).
   02 StatePop      PIC 9(8).
   02 ErrorFlag     PIC 9.
      88 NoError    VALUE ZERO.
        
01 CurrentTime.
   02 FILLER        PIC 9(4).
   02 Seed          PIC 9(4).
01 RandChoice       PIC 9.
01 PrnStatePop      PIC ZZ,ZZZ,ZZ9.
  
PROCEDURE DIVISION.
Begin.
   ACCEPT CurrentTime FROM TIME
   COMPUTE RandChoice = FUNCTION RANDOM(Seed)
   PERFORM 8 TIMES
      DISPLAY SPACES
      INITIALIZE Parameters
      COMPUTE RandChoice = (FUNCTION RANDOM * 4) + 1
      EVALUATE RandChoice
        WHEN      1   DISPLAY "Enter a state number - " WITH NO ADVANCING
                      ACCEPT StateNum
        WHEN      2   DISPLAY "Enter a two letter code - " WITH NO ADVANCING
                      ACCEPT StateCode
        WHEN      3   DISPLAY "Enter a state name - " WITH NO ADVANCING
                      ACCEPT StateName
        WHEN      4   DISPLAY "Enter a state capital - " WITH NO ADVANCING
                      ACCEPT StateCapital
      END-EVALUATE
      CALL "GetStateInfo"
           USING BY REFERENCE  StateNum, StateCode, StateName,
                               StateCapital, StatePop, ErrorFlag
      IF NoError
         MOVE StatePop TO PrnStatePop
         DISPLAY StateNum ". " StateCode SPACE StateName
                 SPACE StateCapital SPACE PrnStatePop
        ELSE
         DISPLAY "There was an error.  Error Code = " ErrorFlag
      END-IF
   END-PERFORM
   STOP RUN.

9781430262534_unFig16-07.jpg

In this program the search term type is chosen at random, the user is asked to supply a value for it, and then GetStateInfo is called to return the appropriate values for that search term.

The IS EXTERNAL Clause

The IS GLOBAL clause allows a program and its contained subprograms to share access to a data item. The IS EXTERNAL clause does the same for any subprogram in a run-unit (that is, any linked subprogram), but it has restrictions that make it much more cumbersome to use than the IS GLOBAL phrase. Whereas a data item that uses the IS GLOBAL phrase only has to be declared in one place, each of the subprograms that wish to access an EXTERNAL shared item must declare the item—and it must be declared exactly the same way in each subprogram. Figure 16-7 illustrates the IS EXTERNAL data-sharing mechanism.

9781430262534_Fig16-07.jpg

Figure 16-7. The IS EXTERNAL data-sharing mechanism

Figure 16-7 shows the calling structure of a run-unit that consists of four linked programs: a main program (ProgramA) and three subprograms. In the illustration, ProgramB and ProgramD share data using the IS EXTERNAL mechanism. In order to share the data, both subprograms must declare the data, and the declarations have to be exactly the same. That is, they must each have the following declaration:

01 SharedRec IS EXTERNAL.
   02 Stock-Id   PIC 9(7).
   02 Manf-Id    PIC X(5).

In this system, ProgramB communicates with ProgramD by passing it data through the shared data item SharedRec.  This might work as follows: ProgramA does some work and then calls ProgramB, which moves a value into SharedRec as part of its work. When control returns to ProgramA, it does some more work, calls ProgramC to do some work, and then calls ProgramD. ProgramD then uses the data from the shared area SharedRec to perform its task.

IS EXTERNAL Problems

The problem with using the IS EXTERNAL phrase is that the transfer of data between ProgramB and ProgramD  is detectable only by inspecting B and D. Even though ProgramA invokes B and D, a programmer inspecting A will not realize that B and D are secretly communicating. Even worse, at some point in the future, a maintenance programmer may decide that ProgramC needs to communicate with ProgramD using the shared area and may overwrite the data placed there by ProgramB.

The kind of hidden data communication between subprograms that you see when you use the IS EXTERNAL clause is generally regarded as very poor practice. According to the measures of module goodness discussed by Myers1common coupling is almost the worst kind of data connection you can have between modules. Subprograms that use the IS EXTERNAL clause to create shared data items are common coupled. Common-coupled modules exhibit a number of problems, such as naming dependencies, creation of dummy structures, and exposure to unnecessary data. Most of these issues are caused by the requirement that each subprogram that wants to use the shared area must describe it exactly the same way.

To illustrate the problem, consider the following scenario. A programmer creates a module to do check digit validation for the Stock-Id.  Instead of using the parameter list to get the number to be validated, the programmer takes advantage of the fact that the Stock-Id is an EXTERNAL shared data item and gets access to the Stock-Id using this shared area. The first problem the programmer has is to make sure that their module is not overwriting the data moved into the shared area by some other subprogram.  The second problem the programmer has is that their module has to describe the shared area as follows:

01 SharedRec IS EXTERNAL.
   02 Stock-Id   PIC 9(7).
   02 Manf-Id    PIC X(5).

Even though the module only requires access to the Stock-Id, the programmer has to create a dummy Manf-Id data item also. A maintenance programmer who was trying to understand how this subprogram worked might spend quite a bit of time trying to figure out the role of the dummy Manf-Id. A naming dependency problem might occur later.

Suppose a programmer writing a subprogram for the system to validate customer records discovers that the seven-digit Customer-Id uses a check digit for validation; so, the programmer decides to use the check-digit validation subprogram that has already been written. To use the subprogram, the programmer must pass the number to be validated through the shared data item. This requires the use of the following declaration:

01 SharedRec IS EXTERNAL.
   02 Stock-Id   PIC 9(7).
   02 Manf-Id    PIC X(5).

Again, a maintenance programmer examining the ValidateCustomerRecord subprogram might wonder why the program includes references to Stock-Id and Manf-Id when it is about validating customer records. The maintenance programmer might also wonder why the subprogram has the statement MOVE Customer-Id TO Stock-Id when these are clearly two very different items.

Using IS EXTERNAL Data Items

Even though using the IS EXTERNAL phrase to create a shared data item has many drawbacks, it may still be preferable to alternative solutions. For instance, sometimes a data item may need to be accessed by many of the subprograms in a system. In that case, your alternatives are to use the IS EXTERNAL phrase to allow the data item to be seen by any subprogram that requires it or to pass the data item as a parameter. The problem with passing the data item as a parameter is that many of the subprograms that do not require access to the data item then only serve as conduits through which the data item is passed to a subordinate subprogram. This kind of data is called tramp data.

Tramp data has a number of drawbacks. It widens the parameter list for subprograms that don’t directly use the data; it exposes those subprograms to unnecessary data, which increases the risk that the data will be compromised; and it unnecessarily complicates the code of those subprograms. Figure 16-8 illustrates the problem. In this system, the data item used by ProgG, ProgI, and ProgK is created in ProgJ. Because none of the subprograms that use the data item are directly called by ProgJ, the data item has to be passed up and down the calling chain as tramp data.

9781430262534_Fig16-08.jpg

Figure 16-8. The problem of tramp data. Connecting arrows show the direction of calls. Circle arrows show the direction of data flow

If you have to use the IS EXTERNAL phrase, there are some things you can do to ameliorate the problems. First, to eliminate the need to create dummy structures, and to reduce exposure to unnecessary data, you should use IS EXTERNAL only with elementary data items. Second, only one subprogram should be permitted to assign a value to an IS EXTERNAL data item. All other subprograms should only be allowed to read that value.

The COPY Verb

The COPY verb is a library statement that includes prewritten library source code in a COBOL program or a subprogram. It is generally used when creating large software systems. These systems are subject to a number of problems that the COPY verb helps to alleviate. For instance, many of the files in a large software system are processed by more than one program. One issue with this is that if each programmer who creates a program or subprogram is allowed to define the files and records used, then there is a strong possibility that in some cases they will get the definitions wrong. They may make errors in defining the key fields (Indexed files); the file organization; the type of access allowed; or the number, type, and size of the fields in a record. At the very least, these kinds of errors will likely result in the failure of the program that contains the erroneous descriptions; but if the program writes to a file, bugs may result that are much harder to find. For instance, if one program writes to a file using an incorrect record description while other programs read from the file using the correct description, a crash may occur in one of the correct subprograms rather than in the one that actually has the problem.

In a large software system, when file, record, or other data descriptions are common to a number of programs, it is very important that those descriptions be described in a central source text library under the control of a copy librarian. In such a system, only the copy librarian has permission to change the data definitions, but any programmer who needs to use the data resource can copy its description into their program using the COPY verb. Using copy libraries makes it more difficult for programmers to make ad hoc changes to file and record formats and makes implementation simpler by reducing the amount of coding required and by eliminating transcription errors. For instance, when a number of programs need to access the same file, the relevant file and record descriptions can be copied from a copy library instead of each programmer having to type their own (and possibly get them wrong).

The COPY verb can also make some maintenance tasks easier and safer. For instance, if a record description in a copy library is changed, then all that is required for that change to take effect is for each affected program to be recompiled.

The COPY Metalanguage

The metalanguage for the COPY verb is given in Figure 16-9. Text can be copied from the copy file or copy library and inserted into the program source code as is, or text words in the copied text can be replaced by the text specified in the REPLACING phrase. If REPLACING is used, then the items before the word BY are the text-matching arguments used to identify the text words in the copied text that should be replaced by the text specified.

9781430262534_Fig16-09.jpg

Figure 16-9. COPY verb metalanguage

How COPY Works

The COPY verb operates in an unusual way. Whereas other COBOL statements are executed at runtime, a COPY statement is executed at compile time. A COPY statement allows programmers to include in their programs the text of frequently used file, record, or other data descriptions. The included text is copied from a copy file or a copy library. The COPY statement is similar to the #include used in C or C++.

When a COPY statement is used in a COBOL program, the source-code text is copied into the program from a copy file or from a copy library before the program is compiled. A copy file is a file containing a segment of COBOL code. A copy library is a collection of code segments, each of which can be referenced using a name. Each client program that wants to use the items described in the copy library uses the COPY verb to include the descriptions it requires. When COPY statements copy source code into a program, the code can be included without change or the text can be changed as it is copied into the program. The ability to change the code as it is being included greatly adds to the versatility of the COPY verb.

How the REPLACING Phrase Works

When the REPLACING phrase is used, as the text is copied from the copy file, each properly matched occurrence of Pseudo-Text1, Identifier1, Literal1, and COBOL-Word1 in the library text is replaced by the corresponding Pseudo-Text2, Identifier2, Literal2, or COBOL-Word2 in the REPLACING phrase:

  • Pseudo-Text is any COBOL text enclosed in double equal signs (for example, ==ADD 1==). It allows you to replace a series of words or characters as opposed to individual items.
  • COBOL-Word is any single COBOL reserved word.

For the purposes of matching, the REPLACING phrase operates on text words. A text word may be defined as follows:

  • Any literal, including opening and closing quotes
  • Any separator except a space, a pseudo-text delimiter (==), a comma, or a semicolon
  • Any other sequence of contiguous characters bounded by separators, except comment lines

COPY Examples

It can be very difficult to get a feel for how REPLACING works by reading textual descriptions alone, so this section presents a number of examples that I hope help your understanding. Listing 16-7 is a simple example that shows how you can use the COPY statement to copy a record description from a copy file.  It also shows how to copy a table description from a copy file in a copy library. The REPLACING phrase is used with the second COPY statement to change the size of the table when the text is copied. Don’t look for any significant meaning in this program—it simply shows how you can the COPY statement to include text in your program source code.

Listing 16-7. Using the COPY Statement to Include Text

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing16-7.
AUTHOR.  Michael Coughlan.
 
ENVIRONMENT DIVISION.
FILE-CONTROL.
    SELECT StudentFile ASSIGN TO "STUDENTS.DAT"
    ORGANIZATION IS LINE SEQUENTIAL.
 
DATA DIVISION.
FILE SECTION.
FD StudentFile.
COPY StudentRec.
 
WORKING-STORAGE SECTION.
01 Idx      PIC 9(3).
 
01 NameTable.
COPY StudentNameTable IN EG-Lib
     REPLACING XYZ BY 120.
PROCEDURE DIVISION.
BeginProg.
   OPEN INPUT StudentFile
   READ StudentFile
      AT END SET EndOfSF TO TRUE
   END-READ
   PERFORM VARYING Idx FROM 1 BY 1 UNTIL EndOfSF
      MOVE Surname TO StudSurname(Idx)
      DISPLAY StudentNumber SPACE StudentName SPACE CourseCode
      READ StudentFile
         AT END SET EndOfSF TO TRUE
      END-READ
   END-PERFORM
   CLOSE StudentFile
   STOP RUN.

9781430262534_unFig16-08.jpg

9781430262534_unFig16-09.jpg

Listing 16-8 is a program used as a container for a number of COPY..REPLACING examples. I inserted comments into the program to indicate the purpose of the particular example, and the output shows that the replacements have been made.

Listing 16-8. COPY Statements with REPLACEMENT Text

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing16-8
AUTHOR.  Michael Coughlan.
 
DATA DIVISION.
WORKING-STORAGE SECTION.
01 CopyData.
 
COPY Copybook1
     REPLACING S BY 15.
* Changes the size of a data item
 
COPY Copybook2 REPLACING ==V99== BY ====.
* Changes the type of a data item to an integer
 
COPY Copybook3 REPLACING "CustKey" BY "MyValue".
COPY Copybook3 REPLACING CustKey BY NewKey.
* demonstrates the difference between a literal and a COBOL-Word
 
COPY Copybook3 REPLACING CustKey BY
==CustAddress.
     03 Adr1         PIC X(10).
     03 Adr2         PIC X(10).
     03 Adr3         PIC X(10).
  02 CustId==.
*Changes the CustKey declaration to add some new data items.
*After REPLACEMENT the included text will be -
*   02 CustAddress.
*     03 Adr1         PIC X(10).
*     03 Adr2         PIC X(10).
*     03 Adr3         PIC X(10).
*   02 CustId         PIC X(7) VALUE "CustKey".
 
PROCEDURE DIVISION.
BeginProg.
  MOVE "123456789012345678901234567890" TO CustomerName
  DISPLAY "CustomerName - " CustomerName
  
  MOVE 1234.56 TO CustomerOrder
  DISPLAY "CustomerOrder - " CustomerOrder
  
  DISPLAY "CustKey value changed to - " CustKey
  
  DISPLAY "NewKey value - " NewKey
  
  MOVE "Dublin"  TO Adr3
  
  DISPLAY "CustId value - "CustId
  
STOP RUN.

9781430262534_unFig16-10.jpg

9781430262534_unFig16-11.jpg

9781430262534_unFig16-12.jpg

9781430262534_unFig16-13.jpg

Summary

This chapter introduced you to the COBOL elements required when you create a large software system. You learned about subprograms and how to create both contained and external subprograms. The chapter discussed the COBOL parameter-passing mechanisms and introduced the LINKAGE SECTION. You learned about state memory and saw how to use the IS INITIAL phrase or the CANCEL verb to create a subprogram that does not have state memory. The chapter covered the need for some shared data items in a system partitioned into subprograms and introduced the IS GLOBAL and IS EXTERNAL clauses.

The final section explored the benefits of holding file, record, and other data descriptions in a centralized library. You also learned about the COPY verb, which allows you to include such descriptions in your program’s source code. You saw how to use the COPY verb to include the text from a copy file or copy library in your program.

The next chapter returns to the subject of file handling. You learn about COBOL’s direct-access file organizations: relative files and indexed files. These direct-access file organizations are more versatile than sequential files, and to take advantage of that versatility, COBOL introduces a number of new verbs and makes changes to some of the file-handling verbs with which you are already familiar. Chapter 17 introduces the DELETE, REWRITE, and START verbs and the concepts of the key of reference and the next record pointer. The chapter concludes with a discussion of the advantages and disadvantages of all the COBOL file organizations and when to use one rather than another.

PROGRAMMING EXERCISE

Ah! Exercise time again. If only I had shares in a 2B pencil company.

Introduction

It has long been suspected that compatibility of Zodiac signs (also called star signs or birth signs) is a strong indicator of sexual and emotional compatibility. By processing the information in the Married Persons Date of Birth file, the program you write will test this hypothesis empirically. For each record in the file, the program will use the couple’s dates of birth to identify their signs and discover whether those signs are compatible.

The program should display the following items:

  • The count of the total number of records in the file
  • The count of the total number of valid records (that is, records where neither is a cusp birth)
  • The count of the number of compatible pairs, and the percentage of the total valid records that this represents
  • The count of the number of incompatible pairs, and the percentage of the total valid records that this represents

Every Zodiac sign is compatible with itself and five other signs. A chance selection of life partner should therefore result in 50% of the pairings having compatible Zodiac signs. A significant deviation either way would be of interest, but if significantly more than 50% of the pairings have compatible signs, you would have to conclude that Zodiac signs are a good indicator of compatibility.

The File

The Census Office has made available to you the Married Persons Date of Birth file (Listing16-9MPDOB.Dat). This file consists of information extracted from the most recent census. The file is an unordered sequential file; each record contains the dates of birth of a married couple. The records have the following description:

pg429.jpg

The Problem of the Cusp

In astrology, people whose birth dates fall near the changeover from one sign to the next are said to be “born on the cusp.” The problem is that these persons may exhibit characteristics from both signs. If this is true, then being born on the cusp may distort the compatibility results. To prevent this, the program should treat as invalid all records where one or both of the dates of birth fall on the cusp.

The Zodiac Table

The Zodiac Table is given next. It contains the SignName, SignType, StartDate, and EndDate of each sign. The cusp is defined as a two-day gap between the EndDate of one sign and the StartDate of the next and is built into the dates shown in the table.

SignType indicates sign compatibility where

  • Air and Fire signs are compatible with themselves and with each other.
  • Earth and Water signs are compatible with themselves and with each other.

The Zodiac Table

pg430.jpg

Processing

Write a contained subprogram called IdentifySign to identify the Zodiac sign for a given birth date. The IdentifySign subprogram should take DateOfBirth as an input parameter and should return SignCode (shown in the previous table) as its return/output parameter. A code of 13 should be returned for cusp births.

For each record in the file, do the following:

  • Increment the TotalRecords count.
  • Call IdentifySign to get ZodiacSign for MaleDOB.
  • Call IdentifySign to get ZodiacSign for FemaleDOB.

If either spouse had a cusp birth, then ignore the record. Otherwise, if the signs are compatible, increment the CompatiblePairs count; and if they are incompatible, increment the IncompatiblePairs count.

PROGRAMMING EXERCISE: ANSWER

Listing 16-9. Zodiac Sign Compatibility Tester

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing16-9.
AUTHOR.  Michael Coughlan.

ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT BirthsFile ASSIGN TO "Listing16-9MPDOB.DAT"
        ORGANIZATION IS LINE SEQUENTIAL.

DATA DIVISION.
FILE SECTION.
FD BirthsFile.
01 BirthsRec.
   88 EndOfFile  VALUE HIGH-VALUES.
   02 MaleDOB             PIC X(8).
   02 FemaleDOB           PIC X(8).

WORKING-STORAGE SECTION.
01 Counts.
   02 CompatiblePairs     PIC 9(7)  VALUE ZEROS.
   02 CompatiblePrn       PIC ZZZZ,ZZ9.
   02 CompatiblePercent   PIC ZZ9.
   02 IncompatiblePairs   PIC 9(7)  VALUE ZEROS.
   02 IncompatiblePrn     PIC ZZZZ,ZZ9.
   02 IncompatiblePercent PIC ZZ9.
   02 ValidRecs           PIC 9(8) VALUE ZEROS.
   02 ValidRecsPrn        PIC ZZ,ZZZ,ZZ9.
   02 TotalRecs           PIC 9(9) VALUE ZEROS.
   02 TotalRecsPrn        PIC ZZ,ZZZ,ZZ9.
01 MaleSignType           PIC 99.
   88 ValidMale           VALUE 1 THRU 12.
01 FemaleSignType         PIC 99.
   88 ValidFemale         VALUE 1 THRU 12.

01 SumOfSigns             PIC 99.

PROCEDURE DIVISION.
Begin.
   OPEN INPUT BirthsFile.
   READ BirthsFile
      AT END SET  EndOfFile TO TRUE
   END-READ
   PERFORM ProcessBirthRecs UNTIL EndOfFile
   COMPUTE ValidRecs = CompatiblePairs + IncompatiblePairs
   COMPUTE CompatiblePercent ROUNDED   = CompatiblePairs / ValidRecs * 100
   COMPUTE InCompatiblePercent ROUNDED = InCompatiblePairs / ValidRecs * 100

   PERFORM DisplayResults

   CLOSE BirthsFile.
   STOP RUN.

DisplayResults.
   MOVE CompatiblePairs   TO CompatiblePrn
   MOVE IncompatiblePairs TO IncompatiblePrn
   MOVE TotalRecs TO TotalRecsPrn
   MOVE ValidRecs TO ValidRecsPrn

   DISPLAY "Total records = " TotalRecsPrn
   DISPLAY "Valid records = " ValidRecsPrn
   DISPLAY "Compatible pairs   = " CompatiblePrn
           " which is " CompatiblePercent "% of total".
   DISPLAY "Incompatible pairs = " IncompatiblePrn
           " which is " InCompatiblePercent "% of total".

ProcessBirthRecs.
*  Get the two sign types and add them together
*  If the result is even then they are compatible
   ADD 1 TO TotalRecs
   CALL "IdentifySign" USING BY CONTENT   MaleDOB
                             BY REFERENCE MaleSignType

   CALL "IdentifySign" USING BY CONTENT   FemaleDOB
                             BY REFERENCE FemaleSignType
   IF ValidMale AND ValidFemale
      COMPUTE SumOfSigns = MaleSignType + FemaleSignType
      IF FUNCTION REM(SumOfSigns 2)  = ZERO
         ADD 1 TO CompatiblePairs
        ELSE
         ADD 1 TO IncompatiblePairs
      END-IF
   END-IF
   READ BirthsFile
      AT END SET  EndOfFile TO TRUE
   END-READ.

IDENTIFICATION DIVISION.
PROGRAM-ID. IdentifySign IS INITIAL.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WorkDate.
   88 Aquarius    VALUE "0122" THRU "0218".
   88 Pisces      VALUE "0221" THRU "0319".
   88 Aries       VALUE "0322" THRU "0419".
   88 Taurus      VALUE "0422" THRU "0520".
   88 Gemini      VALUE "0523" THRU "0620".
   88 Cancer      VALUE "0623" THRU "0722".
   88 Leo         VALUE "0725" THRU "0822".
   88 Virgo       VALUE "0825" THRU "0922".
   88 Libra       VALUE "0925" THRU "1022".
   88 Scorpio     VALUE "1025" THRU "1121".
   88 Sagittarius VALUE "1124" THRU "1220".
   88 Capricorn   VALUE "1223" THRU "1231", "0101" THRU "0119".
   02 WorkMonth     PIC XX.
   02 WorkDay       PIC XX.

LINKAGE SECTION.
01 DateOfBirth.
   02 BirthMonth    PIC XX.
   02 BirthDay      PIC XX.
   02 FILLER        PIC 9(4).

01 SignType         PIC 99.

PROCEDURE DIVISION USING DateOfBirth, SignType.
Begin.
   MOVE BirthDay   TO WorkDay.
   MOVE BirthMonth TO WorkMonth.
   EVALUATE TRUE
     WHEN Aquarius    MOVE  1 TO SignType
     WHEN Pisces      MOVE  2 TO SignType
     WHEN Aries       MOVE  3 TO SignType
     WHEN Taurus      MOVE  4 TO SignType
     WHEN Gemini      MOVE  5 TO SignType
     WHEN Cancer      MOVE  6 TO SignType
     WHEN Leo         MOVE  7 TO SignType
     WHEN Virgo       MOVE  8 TO SignType
     WHEN Libra       MOVE  9 TO SignType
     WHEN Scorpio     MOVE 10 TO SignType
     WHEN Sagittarius MOVE 11 TO SignType
     WHEN Capricorn   MOVE 12 TO SignType
     WHEN OTHER       MOVE 13 TO SignType
  END-EVALUATE.
  EXIT PROGRAM.
END PROGRAM IdentifySign.
END PROGRAM Listing16-9.

1Myers G. Composite/structured design. New York: Van Nostrand Reinhold; 1978.

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

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