21
 Algorithms and code examples y Sequentially processing a file y Matching two files y Sorting a file y Generating a report y Handling an empty report y Control Breaks on a report y Loading a table from a file y Searching a table y Using relative files y Using indexed files y Using indexed files with alternate indexes y Calling one program from another  y R eceive data from the keyboard y Back to COBOL topics Index y Back to Main Sequentially processing a file

Algorithms and Code Examples

Embed Size (px)

Citation preview

Page 1: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 1/21

 

Algorithms and code examples

y  Sequentially processing a file 

y  Matching two files y  Sorting a file 

y  Generating a report 

y  Handling an empty report 

y  Control Breaks on a report 

y  Loading a table from a file 

y  Searching a table 

y  Using relative files 

y  Using indexed files 

y  Using indexed files with alternate indexes 

y  Calling one program from another  

y  R eceive data from the keyboard 

y  Back to COBOL topics Index 

y  Back to Main 

Sequentially processing a file

Page 2: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 2/21

In WORK ING-STORAGE you will need a field that will be used to indicate when the

end of file is reached. Trying to read beyond the end of a file is disastrous. Define a

field similar to:

01 WS-END-OF-FILE-SW PIC X VALUE 'N'.

88 WS-END-OF-FILE VALUE 'Y'.

A skeleton of the PROCEDURE DIVISIO N will be similar to this:

PROCEDURE DIVISION.

PERFORM 100-INITIALIZE.

PERFORM 200-PROCESS-INPUT

UNTIL WS-END-OF-FILE.

PERFORM 900-TERMINATE.

STOP RUN.

100-INITIALIZE.

* THE FOLLOWING STATEMENT CAN BE USED TO OPEN ALL FILES

OPEN INPUT INPUT-FILE.

* DO OTHER INITIALIZATION TASKS IN THIS PARAGRAPH, LIKE

* GETTING CURRENT DATE, INITIALIZING VARIABLES, ETC.

* THE PERFORM OF THE READ PARAGRAPH SHOULD BE THE LAST STATEMENT

* IN THIS PARAGRAPH. THIS IS THE PRIMING READ.

PERFORM 110-READ-INPUT-FILE.

110-READ-INPUT-FILE.

* IF MULTIPLE INPUT FILES HAVE A SEPARATE READ PARAGRAPH

* FOR EACH. ALSO HAVE SEPARATE END-OF-FILE INDICATORS.

READ INPUT-FILE

AT END MOVE 'Y' TO WS-END-OF-FILE-SW

END-READ.

200-PROCESS-INPUT.

* ENTER CODE HERE TO PROCESS THE INPUT DATA

* THE PERFORM OF THE READ PARAGRAPH SHOULD BE THE LAST STATEMENT

* IN THIS PARAGRAPH.

PERFORM 110-READ-INPUT-FILE

900-TERMINATE.

* THE FOLLOWING STATEMENT CAN BE USED TO CLOSE ALL FILES

CLOSE INPUT-FILE.

Back to Table of Contents 

Matching two files

Page 3: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 3/21

File matching is also known as co-sequential file processing, because multiple input

files are being processed at once. All files must be sorted on the field(s) to be

matched.

For example we have two input files, IN-OR DER and IN-CUSTOMER and we need

to match them by customer number, a field appearing on both files. The basic logicwill be similar to this:

PERFORM 200-READ-ORDER.

PERFORM 210-READ-CUSTOMER.

PERFORM 300-COMPARE

UNTIL END-OF-CUSTOMER AND

END-OF-ORDER.

STOP RUN.

200-READ-ORDER.

READ IN-ORDER

AT END

MOVE 'Y' TO END-OF-ORDER-SW

MOVE HIGH-VALUES TO O-CUST-NBR

END-READ.

210-READ-CUSTOMER.

READ IN-ORDER

AT END

MOVE 'Y' TO END-OF-ORDER-SW

MOVE HIGH-VALUES TO C-CUST-NBR

END-READ.

300-COMPARE.

IF O-CUST-NBR = C-CUST-NBR

PERFORM P400-MATCHPERFORM P200-READ-ORDER

PERFORM P210-READ-CUSTOMER

ELSE

IF O-CUST-NBR < C-CUST-NBR

PERFORM P500-ORDER-W-NO-CUSTOMER

PERFORM P200-READ-ORDER

ELSE

PERFORM P600-CUSTOMER-W-NO-ORDER

PERFORM P210-READ-CUSTOMER

END-IF

END-IF.

 Notes:

y  If one file can have multiple records matching a single record on the other file

then that is the only file read after processing a match. In the above example if a customer can have multiple orders then after performing P400-MATCH do

not perform P210-READ-CUSTOMER . Only read from the file that can

