CHAPTER 19

image

OO-COBOL

This chapter introduces you to OO-COBOL. This book adheres to the ANS 85 COBOL standard, so ISO 2002 OO-COBOL is somewhat outside its remit. The ANS 85 version of COBOL was designed to bring structured programming to COBOL, but failings in the way contained subprograms were implemented meant this version did not fully live up to its promise. However, the structured programming weaknesses of ANS 85 COBOL are remedied by OO-COBOL, and the chapter examines OO-COBOL from this perspective. In this chapter, you see how OO-COBOL can be used to create informational strength modules that fully realize Parnas’s1 idea of information hiding. I show you some OO-COBOL programs and introduce you to classes and methods, but the chapter does not delve deeply into topics such as inheritance, polymorphism, properties, and interfaces. In other words, do not expect a course in object-oriented programming.

Module Strength and Module Coupling

Prior to the introduction of the ANS 74 version of COBOL, many COBOL systems consisted of huge, monolithic programs containing as many as 100,000 lines of code. It soon became clear that it was difficult, if not impossible, to maintain programs of this size. As a result, the ANS 74 version of COBOL introduced external subprograms that allowed programmers to create modular systems consisting of a number of independently compiled programs bound together into one run-unit. Unfortunately, this did not entirely solve the maintenance crisis. It turned out that some kinds of partitioned programs were as bad, or worse, than the monolithic programs they replaced. Using empirical research done at IBM as the basis for their ideas, Stevens, Myers, and Constantine2 addressed this issue by introducing structured programming and the criteria for decomposing a system into modules. In structured programming, a module is defined as any collection of executable program statements that meets all the following criteria:

  • It is a closed subroutine.
  • It can be called from any other module in the system.
  • It has the potential of being independently compiled.

Although structured programming introduced a number of criteria for decomposing a system into modules, the main criteria for judging the quality of a module were module strength and module coupling (see Table 19-1).

Table 19-1. Module Strength and Module Coupling Glenford J. Myers, Composite/Structured Design (New York: Van Nostrand Reinhold, 1978).

Table19-1.jpg

Module strength(sometimes called module cohesion) is a measure of the association between the elements of a module. Modules whose elements are strongly related to each other are regarded as more desirable than modules whose elements only have a weak or nonexistent connection. For instance, a functional-strength module is one in which all the elements combine to perform a single specific function or is one that coordinates subordinate modules such that they perform a single function. Modules such as ValidateCheckDigit, ValidateDate, GetStateCode, and GetCustomerRecord are functional-strength modules: they perform one specific task. On the other end of the scale, a coincidental-strength module is one in which the elements are only weakly related to one another and are more strongly related to the elements of other modules. Coincidental-strength modules are likely to be created when, for example, management mandates that a monolithic program be partitioned into subprograms, each 100 lines long.

Module couplingis a measure of the degree to which one module is connected to another. Modules that have low coupling are regarded as being more desirable than those that are highly coupled. A module with no direct coupling (the best) does not rely on data from other modules and provides no data to other modules. This data independence means this module is unlikely to be affected by bugs in other modules, and a bug in this module is unlikely to affect other modules.

In terms of module strength, a functional-strength module is often considered to be the best. However, this is not always the case. An informational-strength module has characteristics that may make it even more desirable than a functional-strength module. An informational-strength module has the following characteristics:

  • It contains multiple entry points.
  • Each entry point performs a single function.
  • All the functions are related by a concept, data structure, or resource that is hidden in the module

For instance, in the dictionary module shown in Figure 19-1, the dictionary is held in a table. The DictionaryModule has four separate entry points: one that allows words to be added to the dictionary, one that allows the dictionary to be searched for a particular word, one that prints the contents of the dictionary, and a final entry point that allows the definition of a dictionary word to be retrieved. Each entry point has functional strength but shares access to the table.

The advantage of this arrangement is that because knowledge of how the dictionary is represented is hidden in the module, you can change it without causing knock-on effects for the modules that use it. In Figure 19-1, the dictionary is held in a table; but if you decide to hold it as a dynamic structure or even an indexed file, the modules that use the dictionary will not be affected. This is the benefit of information hiding:3 the knowledge of the data structure, concept, or resource is isolated in a single module. It is the idea on which information-strength modules are based.4

9781430262534_Fig19-01.jpg

Figure 19-1. Dictionary module with four entry points

Informational-Strength Modules in COBOL

The desirability of being able to create informational-strength modules is self evident. In COBOL, the combination of the IS GLOBAL phrase and contained subprograms seems to allow you create modules of this type. For instance, you could imagine that the dictionary module is an external subprogram that contains the AddWordToDictionary,SearchDictionaryForWord, PrintDictionaryContents, and GetWordDefinition subprograms and in which the dictionary is held in a table made available to all the contained subprograms. Example 19-1 shows the outline of an attempt to create such an external subprogram. This arrangement reflects the structure of the informational-strength module shown in Figure 19-1. Unfortunately, the attempt to create an informational-strength module in this way is prevented by the rule that says a subprogram may only be called by its parent. In other words, the only program that can call AddWordToDictionary, SearchDictionaryForWord, PrintDictionaryContents, and GetWordDefinition is the containing program DictionaryModule. They can’t be called by any other program in the run-unit that wants to use the dictionary. This situation is illustrated in Figure 19-2, where the program UseDictionary is not permitted to call the subprograms contained in DictionaryModule. You might think the IS COMMON PROGRAM clause provides a solution to the problem, but unfortunately that clause only allows the sibling subprograms to call one another.

Example 19-1. Attempting to Create an Informational-Strength Module

IDENTIFICATION DIVISION.
PROGRAM-ID. DictionaryModule.
WORKING-STORAGE SECTION.
01 DictionaryTable IS GLOBAL.
   02 DictionaryEntry  OCCURS 1000 TIMES.
      03 DictionaryWord   PIC X(20).
      03 WordDefinition   PIC X(1000)
 
IDENTIFICATION DIVISION.
PROGRAM-ID.  AddWordToDictionary IS INITIAL.
PROCEDURE DIVISION USING WordToAdd, WordDefinition.
END PROGRAM AddWordToDictionary.
 
IDENTIFICATION DIVISION.
PROGRAM-ID.  SearchDictionaryForWord IS INITIAL.
PROCEDURE DIVISION USING WordToFind, WordFoundFlag.
END PROGRAM SearchDictionaryForWord.
 
IDENTIFICATION DIVISION.
PROGRAM-ID.  PrintDictionaryContents IS INITIAL.
PROCEDURE DIVISION.
END PROGRAM PrintDictionaryContents.
 
IDENTIFICATION DIVISION.
PROGRAM-ID.  GetWordDefinition IS INITIAL.
PROCEDURE DIVISION USING WordToFind, WordDefinition.
END PROGRAM GetWordDefinition.
END PROGRAM DictionaryModule.

9781430262534_Fig19-02.jpg

Figure 19-2. COBOL only allows a subprogram to be called by its parent

