Search code examples
cobolgnucobol

Reading a table from a file only results in the first record being stored


Additional background: this is a follow-up to Adding two integers giving unwanted result in cobol.

As the input data consists of strings and integers are needed for calculating, this program bulk reads each row, then read each field individually from the file and convert the necessary fields to numbers when storing them in the working storage section table.

Now, for some reason, only the first record reads and stores properly. The rest of the records are being read as blanks or nulls, I guess, even though the file contents after the first record are obviously not null.

Here is my current code for the full program:

    IDENTIFICATION DIVISION.
    PROGRAM-ID. GRADEREPORT.
    AUTHOR. JORDAN RENAUD.
    DATE-WRITTEN. 09/18/2020.
    
    ENVIRONMENT DIVISION.
    INPUT-OUTPUT SECTION.
    FILE-CONTROL.
           SELECT GRADES-FILE ASSIGN TO "bill"
               ORGANIZATION IS LINE SEQUENTIAL
               ACCESS IS SEQUENTIAL.
    
    DATA DIVISION.
    FILE SECTION.
    FD GRADES-FILE.
    01     INPUT-TOTAL-POINTS       PIC 9(4).
    01     INPUT-GRADES.
    05         INPUT-GRADE OCCURS 1 to 100 TIMES DEPENDING ON RECORD-COUNT.
    10            INPUT-ASSIGNMENT-NAME   PIC X(20).
    10            INPUT-CATEGORY          PIC X(20).
    10            INPUT-POINTS-POSSIBLE   PIC X(14).
    10            INPUT-POINTS-EARNED     PIC X(14).
    
    WORKING-STORAGE SECTION.
    77     GRADES-FILE-EOF          PIC 9.
    01     RECORD-COUNT             PIC 9(8) VALUE 0.
    01     TOTAL-EARNED-POINTS      PIC 9(14) VALUE ZERO.
    01     TOTAL-POSSIBLE-POINTS    PIC 9(14) VALUE 5.
    01     K                        PIC 9(14) VALUE 1.
    01     TMP                      PIC 9(14).
    01     CURRENT-CATEGORY         PIC X(20).
    01     CATEGORY-WEIGHT          PIC X(3).
    01     LAST-CATEGORY            PIC X(20).
    01     TOTAL-POINTS             PIC 9(4).
    01     GRADES.
    05         GRADE OCCURS 1 TO 100 TIMES DEPENDING ON RECORD-COUNT.
    10            ASSIGNMENT-NAME   PIC X(20).
    10            CATEGORY          PIC X(20).
    10            POINTS-POSSIBLE   PIC 9(14).
    10            POINTS-EARNED     PIC 9(14).
    
    PROCEDURE DIVISION.
           OPEN INPUT GRADES-FILE.
           READ GRADES-FILE INTO TOTAL-POINTS.
           DISPLAY TOTAL-EARNED-POINTS
           PERFORM UNTIL GRADES-FILE-EOF = 1
               READ GRADES-FILE
                  AT END SET
                  GRADES-FILE-EOF TO 1
                  NOT AT END
                     ADD 1 TO RECORD-COUNT
    
                     MOVE INPUT-ASSIGNMENT-NAME(RECORD-COUNT) TO ASSIGNMENT-NAME(RECORD-COUNT)
                     DISPLAY INPUT-ASSIGNMENT-NAME(RECORD-COUNT)
                     DISPLAY ASSIGNMENT-NAME(RECORD-COUNT)
    
                     MOVE INPUT-CATEGORY(RECORD-COUNT) TO CATEGORY(RECORD-COUNT)
                     DISPLAY INPUT-CATEGORY(RECORD-COUNT)
                     DISPLAY CATEGORY(RECORD-COUNT)
    
                     MOVE FUNCTION NUMVAL (INPUT-POINTS-POSSIBLE(RECORD-COUNT)) TO POINTS-POSSIBLE(RECORD-COUNT)
                     DISPLAY INPUT-POINTS-POSSIBLE(RECORD-COUNT)
                     DISPLAY POINTS-POSSIBLE(RECORD-COUNT)
    
                     MOVE FUNCTION NUMVAL (INPUT-POINTS-EARNED(RECORD-COUNT)) TO POINTS-EARNED(RECORD-COUNT)
                     DISPLAY INPUT-POINTS-EARNED(RECORD-COUNT)
                     DISPLAY POINTS-EARNED(RECORD-COUNT)
    
                     COMPUTE TOTAL-EARNED-POINTS = TOTAL-EARNED-POINTS + POINTS-EARNED(RECORD-COUNT)
                     DISPLAY TOTAL-EARNED-POINTS
               END-READ
           END-PERFORM.
           CLOSE GRADES-FILE.
           DISPLAY TOTAL-EARNED-POINTS.
           SORT GRADE ASCENDING CATEGORY.
           MOVE CATEGORY(1) TO LAST-CATEGORY.
           PERFORM RECORD-COUNT TIMES
               MOVE CATEGORY(K) TO CURRENT-CATEGORY
               IF CURRENT-CATEGORY = LAST-CATEGORY THEN
                  DISPLAY "SAME CATEGORY"
               ELSE
                  DISPLAY "NEW CATEGORY"
                  MOVE LAST-CATEGORY TO CURRENT-CATEGORY
               END-IF
               SET K UP BY 1
           END-PERFORM
           DISPLAY GRADES.
           STOP RUN.

and here is the input file, bill:

1000
MS 1 - Join Grps    Group Project       5             5             
Four Programs       Programming         15            9             
Quiz 1              Quizzes             10            7             
FORTRAN             Programming         25            18            
Quiz 2              Quizzes             10            9             
HW 1 - Looplang     Homework            20            15            

As per the code written, the first line read from the table section of the file(lines 2 and forward) has its individual parts DISPLAY 'ed as follows:

MS 1 - Join Grps    
MS 1 - Join Grps    
Group Project       
Group Project       
5             
00000000000005
5             
00000000000005

This is what I expect. Each item is repeated, the first iteration is the input file structure, and the second is the working storage section structure. The difference being that the input structures are read as all strings of 20 and 14 lengths, and the storage structures are formatted as two strings of 20 length, and two ints of 14 length. The numeric strings are converted to ints and stored in the working storage, as stated earlier. The output of the second row's DISPLAYs show as this:

00000000000000
              
00000000000000
00000000000005
                    
                    
                    
                    
              
00000000000000
              
00000000000000
00000000000005
                    
                    
                    
                    
              
00000000000000
              
00000000000000
00000000000005
                    
                    
                    
                    
              
00000000000000
              
00000000000000
00000000000005
                    
                    
                    
                    
              
00000000000000
              
00000000000000
00000000000005

In this case, the 00000000000005 is the total of a summation accumulator variable, which is always 5 because the first row reads 5 for the earned points, and the rest of them are just evaluating to zero because they're being read as blanks.

How can I get my program to properly read the rest of the file?


Solution

  • Turns out, when reading a table from a file, the subscript to access the current line is always 1, so instead of reading RECORD-COUNT as the subscript of the INPUT-items, I just put 1 for all of them, and the program works as expected!