contain multiple records with the same value for the field being matched.

Page 4: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 4/21

y  The purpose of setting the matched field to HIGH-VALUES upon end of file is

 prevent the other file from reaching a record with a higher value causing anattempted read beyond end-of -file.

y  This algorithm can be extrapolated to allow for matching on multiple fields and

for matching three or more files though it gets complicated quickly. Normally,

when matching more than two files multiple programs are used, each matching

two files.

Back to Table of Contents 

Sorting a file

Sorting a file requires defining two files in addition to the input (unsorted) file: the

sorted file and a work file. Each requires a SELECT statement. The sorted filerequires an FD and the work file requires an SD. SDs (Sort file Description) are just

like FDs but cannot have a LABELS clause.

SELECT IN-FILE ASSIGN TO DISK.

SELECT SORTED-FILE ASSIGN TO DISK.

SELECT SORT-WORK ASSIGN TO DISK.

FD IN-FILE

VALUE OF FILE-ID IS 'PAYROLL-FILE'.

01 IN-RECORD PIC X(200).

FD SORTED-FILE

VALUE OF FILE-ID IS 'SORTED-PAYROL-FILE'.

01 SORTED-RECORD PIC X(200).

* ONLY NEED TO DEFINE THE FIELDS THAT THE FILE WILL BE

* SORTED ON. BUT ACCOUNT FOR THE ENTIRE RECORD.

SD SORT-WORK

VALUE OF FILE-ID IS 'TEMP-1'.

01 SORT-RECORD.

05 SR-EMPLOYEE PIC 9(09).

05 PIC X(21).

05 SR-REGION PIC X(03).

05 PIC X(87).

05 SR-DEPT PIC 9(02).05 PIC X(78).

The above SD has prepared us to sort on the employee number, region and department

number. Let's sort on region first, then department and then employee.

One COBOL statement will do the trick. The SOR T statement will read the entire

input file and sort it. You will use the sorted file as input to the rest of the program.

Page 5: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 5/21

Treat it as any other input file (read it, check for end of file, close it, etc.). Normally,

the sort is done during program initialization but this depends on processing needs.

SORT SORT-WORK

ON ASCENDING KEY SR-REGION

ON ASCENDING KEY SR-DEPT

ON ASCENDING KEY SR-EMPLOYEE

USING IN-FILE

GIVING SORTED-FILE.

* SOME COMPILERS CLOSE THE FILE AFTER THE SORT, SOME DO NOT.

* YOU MAY OR MAY NOT HAVE TO OPEN IT BEFORE CONTINUING.

OPEN INPUT SORTED-FILE.

PERFORM UNTIL WS-EOF-SW = 'Y'

READ SORTED-FILE

AT END

MOVE 'Y' TO WS-EOF-SW

NOT AT ENDPERFORM 200-PROCESS

END-READ

END-PERFORM.

CLOSE SORTED-FILE.

STOP RUN.

As an alternative to specifying input and output files in the SOR T you can insteadspecify an INPUT PROCEDURE or OUTPUT PROCEDURE, paragraphs to execute

 before and after the sort takes place.

SORT SORT-WORK

ON ASCENDING KEY SR-REGIONON ASCENDING KEY SR-DEPT

ON ASCENDING KEY SR-EMPLOYEE

INPUT PROCEDURE 100-PRE-SORT

OUTPUT PROCEDURE 200-POST-SORT.

100-PRE-SORT.

OPEN INPUT IN-FILE.

PERFORM UNTIL WS-EOF-SW = 'Y'

READ IN-FILE

AT END

MOVE 'Y' TO WS-EOF-SW

NOT AT END

PERFORM 110-PROCESS

END-READ

END-PERFORM.

CLOSE IN-FILE.

110-PROCESS.

MOVE IN-RECORD TO SORT-RECORD.

* ONLY SORT RECORDS WITH NON-ZERO DEPARTMENT NUMBER

IF SR-DEPT NOT EQUAL ZEROES

Page 6: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 6/21

RELEASE SORT-RECORD

END-IF.

200-POST-SORT.

OPEN INPUT SORT-FILE.

MOVE 'N' TO WS-EOF-SW.

PERFORM UNTIL WS-EOF-SW = 'Y'

RETURN SORT-FILE

AT END

MOVE 'Y' TO WS-EOF-SW

NOT AT END

PERFORM 300-PROCESS

END-READ

END-PERFORM.

CLOSE SORT-FILE.

Back to Table of Contents 

Generating a report

In WORK ING-STORAGE define something similar to this (the lines per page will

depend on the installation. Initialize the line number to the same value as lines per 

 page to trigger the printing of headings for the first page):

01 WS-REPORT-VALUES.

05 WS-PAGE-NBR PIC 9(4).