The only way any kind of informational-strength module can be achieved is for UseDictionary to call the external subprogram DictionaryModule and for DictionaryModuleto call the appropriate subprogram, as shown in Figure 19-3. To do this, UseDictionary has to pass a code to DictionaryModule to tell it which of the subprograms to use; and the parameter list passed to DictionaryModule has to be wide enough to accommodate the needs of the contained subprograms. This means even when PrintDictionaryContents is called, you must pass WordToAdd, WordToFind, WordFoundFlag, and WordDefinition as parameters. The problem with this solution is that although you may have created a kind of informational-strength module, the programs UseDictionary and DictionaryModule are now control coupled. The exposure to unnecessary data is not particularly egregious in this example, but it might prove a serious drawback if the contained programs had more significant data needs.

9781430262534_Fig19-03.jpg

Figure 19-3. Workaround to create an informational-strength module in COBOL

The workaround to the problem of creating an informational-strength module in COBOL is not very satisfactory. Module coupling has been traded for module strength. A kind of informational-strength module has been created, but at the expense of control coupling the DictionaryModule and UseDictionary programs.

When you come to use DictionaryModule, you may discover another limitation: there is only one instance of the dictionary. This means you cannot use the DictionaryModule to create specialized dictionaries for acronyms, networking terms, or slang words without running the program multiple times.

OO-COBOL

OO-COBOL provides a solution to many of the problems outlined so far. In OO-COBOL, you can create a class in which to hide the implementation details of the dictionary, and you can create methods to put words into the dictionary and retrieve word definitions from the dictionary. In addition, a class-based solution goes one step beyond the informational-strength module because it allows you to create instances of the dictionary. This means you can create a dictionary to hold acronyms, a dictionary to hold networking terms, or even a dictionary to hold slang words.

The UseDictionary Program

Listing 19-1 uses OO-COBOL to create a Dictionary class and shows how it can be used to create and use multiple instances of dictionaries. Once you have seen an example program and have a feel for how OO is implemented in COBOL, I introduce the topic more formally. I have kept the Dictionary class short by only implementing the AddWordToDictionary and PrintDictionaryContents methods as well as the internal method SetDictionaryName.

Listing 19-1. COBOL Program that Uses the Dictionary Class

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing19-1.
AUTHOR.  Michael Coughlan.
*UseDictionary program
 
REPOSITORY.
    CLASS DictionaryCls AS "dictionary".
 
DATA DIVISION.
WORKING-STORAGE SECTION.
01 AcronymDictionary  USAGE OBJECT REFERENCE DictionaryCls.
01 NetworkDictionary  USAGE OBJECT REFERENCE DictionaryCls.
01 SlangDictionary    USAGE OBJECT REFERENCE DictionaryCls.
01 CurrentDictionary  USAGE OBJECT REFERENCE.
 
01 WordToAdd          PIC X(20).
   88 EndOfInput      VALUE SPACES.
 
01 WordDefinition     PIC X(1000).
 
PROCEDURE DIVISION.
Begin.
   INVOKE DictionaryCls "new" USING BY CONTENT "Acronym Dictionary"
                                       RETURNING AcronymDictionary
   INVOKE DictionaryCls "new" USING BY CONTENT "Network Dictionary"
                                       RETURNING NetworkDictionary
   INVOKE DictionaryCls "new" USING BY CONTENT "Slang Dictionary"
                                       RETURNING SlangDictionary
 
   SET CurrentDictionary TO AcronymDictionary
   DISPLAY "Fill the Acronym dictionary"
   PERFORM FillTheDictionary WITH TEST AFTER UNTIL EndOfInput
 
   SET CurrentDictionary TO NetworkDictionary
   DISPLAY "Fill the Network dictionary"
   PERFORM FillTheDictionary WITH TEST AFTER UNTIL EndOfInput
 
   SET CurrentDictionary TO SlangDictionary
   DISPLAY "Fill the Slang dictionary"
   PERFORM FillTheDictionary WITH TEST AFTER UNTIL EndOfInput
 
   DISPLAY SPACES
   INVOKE AcronymDictionary "PrintDictionaryContents"
 
   DISPLAY SPACES
   INVOKE NetworkDictionary "PrintDictionaryContents"
 
   DISPLAY SPACES
   INVOKE SlangDictionary "PrintDictionaryContents"
 
   INVOKE SlangDictionary    "finalize" RETURNING SlangDictionary
   INVOKE NetworkDictionary  "finalize" RETURNING NetworkDictionary
   INVOKE AcronymDictionary  "finalize" RETURNING AcronymDictionary
   STOP RUN.
 
FillTheDictionary.
   DISPLAY "Enter a word to add (press return to end) - " WITH NO ADVANCING
   ACCEPT WordToAdd
 
   DISPLAY "Enter the word definition - " WITH NO ADVANCING
   ACCEPT WordDefinition
 
   INVOKE CurrentDictionary "AddWordToDictionary"
          USING BY CONTENT WordToAdd, WordDefinition.

Listing 19-1 uses the dictionary class to create three instances of the dictionary: one to hold acronyms, one for network terms, and the third to hold slang words. The program demonstrates that three instances of the dictionary have been created by filling each with relevant words and then displaying the words in each dictionary.

It is interesting to note how little the language has been changed to accommodate the syntax required to write OO-COBOL programs. In Listing 19-1, the first difference between this and an ordinary COBOL program is the REPOSITORY paragraph. This paragraph lists the classes used in the program. The AS clause specifies the external name for the class.

The second difference is the USAGE OBJECT REFERENCE clause, which is an extension of the USAGE clause that allows you to specify that a data item is capable of holding a reference (handle) to an object. In the program, three data items capable of holding references to dictionary objects are created, and a fourth is created that can hold a reference to any object. I could have made this last a dictionary reference also, but I wanted to show that you can create object-reference data items that are not bound to a particular type of object.

The first thing done in the PROCEDURE DIVISIONis to create three instances of the dictionary and assign their references (handles) to the appropriate object-reference data item. This is done by using the INVOKE verb to execute the new method in the dictionary class (or, to describe it in OO-COBOL terms, the INVOKE verb is used to send the new message to the dictionary class.) Because there are three instances of the dictionary, you need to tell each instance its name, so the name of the dictionary is passed to new as a parameter. The new method creates an object instance and places a reference to the instance (the object handle) in the object-reference data item.

At this point, three instances of the dictionary object have been created, and the next step is to fill each dictionary with the appropriate words. I could have done this by repeating the code in the paragraph FillTheDictionary three times and each time targeting a different dictionary (this is what I do to display the contents of each dictionary). But I wanted to create one piece of code to handle all three dictionaries. To do this, instead of referring to a specific dictionary in the FillTheDictionary paragraph, I refer to the CurrentDictionary object reference and then, just before the  FillTheDictionary paragraph is performed, move the appropriate dictionary object reference to CurrentDictionary.

