Your Browser is not longer supported

Please use Google Chrome, Mozilla Firefox or Microsoft Edge to view the page correctly
Loading...

{{viewport.spaceProperty.prod}}

Parameterized classes and interfaces

A parameterized class is a class with one or more formal parameters. All that is known of a formal parameter is whether a class or an interface is concerned. Concrete characteristics of the formal parameters that go beyond this remain open.

A parameterized class is used by specifying a class K as an expansion of the parameterized class P with current parameters in the REPOSITORY paragraph of the user program: the formal parameters must then be replaced by the names of concrete classes or interfaces (the current parameters), and the name of the parameterized class by that of the concrete expansion. As a result, the new concrete class K, which behaves like a non-parameterized class and is also handled as such, is created at this time from P.

The actual compilation of this new class K with the replaced class and interface names takes place automatically after the user has been compiled (see the "COBOL2000 User Guide" [1]).

The following definitions are required in this context:

  • The concrete class K expands the parameterized class P.

  • The parameterized class P is expanded as concrete class K.

The process of parameter replacement, the compilation and the resulting class are referred to as “expansion of the parameterized class P”.

Every such expansion of a parameterized class generates a separate concrete class. It has its own factory object and is independent of other expansions in the same parameterized class.
However, the names of all referenced classes must be unique within a run unit: if a parameterized class P is expanded in multiple programs of the run unit with the same name K, the current parameters should also be the same in these explansions.

The advantage of parameterized classes over those which provide the same performance using universal object references instead of parameterization is that the compiler can perform tests statically and once only at compilation time; with the other approach these tests would have to be repeated dynamically at runtime.

The descriptions of parameterized classes provided above apply analogously for parameterized interfaces.

Example 12-22

The following example shows a “first-in-first-out” list for including object references. The class of the references is not to be specified more closely and is thus defined as a parameter. Such a list can incorporate any number of elements, the first element entered in the list being the one that is returned first when the list is read, at the same time being removed from the list.

This list is implemented with the two parameterized classes FIFO-LISTE and LIST-ELEMENT1. The FIFO-LISTE class describes the management structure for the entire list. As a parameter it has the class of the objects to be added and also the class of the corresponding concrete expansion of LIST-ELEMENT1.

The parameterized class LIST-ELEMENT1 describes a single list element. As a parameter it has the class of the objects whose reference is stored in such a list element. LIST-ELEMENT1 functions as an “auxiliary class” which does not appear separately on the outside. It is only used within the FIFO-LISTE and should be generated there automatically using the appropriate parameters.

Nesting of parameterized classes is not permitted by the COBOL Standard 2002, however. Users must therefore program the required expansions themselves

       >>IMP Compiler-Action UPDATE-REPOSITORY ON                        a)
       IDENTIFICATION DIVISION.
>>>    CLASS-ID.                LIST-ELEMENT1 INHERITS BASE USING PAR.   b)
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SPECIAL NAMES.
           TERMINAL IS TTT.
       REPOSITORY.
           CLASS                PAR,                                     b)
           CLASS                BASE.

FFF    FACTORY.
       PROCEDURE DIVISION.
+++    METHOD-ID.               MAKE-NEW.                                c)
       DATA DIVISION.
       LINKAGE SECTION.
       01 P USAGE OBJECT REFERENCE PAR.
       01 R USAGE OBJECT REFERENCE ACTIVE-CLASS.
       PROCEDURE DIVISION USING BY VALUE P RETURNING R.
       1.
           INVOKE SELF "NEW" RETURNING R. 
           INVOKE R "SET-CONTENT" USING P. 
           EXIT METHOD. 
       END METHOD               MAKE-NEW. 
       END FACTORY. 

OOO    OBJECT. 
       DATA DIVISION. 
       WORKING-STORAGE SECTION. 
       01 NXT  USAGE OBJECT REFERENCE LIST-ELEMENT1.                     d)
       01 CONT USAGE OBJECT REFERENCE PAR.                               e)
       PROCEDURE DIVISION. 

+++    METHOD-ID.               SET-NEXT.                                f)
       DATA DIVISION. 
       LINKAGE SECTION. 
       01 P USAGE OBJECT REFERENCE LIST-ELEMENT1. 
       PROCEDURE DIVISION USING P. 
       1. 
           SET NXT TO P. 
           EXIT METHOD. 
       END METHOD               SET-NEXT.

+++    METHOD-ID.               GET-NEXT.
       DATA DIVISION. LINKAGE SECTION.
       01 R USAGE OBJECT REFERENCE LIST-ELEMENT1.
       PROCEDURE DIVISION RETURNING R.
       1.
           SET R TO NXT.
           EXIT METHOD.
       END METHOD               GET-NEXT.

