You are on page 1of 20

File Handling in Cobol

File Handling in COBOL

File: A file is a collection of data related to a set of entities and typically exists on a magnetic tape or a disk. We refer file as PS in Mainframe environment. In file data is organized as records. Each record is divided into set of fields.

For example data related to employee file which consists of employee ID, employee name, employee Account.

01 WS-EMP-REC. 02 WS-EMP-ID 02 WS-EMP-NAME 02 WS-EMP-ACCT

PIC X(07). PIC X(20). PIC X(06).

In this above file data is organized as multiple records each consists of 33 bytes. Data name WS-EMP-REC is referred as record. WS-EMP-ID, WS-EMP-NAME and WS-EMP-ACCT is referred as Fields. Cumulative size of all fields is considered as record length. A file can be classified as fixed or variable length files. In fixed length file, size of all records must be same but in variable length file record length can be vary upon some fields which are not common. The above referred WS-EMP-REC is an example for fixed length file.

Files are further classified into 3 types. 1. SEQUENTIAL ORGANIZATION 2. INDEX SEQUENTIAL ORGANIZATION 3. RELATIVE ORGANIZATION

Sequential organization: In mainframe environment we have 2 types of sequential files. 1. Flat file (NON-VSAM Sequential file) 2. Entry sequential data set (VSAM ESDS)

Both type of files created using different type of Storage organization. Sequential files: The records are stored in the file in the

same order in which they are entered. Here, the records can be accessed only sequentially. To process any record, one has to read all its preceding records. Further, records cannot be inserted or deleted. Sequential files are simplest to handle, they are highly inflexible as they do not facilitate insertion and deletion of records. File opened with Extend Mode appends the writing records at the end of the file. In COBOL program there is no much difference between these two types. If you are accessing ESDS VSAM file, then in COBOL program should coded like this.

SELECT FILE ASSIGN TO AS-DDNAME.

Actually DD name matches with JCL DD Name. But in COBOL Program DDNAMEs should be prefixed with AS- (In case of VSAM ESDS file) . If you are not doing that then an S213 ABEND might occur when attempting to open data set.

INDEX SEQUENTIAL ORGANIZATION: Records in this file are stored based on a key field which is part of record and this is also called as index. Records in this file are accessible in sequential , dynamic & random mode. An index sequential file is conceptually made up of two files, a data file and an index file. Though the records are stored in the order in which they are entered, a sorted index is maintained which relates the key value to the position of the record in the file and hence provides a way to access the records both sequentially and randomly.

RELATIVE ORGANIZATION: This file is divided into fixed number of slots each slot has one record. This is identified as relative record number. The access method stores and retrieves a record, based on its relative record number. Records can be accessed as sequentially or randomly or dynamically. This relative files faster access compared to other 2 organizations. But if some of the intermediate records are missing, they occupy space.

File declaration in COBOL Program: To make use of files in COBOL program starts in FILE-CONTROL in ENVIRONMENT DIVISION.

SELECT [OPTIONAL]logical-file-name ASSIGN TO physical-file-name. [; RESERVE integer {AREA, AREAS}] [; ORGANIZATION IS SEQUENTIAL]

[; ACCESS MODE IS SEQUENTIAL] [; FILE STATUS IS data-name]

For example... SELECT EMPFILE ASSIGN TO EMPFILEO.

Here in COBOL Program we refer this file as EMPFILE but physically there is no file exists with this name. For any kind of operation against the file inside the program, make sure you use Logical name only i.e. EMPFILE. Above sentence EMPFILEO is a mapping that connects from logical file to physical file. It means whatever operations we do in COBOL program against the logical file EMPFILE those will be reflected on Physical file.

In JCL...This file is referred as //EMPFILEO DD DSN=DG11.CAPHYD.EMPHYD

Physically data stored in DG11.CAPHYD.EMPHYD in system. Operations against EMPFILE will be reflected in DG11.CAPHYD.EMPHYD.

You must specify SELECT OPTIONAL for those input files that are not necessarily present each time the object program is executed. Files with OPTIONAL option can be opened using INPUT,I-O, EXTEND mode.

RESERVE integer {AREA, AREAS} RESERVE 2 AREAS this instructs system about allocation of buffers while processing large files stored on disk or tapes, it is inefficient to read or write single record at a time. Instead, the usual practice is to group a number of consecutive records to form what is known as a physical record or a block the number of records in a block is termed as the blocking factor. There are two advantages of blocking logical records into a physical record. Firstly, it results in saving the I/O time required for processing a file and secondly it results in saving the storage space for a file.