When the dictionaries have been filled with words, the contents of the dictionaries are displayed. This is done by sending the PrintDictionaryContents message to the appropriate dictionary object.

Finally, the storage used by the dictionaries is released by sending a finalize message to the appropriate dictionary object. This is often a vital step because if the program ends without destroying the object, the memory allocated to the object is still allocated but the object references that allow you to access the object in memory are lost.

The Dictionary Class

Listing 19-1 showed how to use the dictionary class to create and use dictionary object instances. Listing 19-1-cls (identified as Listing 19-1-cls.cbl in the online sources) shows how to define the dictionary class.

Listing 19-1-cls. The Dictionary Class

CLASS-ID.  DictionaryCls AS "dictionary"
           INHERITS FROM Base.
AUTHOR. Michael Coughlan.
 
REPOSITORY.
   CLASS Base AS "base"
   CLASS DictionaryCls AS "dictionary".
 
FACTORY.
METHOD-ID. New.
LINKAGE SECTION.
01 TestObject-lnk  OBJECT REFERENCE.
01 DictionaryName  PIC X(20).
 
PROCEDURE DIVISION USING DictionaryName RETURNING TestObject-lnk.
Begin.
*Create a new dictionary object by invoke "new" in the base class
      INVOKE SUPER "new" RETURNING TestObject-lnk.
 
*Set the dictionary name in the dictionary object
      INVOKE TestObject-lnk "SetDictionaryName"
              USING BY CONTENT DictionaryName
      EXIT METHOD.
END METHOD New.
END FACTORY.
 
OBJECT.
WORKING-STORAGE SECTION.
*Items declared here are visible only to methods of this
*instance.  They have state memory.
01 DictionaryTable.
   02 DictionaryEntry  OCCURS 0 TO 1000 TIMES
      DEPENDING ON NumberOfWords
      INDEXED BY WordIdx.
      03 DictionaryWord   PIC X(20).
      03 WordDefinition   PIC X(1000).
 
01 NumberOfWords          PIC 9(4) VALUE ZERO.
 
01 DictionaryName         PIC X(20).
 
METHOD-ID. SetDictionaryName.
LINKAGE SECTION.
01 DictionaryNameIn     PIC X(20).
PROCEDURE DIVISION USING DictionaryNameIn.
Begin.
    MOVE DictionaryNameIn TO DictionaryName
END METHOD SetDictionaryName.
 
METHOD-ID. AddWordToDictionary.
LINKAGE SECTION.
01 WordIn               PIC X(20).
01 DefinitionIn         PIC X(1000).
PROCEDURE DIVISION USING WordIn, DefinitionIn.
Begin.
    MOVE FUNCTION UPPER-CASE(WordIn) TO WordIn
    SET WordIdx TO 1
    SEARCH DictionaryEntry
        AT END ADD 1 TO NumberOfWords
             MOVE WordIn TO DictionaryWord(NumberOfWords)
             MOVE DefinitionIn TO WordDefinition(NumberOfWords)
        WHEN WordIn = DictionaryWord(WordIdx)
             DISPLAY WordIn " is already in the dictionary"
     END-SEARCH
     EXIT METHOD.
END METHOD AddWordToDictionary.
 
METHOD-ID.  PrintDictionaryContents.
LOCAL-STORAGE SECTION.
PROCEDURE DIVISION.
Begin.
    DISPLAY "Words in  - " DictionaryName
    PERFORM VARYING WordIdx FROM 1 BY 1 UNTIL WordIdx = NumberOfWords
       DISPLAY "Word = " DictionaryWord(WordIdx)
    END-PERFORM
    DISPLAY "------ End of dictionary words  --------"
    EXIT METHOD.
END METHOD PrintDictionaryContents.
END OBJECT.
END CLASS DictionaryCls.

The first difference between this class program and a normal COBOL program is that there is no IDENTIFICATION DIVISION. Actually, the IDENTIFICATION DIVISION is now optional. If you are nostalgic, you can still use it. The second difference is that instead of the PROGRAM-ID, you have a CLASS-ID. The CLASS-ID names the class and specifies from what classes it inherits. In this program, the DictionaryCls class inherits from the Base class. The Base class is a system class from which all classes inherit. It corresponds to the class Object in many other OO languages.

The REPOSITORY paragraph allows you to associate internal names with the name of the external file that contains the code for the class. Internally the dictionary class is known as DictionaryCls, but the system knows it as dictionary.

The next item to consider is the FACTORY. The entries from FACTORY to END FACTORY specify the factory object. The main function of the factory object is to create new object instances where initialization is required. If initialization is not required, the new method inherited from the Base class may be used. For instance, if no initialization was required, you could create new acronym dictionary using the statement

INVOKE DictionaryCls "new" RETURNING AcronymDictionary

In this example, initialization is required, so FACTORY contains a new method that overrides the new method inherited from the Base class. What this new method does is to create a new dictionary object. It does this by using the predefined object identifier SUPER to invoke the new method in the Base class. Once a new dictionary object has been created, it is sent the SetDictionaryName message, and this sets the dictionary name into the dictionary instance object by storing it in a data item declared in the instance object. The factory object could not be used for this purpose because there is only one instance of the factory object (created by including the CLASS entries in the REPOSITORY), and the next time you tried to create a new dictionary, the previous name would be overwritten.

You have probably noticed by now that methods in COBOL bear a very strong resemblance to contained subprograms (with some minor differences). Instead of a PROGRAM-ID, you use a METHOD-ID; instead of delimiting the scope with END PROGRAM, you use END METHOD; instead of terminating the method using an EXIT PROGRAM statement, you use EXIT METHOD; and instead of WORKING-STORAGE SECTION, you use LOCAL-STORAGE SECTION.

In Listing 19-1-cls, the next item of interest is the entries that define the instance object. These entries start at OBJECT and end at END OBJECTand specify the data and methods of each dictionary instance. This is where the table that holds the dictionary entries is defined; each dictionary instance has a separate table. Defining the table in the WORKING-STORAGE SECTION of the OBJECT keeps it alive for the life of the instance and makes it available to the methods of the object. It is also where DictionaryName is defined.

SetDictionaryName is an internal method. It is only invoked by the new method in the factory. Its only purpose is to take the dictionary name passed as a parameter and move it to less transient storage. It can’t be stored in the method because method storage only persists as long as the method is alive. When the method ends, any data stored in the method is lost.

AddWordToDictionary adds the word and definition passed as parameters to the appropriate place in the table. PrintDictionaryContents displays the words in the dictionary. The list of words is preceded by the name of the dictionary. The name of the dictionary is obtained from DictionaryName in the WORKING-STORAGE SECTION of the OBJECT.

To keep the class short, so that you are not overwhelmed by detail, I did not include the methods SearchDictionaryForWord and GetWordDefinition. These are left as an exercise for you.

A Formal Introduction to OO-COBOL