+++    METHOD-ID.               GET-CONTENT.
       DATA DIVISION.
       LINKAGE SECTION.
       01 P USAGE OBJECT REFERENCE PAR.
       PROCEDURE DIVISION RETURNING P.
       1.
           SET P TO CONT.
           EXIT METHOD.
       END METHOD               GET-CONTENT.

+++    METHOD-ID.               SET-CONTENT.
       DATA DIVISION.
       LINKAGE SECTION.
       01 P USAGE OBJECT REFERENCE PAR.
       PROCEDURE DIVISION USING BY VALUE P.
       1.
           SET CONT TO P.
           EXIT METHOD.
       END METHOD               SET-CONTENT.
       END OBJECT.
       END CLASS                LIST-ELEMENT1. 

Notes

a)

The expansions of this class are entered as parameters in the expansions of the parameterized class FIFO-LIST. The repository data of the relevant expansion of LIST-ELEMENT1 must therefore be available. This is ensured by specifying the directive (however, the user must ensure that a repository is assigned correctly, see the "COBOL2000 User Guide" [1]).

b)

Parameter PAR is the name of the class whose object references are to be stored in the list.

c)

The MAKE-NEW method generates a new list element and also supplies the object reference that is to be stored there with values. The list element object is not yet linked to the list, however - that is the task of the list class FIFO-LIST.

d)

The list elements are simply linked “forward” to the next element in the list via an object reference.

e)

The user data of a list element consists of an object reference for objects of the class which is later specified as the current parameter or classes that inherit from this.

f)

The other 4 methods represent the elementary accesses for writing and reading the two data parts of a list element.


The actual list accesses, i.e. the methods APPEND-ENTRY and REMOVE-ENTRY, are made available by FIFO-LIST. The LIST-LENGTH method acts as an additional information service.

 

        IDENTIFICATION DIVISION.
>>>>    CLASS-ID.                 FIFO-LIST INHERITS BASE
                                         USING PAR-OBJ, PAR-ELEM.        a)
        ENVIRONMENT DIVISION.
        CONFIGURATION SECTION.
        SPECIAL NAMES.
            TERMINAL IS TTT.
        REPOSITORY.
            CLASS                PAR-OBJ,
            CLASS                PAR-ELEM,
            CLASS                BASE.

OOO     OBJECT.
        DATA DIVISION. WORKING-STORAGE SECTION.
        01 ELEM-COUNT PIC S9(8) COMP-5 VALUE 0.                          b)
        01 FST        USAGE OBJECT REFERENCE PAR-ELEM.                   c)
        01 LST        USAGE OBJECT REFERENCE PAR-ELEM.                   c)
        PROCEDURE DIVISION.

+++     METHOD-ID.                APPEND-ENTRY.                          d)
        DATA DIVISION. 
        LOCAL-STORAGE SECTION.
        01 W USAGE OBJECT REFERENCE PAR-ELEM. 
        LINKAGE SECTION. 
        01 P USAGE OBJECT REFERENCE PAR-OBJ.
        PROCEDURE DIVISION USING P. 
        1. 
            INVOKE PAR-ELEM "MAKE-NEW" USING P RETURNING W. 
            IF LST = NULL
            THEN                     *> MAKE VERY FIRST ENTRY IN LIST 
              SET FST, LST TO W
              MOVE 1 TO ELEM-COUNT
            ELSE                     *> APPEND ENTRY TO THE END OF LIST
              INVOKE LST "SET-NEXT" USING W 
              SET LST TO W 
              ADD 1 TO ELEM-COUNT 
            END IF.
            EXIT METHOD.
        END METHOD                APPEND-ENTRY. 

+++     METHOD-ID.                REMOVE-ENTRY.                          e)
        DATA DIVISION.
        LOCAL-STORAGE SECTION.
        01 W USAGE OBJECT REFERENCE PAR-ELEM. 
        LINKAGE SECTION. 
        01 R USAGE OBJECT REFERENCE PAR-OBJ. 
        PROCEDURE DIVISION RETURNING R. 
        1.
            IF FST = NULL
            THEN                     *> LIST IS EMPTY 
              SET R TO NULL
            ELSE                     *> DELETE 1st LIST-ELEM,MAKE SURE 
                                     *> THAT IT WILL BE GARBAGE COLLECTED 
              INVOKE FST "GET-CONTENT" RETURNING R 
              SUBTRACT 1 FROM ELEM-COUNT 
              SET W TO FST 
              INVOKE W "GET-NEXT" RETURNING FST
              INVOKE W "SET-NEXT" USING NULL 
            END IF. 
            EXIT METHOD. 
        END METHOD                REMOVE-ENTRY.

