4 Class Members

I’ll continue to extend the examples in order to explore other Java concepts.

Image

The principle of data encapsulation is similar to the difference between a subroutine’s WORKING-STORAGE and its LINKAGE SECTION.

COBOL specifies that items in a subroutine’s WORKING-STORAGE can only be viewed and modified by the subroutine. Conversely, items in a subroutine’s LINKAGE SECTION are constructed by the caller, then passed into the subroutine. Therefore, LINKAGE SECTION items are available to both the subroutine and the caller, and the items in a subroutine’s WORKING-STORAGE are not.

Suppose you want MYSUB to count the number of times it has been called. In this case, you would define a variable in WORKING-STORAGE and increment it each time MYSUB is called.

Figure 4.1 shows how LINKAGE SECTION items are available to both caller and subroutine, whereas WORKING-STORAGE items in the subroutine are private to the subroutine.

Image

FIGURE 4.1
A subroutine has both LINKAGE AREA and WORKING-STORAGE.

In this way, the subroutine specification defines what is available to external programs and what is private to the subroutine. At the same time, the subroutine is free to define any internal items, based on its own requirements. The calling program is not aware of these details.

MYSUB COBOL

In this subroutine, CALL-COUNTER is a private variable and cannot be directly accessed by a caller. As a result, the number of times MYSUB has been called is not discovered by calling programs.

    PROGRAM-ID. MYSUB.
    DATA DIVISION.


    WORKING-STORAGE SECTION.
    01 CALL-COUNTER                          PIC S9(17) COMP-3 VALUE 0.


    LINKAGE SECTION.
    01 MYSUB-CONTROL.

        03   MYSUB-ACTION-SWITCH        PIC X.
             88 MYSUB-ACTION-EVALUATE             VALUE "E".
             88 MYSUB-ACTION-SET-AND-EVALUATE     VALUE "S".
        03   MSG-TEXT                              PIC X(20).
        03   MSG-SIZE                              PIC 9(8).

    01 TEXT-STRING                      PIC X(20).

    PROCEDURE DIVISION USING MYSUB-CONTROL, TEXT-STRING.

    MYSUB-INITIAL SECTION.
    MYSUB-INITIAL-S.
    *   Increment the counter variable in WORKING-STORAGE SECTION.
         ADD 1 TO CALL-COUNTER.
    *   Perform some function to detect the number of arguments.
         PERFORM GET-ARGUMENT-COUNT.
    *   Determine whether TEXT-STRING or MSG-TEXT should be
    *   evaluated. Store the correct item in LOCAL-TEXT.
         IF ARGUMENT-COUNT = 2
              MOVE TEXT-STRING TO LOCAL-TEXT
         ELSE
              MOVE MSG-TEXT TO LOCAL-TEXT.
    *   Now, use LOCAL-TEXT in the subroutine's logic.
         IF LOCAL-TEXT = SPACES
              MOVE 0 TO MSG-SIZE
         ELSE
              MOVE 1 TO MSG-SIZE.

         IF MYSUB-ACTION-SET-AND-EVALUATE
              MOVE LOCAL-TEXT TO MSG-TEXT.

    EXIT-PROGRAM.
         EXIT PROGRAM.

    GET-ARGUMENT-COUNT SECTION.
    GET-ARGUMENT-COUNT-S.
    *   Set ARGUMENT-COUNT to the result.
           CALL "GET$NARGS" USING ARGUMENT-COUNT.

CALL-COUNTER is available only to MYSUB. Of course, you could define a new ACTION-SWITCH that would allow you to get the current value of CALL-COUNTER as follows in the next section.

MYSUB COBOL: ACTION-SWITCH

If this new ACTION-SWITCH is set, MYSUB returns the value from a private variable.

01 MYSUB-CONTROL.
    03   MYSUB-ACTION-SWITCH               PIC X.
         88 MYSUB-ACTION-EVALUATE         VALUE "E".
         88 MYSUB-ACTION-SET-AND-EVALUATE VALUE "S".
         88 MYSUB-ACTION-GET-CALL-COUNTER VALUE "G".
    03   MSG-TEXT                          PIC X(20).
    03   MSG-SIZE                          PIC 9(8).
    03   MYSUB-RETURNED-CALL-COUNTER       S9(17) COMP-3.

      ...

 MYSUB-INITIAL SECTION.
 MYSUB-INITIAL-S.

     ...
*   If requested, return the value in the counter variable.
     IF MYSUB-ACTION-GET-CALL-COUNTER
          MOVE CALL-COUNTER TO MYSUB-RETURNED-CALL-COUNTER.
     ...

This type of interface would allow a calling program to ask MYSUB to return the number of times it has been called. An approach such as this one allows the subroutine designer to decide which internal variables to make available and how a calling program should access them. In support of this design, CALL-COUNTER is managed as a private variable and MYSUB-RETURNED-CALL-COUNTER as a public variable.

JAVA VARIABLES

In a similar way, Java variables can be private or public. Public variables can be directly viewed or modified by other classes, whereas private variables cannot. Java also supports package variables, which are somewhere in between (that is, they are available to classes in a defined group of classes called a package). Variables that are not declared private or public will default to package variables. Finally, Java also defines another type, protected, which has to do with a feature called inheritance, a topic I will discuss later.

ERRORMSG CLASS

This portion of the ErrorMsg class increments the private variable named counter.

public class ErrorMsg {

     public String   msgText;
     public int      msgSize;
     private int     counter = 0;
     package char    interfaceInUse;

     public void setErrorMsg (String inputMsg) {
        counter = counter + 1;
        interfaceInUse = 'S';
        ...
// Some logic
        ...
        }
  }

You can examine the new member definitions and how they are used:

Image

This example also introduces the concept of data variable initialization. Similar to COBOL’s syntax, Java variables can be assigned an initial value. Unless a specific value is given, variables are initialized with their default natural values (for example, NULL for object types, and 0 for numeric types). The developer can assign other initial values to variables using the syntax = value or by using the new directive for objects.

Image