Now that you have seen an OO-COBOL program and have an idea about how to create such programs, this section introduces some of the elements of OO-COBOL more formally. But keep in mind that this book is not about OO-COBOL or object-oriented programming, so I skim over many of the constructs and only stop to deal more thoroughly with those I consider particularly salient.

When you remember all the new syntax that was required for the Report Writer, you may find it amazing that object orientation has been brought to COBOL with so few additions to the language. There is only one new verb (INVOKE), one new data type (OBJECT REFERENCE), and a few new entries such as these:

  • CLASS-ID and END CLASS
  • REPOSITORY
  • FACTORY and END FACTORY
  • METHOD-ID  and END METHOD
  • OBJECT and END OBJECT
  • EXIT METHOD

Objects, Classes, and Methods

Before I begin a discussion about creating objects, classes, and methods in COBOL, I should define some of these terms. An object is an encapsulation of data and procedures that operate on that data. In object orientation, the data is known as the object's attributes, and the procedures are known as its methods. For instance, a Stock object might need attributes such a StockId, QtyInStock, ReorderLevel and ReorderQty and might support such methods as GetStockId, AddToStockQty, SubtractFromStockQty, GetStockQty, GetReorderQty, ChangeReorderQty, GetReorderLevel, and ChangeReorderLevel. Encapsulationmeans the structure and implementation of the attributes (data) is completely hidden in the object and the only access to the attributes of an object is through the object’s methods. For instance, the only way to change the ReorderLevel of a particular stock item is to invoke that item’s ChangeReorderLevel method.

The user of an object can only discover the value of an attribute or change the value of an attribute by making requests to the object. These requests are known as messages. Each message invokes a method supported by the object. The messages to which an object responds is known as the object interface. Each class actually defines two interfaces: an interface defining the methods supported by the class object (such as the new method) and the interface defining the methods supported by each instance of the class (such as ChangeReorderQty).

A classis a template for creating objects. A class contains all the information you need to create objects of a particular type. In OO-COBOL, a class is called an object factory because it “manufactures” the object instances. This idea is reinforced by identifying the area of the program where the factory object is defined using the keywords FACTORY and END FACTORY. The factory object may contain its own factory methods and its own factory data. For instance, the Stock class would allow you to create instances of Stock items by sending the new message to the factory object of the Stock class.

In OO-COBOL, a class definition is a program that starts with a CLASS-ID and ends with an END CLASS statement. The class program may contain its own ENVIRONMENT, DATA, and PROCEDURE DIVISIONS. When you write a class program, you need to distinguish between three different but related entities:

  • The class is the source code program defining the class.
  • The factory object is the class at runtime.
  • Instance objects are created by the factory object at runtime.

Programming with Objects

OO-COBOL is not a fully object-oriented language. This means objects can be used inside a COBOL program that is not itself object oriented. However, whether the program you want to write is an OO-COBOL class or an ordinary procedural COBOL program that uses OO-COBOL objects, the same rules for using the objects apply.

Your program must have a REPOSITORY paragraph. The REPOSITORY lists all the class that the program is going to use. If the program itself is an OO-COBOL class, the REPOSITORY paragraph also lists its superclass (the class from which it is derived).

Your program must declare one or more data items of type OBJECT REFERENCE. An OBJECT REFERENCE data item holds an object handle. An object handle enables you to send messages to the object. Object references can be moved from one OBJECT REFERENCE data item to another or can be passed as parameters when you INVOKE a method or CALL a subprogram.

Your program must use the INVOKE verb to send messages to the object. Sending a message to an object invokes the named method in the object. A method is a piece of code that performs one of the functions of the object. Some methods receive or return parameters, so when you invoke a method you may have to include the parameters as part of the message in the INVOKE statement.

Registering a Class

Before you can use an OO-COBOL class, you must register it by declaring it in the REPOSITORY paragraph. Entries in this paragraph link the internal class name with the name of the external file that contains the code for the class. Registering the class in the REPOSITORY using the CLASS clause creates a data item for each class named, and at runtime this data item holds an object handle to the factory object.

Declaring Object References

When you have declared the class in the REPOSITORY (an action that creates a factory object for the class), you have to declare the data items that will hold the handles of any instance object you may create. To do this, you declare the data items as USAGE OBJECT REFERENCE. For instance, the following data items are declared in Listing 19-1:

01 AcronymDictionary  USAGE OBJECT REFERENCE DictionaryCls.
01 NetworkDictionary  USAGE OBJECT REFERENCE DictionaryCls.
01 SlangDictionary    USAGE OBJECT REFERENCE DictionaryCls.
01 CurrentDictionary  USAGE OBJECT REFERENCE.

An object reference can be used

  • As the target of an INVOKE statement
  • As a parameter to a program or method
  • With the SET verb to set one object reference to the value of another or to NULL
  • In a comparison comparing one object reference for equality with another or to NULL

The object reference for the factory objects is automatically created when you register a class.

An object reference may be typed or untyped. As demonstrated in Listing 19-1, an untyped object reference data item (called a universal object reference) can hold an object reference for any object. A typed object reference data item can only hold an object reference of the type specified. For instance, the AcronymDictionary data item can only hold a handle (object reference) to a DictionaryCls object instance.

Sending Messages to Instance Objects

You interrogate, or change, the values of an object’s attributes by sending messages to the object instance. You send messages to an object instance using the INVOKE verb. When you send a message to an object instance, it causes the method named in the message text to execute. If the method is not found in the object, it is passed up the method inheritance chain until it is recognized and executed. This is how the new and finalize methods that create and destroy object instances are executed. These methods are part of the system provided Base class inherited by every COBOL class.

As you can see from Figure 19-4, the INVOKE verb has a strong similarity to the CALL verb and so requires little in the way of explanation. The ObjectIdentifier is the data item that holds the object reference. MessageLiteral is the name of the method to be invoked. Parameters are passed using the same syntax as the CALL verb except that an additional mechanism (BY VALUE) has been added. The RETURNING phrase allows the invoked method to return a value.

9781430262534_Fig19-04.jpg

Figure 19-4. Metalanguage for the INVOKE verb

Creating a New Object Instance

Once you have created a data item capable of holding an object reference, you need to create an object instance and store its reference in the data item. You create an object instance by sending a creation message to its factory object (the factory object itself is created when you register it in the REPOSITORY). For objects that do not have any initialization parameters, the creation message is new (see Example 19-2 and Example 19-3). When the new method executes, it allocates the storage required for the object and returns the object handle.

Example 19-2. Registering a Class, Declaring an Object Reference Data Item, and Creating an Object Instance

REPOSITORY.
   CLASS StockCls AS "stockclassprogram"
    :    :    :    :    :    :    :    :
WORKING-STORAGE SECTION.
   01  StockItem USAGE OBJECT REFERENCE StockCls.
    :    :    :    :    :    :    :    :
PROCEDURE DIVISION.
    :    :    :    :    :    :    :    :
   INVOKE StockCls "new" RETURNING StockItem

Example 19-3. Registering a Class, Declaring an Object Reference Data Item, and Invoking new with an Initialization Parameter to Create a Dictionary Instance