+++     METHOD-ID.                LIST-LENGTH. 
        DATA DIVISION. 
        LINKAGE SECTION. 
        01 R PIC S9(8) COMP-5. 
        PROCEDURE DIVISION RETURNING R. 
        1. 
            MOVE ELEM-COUNT TO R. 
            EXIT METHOD. 
        END METHOD                LIST-LENGTH. 
        END OBJECT.
        END CLASS                 FIFO-LIST. 

Notes

a)

Parameter PAR-OBJ is the name of the class whose object references (also those of subclasses) are to be stored in the list.
Parameter PAR-ELEM is the name of the associated expanded auxiliary class LIST-ELEMENT1.

b)

This counter is used only for the additional information service LIST-LENGTH. It is not needed for list accesses and the services.

c)

To manage the FIFO list it is sufficient if the first (FST) and last (LST) elements in the list can be found.

d)

The APPEND-ENTRY method itself generates a new list element with the object reference transferred as a parameter as its content. This new element is the last that is linked to the list and the management data is adjusted accordingly.

e)

The REMOVE-ENTRY method removes the first element from the list and returns the object reference stored there. Here it would be sufficient just to adapt the management data - however, to facilitate garbage collection, the link to the list in the list element removed is set to NULL.

The program extract below provides an example of a possible application of these two parameterized classes:

Classes A and B are any required concrete classes. FIFOB is a concrete class for a “first-in-first-out” list of object references for objects of class B (and its subclasses), FIFOA1 and FIFOA2 are concrete classes for “first-in-first-out” lists of object references of class A (and its subclasses).

        IDENTIFICATION DIVISION.
>>>>    PROGRAM-ID.                N.
        ...
        REPOSITORY. 
             CLASS              A,
             CLASS              B,
             CLASS              FIFOA1 EXPANDS FIFO-LIST USING A ELEMA   a)
             CLASS              FIFOA2 EXPANDS FIFO-LIST USING A ELEMA   a)
             CLASS              FIFOB EXPANDS FIFO-LIST USING B ELEMB    b)
             CLASS              ELEMA EXPANDS LIST-ELEMENT1 USING A      c)
             CLASS              ELEMB EXPANDS LIST-ELEMENT1 USING B   b) c)
             CLASS              LIST-ELEMENT1
             CLASS              FIFO-LIST
        ... 
        WORKING-STORAGE SECTION.
        01 FLA1       USAGE OBJECT REFERENCE FIFOA1.
        01 FLA2       USAGE OBJECT REFERENCE FIFOA2.
        01 FLA3       USAGE OBJECT REFERENCE FIFOA2.
        01 FLB        USAGE OBJECT REFERENCE FIFOB.
        01 OB         USAGE OBJECT REFERENCE B.
        01 W          PIC X(10).
        ...
            INVOKE FIFOA1 "NEW" RETURNING FLA1.
            INVOKE FIFOA2 "NEW" RETURNING FLA2.                          d)
            INVOKE FIFOA2 "NEW" RETURNING FLA3.                          d)
            INVOKE FIFOB  "NEW" RETURNING FLAB.
        ...
            INVOKE FLB "APPEND-ENTRY" USING OB. ...
            INVOKE FLB "REMOVE-ENTRY" RETURNING OB.
            IF OB = NULL                                                 e)
              DISPLAY " ---> LISTE LEER"
            ELSE
              ...


Notes

a)

Although the parameterized class and the current parameters are identical in FIFOA1 and FIFOA2, two different concrete classes are produced because of the different names in the two expansions.

b)



It is permissible to use the expansion of a parameterized class (here ELEMB) as the current parameter for another expansion (here FIFOB) provided this does not result in any cyclical dependencies. However, it is not permissible to use a parameterized class itself, e.g. LIST-ELEMENT1, as the current parameter.
The compiler does not necessarily perform subsequent expansions in the order in which they are written in the program, but in such a way that data required for current parameters is available before the expansion takes place.

c)

Owing to the restrictions of the COBOL standard mentioned above, the expansion of the two auxiliary classes ELEMA and ELEMB must be specified by the user. Use of these classes, the generation of objects from them, etc. should be reserved solely for the expansions of FIFO-LIST lists!

d)

Several concrete objects can be generated from the expansion of a parameterized class. The object references FLA2 and FLA3 make 2 FIFO lists for objects of class A available to the program here. This procedure provides the same function as that described in note 1) - using 2 different classes which offer the same performance. However, it is simpler and should thus always be preferred.

e)

If the list is empty, the REMOVE-ENTRY method returns NULL as the object reference.