05 WS-LINE-NBR PIC 99 VALUE 66.

05 WS-LINES-PER-PAGE PIC 99 VALUE 66.

Also in WORK ING-STORAGE define separate records for each page heading line,each column heading line, each detail line and any total lines. The record layout in the

FD for the report file should not contain any fields, only the record name and a PIC X

 big enough to hold any of the heading or detail records plus 1 character. If there are to be totals produced for the report then an accumulator field for each total must also be

defined in WORK ING-STORAGE (make sure it's big enough).

Most reports contain the current date in one of the page headings. If so, get the current

date in the program's initialization paragraph and store it on the page heading record.

Do not get the current date every time the headings are printed. If your detail linesrequire special initializations before they are printed then call that paragraph during

the program's initialization paragraph.

While processing an input record you will be moving data to the detail line. At the end

of the processing loop, but before reading the next input record, call the print detail

line paragraph (the detail line now has all of the data that will be printed).

Page 7: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 7/21

8000-PRINT-DETAIL.

* IF ANY OF THE FIELDS ON THE DETAIL LINE ARE TO BE TOTALLED THEN

* ADD ITS VALUE TO THE ACCUMULATING FIELD HERE, BEFORE ANYTHING

* IS PRINTED.

ADD 1 TO WS-LINE-NBR.

IF WS-LINE-NBR > WS-LINES-PER-PAGE

PERFORM 8100-PRINT-HEADINGS

END-IF.

WRITE OT-REPORT-RECORD

FROM WS-DETAIL-RECORD

AFTER ADVANCING 1 LINE

END-WRITE.

* IF THE DETAIL LINES ARE NOT TO BE SINGLE SPACED THEN CHANGE

* THE NUMBER OF LINES TO ADVANCE IN PREVIOUS WRITE AND ALSO THE

* VALUE IN THE FOLLOWING ADD TO REFLECT DESIRED SPACING.

ADD 1 TO WS-LINE-NBR.

* IF YOUR DETAIL LINES REQUIRE SPECIAL INITIALIZATIONS THEN CALL

* THAT PARAGRAPH AT THE END OF THIS PARAGRAPH

8100-PRINT-HEADINGS.

ADD 1 TO WS-PAGE-NBR* MOVE ANY FIELDS THAT ARE PART OF THE PAGE HEADINGS TO THE

* PAGE HEADING RECORDS NOW (LIKE THE PAGE NUMBER).

WRITE OT-REPORT-RECORD

FROM WS-PAGE-HDR-1-RECORD

AFTER PAGE

END-WRITE.

* INCLUDE SIMILAR WRITES FOR ALL REMAINING PAGE HEADING RECORDS AND

* COLUMN HEADING RECORDS - EACH ADVANCING THE PROPER NUMBER OF LINES

* TO REFLECT DESIRED SPACING (SINGLE, DOUBLE, ETC.).

*

* THE WS-LINE-NBR FIELD WILL NEED POPULATED WITH A VALUE INDICATING

* HOW MANY LINES HAVE BEEN PRINTED ON THE PAGE DURING THIS PARAGRAPH,

* INCLUDING SPACING.

MOVE literal TO WS-LINE-NBR.

If any totals were accumulated during the generation of the report then call the

 paragraph to print the total line(s) from the program's termination paragraph

(bef  or e you close the report file).

Back to Table of Contents 

Handling an empty report

It is often valid for a report to have no data. Either the input file is empty (notnecessarily a problem) or the input file has no records meeting whatever criteria is

necessary in order to get printed on the report. The problem is that in such cases

nothing comes out of the program, not even the headings (In the algorithm above the

1st headings aren't printed until the 1st detail line is built).

Page 8: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 8/21

How does the user know that the report is empty and there wasn't some problem that

crashed the program? A common practice is to print a descriptive message on thereport signifying that there was no data to print so that the end user knows that this

was the case. Such a message needs defined in WORK ING-STORAGE:

01 WS-DETAIL-0.05 PIC X(54) VALUE SPACES.

05 PIC X(24) VALUE '*** NO DATA TO PRINT ***'.

05 PIC X(54) VALUE SPACES.

In the program's termination paragraph check the value of the page number field. If itis still zero then you haven't printed any detail records. Call the paragraph to print the

 page headings, then print the message to signify that there was no data print. If  printing totals on the report then have the call to that paragraph as an 'ELSE' to the 'IF 

WS-PAGE- NBR = 0'.

Back to Table of Contents 

Control Breaks on a report

Click here to view/download txt file with control break algorthims (single and double

level).

In WORK ING-STORAGE define fields to hold the current values of each field that is

a control field. They must be defined exactly as the corresponding input fields aredefined. Initialize them to ZEROS if numeric, LOW-VALUES if alphanumeric.

Special processing is done whenever the value of a control field changes. Totals must

 be produced for the previous control group, fields must be initialized for the newcontrol group and possibly some headings or a new page for the new control group.

Checks for control break processing are done immediately after a record is read.

Compare the value of the control field on the input record to the value in the hold

field. If different then call the paragraph that handles control break processing.

In WORK ING-STORAGE:01 WS-CONTROL-FIELDS.

05 WS-HOLD-DEPARTMENT PIC X(03) VALUE LOW-VALUES.

05 WS-FIRST-BREAK-SW PIC X VALUE 'Y'.

88 WS-FIRST-BREAK VALUE 'Y'.

In the PROCEDURE DIVISIO N:

Page 9: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 9/21

2000-READ-INPUT-RECORD.

READ INPUT-FILE

AT END

MOVE 'Y' TO WS-END-OF-FILE-SW

NOT AT END

PERFORM 2100-CHECK-FOR-BREAK

END-READ.

2100-CHECK-FOR-BREAK.

IF IN-DEPARTMENT NOT = WS-HOLD-DEPARTMENT

* IF THERE WAS NO PREVIOUS CONTROL GROUP THEN DON'T TRY TO TOTAL

* ANYTHING OR PRINT TOTAL LINE(S).

IF WS-FIRST-BREAK

MOVE 'N' TO WS-FIRST-BREAK-SW

ELSE

PERFORM 8100-TOTAL-PREVIOUS-GROUP

END-IF

* BOTH OF THE FOLLOWING PROCESSING MAY NOT BE NECESSARY

PERFORM 8200-INITIALIZE-FOR-NEW-GROUP

PERFORM 8300-HEADINGS-NEW-GROUP

MOVE IN-DEPARTMENT TO WS-HOLD-DEPARTMENTEND-IF.

The above code is for a single-level control break. Multiple-level control breaks take

more care. The control fields will be ordered (i.e. break on salesperson within a

region).

Hold fields must be defined for each control fields. It may also be easier (and cleaner)

to have separate paragraphs for totalling and headings for each control field. Whenchecking for changes in the control fields start with the major field and then work 

your way to the most minor field (i.e. if the breaks were 'a' within 'b' within 'c' within

'd' within 'e' check field 'e' first, then 'd', etc.). A control break in a field implies a

 break in all fields minor to the one with the break. Ensure all the control break  processing that needs to be executed actually happens and happens in the correct

order.

Back to Table of Contents 

Loading a table from a file

We have a file containing part numbers and descriptions. Each record contains a 9-digit part number and a 41- byte description. This file is to be loaded into a table to be

cross-referenced with a part number on another file.

Since we want the entire table to be ready when we start processing our primary input

file the table will be loaded, in its entirity, during program initialization.

Page 10: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 10/21

FD PART-MASTER.

01 PART-MASTER-REC.

05 IN-PART-NBR PIC 9(9).

05 IN-PART-DESC PIC X(41).

(In working storage)

01 FILLER.

05 PART-TABLE OCCURS 100 TIMES.

10 PART-NBR PIC 9(9).

10 PART-DESC PIC X(41).

01 WS-EOF-SW PIC X VALUE 'N'.

88 END-OF-FILE VALUE 'Y'.

88 TBL-OVERFLOW VALUE 'F'.

01 WS-SUB PIC 999.

01 WS-TBL-MAX PIC 999 VALUE 100.

(To load table from file)

P100-LOAD-TABLE.OPEN INPUT PART-MASTER.

MOVE 0 TO WS-SUB.

PERFORM UNTIL END-OF-FILE OR TBL-OVERFLOW

READ PART-MASTER

AT END SET END-OF-FILE TO TRUE

NOT AT END PERFORM P110-ADD-ENTRY

END-READ

END-PERFORM.

CLOSE PART-MASTER.

IF TBL-OVERFLOW

DISPLAY 'ERROR: PART TABLE OVERFLOW!!!!'

DISPLAY 'PROGRAM ENDING...'

STOP RUN

END-IF.

P110-ADD-ENTRY.

ADD 1 TO WS-SUB.

IF WS-SUB > WS-TBL-MAX

SET TBL-OVERFLOW TO TRUE

ELSE

MOVE PART-MASTER-REC TO PART-TABLE (WS-SUB)

END-IF.

Back to Table of Contents 

Searching a table

 Now that the table has been populated with values using the previous algorithm let's

try to use this table. The primary input file to this program (the sales file) contains,

Page 11: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 11/21

among other things, a part number. This is to be printed on a sales report along with

the description of the part. The description is not kept on the sales file so the table is

needed.

A file matching algorithm is not used becuase that would require the sales file to be

sorted by part number and it is doubtful that we would want it that way on the report.

There are many ways to do this. If the table were indexed the SEARCH command

could be used. The following is not using the SEARCH statement:

PERFORM P200-READ-SALES-FILE.

MOVE '*** NO PART DESCRIPTION' TO RPT-DTL-PART-DESC.

PERFORM VARYING WS-SUB FROM 1 BY 1

UNTIL (WS-SUB > WS-TBL-MAX) OR

(IN-PRT-NBR = PART-NBR (WS-SUB))

IF IN-PRT-NBR = PART-NBR (WS-SUB)

MOVE PART-DESC TO RPT-DTL-PART-DESCEND-IF

END-PERFORM.

(if the table was defined as INDEXED BY WS-INDX)

PERFORM P200-READ-SALES-FILE.

SET WS-INDX TO 1.

SEARCH PART-TABLE

AT END

MOVE '*** NO PART DESCRIPTION' TO RPT-DTL-PART-DESC

WHEN IN-PRT-NBR = PART-NBR (WS-INDX)

MOVE PART-DESC TO RPT-DTL-PART-DESCEND-SEARCH.

Back to Table of Contents 

Using relative files

The SELECT for relative files requires the following clauses:

ORGANIZATION IS RELATIVE

ACCESS IS DYNAMIC

RELATIVE KEY IS working-storage-field-1 

FILE STATUS IS working-storage-field-2.

working-storag e- f  ield -1 must be numeric, working-storag e- f  ield -2 is a PIC X(2).

Before a read or write the relative key must be populated with a value by the program.

This is basically a record number. When a read is executed the value of the relative

Page 12: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 12/21

key directs the system to attempt a retrieval of that particular record (if relative key is

5 then the system will try to retrieve a record from the 5th slot in the file). If a write is

executed then the system will attempt to place a record in that slot.

The value of the file status after the statement is executed will indicate whether or not

the statement successfully executed. If not, the value will also indicate what wentwrong. This field can be interrogated with an IF or EVALUATE:

SELECT IN-MASTER

ORGANIZATION IS RELATIVE

ACCESS IS DYNAMIC

RELATIVE KEY IS WS-RELATIVE-KEY

FILE STATUS IS WS-FILE-STATUS.

. . . . . .

MOVE WS-REL-ADDR TO WS-RELATIVE-KEY.

READ IN-MASTER.

EVALUATE WS-FILE-STATUS

WHEN '00'

PERFORM 300-SUCCESSFUL-READ

WHEN '23'

PERFORM 400-RECORD-SLOT-IS-EMPTY

WHEN '92'

DISPLAY 'FILE NOT OPEN'

WHEN OTHER

DISPLAY 'UNEXPECTED FILE ERROR: ' WS-FILE-STATUS

END-EVALUATE.

See theF

ile Errors Page for a list of file status values and their meanings.

As an alternative the INVALID KEY clause can be used:

MOVE WS-REL-ADDR TO WS-RELATIVE-KEY.

READ IN-MASTER

INVALID KEY

PERFORM 400-RECORD-SLOT-IS-EMPTY

NOT INVALID KEY

PERFORM 300-SUCCESSFUL-READ

END-READ.

This lumps all unsuccessful operations into one group so this may not be anappropriate method.

Writes work similarly:

SELECT OT-MASTER

ORGANIZATION IS RELATIVE

ACCESS IS DYNAMIC

RELATIVE KEY IS WS-RELATIVE-KEY

Page 13: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 13/21

FILE STATUS IS WS-FILE-STATUS.

. . . . . .

MOVE WS-REL-ADDR TO WS-RELATIVE-KEY.

WRITE OT-MASTER-RECORD.

EVALUATE WS-FILE-STATUS

WHEN '00'

ADD +1 TO WS-NBR-RECORDS-WRITTEN

WHEN '22'

PERFORM 500-SLOT-ALREADY-USED

WHEN '92'

DISPLAY 'FILE NOT OPEN'

WHEN OTHER

DISPLAY 'UNEXPECTED FILE ERROR: ' WS-FILE-STATUS

END-EVALUATE.

Writes also support INVALID KEY/NOT INVALID KEY.

R elative files can be accessed as if they were sequential files. In the SELECT changethe ACCESS IS DYNAMIC to ACCESS IS SEQUE NTIAL. Can then use READs

(include AT E ND) and WR ITEs as if the file was sequential. Do not specify a

RELATIVE KEY or a FILE STATUS.

R elative files support two other type of operations, but these require the file to be

opened for input and output at the same time. Access cannot be sequential. These

operations are DELETE and REWR ITE.

The DELETE statement will delete the current record. This requires a successfulREAD before the DELETE.

OPEN I-O IN-MASTER.

. . . . . .

MOVE WS-REL-ADDR TO WS-RELATIVE-KEY.

READ IN-MASTER.

EVALUATE WS-FILE-STATUS

. . .

END-EVALUATE.

DELETE IN-MASTER RECORD.EVALUATE WS-FILE-STATUS

WHEN '00'

PERFORM 200-SUCCESSFUL-DELETE

WHEN '43'

DISPLAY ' NO CURRENT RECORD. REL KEY = ' WS-RELATIVE-KEY

. . .

END-EVALUATE.

Page 14: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 14/21

The REWR ITE statement will update the current record. This requires a successful

READ before the REWR ITE.

OPEN I-O IN-MASTER.

. . . . . .

MOVE WS-REL-ADDR TO WS-RELATIVE-KEY.

READ IN-MASTER.

EVALUATE WS-FILE-STATUS

. . .

END-EVALUATE.

* IF THE READ WAS SUCCESSFUL YOU WILL UPDATE WHATEVER FIELDS ON THE

* RECORD WITH THEIR NEW VALUES AT THIS POINT

REWRITE IN-MASTER-RECORD.

EVALUATE WS-FILE-STATUS

. . .

END-EVALUATE.

 Note that READ and DELETE use the file name; WR ITE and REWR ITE use therecord name. DELETE uses the word 'RECOR D' after the file name, do not connect it

to the file name with a hyphen. REWR ITE will not change the number of records in afile, it only alters the data in an existing record. All these statements support the

INVALID KEY/NOT INVALID KEY clauses.

Back to Table of Contents 

Using indexed files

The SELECT for indexed files requires the following clauses:

ORGANIZATION IS INDEXED

ACCESS IS DYNAMIC

RECORD KEY IS field-1 

FILE STATUS IS working-storage-field-2.

With indexed files, the key is actually part of the record. No two records on the same

file can have the same value for this key; the key must uniquely identify therecord. working-storag e- f  ield -2 is a PIC X(2).

Before a read or write the record key must be populated with a value by the program.

When a read is executed the index of the file is searched for the value of the record

key. If the record is in the file then a matching entry will be in the index. If a write is

Page 15: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 15/21

executed then the system will ensure that the file doesn't already contain a record for 

that key.

The value of the file status after the statement is executed will indicate whether or notthe statement successfully executed. If not, the value will also indicate what went

wrong. This field can be interrogated with an IF or EVALUATE:

SELECT IN-MASTER

ORGANIZATION IS INDEXED

ACCESS IS DYNAMIC

RECORD KEY IS IN-CUSTOMER-NBR

FILE STATUS IS WS-FILE-STATUS.

. . . . . .

MOVE WS-CUST-NO TO IN-CUSTOMER-NBR.

READ IN-MASTER.

EVALUATE WS-FILE-STATUSWHEN '00'

PERFORM 300-SUCCESSFUL-READ

WHEN '23'

PERFORM 400-RECORD-NOT-FOUND

WHEN '92'

DISPLAY 'FILE NOT OPEN'

WHEN OTHER

DISPLAY 'UNEXPECTED FILE ERROR: ' WS-FILE-STATUS

END-EVALUATE.

See the File Errors Page for a list of file status values and their meanings.

As an alternative the INVALID KEY clause can be used:

MOVE WS-CUST-NO TO IN-CUSTOMER-NBR.

READ IN-MASTER

INVALID KEY

PERFORM 400-RECORD-NOT-FOUND

NOT INVALID KEY

PERFORM 300-SUCCESSFUL-READ

END-READ.

This lumps all unsuccessful operations into one group so this may not be an

appropriate method.

Writes work similarly:

SELECT OT-MASTER

ORGANIZATION IS INDEXED

ACCESS IS DYNAMIC

RECORD KEY IS OT-CUSTOMER-NBR

FILE STATUS IS WS-FILE-STATUS.

Page 16: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 16/21

 

. . . . . .

MOVE WS-CUST-NO TO OT-CUSTOMER-NBR.

WRITE OT-MASTER-RECORD.

EVALUATE WS-FILE-STATUS

WHEN '00'

ADD +1 TO WS-NBR-RECORDS-WRITTEN

WHEN '22'

PERFORM 500-RECORD-ALREADY-EXISTS

WHEN '92'

DISPLAY 'FILE NOT OPEN'

WHEN OTHER

DISPLAY 'UNEXPECTED FILE ERROR: ' WS-FILE-STATUS

END-EVALUATE.

Writes also support INVALID KEY/NOT INVALID KEY.

Indexed files can be accessed as if they were sequential files. In the SELECT changethe ACCESS IS DYNAMIC to ACCESS IS SEQUE NTIAL. Can then use READs

(include AT E ND) and WR ITEs as if the file was sequential. Do not specify a

RECOR D KEY or a FILE STATUS.

Indexed files support two other type of operations, but these require the file to beopened for input and output at the same time. Access cannot be sequential. These

operations are DELETE and REWR ITE.

The DELETE statement will delete the current record. This requires a successful

READ before the DELETE.

OPEN I-O IN-MASTER.

. . . . . .

MOVE WS-CUST-NO TO IN-CUSTOMER-NBR.

READ IN-MASTER.

EVALUATE WS-FILE-STATUS

. . .

END-EVALUATE.

DELETE IN-MASTER RECORD.

EVALUATE WS-FILE-STATUSWHEN '00'

PERFORM 200-SUCCESSFUL-DELETE

WHEN '43'

DISPLAY ' NO CURRENT RECORD. REL KEY = ' WS-RELATIVE-KEY

. . .

END-EVALUATE.

Page 17: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 17/21

The REWR ITE statement will update the current record. This requires a successful

READ before the REWR ITE.

OPEN I-O IN-MASTER.

. . . . . .

MOVE WS-CUST-NO TO IN-CUSTOMER-NBR.

READ IN-MASTER.

EVALUATE WS-FILE-STATUS

. . .

END-EVALUATE.

* IF THE READ WAS SUCCESSFUL YOU WILL UPDATE WHATEVER FIELDS ON THE

* RECORD WITH THEIR NEW VALUES AT THIS POINT

REWRITE IN-MASTER-RECORD.

EVALUATE WS-FILE-STATUS

. . .

END-EVALUATE.

 Note that READ and DELETE use the file name; WR ITE and REWR ITE use therecord name. DELETE uses the word 'RECOR D' after the file name, do not connect it

to the file name with a hyphen. REWR ITE will not change the number of records in afile, it only alters the data in an existing record. All these statements support the

INVALID KEY/NOT INVALID KEY clauses.

Back to Table of Contents 

Using indexed files with alternate keys

An indexed file can have more than one key (a multi-key file). There will be one key

designated as the primary key, all other keys are secondary, or alternate, keys.

Alternate keys do not have to be unique within the file, primary keys do.

The SELECT for such a file still requires the RECOR D KEY clause (which identifies

the primary key). Immediately following the RECOR D KEY clause are any

ALTER  NATE KEY clauses. Any alternate keys that are used in the program are listed

here. If an alternate key does not have to be unique specify it WITH DUPLICATES.All alternate keys must be part of the record.

SELECT IN-RENTAL-CAR-MASTER

ORGANIZATION IS INDEXED

ACCESS IS DYNAMIC

RECORD KEY IS IN-LICENSE

Page 18: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 18/21

ALTERNATE KEY IS IN-VIN

ALTERNATE KEY IS IN-STYLE WITH DUPLICATES

ALTERNATE KEY IS IN-MFR WITH DUPLICATES

FILE STATUS IS WS-FILE-STATUS.

When the file is opened the access path defaults to that of the primary key. To use an

access path of one of the alternate keys, use the STAR T command. You first primethe alternate key field with some value that you want to start with. You then execute a

STAR T with either 'EQUALS', 'NOT <' or '>'. For example:

MOVE 'HONDA' TO IN-MFR.

START IN-RENTAL-CAR-MASTER

KEY NOT < IN-MFR

END-START.

This will change the access path to that of the alternate key IN-MFR and then position

the file pointer so that it is at the first record whose key is equal to or greater than thespecified value.

MOVE SPACES TO IN-VIN.

START IN-RENTAL-CAR-MASTER

KEY > IN-VIN

END-START.

This one changes the access path to that of IN-VIN. The record pointer here is set to

the first record in the file with an IN-VIN value higher than that of the specified value.

MOVE 'MIDSIZE' TO IN-STYLE.

START IN-RENTAL-CAR-MASTER

KEY EQUALS IN-STYLE

END-START.

This one changes the access path to that of IN-STYLE. The record pointer here is set

to the first record in the file with an IN-STYLE that matches that of the specified

value.

The file status needs to be checked after the STAR T, or the INVALID KEY clause

used. One cause of an unsuccessful STAR T is if no such record can be found in thefile.

The STAR T NOT < and STAR T > do not actually read a record, even if the STAR T

was successful in postioning the file pointer.

Page 19: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 19/21

The READ NEXT statement can then be used to read records along the current access

 path. The file status must be checked after each READ NEXT or the INVALID KEYclause used. One common cause of an unsuccessful READ NEXT is reaching the end

of the file. AT E ND can also be used.

* GET MANUFACTURER FROM KEYBOARD

DISPLAY 'ENTER CAR MANUFACTURER: ' WITH NO ADVANCING.

ACCEPT WS-MFR.

MOVE WS-MFR TO IN-MFR.

* ATTEMPT TO START FILE AT SPECIFIED MANUFACTURER

START IN-RENTAL-CAR-MASTER

KEY NOT < IN-MFR

INVALID KEY DISPLAY 'NO RECORDS ON FILE FOR ' WS-MFR

NOT INVALID KEY PERFORM 300-READ-NEXT-ON-MFR

END-START.

PERFORM 300-READ-NEXT-ON-MFR UNTIL WS-EOF-SW = 'Y'.

. . .

300-READ-NEXT-ON-MFR.

READ IN-RENTAL-CAR-MASTER NEXT RECORD

AT END MOVE 'Y' TO WS-EOF-SW

NOT AT END PERFORM 310-CHECK-MFR

END-READ.

310-CHECK-MFR.

IF IN-MFR = WS-MFR

DISPLAY 'CAR FOUND FOR MFR ' WS-MFR ' LICENSE ' IN-LICENSE

ELSE

MOVE 'Y' TO WS-EOF-SW

END-IF.

Back to Table of Contents 

Calling one program from another

In these examples we will have PROGRAM1 call PROGRAM2. The first example

shows a static call. PROGRAM2 is compiled into PROGRAM2.OBJ.

CALL 'PROGRAM2.OBJ'.

PROGRAM2 requires either a 'GOBACK ' or 'EXIT PROGRAM' in order for control

to return to PROGRAM1. A 'STOP RU N' will terminate all programs.

When a program containing static calls is compiled the object code of all statically

called programs is combined with the object code of the program with the calls into

one package. The advantage is that the object code of called programs need not be present when the program is run, all object code is included in the one package. The

Page 20: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 20/21

disadvantage with this is that if one of the called programs is changed any program

that statically calls it must be re-compiled so that the new version is included.

The other type of call is a dynamic call. When a dynamic call is executed the objectcode for the called program is searched for on disk (it is not part of the calling

 program's object code) and then executed. The advantage is that the newest version of the called program is always executed - no need to re-compile the calling program.

To change this to a dynamic call add the following to PROGRAM1's WORK ING-

STORAGE SECTIO N. PROGRAM2.OBJ must exist when PROGRAM1 is run.

01 WS-CALLED-PGM PIC X(12) VALUE 'PROGRAM2.OBJ'.

The CALL now looks like:

CALL WS-CALLED-PGM.

Static calls have the called program as a literal in the call, dynamic calls have a field.

The value of that field is the name of the called program.

Passing some fields from PROGRAM1 to PROGRAM2 requires a little more work.

First, only WORK ING-STORAGE fields from PROGRAM1 can be passed to

PROGRAM2. These fields are specfied in the CALL as follows:

CALL 'PROGRAM2.OBJ'

USING WS-FIELD-1 WS-FIELD-2 WS-FIELD-3

WS-FIELD-4 WS-FIELD-5

END-CALL.

This can be done with either static or dynamic calls. Group-level fields can be passedso if all 5 of the above fields were under the same group-level field you could just

specify it in the CALL.

PROGRAM2 needs to know some fields are coming in. This is done on the

PROCEDURE DIVISIO N statement of PROGRAM2:

PROCEDURE DIVISION USING LK-FIELD-A LK-FIELD-B LK-FIELD-C

LK-FIELD-D LK-FIELD-E.

The fields can have the same name as they do in PROGRAM1. In PROGRAM2 these

fields are defined in the LINKAGE SECTIO N, which is in the DATA DIVISIO N and

follows the WORK ING-STORAGE SECTIO N. The fields in the two USING clauses

must appear in the same order. R emember that while the names don't have to match

the data types and sizes do.

Page 21: Algorithms and Code Examples

8/3/2019 Algorithms and Code Examples

http://slidepdf.com/reader/full/algorithms-and-code-examples 21/21

All fields are passed by reference (meaning that pointers to the fields are passed and

not copies of the data) so that PROGRAM2 can alter any of them.

Back to Table of Contents 

R eceive data from the keyboard

Say that a 3-digit number will be input into your program. Define:

01 WS-INPUT-FIELDS.

05 WS-INPUT-NUMBER PIC ZZ9.

01 WS-NUMERIC-FIELDS.

05 WS-NUMERIC-NUMBER PIC 999.

In the PROCEDURE DIVISIO N:

DISPLAY 'Enter a number (0-999): ' WITH NO ADVANCING.

ACCEPT WS-INPUT-NUMBER.

MOVE WS-INPUT-NUMBER TO WS-NUMERIC-NUMBER.

* CALCULATIONS ARE TO BE DONE USING WS-NUMERIC-NUMBER

Back to Table of Contents