REPOSITORY.
    CLASS DictionaryCls AS "dictionary".
    :    :    :    :    :    :    :    :
WORKING-STORAGE SECTION.
01 AcronymDictionary  USAGE OBJECT REFERENCE DictionaryCls.
    :    :    :    :    :    :    :    :
PROCEDURE DIVISION.
    :    :    :    :    :    :    :    :
   INVOKE DictionaryCls "new" USING BY CONTENT "Acronym Dictionary"
                                       RETURNING AcronymDictionary

Destroying Objects

When you have finished using an object, you must destroy it. This frees the memory it uses. There is no automatic garbage collection in OO-COBOL, so the memory for objects that have been allocated but whose object handles have been lost cannot be recovered. Once an object has been created, it remains in existence until it is destroyed explicitly, even if the data item that holds its object handle is destroyed or the object handle is overwritten.

You destroy an object by sending it the finalize message. Like the new method, finalize is a method provided by the Base class and inherited by all classes. When you finalize an object, the method returns a NULL object reference. Example 19-4 shows how to use INVOKE with the finalize message to destroy an object.

Example 19-4. Using finalize to Destroy an Object

INVOKE AcronymDictionary "finalize" RETURNING  AcronymDictionary

Predefined Object Identifiers

I mentioned the NULL object reference in the previous section. NULL is one of three predefined object identifiers. The identifiers and their significance are given in Table 19-2.

Table 19-2. Predefined Object Identifiers

Predefined Object Identifier

Meaning

NULL

The predefined object reference NULL contains the null object-reference value that is a unique value guaranteed by the implementer never to reference an object. It represents a value used to indicate that data items defined as USAGE OBJECT REFERENCE do not contain a valid address. NULL must not be specified as a receiving operand, but it can be used in a comparison such as

IF AcronymDictionary = NULL
   DISPLAY "The acronym dictionary object does not exist"
END-IF

SELF

SELF is a predefined object identifier used in the PROCEDURE DIVISION of a method. SELF refers to the object instance used to invoke the currently executing method. By using SELF you can cause an object to send a message to itself. This is useful if you want a method to invoke one of its siblings. For instance, in Listing 19-1-cls you could use SELF to invoke the SetDictionaryName method from one of the other methods using a statement such as

INVOKE SELF "SetDictionaryName"
       USING BY CONTENT NewDictionaryName

You might want to use SELF because you have placed a piece of code that is used by several different methods in a method on its own and want to use this method like a subroutine.

SUPER

SUPER allows an object to send a message to itself, but the method invoked is a not a method in the class itself but rather a method in one of the superclasses of the class.

If SUPER is used from an instance method, the system searches its way up through the instance methods of all the superclasses until it finds a method matching the message. If SUPER is used from a factory method, the system searches for a factory method beginning with the factory object code of the superclass immediately above the class and searches its way up through the factory methods of all the superclasses until it finds a method matching the message.

For instance, in Listing 19-1-cls, the new method in the FACTORY needs to invoke the new method in the base class. This is achieved using the statement

INVOKE SUPER "new" RETURNING TestObject-lnk.

Writing Your Own Classes

When you write an OO application, you need to create your own classes. A class program has the structure shown in Figure 19-5, and the entries required are outlined in the class template in Example 19-5.

9781430262534_Fig19-05.jpg

Figure 19-5. Structure of a class program

Example 19-5. A Class Program Template

CLASS-ID.  Template-cls AS "template"
           inherits from Base.
* Class identification.
ENVIRONMENT DIVISION.
* Optional but when used all normal ENVIRONMENT DIVISION entries are valid
  :      :      :      :      :      :      :      :      :
 
CONFIGURATION SECTION.
* Optional entry but the REPOSITORY is part of the CONFIGURATION SECTION
  :      :      :      :      :      :      :      :      :
REPOSITORY.
* The Repository paragraph names the files containing the executables
* for each class.
* The executable for Template-cls is in the filetemplate.
    CLASS BASE AS "base"
    CLASS Template-cls AS "tester".
 
FACTORY
* Defines the start of the factory object.
ENVIRONMENT DIVISON.
DATA DIVISION.
* Defines factory object data
WORKING-STORAGE SECTION.
* Defines factory object data
  :      :      :      :      :      :      :      :      :
METHOD-ID. new.
* If initialization is required there may be a "new" of factory method.
* This overrides "new" coming from Base.
  :      :      :      :      :      :      :      :      :
END METHOD new.
END FACTORY.
 
OBJECT.
* Start of the code that defines the behaviour of class instances.
WORKING-STORAGE SECTION.
* Defines instance data visible to all methods of the instance.
  :      :      :      :      :      :      :      :      :
METHOD-ID. ExampleTemplateMethod.
* Start of instance method "ExampleTemplateMethod "
     ...
END METHOD ExampleTemplateMethod.
END OBJECT.
* End of code for instance objects.
END CLASS Example.

The Issue of Scope

Whenever you write a class program, you have to be aware of the consequences of declaring data items in various parts of the program. When I refer to the scope of a data item, I am referring to its lifetime: how long it persists. The scoping issues of data items declared in the class program are summarized in Table 19-3, and Listing 19-2 demonstrates these issues in an example program.

Table 19-3. Class Program Scoping Issues

Where Declared

Scope

WORKING-STORAGE SECTIONof theFACTORY

A data item declared in the WORKING-STORAGE SECTION of the FACTORY is visible only to factory methods; and because there is only one factory object, there is only one instance of the data item. The item persists as long as the class program is alive.

WORKING-STORAGE SECTIONof theOBJECT

A data item declared in the WORKING-STORAGE SECTION of the OBJECT is visible only to object instance methods. There is an instance of the data item for each object, and the data item will persist as long as the instance is alive (has not been finalized).

LOCAL-STORAGE SECTION  of any method

A data item declared in the LOCAL-STORAGE SECTION of any method (factory of instance object) visible only to the method, and it persists only as long has the method is alive.

Listing 19-2. Example Program to Demonstrate Scoping Issues

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing19-2.
* AUTHOR.  Michael Coughlan.
* Demonstrates the difference between Factory methods & data
* and instance methods & data.
* It is also used to demonstrate the scope of
* data items declared in different parts of the program.
 
REPOSITORY.
    CLASS Tester-cls AS "tester".
 
DATA DIVISION.
WORKING-STORAGE SECTION.
01 Test1-obj  OBJECT REFERENCE Tester-cls.
01 Test2-obj  OBJECT REFERENCE Tester-cls.
01 Test3-obj  OBJECT REFERENCE Tester-cls.
 
