You can define a file in an object by describing it in a FILE-CONTROL paragraph and a FILE SECTION within a FACTORY or OBJECT area and then specifying appropriate statements to process it, such as OPEN, CLOSE, READ, WRITE, in one or more methods.
If an application has created multiple object instances of a class in which a file is defined then this application is itself responsible for ensuring that no conflicts occur when the file is accessed. This can be achieved as follows:
The file has the attribute EXTERNAL. This means that there is only a single copy of the file and that all objects work with the same file. Thanks to the EXTERNAL attribute, other programs can also simultaneously access the file.
The file’s ASSIGN clause uses the variant “ASSIGN to data-name”. If necessary each object can select a separate copy of such a file on OPEN at runtime by supplying an object-specific value for data-name. In this way it is possible to avoid object conflicts with files in the other object instances of the same class.
If variant 2 is not used then different object instances work with the same object. The application coordinates the file accesses in such a way that, for example, only one object (out of multiple objects of the same class) can open and process the file at any given time. Another possibility is to employ simultaneous file processing (see the "COBOL2000 User Guide" [1]). In this case it is generally advisable to generate only a single object of the class.
Inheritance applies not only to data in the WORKING-STORAGE SECTION, but also to data defined in OBJECT or FACTORY. It should therefore be noted that the inheritance of a class which contains a file definition can also lead to the above-mentioned conflicts, even if each class instantiates only a single object.
Unlike files in objects as described above, files defined in methods behave in the same way as file definitions in normal programs: no further copies of the file definition are created by the instantiation of new objects or through class derivation (inheritance).
Example 12-23
The following class permits access to sequential files consisting of records of 80 characters each.
>>>> CLASS-ID. cseqf80 INHERITS BASE. ENVIRONMENT DIVISION. CONFIGURATION SECTION. REPOSITORY. CLASS BASE. OBJECT. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT seq ASSIGN TO link-name FILE STATUS file-status. DATA DIVISION. FILE SECTION. FD seq RECORD CONTAINS 80. 01 recs PIC X(80). WORKING-STORAGE SECTION. 01 file-status PIC XX. 01 link-namePIC X(8). PROCEDURE DIVISION. +++ METHOD-ID. F-OPEN. DATA DIVISION. LINKAGE SECTION. 01 open-mode PIC X. 88 open-input VALUE "I". 88 open-output VALUE "O". 01 file-link PIC X(8). PROCEDURE DIVISION USING open-mode, file-link. DECLARATIVES. first SECTION. USE AFTER ERROR PROCEDURE ON seq. open-error. IF file-status = .... END DECLARATIVES. 1 SECTION. A. MOVE file-link TO link-name IF open-output OPEN OUTPUT seq ELSE OPEN INPUT seq END-IF EXIT METHOD. END METHOD F-OPEN. +++ METHOD-ID. F-CLOSE. .... *> poss. DECLARATIVES 1 SECTION. A. CLOSE seq. EXIT METHOD. END METHOD F-CLOSE. +++ METHOD-ID. F-READ. DATA DIVISION. LINKAGE SECTION. 01 rec PIC X(80). 01 eof-ind PIC X. 88 eof VALUE "Y" WHEN FALSE "N". PROCEDURE DIVISION USING rec RETURNING eof-ind. .... *> poss. DECLARATIVES 1 SECTION. A. SET eof TO FALSE READ seq INTO rec AT END SET eof TO TRUE END-READ EXIT METHOD. END METHOD F-READ. +++ METHOD-ID. F-WRITE. DATA DIVISION. LINKAGE SECTION. 01 rec PIC X(80). PROCEDURE DIVISION USING rec. .... *> poss. DECLARATIVES 1 SECTION. A. WRITE recs FROM rec. EXIT METHOD. END METHOD F-WRITE. END OBJECT. END CLASS cseqf80.
This class can be used, for example, to process such a file:
.... 01 obj1 USAGE OBJECT REFERENCE cseqf80. 01 obj2 USAGE OBJECT REFERENCE cseqf80. 01 xrec PIC X(80). 01 xind PIX X VALUE "N". 88 xeof VALUE "Y". .... INVOKE cseqf80 "NEW" RETURNING obj1 INVOKE cseqf80 "NEW" RETURNING obj2 INVOKE obj1 "F-OPEN" USING "I", "EIN-DAT" INVOKE obj2 "F-OPEN" USING "O", "AUS-DAT" INVOKE obj1 "F-READ" USING xrec RETURNING xind PERFORM UNTIL xeof .... *> Process record INVOKE obj2 "F-WRITE" USING xrec INVOKE obj1 "F-READ" USING xrec RETURNING xind END-PERFORM INVOKE obj1 "F-CLOSE" INVOKE obj2 "F-CLOSE" ....