For example to search for a record file has to read sequentially, if each record is reading from Disk at a time which is time consuming in order to speed the access of records, a couple records are read from DISK and keep in intermediate storage called buffer. For sequential access allocation of large block sizes faster the access.

For random access a small block size faster the access of records.

ORGANIZATION IS SEQUENTIAL: It describes the file organization. For sequential files ORGANIZATION IS SEQUENTIAL For Indexed files ORGANIZATION IS INDEXED. For relative files ORGANIZATION IS RELATIVE.

ACCESS MODE IS SEQUENTIAL: This sentence identifies the in which mode the file is going to be accessed.

For sequential access For random access For Dynamic access

- ACCESS MODE IS SEQUENTIAL - ACCESS MODE IS RANDOM - ACCESS MODE IS DYNAMIC

Dynamic access is a combination of random and sequential access.

FILE STATUS IS data-name: File status is used to identify the status of each operation that is performed against the file. For instance. FILE STATUS IS WS-STATUS. This WS-STATUS data name declares explicitly in Working storage section. 01 WS-STATUS PIC X(02). After performing each operation on file it is good practice to check the file status code whether the operation was successful or not, based on this appropriate action is performed. In file handling 00 is identified as successful execution.

FILE STATUE Meaning 00 operation sucessful 10 End of record 22 Duplicate key 23 Record Not Found For more file status code click here

File record description is declared in FILE SECTION. In file section

FD EMPFILE [; RECORD CONTAINS integer-1 CHARACTERS] [; BLOCK CONTAINS integer-2 {RECORDS, CHARACTERS}] [; DATA {RECORD IS, RECORDS ARE} data-name-1 [, data-name-2] . . .] 01 WS-EMP-REC. 02 WS-EMP-ID 02 WS-EMP-NAME 02 WS-EMP-ACCT

PIC X(07). PIC X(20). PIC X(06).

FD is abbreviated from FILE DESCRIPTION. The RECORD CONTAINS clause specifies the size of the logical records. Here RECORD CONTAINS 33 CHARCTERS

The BLOCK CONTAINS clause specifies the size of the physical records. If the records in the file are not blocked, BLOCK CONTAINS clause can be omitted. When it is omitted, the compiler assumes that records are not blocked. Even if each physical record contains only one complete logical record, coding BLOCK CONTAINS 1 RECORD would result in fixed blocked records.

The DATA RECORD clause specifies the record names defined for the file. Here DATA RECORD IS WS-EMP-REC.

File Processing

All file processing operations are held in procedure division. File Operations: OPEN READ WRITE REWRITE CLOSE

OPEN EMPFILE:

OPEN {INPUT, OUTPUT, EXTEND, I-O} file-name-1 [, file-name-2] . . .

The OPEN statement initiates the processing of files. The successful execution of an OPEN statement determines the availability of the file for processing. The successful execution of the OPEN statement makes the associated record area available to the program; it does not obtain or release the first data record. If the FILE STATUS clause is specified in the FILE-CONTROL entry, the associated operation status is updated when the OPEN statement is executed.

A sequential file can be opened in one of the following four modes. INPUT, OUTPUT, EXTEND and I-O. A file can be opened in the INPUT mode only if it already exists. Such a file becomes an input file from which records can be read sequentially. When a file is to be created for the first time, it must be opened in the OUTPUT mode. File can be written in this mode. The EXTEND mode also opens a file for writing, but the file pointer is positioned after the end of the last record. Thus any records written will get appended to the file. A file is opened in the I-O mode when it needs to be updated. This mode provides both reading and rewriting of records.

CLOSE EMPFILE: This statement terminates processing of file. In COBOL-85 this CLOSE Statement is optional and STOP RUN automatically closes the File if it is not explicitly closed. This CLOSE statement means termination of link between Physical file and logical file.

READ EMPFILE: If a file is opened in INPUT or I-O mode then a READ statement make available Next logical record for processing. The primary function of the READ statement is to fetch records from a file and place the file pointer at an appropriate position after READ; it performs certain checks to ensure proper execution of the program.

READ EMPFILE AT END imperative statement. END-READ

If the file reached end of the file and if program tries to read a record then AT END condition satisfy and imperative statement will performed.

If INTO condition specified like READ EMPFILE INTO WS-RECORD. Here WS-RECORD is data division data name. Program read the file

and places record into WS-RECORD.

WRITE statement: WRITE CAPGEMINI-REC FROM WS-RECORD END-WRITE.