PROCEDURE DIVISION.
Begin.
   INVOKE Tester-cls "new" RETURNING Test1-obj
   INVOKE Tester-cls "new" RETURNING Test2-obj
   INVOKE Tester-cls "new" RETURNING Test3-obj
 
   DISPLAY SPACES
   DISPLAY "--------- Test3-obj ViewData -----------"
   INVOKE Test3-obj "ViewData"
 
   DISPLAY SPACES
   DISPLAY "--------- Test1-obj ViewData -----------"
   INVOKE Test1-obj "ViewData"
 
   DISPLAY SPACES
   DISPLAY "--------- Test3-obj ViewData again -----"
   INVOKE Test3-obj "ViewData"
 
   DISPLAY SPACES
   DISPLAY "--------- Test2-obj ViewData -----------"
   INVOKE Test2-obj "ViewData" USING BY CONTENT 5
 
   INVOKE Test1-obj "finalize" RETURNING Test1-obj
   INVOKE Test2-obj "finalize" RETURNING Test2-obj
   INVOKE Test3-obj "finalize" RETURNING Test3-obj
   STOP RUN.

9781430262534_unFig19-01.jpg

The program starts by creating three instances of the tester class object. It does this by sending the new message to the class. There is a new method in the class factory, so that method is executed. The purpose of the new method is to demonstrate the difference between data items declared in the WORKING-STORAGE SECTION of the factory and items declared in the LOCAL-STORAGE SECTION of a factory method. The output from the program shows that while the WORKING-STORAGE data items remember their values from invocation to invocation, which allows them to be incremented each time new is invoked, the LOCAL-STORAGE items always show the same value.

There is one other thing going on here under the surface. If you look at the ViewData displays in the Listing 19-2 output, note that the first line displayed shows which instance it is and how many instances there are. In order to display this information, you must note the instance when new is invoked. But although the number of instances can be stored in the factory, the particular instance number cannot. It has to be stored with the particular instance. When you examine the class program, you can see how this is done.

The ViewData displays are also used to show that there are separate data items for each instance. The increment value used to show the difference between data items declared in the WORKING-STORAGE of the OBJECT and those declared in LOCAL-STORAGE of the ViewData method is computed as 10 multiplied by the instance number. That is 10 for instance one, 20 for instance two, and 30 for instance three.

The purpose of the ViewData displays is to show that separate instances have been created and that when you invoke an object for the second time, you can see that it has remembered the contents of one variable but not the other. The class program used by Listing 19-2 is given in Listing 19-2-cls.

Listing 19-2-cls. Class Program Used by Listing 19-2

CLASS-ID. Tester-cls AS "tester"
          INHERITS FROM Base.
* AUTHOR. Michael Coughlan.
* Demonstrates the difference between Factory methods and data and Instance methods
* and data.  Also demonstrates persistence of data items declared in different areas.
 
REPOSITORY.
    CLASS BASE AS "base"
    CLASS Tester-cls AS "tester".
 
FACTORY.
WORKING-STORAGE SECTION.
*Items declared here are visible only to factory methods and have state memory
01 InstCounter-fws   PIC 9 VALUE ZEROS.
01 FactoryData-fws   PIC 9 VALUE ZEROS.
 
METHOD-ID. New.
LOCAL-STORAGE SECTION.
*Items declared here are visible only to this method but do not have state memory.
01 LocalData-mls   PIC 9 VALUE ZEROS.
 
LINKAGE SECTION.
01 TestObject-lnk  OBJECT REFERENCE.
 
PROCEDURE DIVISION RETURNING TestObject-lnk.
Begin.
    ADD 2 TO FactoryData-fws LocalData-mls
    DISPLAY "Factory Working-Storage data has state memory  - "
              FactoryData-fws
    DISPLAY "but Factory Method Local-Storage data does not - "
              LocalData-mls
    DISPLAY SPACES
    INVOKE SUPER "new" RETURNING TestObject-lnk
    ADD 1 TO InstCounter-fws
    INVOKE TestObject-lnk "InitialiseData"
           USING BY CONTENT InstCounter-fws
    EXIT METHOD.
END METHOD New.
 
METHOD-ID. GetTotalInstCount.
LINKAGE SECTION.
01  TotalInstCount-lnk    PIC 9.
PROCEDURE DIVISION RETURNING TotalInstCount-lnk.
Begin.
   MOVE InstCounter-fws TO TotalInstCount-lnk.
END METHOD GetTotalInstCount.
END FACTORY.
 
OBJECT.
WORKING-STORAGE SECTION.
*Items declared here are visible only to methods of this
*instance.  They are persist for the life of the object instance.
01  ThisInstanceNum-ows          PIC 9 VALUE ZEROS.
01  InstObjectData-ows           PIC 99 VALUE ZEROS.
 
METHOD-ID. InitialiseData.
LINKAGE SECTION.
01 InstNumIn-lnk                 PIC 9.
PROCEDURE DIVISION USING InstNumIn-lnk.
Begin.
    MOVE InstNumIn-lnk TO ThisInstanceNum-ows
    EXIT METHOD.
END METHOD InitialiseData.
 
METHOD-ID. ViewData.
LOCAL-STORAGE SECTION.
*Items declared here only exist for the life of the method.
*They do not retain their values between invocations.
01  InstMethodData-mls           PIC 99 VALUE ZEROS.
01  TotalInstCount-mls           PIC 9  VALUE ZEROS.
01  Increment-mls           PIC 99 VALUE ZEROS.
 
PROCEDURE DIVISION.
Begin.
    COMPUTE Increment-mls = 10 * ThisInstanceNum-ows
    ADD Increment-mls TO InstObjectData-ows, InstMethodData-mls
    INVOKE Tester-cls "GetTotalInstCount"
                        RETURNING TotalInstCount-mls
    DISPLAY "This is instance " ThisInstanceNum-ows
              " of " TotalInstCount-mls
    DISPLAY "Instance Object Data = " InstObjectData-ows
    DISPLAY "Instance Method Data = " InstMethodData-mls
    EXIT METHOD.
END METHOD ViewData.
END OBJECT.
END CLASS Tester-cls.

The first thing to note about Listing 19-2-cls is that I have attached a suffix to each data item to assist your understanding. The suffix meanings are as follows:

-ows indicates a data item in the OBJECT WORKING-STORAGE
-mls indicates a data item in the method LOCAL-STORAGE
-lnk indicates a data item in the LINKAGE-SECTION
-fws indicates a data item in the FACTORY WORKING-STORAGE

The factory contains a new method. This method overrides the new method in the Base class and its purpose is to note the number of the particular object instance created and to keep a count of how many instances have been created. There are two data items in the WORKING-STORAGE SECTION of the FACTORY: FactoryData-fws and InstCounter-fws. FactoryData-fws is used for the purpose of contrast with the LocalData-mls data item declared in the new method. As you can see from the output, FactoryData-fws remembers its value from invocation to invocation, whereas LocalData-mls starts with a value of ZEROS each time the new method is called. InstCounter-fws holds the count of the number of instances that have been created. Each time new is invoked, this count is incremented. InstCounter-fws, however, can’t be used to hold the instance number (as soon as the next instance is created, the number is overwritten). Instead, as soon as an instance has been created by the statement

