1 Objects and Classes

Java’s popularity is due to a number of factors. One of the biggest reasons is that it is a popular object-oriented language.

This sounds impressive, but what exactly is an object-oriented language? In fact, what is an object?

Simply put, an object is a collection of code organized to perform a function or simply to retain some information on behalf of another program. Objects are created and then used by programs to perform these functions on behalf of the other programs.

Object-oriented (OO) languages, and the object-oriented design approach, contain many ideas already familiar to you. Chapters 1 through 5 will start by describing these concepts, based on the COBOL language. I will then compare Java’s definition of objects, and the syntax that supports it, to these concepts. This should help you acquire a good understanding of the basic object-oriented concepts.

THE COBOL SUBROUTINE

I’ll start with the COBOL subroutine. A COBOL subroutine is a source file that contains COBOL code and implements a logical function. It is organized so that other programs can prepare the appropriate information, call the subroutine, and perform the function. Subroutine parameters are described in the LINKAGE SECTION of the subroutine. The subroutine is able to evaluate or modify passed parameters as part of its algorithm.

The calling program uses a subroutine when it defines and prepares the parameter items for the subroutine, and then calls it. The parameters are passed to the subroutine, using the CALL SUBROUTINE USING statement. After the subroutine completes its function, the calling program can examine the parameter items to see the information returned by the subroutine.

CALLING A SUBROUTINE

In Figure 1.1 the calling program (CALLER) prepares a text item as a parameter. It then calls the subroutine (MYSUB), passing this parameter and another parameter.

Image

FIGURE 1.1
Calling a subroutine.

The subroutine accepts both of these parameters. Its algorithm is roughly defined as follows: Evaluate the first parameter and set the second, based on some predefined criteria. The details of the evaluation function (that is, the heart of the subroutine’s algorithm) are embedded in the subroutine.

The calling program can now evaluate the return parameter, in effect using the evaluation logic of the subroutine. The calling program only needs to know how to call the subroutine and how to evaluate the result of that call. It does not need to know any other details of the subroutine’s internal logic.

Objects behave in much the same manner. An object is a collection of code that accepts parameters, implements a function, and returns information to the calling program. Objects, however, differ from a standard COBOL subroutine in a number of ways. One important difference is that objects are created dynamically (at runtime) by a program. They are always associated with, or “tied to,” the program that created them. Furthermore, a program can create many objects of the same type, or class.

Image

An object can be understood as a subroutine called with a particular set of linkage items.

MYSUB COBOL

Suppose you’ve defined a subroutine as follows:

IDENTIFICATION DIVISION.
PROGRAM-ID. MYSUB.
***********************************************************************
*
* This routine accepts a text item as a parameter and evaluates the
*
* text. If the text is all spaces, MSG-SIZE will be set to 0. Else,
*
* MSG-SIZE will be set to 1.
*
* The text item will also be stored in the passed control structure in
*
* MSG-TEXT.
*
***********************************************************************
*
DATA DIVISION.
WORKING-STORAGE SECTION.
*   These are the subroutine parameter definitions.
LINKAGE SECTION.
01 MYSUB-CONTROL.
     03     MSG-TEXT     PIC X(20).
     03     MSG-SIZE     PIC 9(8).

01 TEXT-STRING                PIC X(20).
*   This is the interface definition for the subroutine.
PROCEDURE DIVISION USING MYSUB-CONTROL, TEXT-STRING.

MYSUB-INITIAL SECTION.
MYSUB-INITIAL-S.
*   Perform the subroutine's function. Test the passed string for spaces
*   and set MSG-SIZE accordingly.
     IF TEXT-STRING = SPACES
          MOVE 0 TO MSG-SIZE
     ELSE
          MOVE 1 TO MSG-SIZE.
     MOVE TEXT-STRING TO MSG-TEXT.
EXIT-PROGRAM.
     EXIT PROGRAM.

CALLER COBOL

Now, suppose you’ve written a calling program that uses this subroutine:

IDENTIFICATION DIVISION.
PROGRAM-ID. CALLER.
DATA DIVISION.
WORKING-STORAGE SECTION.
*   Create the parameter definitions.
01 MYSUB-CONTROL.
     03     MSG-TEXT     PIC X(20).
     03     MSG-SIZE     PIC 9(8).
01 TEXT-STRING                PIC X(20).

PROCEDURE DIVISION.

START-PROGRAM SECTION.
START-PROGRAM-S.
*   Prepare the parameters.
     MOVE "ANYTEXT" TO TEXT-STRING.
*   Call the subroutine.
     CALL "MYSUB" USING MYSUB-CONTROL, TEXT-STRING.