Finally, data members can also be assigned the static access control. This control specifies that only one instance of the data member exists, and it is available to all instances of this class in the current run unit. In Java, you call this type of variable a class variable. In this sense, these types of data items are like data items in a COBOL subroutine’s WORKING-STORAGE. That is, only one instance of this variable exists, and every class of this type can access it.

Static class members can be either public, private, or protected. If a static data item is private, then only classes of this type can access it (like WORKING-STORAGE items in COBOL). If a static data item is public, then every other class can access it as well (like the EXTERNAL access control in COBOL).

Image

Just like data members, Java methods can also be declared as public, private, package, or static. For example, these statements

public    void setErrorMsg (String inputMsg) () {
private   void countErrorMsg () {
          void checkErrorMsg (String inputMsg) {
public static  void SETLANGUAGE (char languageFlag) {

define four methods: one public, one private, one package method, and one that is a static method. The default access control is package, which is why checkErrorMsg does not have a qualifier.

CLASSES, OBJECTS, AND MEMBERS REVIEW

This is a good time to review some important concepts:

  • A Java class is the blueprint, or specification, for all instances of its type.

  • A Java object is an instance of a class.

  • A calling program (a class itself) first creates a new object prior to using it.

  • In the process, the calling program stores a reference to the object in an object instance variable (also known as a reference variable). This reference variable is a handle, or a pointer, to the object. It contains identifying information about the object, including information such as the object’s storage location (in memory).

  • The calling program can create many instances of a class and manages each instance by managing the reference variable.

  • Data members (variables) and methods that are defined by this class are automatically members of this object. They are associated with this instance of the object and are accessed using the object instance variable as a prefix.

  • A program can use these object instance (reference) variables to manage more than one instance of a class. For example:

    Image

In this example, myErrorMsg is one object instance variable, and myotherErrorMsg is another. They point to different objects of type ErrorMsg.

The object instance variable is used to identify the object that contains the data members or methods:

Image

or

Image

If you understand these terms and followed the descriptions of these concepts, you understand the most important OO concepts (classes, objects, and members). These concepts are the core principles (or building blocks) of any OO language, including Java.

OBJECTS AND COBOL

In the COBOL examples, you simulated the concept of object instance variables by creating unique instances of MYSUB-CONTROL:

01 MYSUB1-CONTROL.
     03   MYSUB1-ACTION-SWITCH                PIC X.
     03   MSG-SIZE                            PIC 9(8).
          ...

01 MYSUB2-CONTROL.
     03   MYSUB2-ACTION-SWITCH                PIC X.
     03   MSG-SIZE                            PIC 9(8).
          ...

The program that contained both of these definitions and also called MYSUB with each one would now have two unique instances of the variables in MYSUBx-CONTROL, reflecting the result of MYSUB’s logic:

IF MSG-SIZE OF MYSUB1-CONTROL = 0
     ...
ELSE IF MSG-SIZE OF MYSUB2-CONTROL = 0
     ...
END-IF

Of course, any other calling program could use the name MYSUB-CONTROL or MYSUB1-CONTROL. These would refer to a different instance of this CONTROL.

This COBOL coding style represents concepts very similar to the Java concepts of classes, objects, and members. That is, a calling program first defines a unique instance of a class, creating an object that can be referenced by name (MYSUB2-CONTROL). This object variable name is used as a prefix to access the member variables for this particular object.

Although very similar, Java’s implementation of these concepts is slightly different. One difference in particular probably causes the most trouble for COBOL programmers. That is, all data members (or properties) of a class, whether private or public, are associated with a class instance (or object). Properties are associated with a particular instance of a class, not with all instances of that class.

To better understand this from a COBOL perspective, imagine that each time you call a subroutine with a new MYSUB-CONTROL, a unique instance of that subroutine is created for you. Further, imagine that the system automatically calls an initialization section in the subroutine (in Java terms, its constructor), so that this instance of the subroutine can perform any initializations required. And finally, suppose that every time a new MYSUB-CONTROL is used as a parameter to the MYSUB subroutine, the system would create your own private copy of the subroutine. Therefore, it would appear as if there were separate copies of all items in the subroutine’s WORKING-STORAGE (items like CALL-COUNTER), one for each instance of MYSUBx-CONTROL. Actually, it is possible to emulate this behavior quite easily in COBOL.

If your subroutine contains only temporary WORKING-STORAGE items, and uses only items in the LINKAGE SECTION, then it behaves very much like an object. Instead of defining items in WORKING-STORAGE, suppose the subroutine defines a slightly different representation of the items in the LINKAGE SECTION, which includes items known only to the subroutine. In this case, these items can be considered private, compared to the public items known to the caller. Add an INITIALIZE action switch, and you pretty much have a COBOL object. In fact, this is more or less what every OO compiler does internally, regardless of language.

Let’s complete the MYSUB example to present this concept. Up to now, you defined only public items in the LINKAGE SECTION and private items in MYSUB’s WORKING-STORAGE SECTION. The items in WORKING-STORAGE will be shared across all instances of MYSUBx-CONTROL. Remember how you used this principle to create the COUNTER variable, which counts the number of times MYSUB is called?

You could create an instance of this COUNTER, one that is specific to each MYSUBx-CONTROL. You do this simply by defining a COUNTER item in MYSUBx-CONTROL. If only MYSUB (the subroutine) is aware of this item, then it could be considered a private variable. Finally, you need to define an INITIALIZE action switch so that you can properly initialize this variable.

01 MYSUB-CONTROL.
     03 MYSUB-ACTION-SWITCH                PIC X.
        88 MYSUB-ACTION-INITIALIZE        VALUE "I".
        88 MYSUB-ACTION-EVALUATE          VALUE "E".
        88 MYSUB-ACTION-SET-AND-EVALUATE  VALUE "S".
        88 MYSUB-ACTION-GET-CALL-COUNTER  VALUE "G".
     03 MSG-TEXT                      PIC X(20).
     03 MSG-SIZE                      PIC 9(8).
     03 MYSUB-RETURNED-CALL-COUNTER        PIC 9(10).

The next item contains the private items in MYSUB-CONTROL:


03 MYSUB-PRIVATE-ITEMS                    PIC X(20).

The MYSUB subroutine is expanded 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.                                           *
* If requested, the text item will also be stored in the               *
* passed control structure.                                            *
* If the text item is not passed, then MSG-TEXT                        *
* will be evaluated instead.                                           *
* MYSUB will count the number of times it has been                     *
* with a particular MYSUBx-CONTROL and the number of                   *
* times it has been called using all CONTROLs.                         *
* MYSUB must be called with the INITIALIZE action when                 *
* any new CONTROL is to be used.                                       *
************************************************************************
DATA DIVISION.

WORKING-STORAGE SECTION.
01 CALL-COUNTER                    PIC 9(10) VALUE 0.
01 ARGUMENT-COUNT                  PIC 9.
01 LOCAL-TEXT                      PIC X(20).

LINKAGE SECTION.
*   Below you have a view of MYSUB-CONTROL that is used by the
*   MYSUB subroutine:
01 MYSUB-CONTROL.

     03  MYSUB-ACTION-SWITCH               PIC X.
         88 MYSUB-ACTION-INITIALIZE       VALUE "I".
         88 MYSUB-ACTION-EVALUATE         VALUE "E".
         88 MYSUB-ACTION-SET-AND-EVALUATE VALUE "S".
         88 MYSUB-ACTION-GET-CALL-COUNTER VALUE "G".
     03 MSG-TEXT                           PIC X(20).
     03 MSG-SIZE                           PIC 9(8).
     03 MYSUB-RETURNED-CALL-COUNTER        PIC 9(10).
     03 MYSUB-PRIVATE-ITEMS                PIC X(20).
*   In the subroutine's definition of MYSUB-CONTROL,
*   PRIVATE-ITEMS is redefined with items known only to the subroutine.
     03   FILLER REDEFINES MYSUB-PRIVATE-ITEMS.
          05   MYSUB-PRIVATE-COUNTER        PIC 9(8).
          05   MYSUB-OTHER-PRIVATE-ITEMS    PIC X(12).

01 TEXT-STRING                              PIC X(20).

PROCEDURE DIVISION USING MYSUB-CONTROL, TEXT-STRING.

MYSUB-INITIAL SECTION.
MYSUB-INITIAL-S.
*   The program then performs some function to detect the number of
*   arguments,
     PERFORM GET-ARGUMENT-COUNT.
     IF ARGUMENT-COUNT = 2
          MOVE TEXT-STRING TO LOCAL-TEXT
     ELSE
          MOVE MSG-TEXT TO LOCAL-TEXT.
*   Increments the Global counter,
     ADD 1 TO CALL-COUNTER.
*   processes the ACTION-SWITCHES,
     IF MYSUB-ACTION-INITIALIZE
*   and initializes the instance counter.
          MOVE 0 TO MYSUB-PRIVATE-COUNTER
*   If requested, the program returns the value in the counter
*   variable.
     ELSE IF MYSUB-ACTION-GET-CALL-COUNTER
          MOVE CALL-COUNTER TO MYSUB-RETURNED-CALL-COUNTER
     ELSE IF MYSUB-ACTION-EVALUATE
*   This is a request to evaluate the text item.
          PERFORM EVALUATE-TEXT-ITEM.
*   The program increments the instance counter.
     ADD 1 TO MYSUB-PRIVATE-COUNTER.

EXIT-PROGRAM.
     EXIT PROGRAM.

EVALUATE-TEXT-ITEM SECTION.
EVALUATE-TEXT-ITEM-S.
     IF LOCAL-TEXT = SPACES
          MOVE 0 TO MSG-SIZE
     ELSE
          MOVE 1 TO MSG-SIZE.
     MOVE LOCAL-TEXT TO MSG-TEXT.

GET-ARGUMENT-COUNT SECTION.
GET-ARGUMENT-COUNT-S.
*   The program sets ARGUMENT-COUNT to the result.
      CALL "C$NARGS" USING ARGUMENT-COUNT.

You have just defined a COBOL subroutine that behaves very much like an object! Two characteristics of the way you’ve used COBOL make this possible. Some data items in MYSUB-CONTROL are public (i.e., known to the caller), some are private (known only to the subroutine), but all data items (in the LINKAGE SECTION) are unique to a given MYSUB-CONTROL. No data associated with a particular MYSUB-CONTROL is stored in the WORKING-STORAGE of the subroutine.

USING OBJECTS IN JAVA

Java naturally associates both data member variables and methods with a particular instance of a class unless the members and methods are defined as static. This means that you should view members of a class as being associated with an instance variable (e.g., myErrorMsg.msgText), even though it is defined by the class.

It is this treatment of data members of the class as properties of a particular class, along with the capability of class members to be declared as public, private, or protected, that implements the OO principle of encapsulation. A class is said to encapsulate some logic or behavior and to publish only those members that are appropriate for other classes to use. Class members are managed as if they were simply attributes of an instance of the class (i.e., an object). In many respects, a class is just another data type, one with user-defined attributes, and it includes whatever code is necessary to support those attributes. By extension, then, an object is a variable of type class.

This approach promotes the principle of reuse, that is, the practice of writing a class (a piece of code) that will be used by other classes. Consumer classes only have the view(s) of the class that the class designer thinks appropriate. Consumer classes then use these classes as if they were simply another type of variable. As I have demonstrated with the COBOL programs, it is certainly possible to write programs that do this in any programming language; but with Java, it is almost impossible to code in any other way.

Up to this point, I’ve introduced some OO concepts and described how Java supports these concepts. So it’s a good time to present a more complete definition of these Java terms and syntax.

JAVA DATA MEMBERS

Data members are variables in the normal understanding of variables in computer languages (for example, data ITEMS in COBOL). They are members of a class in the sense that they are attributes of that class and contain its current state information.

Data members can be qualified with access controls, which define how visible the data members are to other classes. Data members can be either public, private, or package variables. Public members are visible outside the class, and they can be set or evaluated by other classes. Private members are only visible inside the class; other classes cannot view or modify these variables. Package members are visible to all classes in a package (you can think about a package as a sort of directory of related class files). Package is the default access condition.

public int       msgSize;
private int      counter = 0;
        char     interfaceInUse;

Java also defines another data member access control, protected, which is used to support inheritance. I will discuss protected access later, along with inheritance.

All data members are normally associated with an instance of a class (i.e., an object). As I discussed earlier, each new instance of a class contains unique copies of all of its variables, both public and private.

With any rule, there is an exception. (Don’t you hate it when you think you finally understand something, and then the instructor throws a curve ball?) Class variables are data members that are associated with all instances of a class. These variables persist for the duration of the program and are shared by all instances of this class. In many respects, class variables are similar to items defined in a COBOL subroutine’s WORKING-STORAGE, except that they can be visible to other subroutines. You can think of public class variables as analogous to COBOL EXTERNAL items in a subroutine.

Class member variables can also be qualified with the keyword Final, which means that this data member variable cannot be modified by any class. This control is commonly used to declare constants, that is, variables that are only used to set or evaluate other variables. These are very similar to how Level 77 items are used in COBOL.

ERRORMSG CLASS

Here are some examples of data members in the ErrorMsg class that have different access controls:

     public class ErrorMsg {
// Public instance variables:
          public String msgText;
          public int msgSize;
// A private instance variable:
          private int counter = 0;
// A package instance variable:
            char     interfaceInUse;
// A public static variable:
          public static int     total_counter;
// A final (i.e., read only) variable
          public final     static int NO_TEXT_FOUND = 0;

          public void setErrorMsg (String inputMsg) {
               interfaceInUse = 'S';
               msgText = inputMsg;
               msgSize = msgText.length ();
               counter = counter + 1;
               total_counter = total_counter + 1;
               ...
               ...
          }
      }

CALLER CLASS

Some other class would use the ErrorMsg class and its variables in this way:

// Create an instance of ErrorMsg.
     ErrorMsg      myErrorMsg = new      ErrorMsg ();
// Create an instance of a String variable and put some text in it.
     String inputMsg = "Some input Text";
// Call the function setErrorMsg.
     myErrorMsg.setErrorMsg (inputMsg);
// Evaluate the size of this instance of ErrorMsg using the constant
// NO_TEXT_FOUND.
     if (myErrorMsg.msgSize == myErrorMsg.NO_TEXT_FOUND) {
           ...
     // Some logic
           ...
     }
// Evaluate the number of times ErrorMsg has been called.
     if (myErrorMsg.total_counter == 100) {
           ...
     // Some logic
           ...
     }
// A static class variable can also be identified using only the class
// name.
// Static variables are not associated with any instance of a class.
    if (ErrorMsg.total_counter == 100) {
          ...
    // Some logic
          ...
    }

LOCAL VARIABLES

Java supports a concept of local variables, an idea without a traditional COBOL equivalent. A Java program can define a variable when it is needed, rather than right up front as part of the class definition.

Imagine that COBOL allowed you to insert variable definitions (e.g., 01 MY-ITEM PIC X) right in the middle of the PROCEDURE DIVISION. Furthermore, suppose that variables defined this way were only associated with the paragraph in which they were defined. When the paragraph completed, the variable would go away. Finally, suppose that another MY-ITEM variable could be defined in the same program but in a different paragraph. This instance of MY-ITEM would really be a separate variable, having nothing to do with the original MY-ITEM. You might wonder what kind of confused code that could lead to!

Java allows this sort of “as needed” temporary variable definition. You can just define variables as they are needed. There is no need to define them all up front, as in COBOL. The language does attempt to tighten up some of the more egregious rules defined by C and C++. (Many C and C++ programmers have struggled to debug a program, only to discover that some instance of a program variable x was really a different instance of x, even though both instances have the same name.)

Temporary local variables do have some benefits, mostly in the area of efficient memory management. A block of code that temporarily needs a variable does not need to define it as an instance variable for the whole class. Instead, the programmer can define it when necessary, as if it were an executable statement. Then the system will delete the variable when the block of code is completed.

Java restricts the scope of the variable to the block of code in which it is defined. Therefore, a program can define counter variables (x appears to be some sort of a standard) as needed, confident that the compiler will detect conflicts in nested blocks of code. Variables that must be shared by multiple blocks of code must be defined as parameters or as class instance variables.

if (myErrorMsg.total_counter == 100) {

// Some logic
     ...
// Define a local variable.
     int x;
     ...
     }
// It will be deleted after the }.

Finally, values passed as parameters to Java methods are passed by value. This means that a copy of the primitive data types (discussed in the following sections) are passed rather than the variable itself. For object reference variables, the reference variable is passed, but it is in fact a reference to the object. As a result, any passed primitive data type values are implicitly local variables. Any changes you make to the objects referenced in passed object reference variables will be reflected in the objects themselves. I’ll discuss variable scope in Chapter 7, when I discuss Java’s flow control construct.

PRIMITIVE DATA TYPES

As with any language, Java defines some native variable types that can be used to store and represent data. Many languages (especially C) define standard data types, but the implementation details for some types can vary slightly across systems, creating code and data portability problems. Java attempts to deal with these problems by explicitly prescribing these data types and how they are to be defined and implemented across systems.

1. Most COBOL compilers handle single-byte characters as unsigned, that is, with values between 0 and +255.
2. Some COBOL compilers define BINARY as COMP–4 or COMP–5. Only values with four digits (–9999 through 9999) are guaranteed to fit in an integer of this size.
3. The range of valid values may be limited on some compilers to those that fit in 18 digits.
4. Supported by some compilers.

These next types are not intrinsic Java types, but instead are some of the standard classes that are commonly used in Java programs.

1. COBOL strings are always fixed-length 8-bit characters and bank padded to the defined size of the item. Java strings are variable-length Unicode characters and have an embedded size attribute. I will discuss strings later.
2. Sometimes just COMP, COBOL’s packed decimal type.

Values can easily be converted between the various data types, but in many cases, you have to be explicit. A type cast is used to indicate to the compiler that you intend to convert from one type to another; otherwise, the compiler might think you are making a mistake!

           int     counter = 23;
// 'F' indicates a float constant
          float   bigNumber = 1.23F;     // or 1.23f;
          double  biggerNumber = 123.45;
// Direct assignment from integer to floating point data types is possible.
          bigNumber = counter;
// Direct assignment from floating point to integer data types is not
// possible.
          counter = bigNumber;
// this is a compile error
// Move the floating point number to the integer, using a cast. Of course,
// some precision may be lost, but you've told the compiler you know what
// you're doing.
          counter = (int) bigNumber;
// Direct assignment from floating point to double is fine, but you need a
// cast to go from double to float:
          biggerNumber = bigNumber;
// OK
          bigNumber = biggerNumber;
// an error
          bigNumber = (float) biggerNumber;
// OK

ARRAYS

Arrays in Java are very similar to arrays in COBOL. Arrays are objects that contain a set of other objects or a set of data elements. All the elements in an array must be of the same type. In addition, the size of an array must be defined when it is created and cannot be dynamically adjusted in size. These are all specifications that should be familiar to the COBOL programmer.

     01 ERROR-MESSAGE-ITEMS.
          03 ERROR-MESSAGE OCCURS 10 TIMES PIC X(80).
// In Java this would be:
     ErrorMsg myErrorMsgs[] = new ErrorMsg[10];
// or
     int errorNumbers[] = new int [10];

Note that in the first example, the myErrorMsgs array was created, but the ErrorMsg objects that it will eventually contain were not created. Instead, the object reference variables inside the array are initialized to null. In contrast, an array of data items that contains numeric data items are initialized to 0 by default.

The array brackets can be placed by the type name instead of the variable name. This actually is the more common syntax:

int[] errorNumbers = new int [10];

Interestingly, it is possible to define an array with no more information than the types of elements it will contain:

ErrorMsg[] myErrorMsgs;

The array variable myErrorMsgs can be subsequently assigned to some other ErrorMsg array. This feature can be very useful in managing arguments and return values for methods, although you should try to use the newer collection classes for this purpose, which I will discuss in a moment.

Arrays can be created with initial values assigned to its elements using a syntax similar to C’s syntax:

int errorNumbers[] = {1, 2, 10, 22, 23};

As you might suspect, this array will contain five integer values.

Unlike COBOL, in which an array’s size is defined only at compile time, the size of a Java array can be defined at runtime:

int array_size = 10;
ErrorMsg[] myErrorMsgs = new ErrorMsg[array_size];

As in COBOL, an array in Java can be multidimensional:

int[][] errorNumbers = new int[10][3];

Based on the preceding declaration, errorNumbers is an array of 10 integer arrays (each of which is three integers in size).

Every array contains a length member, which is the number of elements in the array.

This loop will execute five times because there are five elements in errorNumbers and none is equal to 30. I will discuss for loops in more detail in Chapter 7, but for now, read the following for statement as “Initialize an int variable named x to 0, perform the next statement until x < errorNumbersIO.length, and increment x by one after each iteration.”

int[] errorNumbersIO = {1, 2, 10, 22, 23};
for (int x = 0; x < errorNumbersIO.length; x++) {
     if (errorNumbersIO[x] == 30) {
          break;
     }
}

Java checks all array references to prevent out-of-bounds references. Any out-of-bounds reference will generate an ArrayIndexOutOfBoundsException exception. (Whew! And you thought COBOL was a bit wordy.)

Although I did introduce arrays as a type of object, Java does not treat arrays simply as standard objects. There is enough special syntax in the language for arrays to view them as a special type of reference variable, slightly different from objects.

For example, the assignment and evaluation statements for arrays that contain primitive data types are very similar to the same statements used by the primitive data type. This syntax is valid for arrays: if (errorNumbersIO[x] == 30). It is quite similar to the syntax used by primitive integer types: if (errorNumber == 30). If arrays were simply objects, this syntax would compare the objects in the arrays, not the numeric values.

Java also provides a set of useful array-specific methods. In order to copy some part of an array into another array, use the arraycopy() function in the Java

System.arraycopy (sourceArray, int sourcePosition,
      destinationArray, int destinationPosition, int
      numberOfEntriesToCopy);

Suppose you want to copy the I/O error numbers array and the logical error numbers array into a single array. You could use the arraycopy() method to do this:

     int[] errorNumbersIO = {1, 2, 10, 22, 23};
     int[] errorNumbersLogical = {101, 102, 108, 122};
     int[] errorNumbersAll = new int[errorNumbersIO.length
                            + errorNumbersLogical.length];
     System.arraycopy (errorNumbersIO, 0,
                           errorNumbersAll, 0, 5);
     System.arraycopy (errorNumbersLogical, 0,
                           errorNumbersAll, 5, 4);
// A temporary array can be defined, and then it can be assigned to any of
// these arrays.
     int[] tempNumbers;
     tempNumbers = errorNumbersIO;
     tempNumbers = errorNumbersLogical;
     tempNumbers = errorNumbersAll;

Arrays can be passed into methods and returned from a method as its return value. This is very useful when a method needs to return a set of values instead of just one.

     public class ErrorCodes {
// Define a static structure that contains all the I/O error codes.
         static int[] IOCodes = {1, 2, 3, 10, 12, 22, 23, 30};
// A method that returns all the error codes for I/O functions:
         public int[] errorCodesIO {
// Create an array to hold the error codes.
             int[] results = new int[IOCodes.length];
// Copy the array (actually the method System.arraycopy() would be a
// better choice than this loop).
             for(int x = 0; x < IOCodes.length; x++) {
                results[x] = IOCodes[x];
             }
// Return the array that you have just loaded.
             return results;
         }

Before I move on to the next topic, let’s visit this statement again.

ErrorMsg[] myErrorMsgs;

What does myErrorMsgs[0] contain after this statement?

 ErrorMsg[] myErrorMsgs;
  myErrorMsgs = getErrorMsgs();
if (someCondition)
      myErrorMsgs = getExtendedErrorMsgs();

Since the array has not been initialized via the new operator, it does not contain any ErrorMsgs. However, I did say it will contain reference variables of this object type.

After this statement,

myErrorMsgs = new ErrorMsg[10];

all the elements in myErrorMsgs will contain empty object reference variables, or null. Therefore, this statement:

if (myErrorMsgs[0] == null)

will always evaluate to true until myErrorMsgs[0] is assigned to an actual reference variable.

     myErrorMsgs[0] = new ErrorMsg ();
     if (myErrorMsgs[0] == null) {
// This section will not be executed, since myErrorMsgs[0] has been
// assigned to an object.
     }

ARRAYS AS PARAMETERS

Parameters passed to Java methods are passed by value, not by reference. In COBOL, parameters are passed by reference to a subroutine, although some compilers support an optional “by value” mechanism.

When arrays are passed to methods as parameters, the method cannot change the array. However, if the array contains objects, then the called method can change the objects contained in the array. Though not exactly the same as a parameter that is passed by reference, this can be a useful mechanism to construct a method that modifies the objects passed to it as an argument.

A way to look at it is that a copy of the reference is made and that copy is passed into the method. They both point to the same thing, but only the copy can be changed to point to something different.

METHOD MEMBERS

Method members are the functions that a class provides. This concept is similar to the COBOL subroutine that provided multiple functions based on an ACTION-SWITCH. Method members are identified by their names (e.g., setErrorMsg) and their method signatures (that is, the types and number of parameters). Method member references are distinguished from data member references by an argument definition, which is enclosed in an open parenthesis or closed parentheses for no arguments.

Remember how class data members could be made visible or invisible to other classes? Class method members can also be qualified with access controls. These controls define whether other classes can access methods directly. Class method members can be public, private, or package methods.

Some of Java’s method members are not associated with any instance of a class but rather with all instances of a class. These are called class methods. Since class methods do not belong to an instance of a class, class methods can access only static variables, not instance variables. Such methods are helpful in managing static variables (for example, resetting a static variable based on some condition).

ERRORMSG CLASS: STATIC VARIABLE

The ErrorMsg class is enhanced to define a static variable, and a default static method to initialize that variable.

       public class ErrorMsg {

            public String msgText;
            public int     msgSize;
            private int    counter = 0;
                    char   interfaceInUse;
            public static int total_counter;
            public final    static int   NO_TEXT_FOUND = 0;
//   A static initializer method with no name and no parameters
            static {
                 total_counter = 0;
            }
//   A public method with no parameters:
            public void setErrorMsg () {
            }
//   A public method with the same name and one parameter of type String.
//    This is actually a different method, or interface definition.
            public void setErrorMsg (String inputMsg) {
                 interfaceInUse = 'S';
                 msgText = inputMsg;
                 msgSize = msgText.length ();
//   Call the manageCounters method.
                 manageCounters ();
            }
//   A package method named manageCounters.
//    This method is only visible to other classes in this package.
            void manageCounters () {
                 counter = counter + 1;
                 total_counter = total_counter + 1;
            }

      }

ERRORMSG CLASS: STATIC INITIALIZER

Classes can also define specialized static initializer code. Like a class variable, this block of code will be executed when the first instance of the class is initiated by a runtime. Often this code will perform special initialization logic for the static class variables. In fact, only static class variables can be accessed by the initializer code. There are no instance member variables available to this code, since class initializer code is performed only once and before any instances of the class have been created.

     public class ErrorMsg {
// Public instance variables:
          public String msgText;
          public int    msgSize;
// A public class variable
          public static int     TOTAL_COUNTER;
// A class initializer code block
          static void   TOTAL_COUNTER (){
               TOTAL_COUNTER = 1;
          }
// A regular instance method
          public void setErrorMsg (String inputMsg) {
               ...
               ...
          }
     }

CONSTRUCTORS

Now is a good time to talk about constructors. When an object is first instantiated (with the new operator), the JVM will create the new instance of the class and call its constructor. This is a special built-in definition that performs any initialization logic that may be required by that class. Constructors are not methods, but they are similar to methods in some respects. This special, perform-one-time-only definition exists in every object, even if the class designer didn’t explicitly define it.

As with real methods, a class can have more than one constructor; each one is identified by a unique parameter signature. By default, every class will have at least one constructor, a constructor that accepts no parameters. This default constructor will be generated by the compiler if the class has no constructors defined for it. Sometimes the default constructor is called the “no arguments” constructor.

These constructors are useful for any number of reasons, such as initializing an important member of the object. The programmer defines a constructor by declaring a special definition in the class. This definition must have exactly the same name as the class and have no return type.

     public class ErrorMsg {
          public static int total_counter;
// A constructor definition for this class. Note that all constructors
// have the same name as the class. This constructor has no parameters:
          ErrorMsg () {
               total_counter = -1;
          }
// A regular class instance method with no parameters:
          public static void resetErrorMsgCount () {
                total_counter = 0;
          }

As in regular method definitions, a class can have more than one constructor definition. They are identified by their signature, or number and types of parameters.

     public class ErrorMsg {
          public  static  int   total_counter;
// A constructor for this class. Note that this constructor has no
// parameters:
          ErrorMsg () {
               total_counter = -1;
          }
// A constructor for this class that is passed one parameter.
          ErrorMsg (String initialMsgText) {
               total_counter = -1;
               msgText = initialMsgText;
          }

The consumer class does not explicitly call the constructor method. Instead, the new operation implicitly calls it. The class consumer identifies which constructor to call by adding parameters to the new operation.

// Create an instance of ErrorMsg.
// The constructor with no parameters will be called.
     ErrorMsg      myErrorMsg = new      ErrorMsg ();
// Create another instance of ErrorMsg.
// The constructor with one parameters will be called.
      ErrorMsg myotherErrorMsg = new ErrorMsg ("Some Text");

A constructor can execute some other constructor in the current class. This is useful if a class has more than one constructor definition but would like to share some code between them. The this keyword is used as an object reference variable that points to the current object.

// The standard constructor for a class
// It is passed no parameters.
          ErrorMsg () {
              total_counter = -1;
          }
// A constructor for this same class that is passed one parameter
// It will call the standard constructor (to initialize the counter member).
          ErrorMsg (String initialMsgText) {
               this.ErrorMsg       // Perform the standard constructor
               msgText = initialMsgText;
          }

EXERCISES: CLASS MEMBERS

It’s time to revisit the example classes and try out all these new ideas.

  1. Using a text editor, edit the Java source file ErrorMsg.java in the java4cobol directory. You will add some additional variables to it and examine how a calling program can access these variables. Add the bolded lines of code to the beginning of the file so that it looks like this:

    public class ErrorMsg {
    // Define some public class instance variables.
              public String msgText = " ";
              public int msgSize;
    // Define some private class instance variables.
              private int counter = 0;
              char interfaceInUse;
    // Define a public method.
              public void setErrorMsg (String inputMsg) {
    // Modify some of the private variables.
                  counter = counter + 1;
                  interfaceInUse = 'S';
    // Modify one of the public variables. Set this variable to the text
    // String parameter.
                  msgText = inputMsg;
    // Set this variable to the length of the text String.
                  msgSize = msgText.length ();
    // Return from this method. Since this method has no return value
    // (i.e.,
    // it is declared as void), no return statement is necessary.
              }

    ...

  2. Compile the class in the DOS command window:

    →   javac ErrorMsg.java

  3. Modify HelloWorld so that it uses these new members. With the text editor, edit the Java source file HelloWorld.java in the java4cobol directory. Add the bolded lines of code after the third println statement so that it looks like this:

    // Set the text item in ErrorMsg to some text String, and print its
    // contents:
              myErrorMsg.setErrorMsg ("Some Text");
              tempMsg = myErrorMsg.getErrorMsg ();
              System.out.println (tempMsg);
    // Print the contents of ErrorMsgs String data member directly.
              System.out.println (myErrorMsg.msgText);

  4. Save the file, and then compile and execute the program in the DOS command window:

    →   javac HelloWorld.java

    →   java HelloWorld

    Your output window should contain these lines:

    C:>javac ErrorMsg.java

    C:>javac HelloWorld.java

    C:>java HelloWorld
    Hello World!

    Some Text
    Some Text
    Some New Text
    ...

    The second “Some Text” line in the output window is the result of your new println statement. This statement printed the text in data member msgText directly from the object myErrorMsg. It can do this because msgText has been defined as a public data member in the class ErrorMsg. For the sake of brevity, the entire output window is not shown here.

  5. Now you will try to access ErrorMsg’s other data members from Hello-World. Add the bolded lines of code after your new println statement so that it looks like this:

    // Set the text item in ErrorMsg to some text String, and print its
    // contents:
              myErrorMsg.setErrorMsg ("Some Text");
              tempMsg = myErrorMsg.getErrorMsg ();
              System.out.println (tempMsg);
    // Print the contents of ErrorMsg's String data member directly.
              System.out.println (myErrorMsg.msgText);
    // Try to access the other data member (s) in ErrorMsg.
              System.out.println ("msgSize " + myErrorMsg.msgSize);
              System.out.println ("counter " + myErrorMsg.counter);

  6. What happens when you try to compile this class (remember to save the file as a text file)?

    →   javac HelloWorld.java

    The compiler knows that private data members cannot be accessed, so don’t try it again!

  7. Remove the offending statement, and recompile. Now try running the modified program:

    →   javac HelloWorld.java

    →   java HelloWorld

    Your output window should look like this:

    Hello World!

    Some Text
    Some Text
    msgSize 9
    Some New Text
    Some Text for #2
    Some New Text
    SOME NEW TEXT

    The data member msgSize (9) is now printed in the output window. What is the conclusion? Public members (msgSize and MsgText) can be accessed outside the ErrorMsg class. However, private members (counter) cannot be.

  8. Let’s build a new method in ErrorMsg that will return counter. You will also adjust ErrorMsg so that counter is incremented for each method. Along the way, you will correct the implementation of one of the setErrorMsg methods to make sure that the overloaded version of this method (the one with one parameter) reuses the original method.

  9. Open the ErrorMsg class in the editor. Add the bolded lines of code to the first getErrorMsg method so that it looks like this:

              public String getErrorMsg () {
                 String returnMsg;
    // Modify some of the private variables.
                 counter = counter + 1;
                 interfaceInUse = 'G';
    // Set the local variable returnMsg to the data member msgText.
                  returnMsg = msgText;
    // Return from this method, and return the String variable.
                  return (returnMsg);
               }

  10. Add this new method to ErrorMsg:

    // Define a method to return counter.
              public int getCounter () {
    // Return from this method with the value of 'counter'.
                  return (counter);
              }

  11. Save this class, and then compile it in the command window:

    →   javac ErrorMsg.java

  12. Now, you’ll adjust HelloWorld so that it uses these new members. Open the HelloWorld class in the editor. Add the bolded lines of code after the print of msgSize so that it looks like this:

    // Print the other data members in ErrorMsg.
              System.out.println ("msgSize " + myErrorMsg.msgSize);
              System.out.println ("interface " + myErrorMsg.interfaceInUse);
              System.out.println ("counter " + myErrorMsg.getCounter ());

  13. Save the source file, then recompile and run the modified program in the command window:

    →   javac HelloWorld.java

    →   java HelloWorld

    Your output window should look like this:

    Hello World!

    Some Text
    Some Text
    msgSize 9
    interface G
    counter 3
    Some New Text
    Some Text for #2
    Some New Text
    SOME NEW TEXT

    msgSize, interface, and counter are now printed in the output window.

  14. As another experiment, you’ll adjust HelloWorld so that it prints out the data members after it calls the overloaded getErrorMsg method (that is, the one that accepts a parameter). Add the bolded lines of code to the end of the HelloWorld class so that it looks like this:

    // Call the new variation on getErrorMsg.
              tempMsg = myErrorMsg.getErrorMsg ('U'),
              System.out.println (tempMsg);
    // Print the public variables after performing this overloaded call.
              System.out.println ("msgSize " + myErrorMsg.msgSize);
              System.out.println ("interface " + myErrorMsg.interfaceInUse);
              System.out.println ("counter " + myErrorMsg.getCounter ());

  15. Save the source file, then recompile and run the modified program in the command window:

    →   javac HelloWorld.java

    →   java HelloWorld

    Your output window should look like this:

    Hello World!

    Some Text
    Some Text
    msgSize 9
    interface G
    counter 3
    Some New Text
    Some Text for #
    Some New Text
    SOME NEW TEXT
    msgSize 13
    interface G
    counter 7

  16. For the next experiment, you will examine the behavior of local variables and observe how they are different from class variables. Add the bolded lines of code to the setErrorMsg method and the first getErrorMsg method so that they look like this:

    // Define a public method.
              public void setErrorMsg (String inputMsg) {
    // Define a local variable and increment it.
                   int localCounter = 0;
                   localCounter = localCounter + 1;
    // Modify some of the private variables.
                   counter = counter + 1;
                   interfaceInUse = 'S';

              . . .
    // Define another public method.
              public String getErrorMsg () {
                   String returnMsg;
    // Define a local variable and increment it.
                   int localCounter = 0;
                   localCounter = localCounter + 1;
    // Modify some of the private variables.
                   counter = counter + 1;
                   interfaceInUse = 'G';
              }

  17. Add the bolded lines of code to the end of ErrorMsg:

    // Define a method to return localCounter.
              public int getLocalCounter () {
                   int localCounter = 0;
                   localCounter = localCounter + 1;
    // Return from this method with the value of localCounter.
                   return (localCounter);
              }

  18. Save this class, and then compile it in the command window:

    →   javac ErrorMsg.java

  19. Add the bolded lines of code to the end of the HelloWorld class so that it looks like this:

    // Call the new variation on getErrorMsg.
              tempMsg = myErrorMsg.getErrorMsg ('U'),
              System.out.println (tempMsg);
    // Print the public variables after performing this overloaded call.
              System.out.println ("msgSize " + myErrorMsg.msgSize);
              System.out.println ("interface " + myErrorMsg.interfaceInUse);
              System.out.println ("counter " + myErrorMsg.getCounter ());
    // Print the localCounter variable.
              System.out.println
                 ("localCounter " + myErrorMsg.getLocalCounter ());

  20. Save the source file, then recompile and run the modified program in the command window:

    →  javac HelloWorld.java
    →  java HelloWorld
    Hello World!

    Some Text
    Some Text
    msgSize 9
    interface G
    counter 3
    Some New Text
    Some Text for #2
    Some New Text
    SOME NEW TEXT
    msgSize 13
    interface G
    counter 7
    localCounter 1

  21. For this last experiment, you will work with arrays. Edit the HelloWorld source file and add these Java statements to the end of the previous statement. Enter the checkIntArray() method inside the brackets that define the class.

    // Create an array of five error codes.
           int[] errorNumbersIO = {1, 2, 10, 22, 23};
    // Test if any are equal to 30.

           checkIntArray (errorNumbersIO);
         }

    // Test if any integers in the passed array are equal to 30.
         static void checkIntArray (int[] intArray) {
              System.out.println ();
              for (int x = 0; x < intArray.length; x++) {
                      if (intArray[x] == 30) {
                 System.out.println ("Found '30' at index " + x);
                 break;
               }
                else
                      {
                           System.out.println ("error Number " + x + " = " +
       intArray[x]);
                       }
                    }
             }

  22. Save these modifications as a text file, and then compile the class in the DOS command window. (You may need to add this statement import java.util.*; to the beginning of your HelloWorld class.)

    →  javac HelloWorld.java
    →  java HelloWorld
    error Number 0 = 1
    error Number 1 = 2
    error Number 2 = 10
    error Number 3 = 22
    error Number 4 = 23

  23. Add these Java bolded statements to the end of the HelloWorld class, but before the checkIntArray() function:

    // Test if any are equal to 30.
         checkIntArray (errorNumbersIO);
    // Set an error code to 30, and call the checkIntArray function again.
        errorNumbersIO[1] = 30;
         checkIntArray (errorNumbersIO);

    Following are the results when you execute the program:

    }
    error Number 0 = 1
    error Number 1 = 2
    error Number 2 = 10
    error Number 3 = 22
    error Number 4 = 23

    error Number 0 = 1
    Found '30' at index 1

Image

Since you are a very clever programmer, try out these adjustments on your own in the HelloWorld applet. For your convenience, the completed applet sample code is included on the CD-ROM.

REVIEWING THE SAMPLES

Let’s review the changes you’ve made to ErrorMsg and HelloWorld. Try to relate the sample source statements to the result (the output) each statement creates. If necessary, rerun the samples or look at the complete source code for this exercise on the CD-ROM. Feel free to experiment by yourself.

Image
  • The ErrorMsg class was adjusted to include some private and package data members.

  • HelloWorld could access the public (msgText and msgSize) and package (inter-faceInUse) data members directly but could not access the private (counter) data members.

  • You needed to create a new method (getCounter) in order to access this private data member.

  • You changed the second version of the method getErrorMsg (in ErrorMsg) so that it called the first version and then performed its custom logic. Notice that you did not need an object reference variable (like myErrorMsg) for this statement; you can just call the method. In this case, the compiler assumes that you mean this object (that is, the current object).

    // Perform the standard getErrorMsg method.
                   returnMsg = getErrorMsg ();
    // Convert to all uppercase, if requested.
                   if (caseFlag == 'U')
                       ...

  • Local variables are automatically created and then destroyed as needed. They are not shared by various blocks of code, even if these blocks of code are members of the same class. The variable localCount was defined, initialized, and incremented in each method. Each method created its own copy of this temporary variable.

Here are a few more important notes:

  • The println method can accept one String parameter. If your source combines many different variables with the + operator, these are all converted into Strings, and then combined into a single String, which is passed to println. Therefore,

    System.out.println ("msgSize " + myErrorMsg.msgSize);

    results in this output window:

    msgSize 9

  • The result of a method that returns a value (for example, getCounter returns an integer value) can be used right away in a single statement. There is no need to store the result of the method in a variable, if the result is only to be used for the current statement. Therefore, this statement

      System.out.println
                ("counter " + myErrorMsg.getCounter ());

    results in this output window:

    counter 3

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

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