INVOKE SUPER "new" RETURNING TestObject-lnk

the method InitialiseData in the instance just created is invoked and is passed the current value of InstCounter-fws. InitialiseData then records the number in the instance variable ThisInstanceNum-ows.

Two data items have been declared in the WORKING-STORAGE SECTION of the OBJECT: ThisInstanceNum-ows and InstObjectData-ows. As I have already mentioned, ThisInstanceNum-owsis used to hold the instance number. InstObjectData-ows is used to show the contrast between items declared in the WORKING-STORAGE of the OBJECT and items declared in the LOCAL-STORAGE of the method.

One last issue needs some explanation. ViewData can display the instance number because it is stored in the instance data item ThisInstanceNum-ows, but ViewData does not know how many instances have been created. That information is stored in the factory in InstCounter-fws. The problem is that an instance method cannot see a data item declared in the factory. In order to get access to that information the statement

INVOKE Tester-cls "GetTotalInstCount"
                    RETURNING TotalInstCount-mls

invokes the factory method GetTotalInstCount. This method returns the number of instances as a parameter. Pay particular attention to the target of the INVOKE statement. Instead of targeting the instance object, or SELF, or SUPER, the class name is used (registering the class in the REPOSITORY created the factory object.)

Summary

This chapter introduced OO-COBOL from a particular perspective. The ANS 85 version of COBOL was supposed to bring structured programming to COBOL, but although it had many fine features, it was not entirely successful in this respect. This chapter discussed the shortcomings of the ANS 85 version when attempting to create informational-strength modules and showed how OO-COBOL can be used to fulfill the structured programming promise of ANS 85 COBOL. You then saw an OO program that implemented the information hiding techniques of an informational-strength module. Having demonstrated how to create an OO program through an example, I introduced the topic more formally, and you saw the entries required to use a class, invoke a method, and create a class program. The final section discussed the issue of data-item scope and demonstrated the effect of declaring data items in various parts of the class program.

This has been a long journey. I hope that you have enjoyed the trip and have learned something along the way. Although COBOL has its flaws, its many strengths in the area of its chosen domain account for its dominance in the world of enterprise computing.

PROGRAMMING EXERCISE

Well, it’s time for the final exercise. If you can locate the stub of your 2B pencil, why not have a go at writing an OO-COBOL program?

The Zodiac Signs Compatibility exercise in Chapter 16 required you to write a program that used a contained subprogram called IdentifySign to identify the Zodiac sign for a given birth date. Using the program that you wrote for that exercise as a starting point, write a Zodiac class that supplies the following methods, and then rewrite the Zodiac Sign Compatibility Experiment program so that it uses that Zodiac class:

METHOD-ID. "getSignHouse".
LINKAGE SECTION.
01 InDate.
   02 InDay          PIC XX.
   02 InMonth        PIC XX.
01 OutZodiacHouse    PIC 99.
01 OpStatus          PIC 9.
* value of 0 indicates operation was successful
* value of 1 indicates sign is a Cusp Sign
* value of 2 indicates date supplied was invalid
PROCEDURE DIVISION USING InDate, OutZodiacHouse RETURNING OpStatus.
*Accepts a date in form DDMM and returns the Zodiac House value (01-12)
*The twelve houses are Aries, Taurus,Gemini, Cancer, Leo, Virgo,
*Libra, Scorpio, Sagittarius Capricorn, Aquarius, Pisces
*Method should note if the sign is a cusp sign
END METHOD "getSignHouse".

METHOD-ID. "getSignName".
LINKAGE SECTION.
01 INZodiacHouse    PIC 99.
01 OutSignName          PIC X(11).
01 OpStatus             PIC 9.
* value of 0 indicates operation was successful
* value of 1 indicates InZodiacHouse value not in range 01-12
PROCEDURE DIVISION USING InZodiacHouse, OutSignName RETURNING OpStatus.
*Accepts a Zodiac House value and returns the Zodiac Sign name
*For instance house 3 = Gemini
END METHOD "getSignName".

METHOD-ID. "getSignElement".
LINKAGE SECTION.
01 InZodiacHouse      PIC 99.
   88 ValidSignHouse  VALUE 01 THRU 12.
01 OutSignElement     PIC X(5).

01 OpStatus    PIC 9.
   88 InvalidSignHouse   VALUE 1.
   88 OperationOk        VALUE 0.

PROCEDURE DIVISION USING InZodiacHouse, OutSignElement RETURNING OpStatus.
*Accepts a Zodiac House value and returns the element of the sign
*Viz – Fire Earth Air  Water.
*Houses 1,5,9 = Fire; 2,6,10 = Earth; 3,7,11 = Air; 4,8,12 = Water
END METHOD "getSignElement".

Before you rewrite the Zodiac Sign Compatibility Experiment program, you can test the Zodiac class you have written using the following test program:

IDENTIFICATION DIVISION.
PROGRAM-ID. UseZodiac.
AUTHOR.  Michael Coughlan.
REPOSITORY.
    CLASS ZodiacFactory AS "zodiac".

DATA DIVISION.
WORKING-STORAGE SECTION.
01 MyZodiac   USAGE OBJECT REFERENCE ZodiacFactory.

01 Date-DDMM   PIC X(4).
   88  EndOfData  VALUE SPACES.

01 SignCode    PIC 99.

01 OpStatus1    PIC 9.
   88 CuspSign  VALUE 1.

01 OpStatus2    PIC 9.
   88 OperationOK VALUE ZEROS.

01 SignName     PIC X(11).

01 SignElement   PIC X(5).

PROCEDURE DIVISION.
Begin.
   INVOKE ZodiacFactory "new" RETURNING MyZodiac
   DISPLAY "Enter the Date DDMM :- " WITH NO ADVANCING
   ACCEPT Date-DDMM

   PERFORM GetAndDisplay UNTIL EndOfdata
   INVOKE MyZodiac "finalize" RETURNING MyZodiac
   DISPLAY "End of Program"
   STOP RUN.

GetAndDisplay.
   INVOKE MyZodiac "getSignHouse" USING BY CONTENT Date-DDMM
                                       BY REFERENCE SignCode
                                       RETURNING OpStatus1

   INVOKE MyZodiac "getSignName"       USING BY CONTENT SignCode
                                       BY REFERENCE SignName
                                       RETURNING OpStatus2

   INVOKE MyZodiac "getSignElement"    USING BY CONTENT SignCode
                                       BY REFERENCE SignElement
                                       RETURNING OpStatus2

   DISPLAY "SignCode = " SignCode
   DISPLAY "Sign name is " SignName
   DISPLAY "Sign Element is " SignElement
   IF CuspSign
      DISPLAY "The sign is a cusp"
   END-IF
   DISPLAY "Enter the Date DDMM :- " WITH NO ADVANCING
   ACCEPT Date-DDMM.

PROGRAMMING EXERCISE: ANSWER

Listing 19-3. Zodiac Compatibility Program Using the Zodiac Class