*   Evaluate the result.
     IF MSG-SIZE OF MYSUB-CONTROL = 0
        DISPLAY "MSG SIZE equals 0"
     ELSE
        DISPLAY "MSG SIZE equals," MSG-SIZE.

EXIT-PROGRAM.
    EXIT PROGRAM.
    STOP RUN.

Let’s examine these two programs from an object-oriented perspective, using the terminology of the object-oriented design methodology.

You can consider the subroutine MYSUB a class. That is, every time MYSUB is called—even if it is called from different programs—it will behave the same way. Any features, or logic, that MYSUB has will be available to all calling programs. At the same time, some parts of MYSUB are not available to the outside world. For example, any variables in MYSUB’s WORKING-STORAGE are private to MYSUB. And the details of MYSUB’s logic are not known to any calling programs; only its interface (or LINKAGE SECTION) is published.

You can consider any instance of the parameter item MYSUB-CONTROL in a calling program as an object after MYSUB has been called. That is, after MYSUB has performed its logic (at the request of a calling program), the result of that logic is available in MYSUB-CONTROL.

A calling program can examine or modify the contents of items in MYSUB-CONTROL (MSG-TEXT or MSG-SIZE) and perform some logic based on those contents. These items are called class data members, or properties in OO terminology.

Another program in the COBOL run unit can call MYSUB, with its own MYSUB-CONTROL (parameter), and evaluate the result. In this case, CALLER #1’s copy of MYSUB-CONTROL will, of course, not be affected by CALLER #2. Each instance of a MYSUB-CONTROL area will now contain unique information. In this case, the unique MYSUB-CONTROL areas are objects. In fact, a single program can manage two separate MYSUB-CONTROL(s) as long as they have unique names.

CALLER COBOL: CONTROL

Suppose you’ve defined CONTROL areas for two subroutines as follows:

IDENTIFICATION DIVISION.
PROGRAM-ID. CALLER.
DATA DIVISION.
WORKING-STORAGE SECTION.
*   Create one set of parameter definitions.
01 MYSUB1-CONTROL.
     03     MSG-TEXT     PIC X(20).
     03     MSG-SIZE     PIC 9(8).
*   Create a second set of parameter definitions.

01 MYSUB2-CONTROL.
     03     MSG-TEXT        PIC X(20).
     03     MSG-SIZE        PIC 9(8).

01 DISPLAY-MESSAGE          PIC X(20).
01 TEXT-STRING              PIC X(20).

PROCEDURE DIVISION.

PROGRAM-START SECTION.
PROGRAM-START-S.
*   Prepare the first set of parameters, and call MYSUB.
     MOVE "ANYTEXT" TO TEXT-STRING.
     CALL "MYSUB" USING MYSUB1-CONTROL, TEXT-STRING.
*   Prepare the second set and call MYSUB.
     MOVE SPACES TO TEXT-STRING.
     CALL "MYSUB" USING MYSUB2-CONTROL, TEXT-STRING.
*   Evaluate the data associated with the first set and then the second
*    set.
     IF MSG-SIZE OF MYSUB1-CONTROL > 0
          MOVE MSG-TEXT OF MYSUB1-CONTROL TO DISPLAY-MESSAGE
     ELSE IF MSG-SIZE OF MYSUB2-CONTROL > 0
          MOVE MSG-TEXT OF MYSUB2-CONTROL TO DISPLAY-MESSAGE.

     DISPLAY "DISPLAY-MESSAGE: ", DISPLAY-MESSAGE.

EXIT-PROGRAM.
    EXIT PROGRAM.
    STOP RUN.

You can consider all instances of MYSUB-CONTROL (after MYSUB has been called) to be class instances, or objects. In the example, MYSUB1-CONTROL is one object, and MYSUB2-CONTROL is a second. It is up to the calling program (the consumer of MYSUB) to manage these objects (i.e., the two instances of MYSUBx-CONTROL) as part of the application logic.

For example, if one MYSUBx-CONTROL contains an error message from the database system, and the other MYSUBx-CONTROL contains an error message from the communications system, it is up to the calling application to decide which one to display at the correct time.

*   Prepare the database message parameters, and call MYSUB.
     MOVE "Unable to connect to the DataBase." TO TEXT-STRING.
     CALL "MYSUB" USING MYSUB1-CONTROL, TEXT-STRING.
*   Prepare the communications message parameters, and call MYSUB.
     MOVE "Invalid connection request." TO TEXT-STRING.
     CALL "MYSUB" USING MYSUB2-CONTROL, TEXT-STRING.
*   Prepare the generic message parameters, and call MYSUB.
     MOVE "An unknown error has occurred." TO TEXT-STRING.
     CALL "MYSUB" USING MYSUB3-CONTROL, TEXT-STRING.

     ...

Later on in this program:

*   An error has occurred. The type of error has been recorded in
*   DISPLAY-MSG-TYPE-SW.
*   Evaluate which type of error occurred, and display the correct
error
*   message text item.
     IF DISPLAY-MSG-TYPE-SW = "D"
          MOVE MSG-TEXT OF MYSUB1-CONTROL TO DISPLAY-MESSAGE
     ELSE IF DISPLAY-MSG-TYPE-SW = "C"
          MOVE MSG-TEXT OF MYSUB2-CONTROL TO DISPLAY-MESSAGE
     ELSE
          MOVE MSG-TEXT OF MYSUB3-CONTROL TO DISPLAY-MESSAGE.
     PERFORM DISPLAY-ERROR-MESSAGE.

The previous code fragments are examples of how a COBOL program might use three objects. Each of these objects is based on the class MYSUB.

TERMS TO REVIEW: SUBROUTINES

Here are some of the concepts that have been discussed and how to understand them from a COBOL perspective.

Class: A subroutine is similar to a class. It can perform certain functions when called. The subroutine developer defines these functions. Many calling programs can use this subroutine in order to perform those functions.

Interface: The signature, or parameter specification, for a particular subroutine (or class, in OO terms). In COBOL, a subroutine’s signature is the list of items in the subroutine’s LINKAGE SECTION. Some items in an interface may be input parameters, and some may be result parameters, or both.

Object: An instance of a class, similar to an instance of the COBOL subroutine’s CONTROL area, after the subroutine has been called. You can think of an object as the result of initializing the subroutine or calling it for the first time. This result is stored in the subroutine’s CONTROL area.

Class data members: The data items that are associated with the subroutine (or class). Class data members include both the data elements in the subroutine’s LINKAGE SECTION and the data elements in the subroutine’s WORKING-STORAGE. Class data members are also called properties of the class.

Private: Any data elements (or properties) that belong to the class but are not available outside the class. In COBOL, the items in a subroutine’s WORKING-STORAGE area are private. (This COBOL allegory is not precise; I will clarify it as I go.)

Public: Any data elements (or properties) that belong to the class but are available outside the class. They are similar to items in a COBOL subroutine’s LINKAGE SECTION.

The elementary items in MYSUB-CONTROL (e.g., MSG-TEXT and MSG-SIZE) can be considered data members of the class for the following reasons:

  • They are data elements that belong to the class definition. This means that they are only useful as part of the parameter definition for MYSUB. The items in MYSUB-CONTROL will behave correctly (i.e., MSG-SIZE will be set to 0 or 1) only after MYSUB is called.

  • They are unique to each instance of the class. More than one instance of MYSUB-CONTROL can be defined and passed as a parameter to MYSUB. The items in any instance of MYSUB-CONTROL will contain information based on the last time MYSUB was called with that instance of MYSUB-CONTROL.

  • They can be evaluated and/or set by both the calling program and the subroutine. The data items in the MYSUB-CONTROL define the interface to MYSUB. This means that a calling program can communicate with MYSUB by using the data items defined in MYSUB-CONTROL.

OBJECTS AND JAVA

Let’s examine what what’s been discussed using Java’s syntax.

ERRORMSG CLASS

This is the outline of a Java class definition:

public class ErrorMsg {
     public String msgText;
     public int msgSize;
          ...
 // Some logic
          ...
}

The first line defines the class.

Image

These next two lines declare the class instance data members, or properties. These are associated with each instance of this class and can be of any valid type. In many ways, they are analogous to the data items in MYSUB-CONTROL.

Image

These two statements define the public data members for the class ErrorMsg.

The statements could be read this way: “The first data member is a public data member, its type is String, and its name is msgText.” “The second data member is a public data member, its type is int, and its name is msgSize.”

In order to use (or to call) this class, the consumer of this class (i.e., the caller) creates a new instance of the class with the new operation. This is very similar in concept to the COBOL example that defined several unique MYSUBx-CONTROL areas in calling the COBOL program.

CALLER CLASS

Image

This statement could be read as follows: “Create a new object of class ErrorMsg, and give it the name myErrorMsg.”

This statement allocates memory for the new object, calls its constructor (more on this later), and returns a reference variable (a kind of pointer) to this new object. In the example, the pointer to the new class is stored in the object reference variable myErrorMsg. This reference variable is managed by the calling program in a manner very similar to the way MYSUBx-CONTROL areas are managed in the COBOL program. Note that the class name and the constructor name are the same and that the constructor is called with an empty parameter list, indicating the default constructor.

Later, the program that contains this statement can use the reference variable name myErrorMsg to refer to any class data members that belong to this object. The period (.) operator is used to access members of an object. The member name is used to specify which member is being accessed.

For example, statement 1 will assign a string containing "Some Text" to the member variable msgText. The object that is modified is “pointed to” by the reference variable myErrorMsg.