File opened in OUTPUT or EXTEND mode then we can use WRITE statement to write records into the file. If from is used then the data in WS-RECORD is moved to record and writing take place. If FROM is omitted then Data moved to record name will be written into file. If we are reading file we refer file name in READ statement, where as while writing we refer record name with WRITE command.

REWRITE statement: REWRITE command is used to update a record in a file. If file is opened in I-O mode then only we can use REWRITE command on that file. This REWRITE is not available in Sequential file. Before using REWRITE command, corresponding record should be read.

A Sample COBOL Program that READ a Sequential files and Write into another file.

Click here to see sample cobol program

Sequential file processing program


IDENTIFICATION DIVISION. PROGRAM-ID. TESTCOBL. AUTHOR. TESTTEST. DATE-WRITTEN. 19-NOV-2010. DATE-COMPILED. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT WS-INFILE ASSIGN TO INPIWS01 FILE STATUS IS WS-INFILE-SW. DATA DIVISION. FILE SECTION. FD WS-INFILE.

01 INP-EMP-REC. 05 INP-EMPID PIC X(08). 05 INP-EMPID PIC X(08). 05 INP-EMP-NAME PIC X(15). 05 INP-EMP-LOB PIC X(10). 05 FILLER PIC X(47). WORKING-STORAGE SECTION. 01 WS-INFILE-SW PIC X(02) VALUE SPACES. 88 WS-INFILE-SUCESS VALUE '00'. 88 WS-INFILE-EOF VALUE '10'. 01 WS-INP-EMP-REC. 05 WS-INP-EMPID PIC X(08). 05 WS-INP-EMP-NAME PIC X(15). 05 WS-INP-EMP-LOB PIC X(10). 05 FILLER PIC X(47). 01 WS-EOF-SW PIC X(01) VALUE 'N'. 88 WS-EOF-NO VALUE 'N'. 88 WS-EOF-YES VALUE 'Y'. PROCEDURE DIVISION. A1000-MAIN-PARA. PERFORM A2000-OPEN-PARA THRU A200-EXIT. PERFORM A3000-INPUT-PARA THRU A300-EXIT. PERFORM A4000-INSERT-PARA THRU A400-EXIT. PERFORM A5000-CLOSE-PARA THRU A500-EXIT. STOP RUN. A100-EXIT. EXIT. A2000-OPEN-PARA. INITIALIZE WS-INFILE-SW WS-INP-EMP-REC WS-EOF-SW. OPEN OUTPUT WS-INFILE IF WS-INFILE-SUCESS DISPLAY "FILE OPEN SUCCESSFUL" ELSE DISPLAY "FILE OPENING ERROR" GO TO A100-EXIT END-IF. A200-EXIT. EXIT. A3000-INPUT-PARA. ACCEPT WS-INP-EMPID. ACCEPT WS-INP-EMP-NAME. ACCEPT WS-INP-EMP-LOB. DISPLAY WS-INP-EMPID WS-INP-EMP-NAME WS-INP-EMP-LOB . A300-EXIT. EXIT. A4000-INSERT-PARA. WRITE INP-EMP-REC FROM WS-INP-EMP-REC. A400-EXIT. EXIT.

A5000-CLOSE-PARA. CLOSE WS-INFILE. A500-EXIT. EXIT.

INDEXED File Processing


INDEX SEQUENTIAL ORGANIZATION: Records in this file are stored based on a key field which is part of record and this is also called as index. Records in this file are accessible in sequential , dynamic & random mode. An index sequential file is conceptually made up of two files, a data file and an index file.

INDEXED FILE PROCESSING: SELECT logical-file-name ASSIGN TO physical-file-name [ORGANIZATION IS INDEXED] [ACCESS MODE IS {SEQUENTIAL, RANDOM, DYNAMIC}] [RECORD KEY IS data-name-1] [ALTERNATE RECORD KEY is data-name-2 [WITH DUPLICATES]] [FILE STATUS IS data-name-2]

Records in this file are stored based on a key field which is part of record and this is also called as index and this organization is called INDEXED. Here RECORD KEY clause specifies the index based on which the file is sequenced. The data-name-1 must be an alphanumeric field within the record description for the file. In case there are multiple record descriptions, the key field from any of the descriptions can be used. Index sequential file is sorted and maintained on the primary key, the records can also be accessed using the ALTERNATE KEY. Further, the ALTERNATE KEY data item may also find duplicate entries for records. To incorporate this, specify WITH DUPLICATES option.

