The New method is a factory method that provides a standard mechanism for creating object instances of a class. Described with COBOL semantics, the interface for the New method is as follows:
Interface-id. BaseFactoryInterface. Procedure division. Method-id. New. Data division. Linkage section. 01 outObject usage object reference active-class. Procedure division returning outObject. End-method New. End Interface BaseFactoryInterface.
General rules
The New method allocates storage for an object and initializes its data. An object is in the initial state immediately after it is created.
If there is not enough storage space to create a new object, the exception condition EC-OO-RESOURCE occurs. The procedure continues in accordance with rule 6 f) of the INVOKE statement (see the section "INVOKE statement" ).
Example 12-25
Override New method
The New method can be overridden in order to perform additional object-specific initialization operations which go beyond the initial values specified in the VALUE clause. In this case, the new object must first be generated using the “original” New method.
FACTORY. DATA DIVISION. WORKING-STORAGE SECTION. 01 ident pic 9(9) COMP VALUE 0. ... METHOD-ID. NEW OVERRIDE. DATA DIVISION. LINKAGE SECTION. 01 new-object USAGE OBJECT REFERENCE ACTIVE-CLASS. PROCEDURE DIVISION RETURNING new-object. 1. INVOKE SUPER "NEW" RETURNING new-object. COMPUTE ident = ident + ... INVOKE new-object "SPECIAL-INITIALIZATIONS" USING ident... ... 2. EXIT METHOD. END METHOD NEW.