Image

Statement 2 is another example of how myErrorMsg.msgText can be used:

Image

Statement 1 assigns the string "Some Text" to the data member msgText. The object whose data member is being set is, of course, myErrorMsg. This object is an object of type ErrorMsg. That is, it is an instance of the class ErrorMsg. Statement 2 assigns the current string in the data member msgText to a local string variable called localText.

TERMS TO REVIEW: OBJECTS

Here are some object-oriented concepts and how to understand them from a Java perspective.

Class: A Java class is a logical grouping of data and methods (methods are conceptually similar to functions) that use the data. In concept, a Java class is similar to a COBOL subroutine: It contains some data elements, it can perform functions when requested, and the subroutine developer defines these functions. Many calling programs can use this class to perform available functions and can manage the data that belong to the class.

Object: An instance of a class. This is similar to an instance of a COBOL subroutine and a unique set of LINKAGE AREA items. You can think of an object as the result of initializing the class or calling it for the first time. However, unlike a COBOL subroutine, many instances of a class can be easily created and managed by the same calling program.

Reference variable: A variable that contains a pointer to an object. After an object is created, the reference variable points to it. A reference variable is used by the calling program to access the data members and functions (that is, the methods) that belong to the object. This is similar to an instance of CALLER’s MYSUBx-CONTROL area after the subroutine has been called.

New: The Java operation that creates an instance of the class (i.e., the object). It returns a reference variable that points to the new object.

Constructor: Constructors are invoked when an object is first created. Constructors are similar to methods, but are not considered real methods in Java. For example, constructors cannot be invoked directly.

Data members of the class: The data items or properties that are associated with the class. They include all of the data elements that are defined in the class. These variables are created at the same time each instance of a class is created. They normally belong to each instance of a class and are not shared by unique class instances.

Private: Any data elements (or properties) that belong to the class but are not available outside the class. Private data elements are identified with the keyword private. They are similar in this respect to items in a COBOL subroutine’s WORKING-STORAGE area, since a calling program cannot directly access these items.

Public: Any data elements (or properties) that belong to the class but are available outside the class. Public data elements are identified with the access keyword public. They are similar in this respect to items in a COBOL subroutine’s LINKAGE SECTION.

Now let’s explore another object-oriented design principle and how it relates to some COBOL concepts.

Image

A calling program contains its objects.

Try to visualize for a moment what happens when a COBOL main program calls a subroutine. At runtime, and after the subroutine has been called, both the main program and the subroutine exist in memory. The executing program environment (the COBOL run unit) contains both the main program and the subroutine, as depicted in Figure 1.2.

Image

FIGURE 1.2
A COBOL run unit.

The items passed in the USING clause are the parameters to the subroutine. The subroutine can access any of the items that have been passed to it and can access items in its own WORKING-STORAGE area. The MYSUBx-CONTROL areas contain the results of the most recent call to MYSUB.

Note that while the main program can access items in the passed parameters, it cannot access any items in the subroutine’s WORKING-STORAGE area. Further, Figure 1.2 shows two separate instances of MYSUBx-CONTROL data items but only one instance of the MYSUB subroutine. This means that all of the items in MYSUB’s WORKING-STORAGE area will be shared, regardless of whether MYSUB1-CONTROL or MYSUB2-CONTROL is passed. Because of this limitation, the COBOL program does not behave exactly like an object.

In much the same way, a Java program contains any instances of the classes that it creates. The major difference between a COBOL subroutine and a Java class is that a Java program can contain many instances of its classes. These are called objects (see Figure 1.3).

Image

FIGURE 1.3
A Java run unit.

The new operation creates a completely new instance of the class in memory, including any private data members (WORKING-STORAGE items) and then loads the class code into memory, if it has not been loaded already. All of the data members defined for that class are created. A reference variable is returned from the new operation, and this reference variable, or handle, points to the new class instance. These class instances are called objects.

Like items in a COBOL routine’s LINKAGE SECTION, public data members defined by the class can be accessed by either the main (calling) program or by the object itself. Unlike the COBOL subroutine’s WORKING-STORAGE area, internal data members are not shared between instances of these two classes.

An object reference variable (for example, myErrorMsg) points to each unique instance of the class. The Java main program uses the reference variable to refer to the data members of a particular class instance in much the same way that COBOL’s OF operator works (for example, MSG-TEXT OF MYSUB1-CONTROL). Therefore, the statement

myErrorMsg.msgText     = "Some Text";

could be compared to the COBOL statement

MOVE "Some Text" TO MSG-TEXT OF MY-ERROR-MSG.

It’s time to interrupt this object-oriented presentation and write some code. Before you write your first program, however, let’s take a moment to examine how Java programs are compiled and executed.

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

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