READ Statement READ File name [NEXT RECORD] INTO data-name [KEY is data-name] [INVALID KEY imperative statements]

Here, the data-name in the KEY phrase must be either the primary

key or one of the alternate keys. The option NEXT RECORD is specified when an index sequential file is being read sequentially INVALID KEY condition arises when the specified key is not found in the file.

WRITE statement: If a file is opened in the OUTPUT mode, then the WRITE statement releases the records to the file in the ascending order of the record key values regardless of the access mode. ACCESS mode SEQUENTIAL is specified and the file is opened OUTPUT and the value of the primary key is not greater than that of the previous record. The file is opened in the OUTPUT or I-O modes and the value of the primary record key is equal to that of an already existing record.

WRITE record-name [FROM data-name] {INVALID KEY imperative statements}

REWRITE statement: REWRITE statement requires that the file must be opened in the I-O mode and if the SEQUENTIAL ACCESS mode is specified, the value of the RECORD KEY being replaced must be equal to that of the record last read from the file.

The INVALID KEY condition arises in the following situations. The access mode is sequential and the value contained in the RECORD KEY of the record to be replaced is not equal to the value of the RECORD KEY data item of the last-retrieved record from the file.

The value of an ALTERNATE RECORD KEY data item for which DUPLICATES is not specified is equal to that of a record already in the file.

Format: REWRITE record-name [FROM data-name] {INVALID KEY imperative statements}

DELETE statement:

To delete a record from an index sequential file, the file must be opened in the I-O mode. If the access mode is sequential, then the INVALID KEY phrase should not be specified. Instead, the last I/O statement executed on the file must be a successful READ statement for the record specified. IF the access mode is RANDOM or DYNAMIC, then the record to be deleted is determined by the value of the RECORD KEY. In this case the INVALID KEY phrase should be specified. The INVALID KEY condition arises if the specified is not found in the file.

DELETE file-name RECORD {INVALID KEY imperative statements}

START statement: The START statement provides positioning the file pointer at a specific location within an index Sequential file for subsequent sequential record retrieval. The access mode must be SEQUENTIAL or DYNAMIC and the file must be opened in the INPUT or I-O modes. Further, if the KEY phrase is specified, the file pointer is positioned at the logical record in the file whose key field satisfies the comparison and if it is omitted, then KEY IS EQUAL (to the RECORD KEY) is implied. If the comparison is not satisfied by any record in the file, an invalid key condition exists; the position of the file position indicator is undefined and (if specified) the INVALID KEY imperative-statement is executed. START file-name [KEY is {=, <, >} data-name] [INVALID KEY imperative statements]
click here to see the sample indexed cobol program

indexed sequential file prosessing program.


How to define VSAM file. How to write records into VSAM file.
//B19895J JOB DEFINEC,'GSS', // CLASS=X,MSGCLASS=T,NOTIFY=&SYSUID //VIDCOPY EXEC PGM=IDCAMS //SYSPRINT DD SYSOUT=* //SYSIN DD *