IDENTIFICATION DIVISION.
PROGRAM-ID. Listing19-3.
* Zodiac Compatibility program
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT BirthsFile ASSIGN TO "Listing19-3-MPDOB.DAT"
        ORGANIZATION IS LINE SEQUENTIAL.

CLASS-CONTROL.
    ZodiacFactory IS CLASS "zodiac".

DATA DIVISION.
FILE SECTION.
FD BirthsFile.
01 BirthsRec.
   88 EndOfFile  VALUE HIGH-VALUES.
   02 MaleDOB.
      03 MaleDate         PIC X(4).
      03 FILLER           PIC X(4).
   02 FemaleDOB.
      03 FemaleDate       PIC X(4).
      03 FILLER           PIC X(4).

WORKING-STORAGE SECTION.
01 MyZodiac   USAGE OBJECT REFERENCE.

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 MaleSign           PIC 99.
01 FemaleSign         PIC 99.
01 SumOfSigns         PIC 99.

01 OpStatusM          PIC 9.
   88 ValidMale       VALUE ZEROS.

01 OpStatusF           PIC 9.
   88 ValidFemale     VALUE ZEROS.

PROCEDURE DIVISION.
Begin.
   INVOKE ZodiacFactory "new" RETURNING MyZodiac
   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
   INVOKE MyZodiac "getSignHouse" USING BY CONTENT MaleDate
                                        BY REFERENCE MaleSign
                                        RETURNING OpStatusM

   INVOKE MyZodiac "getSignHouse" USING BY CONTENT FemaleDate
                                        BY REFERENCE FemaleSign
                                        RETURNING OpStatusF

   IF ValidMale AND ValidFemale
      COMPUTE SumOfSigns = MaleSign + FemaleSign
      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.

Listing 19-3-cls. The Zocodiac Class Program

CLASS-ID. Zodiac AS "zodiac" INHERITS FROM Base.
* AUTHOR. Michael Coughlan.

REPOSITORY.
    CLASS BASE AS "base"
    CLASS Zodiac AS "zodiac".

* No FACTORY in this program

OBJECT.
WORKING-STORAGE SECTION.
01 ZodiacTable.
   02 ZodiacTableData.
      03 FILLER   PIC X(20) VALUE "Aries      103210419".
      03 FILLER   PIC X(20) VALUE "Taurus     204200520".
      03 FILLER   PIC X(20) VALUE "Gemini     305210620".
      03 FILLER   PIC X(20) VALUE "Cancer     406210722".
      03 FILLER   PIC X(20) VALUE "Leo        107230822".
      03 FILLER   PIC X(20) VALUE "Virgo      208230922".
      03 FILLER   PIC X(20) VALUE "Libra      309231022".
      03 FILLER   PIC X(20) VALUE "Scorpio    410231121".
      03 FILLER   PIC X(20) VALUE "Sagittarius111221221".
      03 FILLER   PIC X(20) VALUE "Capricorn  212221231".
      03 FILLER   PIC X(20) VALUE "Aquarius   301200218".
      03 FILLER   PIC X(20) VALUE "Pisces     402190320".
   02 ZodiacSign REDEFINES ZodiacTableData
                 OCCURS 12 TIMES
                 INDEXED BY Zidx.
      03 SignName        PIC X(11).
      03 SignElement     PIC 9.
      03 StartDate       PIC X(4).
      03 EndDate         PIC X(4).

01 ElementTable VALUE "Fire EarthAir  Water".
   02 Element OCCURS 4 TIMES PIC X(5).

METHOD-ID. getSignHouse.
LOCAL-STORAGE SECTION.
01 WorkDate.
   88 SignIsCusp  VALUE "0120", "0121", "0219", "0220",
                        "0320", "0321", "0420", "0421",
                        "0521", "0522", "0621", "0622",
                        "0723", "0724", "0823", "0824",
                        "0923", "0924", "1023", "1024",
                        "1122", "1123", "1221", "1222".
   02 WorkMonth          PIC XX.
   02 WorkDay            PIC XX.

LINKAGE SECTION.
01 InDate.
   02 InDay              PIC XX.
   02 InMonth            PIC XX.

01 House                 PIC 99.
01 OpStatus              PIC 9.
   88 CuspSign           VALUE 1.
   88 InvalidDate        VALUE 2.

PROCEDURE DIVISION USING InDate, House RETURNING OpStatus.
  MOVE InDay   TO WorkDay
  MOVE InMonth TO WorkMonth
  MOVE 0 TO OpStatus
  SET Zidx TO 1
  SEARCH ZodiacSign
     AT END IF WorkDate >= "0101" AND <= "0119"
                         MOVE 11 TO House
            END-IF
     WHEN WorkDate >= StartDate(Zidx) AND <= EndDate(Zidx)
          SET House TO Zidx
  END-SEARCH
  IF SignIsCusp SET CuspSign TO TRUE
  END-IF

  EXIT METHOD.
END METHOD getSignHouse.

METHOD-ID. getSignName.
LINKAGE SECTION.
01 House                 PIC 99.
   88 ValidSignHouse     VALUE 01 THRU 12.
01 OutSignName           PIC X(11).

01 OpStatus              PIC 9.
   88 InvalidSignHouse   VALUE 1.
   88 OperationOk        VALUE 0.

PROCEDURE DIVISION USING House, OutSignName RETURNING OpStatus.
  IF NOT ValidSignHouse
     SET InvalidSignHouse TO TRUE
   ELSE
     MOVE SignName(House) TO OutSignName
     SET OperationOk TO TRUE
  END-IF
  EXIT METHOD.
END METHOD getSignName.

METHOD-ID. getSignElement.
LINKAGE SECTION.
01 House    PIC 99.
   88 ValidSignHouse     VALUE 01 THRU 12.
01 OutSignElement        PIC X(5).

01 OpStatus              PIC 9.
   88 InvalidSignHouse   VALUE 1.
   88 OperationOk        VALUE 0.

PROCEDURE DIVISION USING House, OutSignElement RETURNING OpStatus.
  IF NOT ValidSignHouse
     SET InvalidSignHouse TO TRUE
   ELSE
     MOVE Element(SignElement(House)) TO OutSignElement
     SET OperationOk TO TRUE
  END-IF
  EXIT METHOD.
END METHOD getSignElement.
END OBJECT.
END CLASS Zodiac.

1  On the Criteria to Be Used in Decomposing Systems into Modules. Commun. ACM 15, no. 12 (December 1972).

2  Wayne P. Stevens, Glenford J. Myers, and Larry L. Constantine. “Structured Design,” in Classics in Software Engineering, ed. Edward N. Yourdon (Upper Saddle River, NJ: Yourdon Press, 1979), 205–232.

3  David Parnas, “On the Criteria to Be Used in Decomposing Systems into Modules. Commun. ACM 15, no. 12 (December 1972).

4  Glenford J. Myers, Reliable Software through Composite Design (New York: Van Nostrand Reinhold, 1975).

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

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