DEFINE CLUSTER( NAME(B19895.VSAM.CLST) VOL (TSU151) FREESPACE (10 10) RECSZ (20 20) CISZ(200) KEYS(5 0) INDEXED) DATA (NAME(B19895.VSAM.CLST.DATA))INDEX( NAME(B19895.VSAM.CLST.INDEX)) /* //B19895J JOB COMPILE,'GSS', // CLASS=X,MSGCLASS=T,NOTIFY=&SYSUID, // TIME=(0001,00) //JOBLIB DD DSN=PC1G0.PDS.GRD1HK.UTESTB.AP.V011.LOADLIB,DISP=SHR //TEST EXEC PGM=TSTCOBL //SYSIN DD * 34462VASANTA KUMRTDI /* //INFILE DD DSN=B19895.VSAM.CLST,DISP=MOD //

IDENTIFICATION DIVISION. PROGRAM-ID. TESTCOBL. AUTHOR. TESTTEST. DATE-WRITTEN. 19-NOV-2010. DATE-COMPILED. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT WS-INFILE ASSIGN TO INFILE ORGANIZATION IS INDEXED ACCESS MODE IS RANDOM RECORD KEY IS INP-EMPID FILE STATUS IS WS-INFILE-SW.

DATA DIVISION. FILE SECTION. FD WS-INFILE. 01 INP-EMP-REC. 05 INP-EMPID PIC X(05). 05 INP-EMPNAME PIC X(12). 05 INP-EMP-LOB PIC X(03). WORKING-STORAGE SECTION. 01 WS-INFILE-SW PIC X(02) VALUE SPACES. 88 WS-INFILE-SUCESS VALUE '00'. 88 WS-INFILE-EOF VALUE '10'. 01 WS-INP-EMP-REC PIC X(20).

01 WS-EOF-SW 88 WS-EOF-NO 88 WS-EOF-YES

PIC X(01) VALUE 'N'. VALUE 'N'. VALUE 'Y'.

PROCEDURE DIVISION. A1000-MAIN-PARA. PERFORM A2000-OPEN-PARA THRU A200-EXIT. PERFORM A3000-INPUT-PARA THRU A300-EXIT. PERFORM A4000-INSERT-PARA THRU A400-EXIT. PERFORM A5000-CLOSE-PARA THRU A500-EXIT. STOP RUN. A100-EXIT. EXIT. A2000-OPEN-PARA. INITIALIZE WS-INFILE-SW WS-INP-EMP-REC WS-EOF-SW. OPEN OUTPUT WS-INFILE. IF WS-INFILE-SUCESS DISPLAY "FILE OPEN SUCCESSFUL" ELSE DISPLAY "FILE OPENING ERROR" GO TO A100-EXIT END-IF. A200-EXIT. EXIT. A3000-INPUT-PARA. ACCEPT WS-INP-EMP-REC. DISPLAY WS-INP-EMP-REC. . A300-EXIT. EXIT. A4000-INSERT-PARA. WRITE INP-EMP-REC FROM WS-INP-EMP-REC. A400-EXIT. EXIT. A5000-CLOSE-PARA. CLOSE WS-INFILE. . A500-EXIT. EXIT.

RELATIVE File Processing


RELATIVE ORGANIZATION: This file is divided into fixed number of slots each slot has one record. This is identified as relative record number. The access method stores and retrieves a record, based on its relative record number. Records can be accessed as sequentially or randomly or dynamically. This relative files faster access compared to other 2 organizations.

File description entries for a Relative file: SELECT logical-file-name ASSIGN TO physical-file-name [RESERVE integer {AREA, AREAS}] [ORGANIZATION IS RELATIVE] [ACCESS MODE IS {SEQUENTIAL {RANDOM, DYNAMIC}, RELATIVE KEY is data-name-1}] [FILE STATUS IS data-name-2]

Here records are stored based on unique record number which is not part of record is called relative organization.

Here, RELATIVE KEY must be specified when the access mode is RANDOM or DYNAMIC. The dataname-1 is called the relative key data item and it indicates the field that contains the relative record number. This dataname-1 is not part of record description.

The programmer must place an appropriate value in the relative key data item while accessing a record randomly.

READ file-name RECORD [INTO identifier] [; AT END imperative statements] [END-READ]

This format is applicable to SEQUENTIAL ACCESS MODE. If the RELATIVE KEY phrase is also specified with the ACCESS MODE SEQUENTIAL clause, then upon the successful completion of the READ statement, the relative record number of the accessed record is placed in the relative key data item.

Format 2:

READ file-name RECORD [INTO identifier] [; INVALID KEY imperative statements]

This format is applicable when ACCESS MODE is either RANDOM or DYNAMIC. In this case the record to be read is identified from the contents of the RELATIVE KEY data item. The INVALID KEY case arises when the READ is unsuccessful.

Format 3: READ file-name [NEXT] RECORD [INTO identifier] [; INVALID KEY imperative statements]

This format is applicable when the ACCESS MODE is DYNAMIC and the records are to read sequentially. Here the NEXT RECORD is identified according to the following rules.

The READ NEXT statement is the first statement to be executed after the OPEN statement, Then the NEXT RECORD is the first record itself. The READ NEXT statement follows a successful execution of another READ NEXT on the same file; the NEXT RECORD is the record following the one previously read record.

WRITE statement: If a file is opened in the OUTPUT mode, then the WRITE statement releases the records to the file in the ascending order of the record key values regardless of the access mode. The INVALID KEY condition arises for an index sequential file in the following situations. Format: WRITE record-name [FROM data-name] {INVALID KEY imperative statements} {NOT INALID KEY imperative statements} [END-WRITE]

REWRITE statement: The REWRITE statement requires that the file must be opened in the

I-O mode and if the SEQUENTIAL ACCESS MODE is specified, the value of the RECORD KEY being replaced must be equal to that of the record last read from the file. The INVALID key condition arises in the following situations.

The access mode is sequential and the value contained in the RECORD KEY of the record to be replaced does not equal the value of the RECORD KEY data item of the last-retrieved record from the file. The value of an ALTERNATE RECORD KEY data item for which DUPLICATES is not specified is equal to that of a record already in the file. Format: REWRITE record-name [FROM data-name] {INVALID KEY imperative statements}

DELETE statement: If access mode is sequential, then the INVALID KEY phrase should not be specified. Instead, the last I/O statement executed on the file must be a successful READ statement for the record specified. IF the access mode is RANDOM or DYNAMIC, then the record to be deleted is determined by the value of the RECORD KEY. In this case the INVALID KEY phrase should be specified. The INVALID KEY condition arises if the specified is not found in the file.

Format: DELETE file-name RECORD {INVALID KEY imperative statements} {NOT INVALID KEY imperative statements} [END-REWRITE]

START statement: The START statement enables the programmer to position the relative file at some specified point so that subsequent sequential operations on the file can start from this point instead of the beginning. They KEY IS phrase indicates how the file is to be positioned. The data-name in this phrase must be the data-name in the RELATIVE KEY phrase of the SELECT . . . ASSIGN clause. When the EQUAL TO or NOT LESS THAN condition is specified, the file is positioned at the point indicated by the relative key-data item. When the GREATER THAN condition is specified, the file is positioned at the next relative position of the position indicated

by the RELATIVE KEY data item.

START file-name Key is OPERATOR data name [; INVALID KEY imperative statements]

Below is sample COBOL program using relative file


click here to see the sample RRDS cobol program

program for relative organization file processing.


how to define RRDS file. How to write records into VSAM RRDS file.
//B19895J JOB DEFINEC,'GSS', // CLASS=X,MSGCLASS=T,NOTIFY=&SYSUID //VIDCOPY EXEC PGM=IDCAMS //SYSPRINT DD SYSOUT=* //SYSIN DD * DEFINE CLUSTER( NAME(B19895.VSAM.RRCL) VOL (TSU151) CYLINDERS (1 2) CISZ(200) NUMBERED RECORDSIZE (20 20)) DATA (NAME(B19895.VSAM.RRDS.DATA))INDEX( NAME(B19895.VSAM.RRDS.INDEX)) /*

IDENTIFICATION DIVISION. PROGRAM-ID. TESTCOBL. AUTHOR. TESTTEST. DATE-WRITTEN. 19-NOV-2010. DATE-COMPILED. ENVIRONMENT DIVISION.

INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT WS-INFILE ASSIGN TO INFILE ORGANIZATION IS RELATIVE ACCESS MODE IS RANDOM RELATIVE KEY IS RELKEY FILE STATUS IS WS-INFILE-SW. DATA DIVISION. FILE SECTION. FD WS-INFILE. 01 INP-EMP-REC. 05 INP-EMPID PIC X(05). 05 INP-EMPNAME PIC X(12). 05 INP-EMP-LOB PIC X(03). WORKING-STORAGE SECTION. 01 WS-INFILE-SW PIC X(02) VALUE SPACES. 88 WS-INFILE-SUCESS VALUE '00'. 88 WS-INFILE-EOF VALUE '10'. 01 WS-INP-EMP-REC PIC X(20). 01 RELKEY PIC 9(02). PROCEDURE DIVISION. A1000-MAIN-PARA. PERFORM A2000-OPEN-PARA THRU A200-EXIT. PERFORM A3000-INPUT-PARA THRU A300-EXIT. PERFORM A4000-INSERT-PARA THRU A400-EXIT. PERFORM A5000-CLOSE-PARA THRU A500-EXIT. STOP RUN. A100-EXIT. EXIT. A2000-OPEN-PARA. INITIALIZE WS-INFILE-SW WS-INP-EMP-REC. OPEN OUTPUT WS-INFILE. IF WS-INFILE-SUCESS DISPLAY "FILE OPEN SUCCESSFUL" ELSE DISPLAY "FILE OPENING ERROR" GO TO A100-EXIT END-IF. A200-EXIT. EXIT. A3000-INPUT-PARA. ACCEPT WS-INP-EMP-REC. DISPLAY WS-INP-EMP-REC. . A300-EXIT. EXIT. A4000-INSERT-PARA. WRITE INP-EMP-REC FROM WS-INP-EMP-REC. A400-EXIT. EXIT. A5000-CLOSE-PARA.

CLOSE WS-INFILE. . A500-EXIT. EXIT.

You might also like